CONOPT
Loading...
Searching...
No Matches
mp_leastsq14.f90
Go to the documentation of this file.
1!> @file mp_leastsq14.f90
2!! @ingroup FORTOPENMP_EXAMPLES
3!!
4!!
5!! This model is an extension of leastsq.f90 in which we test that the
6!! solution with 1, 2, and 4 threads give the same solution when
7!! threadc is defined as 4.
8!!
9!! We solve the following nonlinear least squares model:
10!!
11!! min sum(i, res(i)**2 )
12!!
13!! sum(j, a(i,j)*x(j) + b(i,j)*x(j)**2 ) + res(i) = obs(i)
14!!
15!! where a, b, and obs are known data, and res and x are the
16!! variables of the model.
17!!
18!!
19!! For more information about the individual callbacks, please have a look at the source code.
20
21module lsq14
22 Integer, parameter :: nobs = 700
23 Integer, parameter :: dimx = 500
24 real*8, dimension(Nobs,DimX) :: a, b
25 real*8, dimension(Nobs) :: obs
26 real*8, dimension(Nobs+DimX) :: xprim, xprim1, xprim2, xprim4
27end module lsq14
28
29
30REAL FUNCTION rndx( )
31!
32! Defines a pseudo random number between 0 and 1
33!
34 IMPLICIT NONE
35
36 Integer, save :: seed = 12359
37
38 seed = mod(seed*1027+25,1048576)
39 rndx = float(seed)/float(1048576)
40
41END FUNCTION rndx
42
43subroutine defdata
44!
45! Define values for A, B, and Obs
46!
47 Use lsq14
48 IMPLICIT NONE
49
50 Integer :: i, j
51 real*8, Parameter :: xtarg = -1.0
52 real*8, Parameter :: noise = 1.0
53 Real, External :: Rndx
54 real*8 :: o
55
56 do i = 1, nobs
57 o = 0.d0
58 do j = 1, dimx
59 a(i,j) = rndx()
60 b(i,j) = rndx()
61 o = o + a(i,j) * xtarg + b(i,j) * xtarg**2
62 enddo
63 obs(i) = o + noise * rndx()
64 enddo
65
66end subroutine defdata
67!
68! Main program.
69!
70!> Main program. A simple setup and call of CONOPT
71!!
73
74 Use proginfop
75 Use coidef
76 Use lsq14
77 Use omp_lib
78 implicit None
79!
80! Declare the user callback routines as Integer, External:
81!
82 Integer, External :: lsq_readmatrix ! Mandatory Matrix definition routine defined below
83 Integer, External :: lsq_fdeval ! Function and Derivative evaluation routine
84 ! needed a nonlinear model.
85 Integer, External :: std_status ! Standard callback for displaying solution status
86 Integer, External :: lsq_solution ! Special callback for displaying and testing solution values
87 Integer, External :: std_message ! Standard callback for managing messages
88 Integer, External :: std_errmsg ! Standard callback for managing error messages
89#if defined(itl)
90!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Lsq_ReadMatrix
91!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Lsq_FDEval
92!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Status
93!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Lsq_Solution
94!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Message
95!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_ErrMsg
96#endif
97!
98! Control vector
99!
100 INTEGER, Dimension(:), Pointer :: cntvect
101 INTEGER :: coi_error
102
103 real*8 time0, time1, time2, time4
104 Integer :: i, maxthread
105 Logical :: same12, same14, same24
106
107 call startup
108!
109! Define data
110!
111 Call defdata
112!
113! Create and initialize a Control Vector
114!
115 coi_error = coi_createfort( cntvect )
116!
117! Tell CONOPT about the size of the model by populating the Control Vector:
118!
119 coi_error = max( coi_error, coidef_numvar( cntvect, nobs + dimx ) )
120 coi_error = max( coi_error, coidef_numcon( cntvect, nobs + 1 ) )
121 coi_error = max( coi_error, coidef_numnz( cntvect, nobs * (dimx+2) ) )
122 coi_error = max( coi_error, coidef_numnlnz( cntvect, nobs * (dimx+1) ) )
123 coi_error = max( coi_error, coidef_optdir( cntvect, -1 ) ) ! Minimize
124 coi_error = max( coi_error, coidef_objcon( cntvect, nobs + 1 ) ) ! Objective is last constraint
125 coi_error = max( coi_error, coidef_optfile( cntvect, 'mp_leastsq14.opt' ) )
126!
127! Tell CONOPT about the callback routines:
128!
129 coi_error = max( coi_error, coidef_readmatrix( cntvect, lsq_readmatrix ) )
130 coi_error = max( coi_error, coidef_fdeval( cntvect, lsq_fdeval ) )
131 coi_error = max( coi_error, coidef_status( cntvect, std_status ) )
132 coi_error = max( coi_error, coidef_solution( cntvect, lsq_solution ) )
133 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
134 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
135 coi_error = max( coi_error, coidef_debugfv( cntvect, 0 ) ) ! Debug Fdeval on or off
136
137#if defined(LICENSE_INT_1) && defined(LICENSE_INT_2) && defined(LICENSE_INT_3) && defined(LICENSE_TEXT)
138 coi_error = max( coi_error, coidef_license( cntvect, license_int_1, license_int_2, license_int_3, license_text) )
139#endif
140
141 If ( coi_error .ne. 0 ) THEN
142 write(*,*)
143 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
144 write(*,*)
145 call flog( "Skipping Solve due to setup errors", 1 )
146 ENDIF
147 maxthread = omp_get_max_threads() ! Define ThreadC as the largest number of threads we can get
148 coi_error = max( coi_error, coidef_threadc( cntvect, maxthread ) )
149!
150! Start CONOPT -- First time using a single thread:
151!
152 coi_error = max( coi_error, coidef_threads( cntvect, 1 ) ) ! 1 means use 1 thread
153 time0 = omp_get_wtime()
154 coi_error = coi_solve( cntvect )
155 time1 = omp_get_wtime() - time0
156
157 write(*,*)
158 write(*,*) 'End of Least Square example 1 with 1 thread. Return code=',coi_error
159
160 If ( coi_error /= 0 ) then
161 call flog( "One thread: Errors encountered during solution", 1 )
162 elseif ( stacalls == 0 .or. solcalls == 0 ) then
163 call flog( "One thread: Status or Solution routine was not called", 1 )
164 elseif ( .not. ( sstat == 1 .and. mstat == 2 ) ) then
165 call flog( "One thread: Solver or Model status was not as expected (1,2)", 1 )
166 elseif ( abs( obj - 19.44434311d0 ) > 1.d-7 ) then
167 call flog( "One thread: Incorrect objective returned", 1 )
168 endif
169 xprim1 = xprim
170!
171! Start CONOPT again -- this time using 2 threads:
172!
173 coi_error = max( coi_error, coidef_threads( cntvect, 2 ) ) ! 2 means use 2 threads
174 time0 = omp_get_wtime()
175 coi_error = coi_solve( cntvect )
176 time2 = omp_get_wtime() - time0
177
178 write(*,*)
179 write(*,*) 'Two threads: End of Least Square example 1. Return code=',coi_error
180
181 If ( coi_error /= 0 ) then
182 call flog( "Two threads: Errors encountered during solution", 1 )
183 elseif ( stacalls == 0 .or. solcalls == 0 ) then
184 call flog( "Two threads: Status or Solution routine was not called", 1 )
185 elseif ( .not. ( sstat == 1 .and. mstat == 2 ) ) then
186 call flog( "Two threads: Solver or Model status was not as expected (1,2)", 1 )
187 elseif ( abs( obj - 19.44434311d0 ) > 1.d-7 ) then
188 call flog( "Two threads: Incorrect objective returned", 1 )
189 endif
190 xprim2 = xprim
191 if ( maxthread >= 4 ) then
192!
193! Start CONOPT again -- this time using 4 threads (if available on this machine):
194!
195 coi_error = max( coi_error, coidef_threads( cntvect, 4 ) ) ! 4 means use 4 threads
196 time0 = omp_get_wtime()
197 coi_error = coi_solve( cntvect )
198 time4 = omp_get_wtime() - time0
199
200 write(*,*)
201 write(*,*) 'Four threads: End of Least Square example 1. Return code=',coi_error
202
203 If ( coi_error /= 0 ) then
204 call flog( "Four threads: Errors encountered during solution", 1 )
205 elseif ( stacalls == 0 .or. solcalls == 0 ) then
206 call flog( "Four threads: Status or Solution routine was not called", 1 )
207 elseif ( .not. ( sstat == 1 .and. mstat == 2 ) ) then
208 call flog( "Four threads: Solver or Model status was not as expected (1,2)", 1 )
209 elseif ( abs( obj - 19.44434311d0 ) > 1.d-7 ) then
210 call flog( "Four threads: Incorrect objective returned", 1 )
211 endif
212 xprim4 = xprim
213 Endif
214
215 same12 = .true.
216 same14 = .true.
217 same24 = .true.
218 Do i = 1, nobs+dimx
219 If ( xprim2(i) /= xprim1(i) ) then
220 if ( same12 ) then
221 write(*,*) 'Solution 2 is different from Solution 1. First diff for index',i
222 endif
223 same12 = .false.
224 endif
225 if ( maxthread >= 4 ) then
226 If ( xprim4(i) /= xprim1(i) ) then
227 if ( same14 ) then
228 write(*,*) 'Solution 4 is different from Solution 1. First diff for index',i
229 endif
230 same14 = .false.
231 endif
232 If ( xprim4(i) /= xprim2(i) ) then
233 if ( same24 ) then
234 write(*,*) 'Solution 4 is different from Solution 2. First diff for index',i
235 endif
236 same24 = .false.
237 endif
238 endif
239 Enddo
240 write(*,*)
241 write(*,"('Time for single thread ',f10.3)") time1
242 write(*,"('Time for two threads',f10.3)") time2
243 if ( maxthread >= 4 ) &
244 write(*,"('Time for four threads',f10.3)") time4
245 write(*,"('Speedup two threads',f10.3)") time1/time2
246 write(*,"('Efficiency two threads',f10.3)") time1/time2/2
247 if ( maxthread >= 4 ) &
248 write(*,"('Speedup four threads',f10.3)") time1/time4
249 if ( maxthread >= 4 ) &
250 write(*,"('Efficiency four threads',f10.3)") time1/time4/4
251
252#if defined (nocomp)
253#else
254 if ( same12 .and. same14 .and. same24 ) then
255 write(*,*) 'All solutions are the same'
256 else
257 write(*,*) 'The solutions are NOT the same'
258 call flog( "Solutions are not the same", 1 )
259 Endif
260#endif
261
262 if ( coi_free( cntvect ) /= 0 ) call flog( "Error while freeing control vector", 1 )
263
264 call flog( "Successful Solve", 0 )
265
266End Program leastsquare
267!
268! ============================================================================
269! Define information about the model:
270!
271
272!> Define information about the model
273!!
274!! @include{doc} readMatrix_params.dox
275Integer Function lsq_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
276 colsta, rowno, value, nlflag, n, m, nz, &
277 usrmem )
278#if defined(itl)
279!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Lsq_ReadMatrix
280#endif
281 Use lsq14
282 implicit none
283 integer, intent (in) :: n ! number of variables
284 integer, intent (in) :: m ! number of constraints
285 integer, intent (in) :: nz ! number of nonzeros
286 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
287 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
288 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
289 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
290 ! (not defined here)
291 integer, intent (out), dimension(m) :: type ! vector of equation types
292 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
293 ! (not defined here)
294 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
295 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
296 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
297 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
298 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
299 real*8 usrmem(*) ! optional user memory
300
301 Integer :: i, j, k
302!
303! Information about Variables:
304! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
305! Default: the status information in Vsta is not used.
306!
307 do i = 1, dimx
308 curr(i) = -0.8d0
309 enddo
310!
311! Information about Constraints:
312! Default: Rhs = 0
313! Default: the status information in Esta and the function
314! value in FV are not used.
315! Default: Type: There is no default.
316! 0 = Equality,
317! 1 = Greater than or equal,
318! 2 = Less than or equal,
319! 3 = Non binding.
320!
321! Constraints 1 to Nobs:
322! Rhs = Obs(i) and type Equality
323!
324 do i = 1, nobs
325 rhs(i) = obs(i)
326 type(i) = 0
327 enddo
328!
329! Constraint Nobs + 1 (Objective)
330! Rhs = 0 and type Non binding
331!
332 type(nobs+1) = 3
333!
334! Information about the Jacobian. We use the standard method with
335! Rowno, Value, Nlflag and Colsta and we do not use Colno.
336!
337! Colsta = Start of column indices (No Defaults):
338! Rowno = Row indices
339! Value = Value of derivative (by default only linear
340! derivatives are used)
341! Nlflag = 0 for linear and 1 for nonlinear derivative
342! (not needed for completely linear models)
343!
344!
345! Indices
346! x(i) res(j)
347! j: NL L=1
348! obj: NL
349!
350 k = 1
351 do j = 1, dimx
352 colsta(j) = k
353 do i = 1, nobs
354 rowno(k) = i
355 nlflag(k) = 1
356 k = k + 1
357 enddo
358 enddo
359 do i = 1, nobs
360 colsta(dimx+i) = k
361 rowno(k) = i
362 nlflag(k) = 0
363 value(k) = 1.d0
364 k = k + 1
365 rowno(k) = nobs+1
366 nlflag(k) = 1
367 k = k + 1
368 enddo
369 colsta(dimx+nobs+1) = k
370
371 lsq_readmatrix = 0 ! Return value means OK
372
373end Function lsq_readmatrix
374!
375!==========================================================================
376! Compute nonlinear terms and non-constant Jacobian elements
377!
378
379!> Compute nonlinear terms and non-constant Jacobian elements
380!!
381!! @include{doc} fdeval_params.dox
382Integer Function lsq_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
383 n, nz, thread, usrmem )
384#if defined(itl)
385!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Lsq_FDEval
386#endif
387 use lsq14
388 implicit none
389 integer, intent (in) :: n ! number of variables
390 integer, intent (in) :: rowno ! number of the row to be evaluated
391 integer, intent (in) :: nz ! number of nonzeros in this row
392 real*8, intent (in), dimension(n) :: x ! vector of current solution values
393 real*8, intent (in out) :: g ! constraint value
394 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
395 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
396 ! in this row. Ffor information only.
397 integer, intent (in) :: mode ! evaluation mode: 1 = function value
398 ! 2 = derivatives, 3 = both
399 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
400 ! as errcnt is incremented
401 integer, intent (in out) :: errcnt ! error counter to be incremented in case
402 ! of function evaluation errors.
403 integer, intent (in) :: thread
404 real*8 usrmem(*) ! optional user memory
405
406 integer :: i,j
407 real*8 :: s
408!
409! Row Nobs+1: the objective function is nonlinear
410!
411 if ( rowno .eq. nobs+1 ) then
412!
413! Mode = 1 or 3. Function value: G = sum(i, res(i)**2)
414!
415 if ( mode .eq. 1 .or. mode .eq. 3 ) then
416 s = 0.d0
417 do i = 1, nobs
418 s = s + x(dimx+i)**2
419 enddo
420 g = s
421 endif
422!
423! Mode = 2 or 3: Derivative values:
424!
425 if ( mode .eq. 2 .or. mode .eq. 3 ) then
426 do i = 1, nobs
427 jac(dimx+i) = 2*x(dimx+i)
428 enddo
429 endif
430!
431! Row 1 to Nobs: The observation definitions:
432!
433 else
434!
435! Mode = 1 or 3: Function value - x-part only
436!
437 if ( mode .eq. 1 .or. mode .eq. 3 ) then
438 s = 0.d0
439 do j = 1, dimx
440 s = s + a(rowno,j)*x(j) + b(rowno,j)*x(j)**2
441 enddo
442 g = s
443 endif
444!
445! Mode = 2 or 3: Derivatives
446!
447 if ( mode .eq. 2 .or. mode .eq. 3 ) then
448 do j = 1, dimx
449 jac(j) = a(rowno,j) + 2.d0*b(rowno,j)*x(j)
450 enddo
451 endif
452 endif
453 lsq_fdeval = 0
454
455end Function lsq_fdeval
456
457Integer Function lsq_solution( XVAL, XMAR, XBAS, XSTA, YVAL, YMAR, YBAS, YSTA, N, M, USRMEM )
458#if defined(itl)
459!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Lsq_Solution
460#endif
461!
462! Simple implementation in which we write the solution values to
463! the 'Documentation file' on unit 10.
464!
465 Use proginfop
466 Use lsq14
467 IMPLICIT NONE
468 INTEGER, Intent(IN) :: n, m
469 INTEGER, Intent(IN), Dimension(N) :: xbas, xsta
470 INTEGER, Intent(IN), Dimension(M) :: ybas, ysta
471 real*8, Intent(IN), Dimension(N) :: xval, xmar
472 real*8, Intent(IN), Dimension(M) :: yval, ymar
473 real*8, Intent(IN OUT) :: usrmem(*)
474
475 INTEGER i
476 CHARACTER*5, Parameter, Dimension(4) :: stat = (/ 'Lower','Upper','Basic','Super' /)
477
478 WRITE(10,"(/' Variable Solution value Reduced cost B-stat')")
479 DO i = 1, n
480 WRITE(10,"(1P,I7,E20.6,E16.6,4X,A5 )") i, xval(i), xmar(i), stat(1+xbas(i))
481 ENDDO
482
483 WRITE(10,"(/' Constrnt Activity level Marginal cost B-stat')")
484 DO i = 1, m
485 WRITE(10,"(1P,I7,E20.6,E16.6,4X,A5 )") i, yval(i), ymar(i), stat(1+ybas(i))
486 ENDDO
487 xprim(1:n) = xval(1:n)
488#if defined (wei)
489 Call flush(10)
490#endif
491
492 solcalls = solcalls + 1
493 lsq_solution = 0
494
495END Function lsq_solution
integer function std_status(modsta, solsta, iter, objval, usrmem)
Definition comdecl.f90:82
integer function std_message(smsg, dmsg, nmsg, llen, usrmem, msgv)
Definition comdecl.f90:203
integer function std_errmsg(rowno, colno, posno, msglen, usrmem, msg)
Definition comdecl.f90:248
integer function coidef_fdeval(cntvect, coi_fdeval)
define callback routine for performing function and derivative evaluations.
integer function coidef_errmsg(cntvect, coi_errmsg)
define callback routine for returning error messages for row, column or Jacobian elements.
integer function coidef_message(cntvect, coi_message)
define callback routine for handling messages returned during the solution process.
integer function coidef_readmatrix(cntvect, coi_readmatrix)
define callback routine for providing the matrix data to CONOPT.
integer function coidef_status(cntvect, coi_status)
define callback routine for returning the completion status.
integer function coidef_solution(cntvect, coi_solution)
define callback routine for returning the final solution values.
integer function coidef_optfile(cntvect, optfile)
define callback routine for defining an options file.
integer function coidef_threads(cntvect, threads)
number of threads allowed internally in CONOPT.
integer function coidef_debugfv(cntvect, debugfv)
turn Debugging of FDEval on and off.
integer function coidef_license(cntvect, licint1, licint2, licint3, licstring)
define the License Information.
Definition coistart.f90:680
integer function coidef_threadc(cntvect, threadc)
check for thread compatibility.
integer function coidef_numvar(cntvect, numvar)
defines the number of variables in the model.
Definition coistart.f90:358
integer function coidef_objcon(cntvect, objcon)
defines the Objective Constraint.
Definition coistart.f90:629
integer function coidef_numnz(cntvect, numnz)
defines the number of nonzero elements in the Jacobian.
Definition coistart.f90:437
integer function coidef_optdir(cntvect, optdir)
defines the Optimization Direction.
Definition coistart.f90:552
integer function coidef_numnlnz(cntvect, numnlnz)
defines the Number of Nonlinear Nonzeros.
Definition coistart.f90:476
integer function coidef_numcon(cntvect, numcon)
defines the number of constraints in the model.
Definition coistart.f90:398
integer function coi_solve(cntvect)
method for starting the solving process of CONOPT.
Definition coistart.f90:14
integer function lsq_readmatrix(lower, curr, upper, vsta, type, rhs, esta, colsta, rowno, value, nlflag, n, m, nz, usrmem)
Define information about the model.
Definition leastl1.f90:176
integer function lsq_fdeval(x, g, jac, rowno, jcnm, mode, ignerr, errcnt, n, nz, thread, usrmem)
Compute nonlinear terms and non-constant Jacobian elements.
Definition leastl1.f90:300
#define dimx
Definition leastsq.c:17
#define nobs
Definition leastsq.c:16
void defdata()
Defines the data for the problem.
Definition leastsq.c:36
float rndx()
Defines a pseudo random number between 0 and 1.
Definition leastsq.c:23
program leastsquare
Main program. A simple setup and call of CONOPT.
Definition leastsq.f90:62
integer function lsq_solution(xval, xmar, xbas, xsta, yval, ymar, ybas, ysta, n, m, usrmem)
real *8, dimension(nobs+dimx) xprim1
real *8, dimension(nobs+dimx) xprim4
real *8, dimension(nobs, dimx) b
real *8, dimension(nobs+dimx) xprim
real *8, dimension(nobs+dimx) xprim2
real *8, dimension(nobs, dimx) a
real *8, dimension(nobs) obs
subroutine flog(msg, code)
Definition comdeclp.f90:42
real *8 obj
Definition comdeclp.f90:13
subroutine startup
Definition comdeclp.f90:25