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