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