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