CONOPT
Loading...
Searching...
No Matches
fvforall.f90
Go to the documentation of this file.
1!> @file fvforall.f90
2!! @ingroup FORT1THREAD_EXAMPLES
3!!
4!!
5!! This is the pindyck example rewritten to use the FVforAll
6!! way of defining nonlinear functions. All functions, linear as
7!! well as nonlinear, will be called.
8!!
9!!
10!! For more information about the individual callbacks, please have a look at the source code.
11
12!> Main program. A simple setup and call of CONOPT
13!!
14Program fvforall
15 Use proginfo
16 Use coidef
17 Use data_t
18 Implicit none
19!
20! Declare the user callback routines as Integer, External:
21!
22 Integer, External :: pin_readmatrix ! Mandatory Matrix definition routine defined below
23 Integer, External :: pin_fdeval ! Function and Derivative evaluation routine
24 ! needed a nonlinear model.
25 Integer, External :: std_status ! Standard callback for displaying solution status
26 Integer, External :: pin_solution ! Specialized callback for displaying solution values
27 Integer, External :: std_message ! Standard callback for managing messages
28 Integer, External :: std_errmsg ! Standard callback for managing error messages
29#if defined(itl)
30!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_ReadMatrix
31!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_FDEval
32!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Status
33!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_Solution
34!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Message
35!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_ErrMsg
36#endif
37!
38! Control vector
39!
40 INTEGER :: numcallback
41 INTEGER, Dimension(:), Pointer :: cntvect
42 INTEGER :: coi_error
43!
44! Other variables
45!
46 INTEGER :: major, minor, patch
47
48 call startup
49!
50! Create and initialize a Control Vector
51!
52 numcallback = coidef_size()
53 Allocate( cntvect(numcallback) )
54 coi_error = coidef_inifort( cntvect )
55
56! Write which version of CONOPT we are using.
57
58 call coiget_version( major, minor, patch )
59 write(*,"('Solving Pindyck Model using CONOPT version ',i2,'.',i2,'.',i2)") major, minor, patch
60!
61! Define the number of time periods, T.
62!
63 t = 16
64!
65! Tell CONOPT about the size of the model by populating the Control Vector:
66!
67! Number of variables (excl. slacks): 7 per period
68!
69 coi_error = max( coi_error, coidef_numvar( cntvect, 7 * t ) )
70!
71! Number of equations: 1 objective + 6 per period
72!
73 coi_error = max( coi_error, coidef_numcon( cntvect, 1 + 6 * t ) )
74!
75! Number of nonzeros in the Jacobian. See the counting in ReadMatrix below:
76! For each period there is 1 in the objective, 16 for unlagged
77! variables and 4 for lagged variables.
78!
79 coi_error = max( coi_error, coidef_numnz( cntvect, 17 * t + 4 * (t-1) ) )
80!
81! Number of nonlinear nonzeros. 5 unlagged for each period.
82!
83 coi_error = max( coi_error, coidef_numnlnz( cntvect, 5 * t ) )
84!
85! Direction: +1 = maximization.
86!
87 coi_error = max( coi_error, coidef_optdir( cntvect, 1 ) )
88!
89! Objective: Constraint no 1
90!
91 coi_error = max( coi_error, coidef_objcon( cntvect, 1 ) )
92!
93! Define that all functions should be called.
94!
95 coi_error = max( coi_error, coidef_fvforall( cntvect, +1 ) )
96!
97! Turn function debugging on in the initial point to check if it is consistent
98! with FVforAll:
99!
100 coi_error = max( coi_error, coidef_debugfv( cntvect, +1 ) )
101!
102! Tell CONOPT about the callback routines:
103!
104 coi_error = max( coi_error, coidef_readmatrix( cntvect, pin_readmatrix ) )
105 coi_error = max( coi_error, coidef_fdeval( cntvect, pin_fdeval ) )
106 coi_error = max( coi_error, coidef_status( cntvect, std_status ) )
107 coi_error = max( coi_error, coidef_solution( cntvect, pin_solution ) )
108 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
109 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
110
111#if defined(LICENSE_INT_1) && defined(LICENSE_INT_2) && defined(LICENSE_INT_3) && defined(LICENSE_TEXT)
112 coi_error = max( coi_error, coidef_license( cntvect, license_int_1, license_int_2, license_int_3, license_text) )
113#endif
114
115 If ( coi_error .ne. 0 ) THEN
116 write(*,*)
117 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
118 write(*,*)
119 call flog( "Skipping Solve due to setup errors", 1 )
120 ENDIF
121!
122! Save the solution so we can check the duals:
123!
124 do_allocate = .true.
125!
126! Start CONOPT:
127!
128 coi_error = coi_solve( cntvect )
129
130 write(*,*)
131 write(*,*) 'End of FVforAll Model. Return code=',coi_error
132
133 If ( coi_error /= 0 ) then
134 call flog( "Errors encountered during solution", 1 )
135 elseif ( stacalls == 0 .or. solcalls == 0 ) then
136 call flog( "Status or Solution routine was not called", 1 )
137 elseif ( sstat /= 1 .or. mstat /= 2 ) then
138 call flog( "Solver and Model Status was not as expected (1,2)", 1 )
139 elseif ( abs( obj-1170.4863d0 ) > 0.0001d0 ) then
140 call flog( "Incorrect objective returned", 1 )
141 Else
142 Call checkdual( 'FVforAll', maximize )
143 endif
144
145 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
146
147 call flog( "Successful Solve", 0 )
148
149end Program fvforall
150!
151! =====================================================================
152! Define information about the model structure
153!
154
155!> Define information about the model
156!!
157!! @include{doc} readMatrix_params.dox
158Integer Function pin_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
159 colsta, rowno, value, nlflag, n, m, nz, usrmem )
160#if defined(itl)
161!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_ReadMatrix
162#endif
163 Use data_t
164 implicit none
165 integer, intent (in) :: n ! number of variables
166 integer, intent (in) :: m ! number of constraints
167 integer, intent (in) :: nz ! number of nonzeros
168 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
169 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
170 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
171 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
172 ! (not defined here)
173 integer, intent (out), dimension(m) :: type ! vector of equation types
174 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
175 ! (not defined here)
176 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
177 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
178 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
179 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
180 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
181 real*8 usrmem(*) ! optional user memory
182
183 Integer :: it, is, i, icol, iz
184!
185! Define the information for the columns.
186!
187! We should not supply status information, vsta.
188!
189! We order the variables as follows:
190! td, cs, s, d, r, p, and rev. All variables for period 1 appears
191! first followed by all variables for period 2 etc.
192!
193! td, cs, s, and d have lower bounds of 0, r and p have lower
194! bounds of 1, and rev has no lower bound.
195! All have infinite upper bounds (default).
196! The initial value of td is 18, s is 7, cs is 7*t, d is td-s,
197! p is 14, and r is r(t-1)-d. No initial value for rev.
198!
199 do it = 1, t
200 is = 7*(it-1)
201 lower(is+1) = 0.d0
202 lower(is+2) = 0.d0
203 lower(is+3) = 0.d0
204 lower(is+4) = 0.d0
205 lower(is+5) = 1.d0
206 lower(is+6) = 1.d0
207 curr(is+1) = 18.d0
208 curr(is+2) = 7.d0*it
209 curr(is+3) = 7.d0
210 curr(is+4) = curr(is+1) - curr(is+3)
211 if ( it .gt. 1 ) then
212 curr(is+5) = curr(is+5-7) - curr(is+4)
213 else
214 curr(is+5) = 500.d0 - curr(is+4)
215 endif
216 curr(is+6) = 14.d0
217 enddo
218!
219! Define the information for the rows
220!
221! We order the constraints as follows: The objective is first,
222! followed by tddef, sdef, csdef, ddef, rdef, and revdef for
223! the first period, the same for the second period, etc.
224!
225! The objective is a nonbinding constraint:
226!
227 type(1) = 3
228!
229! All others are equalities:
230!
231 do i = 2, m
232 type(i) = 0
233 enddo
234!
235! Right hand sides: In all periods except the first, only tddef
236! has a nonzero right hand side of 1+2.3*1.015**(t-1).
237! In the initial period there are contributions from lagged
238! variables in the constraints that have lagged variables.
239!
240 do it = 1, t
241 is = 1 + 6*(it-1)
242 rhs(is+1) = 1.d0+2.3d0*1.015d0**(it-1)
243 enddo
244!
245! tddef: + 0.87*td(0)
246!
247 rhs(2) = rhs(2) + 0.87d0*18.d0
248!
249! sdef: +0.75*s(0)
250!
251 rhs(3) = 0.75d0*6.5d0
252!
253! csdef: +1*cs(0)
254!
255 rhs(4) = 0.d0
256!
257! rdef: +1*r(0)
258!
259 rhs(6) = 500.d0
260!
261! Define the structure and content of the Jacobian:
262! To help define the Jacobian pattern and values it can be useful to
263! make a picture of the Jacobian. We describe the variables for one
264! period and the constraints they are part of:
265!
266! td cs s d r p rev
267! Obj (1+r)**(1-t)
268! Period t:
269! tddef 1.0 0.13
270! sdef NL 1.0 NL
271! csdef 1.0 -1.0
272! ddef -1.0 1.0 1.0
273! rdef 1.0 1.0
274! revdef NL NL NL 1.0
275! Period t+1:
276! tddef -0.87
277! sdef -0.75
278! csdef -1.0
279! ddef
280! rdef -1.0
281! revdef
282!
283! The Jacobian has to be sorted column-wise so we will just define
284! the elements column by column according to the table above:
285!
286 iz = 1
287 icol = 1
288 do it = 1, t
289!
290! is points to the position before the first equation for the period
291!
292 is = 1 + 6*(it-1)
293!
294! Column td:
295!
296 colsta(icol) = iz
297 icol = icol + 1
298 rowno(iz) = is+1
299 value(iz) = +1.d0
300 nlflag(iz) = 0
301 iz = iz + 1
302 rowno(iz) = is+4
303 value(iz) = -1.d0
304 nlflag(iz) = 0
305 iz = iz + 1
306 if ( it .lt. t ) then
307 rowno(iz) = is+7
308 value(iz) = -0.87d0
309 nlflag(iz) = 0
310 iz = iz + 1
311 endif
312!
313! Column cs
314!
315 colsta(icol) = iz
316 icol = icol + 1
317 rowno(iz) = is+2
318 nlflag(iz) = 1
319 iz = iz + 1
320 rowno(iz) = is+3
321 value(iz) = +1.d0
322 nlflag(iz) = 0
323 iz = iz + 1
324 if ( it .lt. t ) then
325 rowno(iz) = is+9
326 value(iz) = -1.d0
327 nlflag(iz) = 0
328 iz = iz + 1
329 endif
330!
331! Column s
332!
333 colsta(icol) = iz
334 icol = icol + 1
335 rowno(iz) = is+2
336 value(iz) = +1.d0
337 nlflag(iz) = 0
338 iz = iz + 1
339 rowno(iz) = is+3
340 value(iz) = -1.d0
341 nlflag(iz) = 0
342 iz = iz + 1
343 rowno(iz) = is+4
344 value(iz) = +1.d0
345 nlflag(iz) = 0
346 iz = iz + 1
347 if ( it .lt. t ) then
348 rowno(iz) = is+8
349 value(iz) = -0.75d0
350 nlflag(iz) = 0
351 iz = iz + 1
352 endif
353!
354! Column d:
355!
356 colsta(icol) = iz
357 icol = icol + 1
358 rowno(iz) = is+4
359 value(iz) = +1.d0
360 nlflag(iz) = 0
361 iz = iz + 1
362 rowno(iz) = is+5
363 value(iz) = +1.d0
364 nlflag(iz) = 0
365 iz = iz + 1
366 rowno(iz) = is+6
367 nlflag(iz) = 1
368 iz = iz + 1
369!
370! Column r:
371!
372 colsta(icol) = iz
373 icol = icol + 1
374 rowno(iz) = is+5
375 value(iz) = +1.d0
376 nlflag(iz) = 0
377 iz = iz + 1
378 rowno(iz) = is+6
379 nlflag(iz) = 1
380 iz = iz + 1
381 if ( it .lt. t ) then
382 rowno(iz) = is+11
383 value(iz) = -1.d0
384 nlflag(iz) = 0
385 iz = iz + 1
386 endif
387!
388! Column p:
389!
390 colsta(icol) = iz
391 icol = icol + 1
392 rowno(iz) = is+1
393 value(iz) = +0.13d0
394 nlflag(iz) = 0
395 iz = iz + 1
396 rowno(iz) = is+2
397 nlflag(iz) = 1
398 iz = iz + 1
399 rowno(iz) = is+6
400 nlflag(iz) = 1
401 iz = iz + 1
402!
403! Column rev:
404!
405 colsta(icol) = iz
406 icol = icol + 1
407 rowno(iz) = +1
408 value(iz) = 1.05d0**(1-it)
409 nlflag(iz) = 0
410 iz = iz + 1
411 rowno(iz) = is+6
412 value(iz) = 1.d0
413 nlflag(iz) = 0
414 iz = iz + 1
415 enddo
416 colsta(icol) = iz
417
419
420end Function pin_readmatrix
421!
422! =====================================================================
423! Compute nonlinear terms and non-constant Jacobian elements
424!
425
426!> Compute nonlinear terms and non-constant Jacobian elements
427!!
428!! @include{doc} fdeval_params.dox
429Integer Function pin_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
430 n, nz, thread, usrmem )
431#if defined(itl)
432!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_FDEval
433#endif
434 Use data_t
435 implicit none
436 integer, intent (in) :: n ! number of variables
437 integer, intent (in) :: rowno ! number of the row to be evaluated
438 integer, intent (in) :: nz ! number of nonzeros in this row
439 real*8, intent (in), dimension(n) :: x ! vector of current solution values
440 real*8, intent (in out) :: g ! constraint value
441 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
442 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
443 ! in this row. Ffor information only.
444 integer, intent (in) :: mode ! evaluation mode: 1 = function value
445 ! 2 = derivatives, 3 = both
446 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
447 ! as errcnt is incremented
448 integer, intent (in out) :: errcnt ! error counter to be incremented in case
449 ! of function evaluation errors.
450 integer, intent (in) :: thread
451 real*8 usrmem(*) ! optional user memory
452
453 integer it, is
454 real*8 h1, h2
455!
456! Compute the number of the period
457!
458 pin_fdeval = 0
459 it = (rowno+4) / 6
460 is = 7*(it-1)
461 if ( rowno == 1 ) then
462!
463! This is the linear objective
464!
465 if ( mode == 1 .or. mode == 3 ) then
466 g = 0.0d0
467 endif
468 else if ( rowno == (it-1)*6+3 ) then
469!
470! sdef equation. NL Terms: -(1.1+0.1*p)*1.02**(-cs/7)
471!
472 h1 = (1.1d0+0.1d0*x(is+6))
473 h2 = 1.02d0**(-x(is+2)/7.d0)
474 if ( mode == 1 .or. mode == 3 ) then
475 g = -h1*h2
476 endif
477 if ( mode == 2 .or. mode == 3 ) then
478 jac(is+2) = h1*h2*log(1.02d0)/7.d0
479 jac(is+6) = -h2*0.1d0
480 endif
481 elseif ( rowno == (it-1)*6+7 ) then
482!
483! revdef equation. NL term: d*(p-250/r)
484!
485 if ( mode == 1 .or. mode == 3 ) then
486 g = -x(is+4)*(x(is+6)-250.d0/x(is+5))
487 endif
488 if ( mode == 2 .or. mode == 3 ) then
489 jac(is+4) = -(x(is+6)-250.d0/x(is+5))
490 jac(is+5) = -x(is+4)*250d0/x(is+5)**2
491 jac(is+6) = -x(is+4)
492 endif
493 else
494!
495! This is a linear constraint so we return function value zero and
496! no derivatives.
497!
498 if ( mode == 1 .or. mode == 3 ) then
499 g = 0.0d0
500 endif
501 endif
502
503end Function pin_fdeval
504
505Integer Function pin_solution( XVAL, XMAR, XBAS, XSTA, YVAL, YMAR, YBAS, YSTA, N, M, USRMEM )
506#if defined(itl)
507!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_Solution
508#endif
509!
510! Specialized solution callback routine with names for variables and constraints
511!
512 Use proginfo
513 Use data_t
514 IMPLICIT NONE
515 INTEGER, Intent(IN) :: n, m
516 INTEGER, Intent(IN), Dimension(N) :: xbas, xsta
517 INTEGER, Intent(IN), Dimension(M) :: ybas, ysta
518 real*8, Intent(IN), Dimension(N) :: xval, xmar
519 real*8, Intent(IN), Dimension(M) :: yval, ymar
520 real*8, Intent(IN OUT) :: usrmem(*)
521 character*6, parameter, dimension(7) :: vname = (/'td ','cs ','s ','d ','r ','p ','rev '/)
522 character*6, parameter, dimension(6) :: ename = (/'tddef ','sdef ','csdef ','ddef ','rdef ','revdef'/)
523
524 INTEGER :: i, it, i1
525 CHARACTER*5, Parameter, Dimension(4) :: stat = (/ 'Lower','Upper','Basic','Super' /)
526
527 WRITE(10,"(/' Variable Solution value Reduced cost B-stat'/)")
528 i = 0
529 do it = 1, t
530 DO i1 = 1, 7
531 i = i + 1
532 WRITE(10,"(1X,A6,i2,1p,E20.6,E16.6,4X,A5 )") vname(i1), it, xval(i), xmar(i), stat(1+xbas(i))
533 ENDDO
534 enddo
535
536 WRITE(10,"(/' Constrnt Activity level Marginal cost B-stat'/)")
537 i = 1
538 WRITE(10,"(1x,'Objective',1P,E19.6,E16.6,4X,A5 )") yval(i), ymar(i), stat(1+ybas(i))
539 do it = 1, t
540 do i1 = 1, 6
541 i = i + 1
542 WRITE(10,"(1x,A6,i2,1P,E20.6,E16.6,4X,A5 )") ename(i1),it, yval(i), ymar(i), stat(1+ybas(i))
543 enddo
544 ENDDO
545
546 solcalls = solcalls + 1
547 pin_solution = 0
548
549END Function pin_solution
integer function std_status(modsta, solsta, iter, objval, usrmem)
Definition comdecl.f90:82
subroutine checkdual(case, minmax)
Definition comdecl.f90:365
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 pin_fdeval(x, g, jac, rowno, jcnm, mode, ignerr, errcnt, n, nz, thread, usrmem)
Compute nonlinear terms and non-constant Jacobian elements.
Definition fvboth.f90:436
integer function pin_readmatrix(lower, curr, upper, vsta, type, rhs, esta, colsta, rowno, value, nlflag, n, m, nz, usrmem)
Define information about the model.
Definition fvboth.f90:165
integer function pin_solution(xval, xmar, xbas, xsta, yval, ymar, ybas, ysta, n, m, usrmem)
Definition fvboth.f90:545
program fvforall
Main program. A simple setup and call of CONOPT.
Definition fvforall.f90:14
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_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_fvforall(cntvect, fvforall)
call the FDEval for all constraints, including linear constraints.
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 coidef_size()
returns the size the Control Vector must have, measured in standard Integer units.
Definition coistart.f90:176
integer function coidef_inifort(cntvect)
initialisation method for Fortran applications.
Definition coistart.f90:314
subroutine coiget_version(major, minor, patch)
returns the version number. It can be used to ensure that the modeler is linked to the correct versio...
Definition coistart.f90:67
integer function coi_solve(cntvect)
method for starting the solving process of CONOPT.
Definition coistart.f90:14
real *8 obj
Definition comdecl.f90:10
integer solcalls
Definition comdecl.f90:9
integer sstat
Definition comdecl.f90:12
integer stacalls
Definition comdecl.f90:8
subroutine flog(msg, code)
Definition comdecl.f90:56
logical do_allocate
Definition comdecl.f90:21
integer, parameter maximize
Definition comdecl.f90:25
integer mstat
Definition comdecl.f90:11
subroutine startup
Definition comdecl.f90:35