CONOPT
Loading...
Searching...
No Matches
fvinclin.f90
Go to the documentation of this file.
1!> @file fvinclin.f90
2!! @ingroup FORT1THREAD_EXAMPLES
3!!
4!!
5!! This is the pindyck example rewritten to use the FVincLin
6!! way of defining nonlinear functions. The nonlinear functions
7!! must contain both linear and nonlinear terms.
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 fvinclin
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 functions will include linear terms
94!
95 coi_error = max( coi_error, coidef_fvinclin( cntvect, +1 ) )
96!
97! Turn function debugging on in the initial point to check if it is consistent
98! with FVincLin:
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 coi_error = coi_solve( cntvect )
127
128 write(*,*)
129 write(*,*) 'End of FVincLin Model. Return code=',coi_error
130
131 Deallocate( cntvect )
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( 'FVincLin', maximize )
143 endif
144
145 call flog( "Successful Solve", 0 )
146
147end Program fvinclin
148!
149! =====================================================================
150! Define information about the model structure
151!
152
153!> Define information about the model
154!!
155!! @include{doc} readMatrix_params.dox
156Integer Function pin_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
157 colsta, rowno, value, nlflag, n, m, nz, usrmem )
158#if defined(itl)
159!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_ReadMatrix
160#endif
161 Use data_t
162 implicit none
163 integer, intent (in) :: n ! number of variables
164 integer, intent (in) :: m ! number of constraints
165 integer, intent (in) :: nz ! number of nonzeros
166 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
167 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
168 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
169 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
170 ! (not defined here)
171 integer, intent (out), dimension(m) :: type ! vector of equation types
172 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
173 ! (not defined here)
174 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
175 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
176 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
177 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
178 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
179 real*8 usrmem(*) ! optional user memory
180
181 Integer :: it, is, i, icol, iz
182!
183! Define the information for the columns.
184!
185! We should not supply status information, vsta.
186!
187! We order the variables as follows:
188! td, cs, s, d, r, p, and rev. All variables for period 1 appears
189! first followed by all variables for period 2 etc.
190!
191! td, cs, s, and d have lower bounds of 0, r and p have lower
192! bounds of 1, and rev has no lower bound.
193! All have infinite upper bounds (default).
194! The initial value of td is 18, s is 7, cs is 7*t, d is td-s,
195! p is 14, and r is r(t-1)-d. No initial value for rev.
196!
197 do it = 1, t
198 is = 7*(it-1)
199 lower(is+1) = 0.d0
200 lower(is+2) = 0.d0
201 lower(is+3) = 0.d0
202 lower(is+4) = 0.d0
203 lower(is+5) = 1.d0
204 lower(is+6) = 1.d0
205 curr(is+1) = 18.d0
206 curr(is+2) = 7.d0*it
207 curr(is+3) = 7.d0
208 curr(is+4) = curr(is+1) - curr(is+3)
209 if ( it .gt. 1 ) then
210 curr(is+5) = curr(is+5-7) - curr(is+4)
211 else
212 curr(is+5) = 500.d0 - curr(is+4)
213 endif
214 curr(is+6) = 14.d0
215 enddo
216!
217! Define the information for the rows
218!
219! We order the constraints as follows: The objective is first,
220! followed by tddef, sdef, csdef, ddef, rdef, and revdef for
221! the first period, the same for the second period, etc.
222!
223! The objective is a nonbinding constraint:
224!
225 type(1) = 3
226!
227! All others are equalities:
228!
229 do i = 2, m
230 type(i) = 0
231 enddo
232!
233! Right hand sides: In all periods except the first, only tddef
234! has a nonzero right hand side of 1+2.3*1.015**(t-1).
235! In the initial period there are contributions from lagged
236! variables in the constraints that have lagged variables.
237!
238 do it = 1, t
239 is = 1 + 6*(it-1)
240 rhs(is+1) = 1.d0+2.3d0*1.015d0**(it-1)
241 enddo
242!
243! tddef: + 0.87*td(0)
244!
245 rhs(2) = rhs(2) + 0.87d0*18.d0
246!
247! sdef: +0.75*s(0)
248!
249 rhs(3) = 0.75d0*6.5d0
250!
251! csdef: +1*cs(0)
252!
253 rhs(4) = 0.d0
254!
255! rdef: +1*r(0)
256!
257 rhs(6) = 500.d0
258!
259! Define the structure and content of the Jacobian:
260! To help define the Jacobian pattern and values it can be useful to
261! make a picture of the Jacobian. We describe the variables for one
262! period and the constraints they are part of:
263!
264! td cs s d r p rev
265! Obj (1+r)**(1-t)
266! Period t:
267! tddef 1.0 0.13
268! sdef NL 1.0 NL
269! csdef 1.0 -1.0
270! ddef -1.0 1.0 1.0
271! rdef 1.0 1.0
272! revdef NL NL NL 1.0
273! Period t+1:
274! tddef -0.87
275! sdef -0.75
276! csdef -1.0
277! ddef
278! rdef -1.0
279! revdef
280!
281! The Jacobian has to be sorted column-wise so we will just define
282! the elements column by column according to the table above:
283!
284 iz = 1
285 icol = 1
286 do it = 1, t
287!
288! is points to the position before the first equation for the period
289!
290 is = 1 + 6*(it-1)
291!
292! Column td:
293!
294 colsta(icol) = iz
295 icol = icol + 1
296 rowno(iz) = is+1
297 value(iz) = +1.d0
298 nlflag(iz) = 0
299 iz = iz + 1
300 rowno(iz) = is+4
301 value(iz) = -1.d0
302 nlflag(iz) = 0
303 iz = iz + 1
304 if ( it .lt. t ) then
305 rowno(iz) = is+7
306 value(iz) = -0.87d0
307 nlflag(iz) = 0
308 iz = iz + 1
309 endif
310!
311! Column cs
312!
313 colsta(icol) = iz
314 icol = icol + 1
315 rowno(iz) = is+2
316 nlflag(iz) = 1
317 iz = iz + 1
318 rowno(iz) = is+3
319 value(iz) = +1.d0
320 nlflag(iz) = 0
321 iz = iz + 1
322 if ( it .lt. t ) then
323 rowno(iz) = is+9
324 value(iz) = -1.d0
325 nlflag(iz) = 0
326 iz = iz + 1
327 endif
328!
329! Column s
330!
331 colsta(icol) = iz
332 icol = icol + 1
333 rowno(iz) = is+2
334 value(iz) = +1.d0
335 nlflag(iz) = 0
336 iz = iz + 1
337 rowno(iz) = is+3
338 value(iz) = -1.d0
339 nlflag(iz) = 0
340 iz = iz + 1
341 rowno(iz) = is+4
342 value(iz) = +1.d0
343 nlflag(iz) = 0
344 iz = iz + 1
345 if ( it .lt. t ) then
346 rowno(iz) = is+8
347 value(iz) = -0.75d0
348 nlflag(iz) = 0
349 iz = iz + 1
350 endif
351!
352! Column d:
353!
354 colsta(icol) = iz
355 icol = icol + 1
356 rowno(iz) = is+4
357 value(iz) = +1.d0
358 nlflag(iz) = 0
359 iz = iz + 1
360 rowno(iz) = is+5
361 value(iz) = +1.d0
362 nlflag(iz) = 0
363 iz = iz + 1
364 rowno(iz) = is+6
365 nlflag(iz) = 1
366 iz = iz + 1
367!
368! Column r:
369!
370 colsta(icol) = iz
371 icol = icol + 1
372 rowno(iz) = is+5
373 value(iz) = +1.d0
374 nlflag(iz) = 0
375 iz = iz + 1
376 rowno(iz) = is+6
377 nlflag(iz) = 1
378 iz = iz + 1
379 if ( it .lt. t ) then
380 rowno(iz) = is+11
381 value(iz) = -1.d0
382 nlflag(iz) = 0
383 iz = iz + 1
384 endif
385!
386! Column p:
387!
388 colsta(icol) = iz
389 icol = icol + 1
390 rowno(iz) = is+1
391 value(iz) = +0.13d0
392 nlflag(iz) = 0
393 iz = iz + 1
394 rowno(iz) = is+2
395 nlflag(iz) = 1
396 iz = iz + 1
397 rowno(iz) = is+6
398 nlflag(iz) = 1
399 iz = iz + 1
400!
401! Column rev:
402!
403 colsta(icol) = iz
404 icol = icol + 1
405 rowno(iz) = +1
406 value(iz) = 1.05d0**(1-it)
407 nlflag(iz) = 0
408 iz = iz + 1
409 rowno(iz) = is+6
410 value(iz) = 1.d0
411 nlflag(iz) = 0
412 iz = iz + 1
413 enddo
414 colsta(icol) = iz
415
417
418end Function pin_readmatrix
419!
420! =====================================================================
421! Compute nonlinear terms and non-constant Jacobian elements
422!
423
424!> Compute nonlinear terms and non-constant Jacobian elements
425!!
426!! @include{doc} fdeval_params.dox
427Integer Function pin_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
428 n, nz, thread, usrmem )
429#if defined(itl)
430!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_FDEval
431#endif
432 Use data_t
433 implicit none
434 integer, intent (in) :: n ! number of variables
435 integer, intent (in) :: rowno ! number of the row to be evaluated
436 integer, intent (in) :: nz ! number of nonzeros in this row
437 real*8, intent (in), dimension(n) :: x ! vector of current solution values
438 real*8, intent (in out) :: g ! constraint value
439 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
440 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
441 ! in this row. Ffor information only.
442 integer, intent (in) :: mode ! evaluation mode: 1 = function value
443 ! 2 = derivatives, 3 = both
444 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
445 ! as errcnt is incremented
446 integer, intent (in out) :: errcnt ! error counter to be incremented in case
447 ! of function evaluation errors.
448 integer, intent (in) :: thread
449 real*8 usrmem(*) ! optional user memory
450
451 integer it, is
452 real*8 h1, h2
453!
454! Compute the number of the period
455!
456 pin_fdeval = 0
457 it = (rowno+4) / 6
458 is = 7*(it-1)
459 if ( rowno == (it-1)*6+3 ) then
460!
461! sdef equation. All terms: s - 0.75*s(t-1) -(1.1+0.1*p)*1.02**(-cs/7)
462!
463 h1 = (1.1d0+0.1d0*x(is+6))
464 h2 = 1.02d0**(-x(is+2)/7.d0)
465 if ( mode == 1 .or. mode == 3 ) then
466 g = x(is+3) -h1*h2
467 if ( it > 1 ) g = g - 0.75d0*x(is+3-7) ! 0.75*s(t-1) only it t > 1
468 endif
469 if ( mode == 2 .or. mode == 3 ) then
470 jac(is+2) = h1*h2*log(1.02d0)/7.d0
471 jac(is+6) = -h2*0.1d0
472 endif
473 elseif ( rowno == (it-1)*6+7 ) then
474!
475! revdef equation. All terms: rev - d*(p-250/r)
476!
477 if ( mode == 1 .or. mode == 3 ) then
478 g = x(is+7) -x(is+4)*(x(is+6)-250.d0/x(is+5))
479 endif
480 if ( mode == 2 .or. mode == 3 ) then
481 jac(is+4) = -(x(is+6)-250.d0/x(is+5))
482 jac(is+5) = -x(is+4)*250d0/x(is+5)**2
483 jac(is+6) = -x(is+4)
484 endif
485 else
486!
487! Error - this equation is not nonlinear
488!
489 write(*,*)
490 write(*,*) 'Error. FDEval called with rowno=',rowno
491 write(*,*)
492 pin_fdeval = 1
493 endif
494
495end Function pin_fdeval
496
497Integer Function pin_solution( XVAL, XMAR, XBAS, XSTA, YVAL, YMAR, YBAS, YSTA, N, M, USRMEM )
498#if defined(itl)
499!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_Solution
500#endif
501!
502! Specialized solution callback routine with names for variables and constraints
503!
504 Use proginfo
505 Use data_t
506 IMPLICIT NONE
507 INTEGER, Intent(IN) :: n, m
508 INTEGER, Intent(IN), Dimension(N) :: xbas, xsta
509 INTEGER, Intent(IN), Dimension(M) :: ybas, ysta
510 real*8, Intent(IN), Dimension(N) :: xval, xmar
511 real*8, Intent(IN), Dimension(M) :: yval, ymar
512 real*8, Intent(IN OUT) :: usrmem(*)
513 character*6, parameter, dimension(7) :: vname = (/'td ','cs ','s ','d ','r ','p ','rev '/)
514 character*6, parameter, dimension(6) :: ename = (/'tddef ','sdef ','csdef ','ddef ','rdef ','revdef'/)
515
516 INTEGER :: i, it, i1
517 CHARACTER*5, Parameter, Dimension(4) :: stat = (/ 'Lower','Upper','Basic','Super' /)
518
519 WRITE(10,"(/' Variable Solution value Reduced cost B-stat'/)")
520 i = 0
521 do it = 1, t
522 DO i1 = 1, 7
523 i = i + 1
524 WRITE(10,"(1X,A6,i2,1p,E20.6,E16.6,4X,A5 )") vname(i1), it, xval(i), xmar(i), stat(1+xbas(i))
525 ENDDO
526 enddo
527
528 WRITE(10,"(/' Constrnt Activity level Marginal cost B-stat'/)")
529 i = 1
530 WRITE(10,"(1x,'Objective',1P,E19.6,E16.6,4X,A5 )") yval(i), ymar(i), stat(1+ybas(i))
531 do it = 1, t
532 do i1 = 1, 6
533 i = i + 1
534 WRITE(10,"(1x,A6,i2,1P,E20.6,E16.6,4X,A5 )") ename(i1),it, yval(i), ymar(i), stat(1+ybas(i))
535 enddo
536 ENDDO
537
538 solcalls = solcalls + 1
539 pin_solution = 0
540
541END 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 fvinclin
Main program. A simple setup and call of CONOPT.
Definition fvinclin.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_fvinclin(cntvect, fvinclin)
include the linear terms in function evaluations.
integer function coidef_license(cntvect, licint1, licint2, licint3, licstring)
define the License Information.
Definition coistart.f90:680
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