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