CONOPT
Loading...
Searching...
No Matches
pinadd2.f90
Go to the documentation of this file.
1!> @file pinadd2.f90
2!! @ingroup FORT1THREAD_EXAMPLES
3!!
4!!
5!! This is a CONOPT implementation of the Pindyck model from the
6!! GAMS model library. The implementation is similar to the one
7!! in pindyck, but this time we first solve the model for 16
8!! periods and then we gradually increase the number of periods
9!! one at a time up to 20.
10!!
11!!
12!! For more information about the individual callbacks, please have a look at the source code.
13
15 integer :: t
16 integer, Parameter :: tmin = 16, tmax = 20
17 integer, Parameter :: vpp = 7 ! Variables per period
18 integer, Parameter :: epp = 6 ! Equations per period
19 Integer, Parameter :: hpp = 5 ! Hessian elements per period -- see in 2DLagr* routines
20 real*8, Dimension(Tmax*Vpp) :: xkeep ! Store previous solutions
21 Integer, Dimension(Tmax*Vpp) :: xstas ! Store previous status
22 Integer, Dimension(Tmax*Epp) :: estat ! for variables and equations
23End Module pinadd2data
24
25!> Main program. A simple setup and call of CONOPT
26!!
27Program pinadd2
28 Use proginfo
29 Use coidef
30 Use pinadd2data
31 Implicit none
32!
33! Declare the user callback routines as Integer, External:
34!
35 Integer, External :: pin_readmatrix ! Mandatory Matrix definition routine defined below
36 Integer, External :: pin_fdeval ! Function and Derivative evaluation routine
37 ! needed a nonlinear model.
38 Integer, External :: std_status ! Standard callback for displaying solution status
39 Integer, External :: pin_solution ! Specialized callback for displaying solution values
40 Integer, External :: std_message ! Standard callback for managing messages
41 Integer, External :: std_errmsg ! Standard callback for managing error messages
42 Integer, External :: pin_2dlagrstr ! Hessian structure evaluation routine
43 Integer, External :: pin_2dlagrval ! Hessian value evaluation routine
44#if defined(itl)
45!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_ReadMatrix
46!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_FDEval
47!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Status
48!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_Solution
49!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Message
50!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_ErrMsg
51!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_2DLagrStr
52!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_2DLagrVal
53#endif
54!
55! Control vector
56!
57 INTEGER :: numcallback
58 INTEGER, Dimension(:), Pointer :: cntvect
59 INTEGER :: coi_error
60
61 call startup
62!
63! Create and initialize a Control Vector
64!
65 numcallback = coidef_size()
66 Allocate( cntvect(numcallback) )
67 coi_error = coidef_inifort( cntvect )
68!
69! Define the number of time periods, T.
70!
71 t = tmin
72!
73! Tell CONOPT about the size of the model by populating the Control Vector:
74!
75! Number of variables (excl. slacks): Vpp per period
76!
77 coi_error = max( coi_error, coidef_numvar( cntvect, vpp * t ) )
78!
79! Number of equations: 1 objective + Epp per period
80!
81 coi_error = max( coi_error, coidef_numcon( cntvect, 1 + epp * t ) )
82!
83! Number of nonzeros in the Jacobian. See the counting in ReadMatrix below:
84! For each period there is 1 in the objective, 16 for unlagged
85! variables and 4 for lagged variables.
86!
87 coi_error = max( coi_error, coidef_numnz( cntvect, 17 * t + 4 * (t-1) ) )
88!
89! Number of nonlinear nonzeros. 5 unlagged for each period.
90!
91 coi_error = max( coi_error, coidef_numnlnz( cntvect, 5 * t ) )
92!
93! Number of nonzeros in the Hessian. 5 for each period.
94!
95 coi_error = max( coi_error, coidef_numhess( cntvect, hpp * t ) )
96!
97! Direction: +1 = maximization.
98!
99 coi_error = max( coi_error, coidef_optdir( cntvect, 1 ) )
100!
101! Objective: Constraint no 1
102!
103 coi_error = max( coi_error, coidef_objcon( cntvect, 1 ) )
104!
105! Turn Hessian debugging on in the initial point
106!
107 coi_error = max( coi_error, coidef_debug2d( cntvect, -1 ) )
108!
109! Options file = test.opt
110!
111 coi_error = max( coi_error, coidef_optfile( cntvect, 'test.opt' ) )
112!
113! Tell CONOPT about the callback routines:
114!
115 coi_error = max( coi_error, coidef_readmatrix( cntvect, pin_readmatrix ) )
116 coi_error = max( coi_error, coidef_fdeval( cntvect, pin_fdeval ) )
117 coi_error = max( coi_error, coidef_status( cntvect, std_status ) )
118 coi_error = max( coi_error, coidef_solution( cntvect, pin_solution ) )
119 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
120 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
121 coi_error = max( coi_error, coidef_2dlagrstr( cntvect, pin_2dlagrstr ) )
122 coi_error = max( coi_error, coidef_2dlagrval( cntvect, pin_2dlagrval ) )
123
124#if defined(LICENSE_INT_1) && defined(LICENSE_INT_2) && defined(LICENSE_INT_3) && defined(LICENSE_TEXT)
125 coi_error = max( coi_error, coidef_license( cntvect, license_int_1, license_int_2, license_int_3, license_text) )
126#endif
127
128 If ( coi_error .ne. 0 ) THEN
129 write(*,*)
130 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
131 write(*,*)
132 call flog( "Skipping First Solve due to setup errors", 1 )
133 ENDIF
134!
135! Start CONOPT:
136!
137 coi_error = coi_solve( cntvect )
138 If ( coi_error .ne. 0 ) THEN
139 write(*,*)
140 write(*,*) '**** Fatal Error while Solving first model.'
141 write(*,*)
142 call flog( "Errors encountered during first Solve.", 1 )
143 elseif ( stacalls == 0 .or. solcalls == 0 ) then
144 call flog( "Status or Solution routine was not called during first Solve", 1 )
145 else if ( mstat /= 2 .or. sstat /= 1 ) then
146 call flog( "Incorrect Model or Solver Status during first solve", 1 )
147 ENDIF
148!
149! Now increase the time horizon gradually up to 20.
150! All sizes that depend on T must be registered again.
151!
152 Do t = tmin+1, tmax
153 coi_error = max( coi_error, coidef_numvar( cntvect, 7 * t ) )
154 coi_error = max( coi_error, coidef_numcon( cntvect, 1 + 6 * t ) )
155 coi_error = max( coi_error, coidef_numnz( cntvect, 17 * t + 4 * (t-1) ) )
156 coi_error = max( coi_error, coidef_numnlnz( cntvect, 5 * t ) )
157 coi_error = max( coi_error, coidef_numhess( cntvect, hpp * t ) )
158!
159! This time we have status information copied from a previous solve, i.e.
160! IniStat = 2
161!
162 coi_error = max( coi_error, coidef_inistat( cntvect, 2 ) )
163!
164! Turn Hessian debugging off again
165!
166 coi_error = max( coi_error, coidef_debug2d( cntvect, 0 ) )
167 If ( coi_error .ne. 0 ) THEN
168 write(*,*)
169 write(*,*) '**** Fatal Error while revising CONOPT Sizes.'
170 write(*,*)
171 call flog( "Skipping Later Solve due to setup errors", 1 )
172 ENDIF
173 coi_error = coi_solve( cntvect )
174 If ( coi_error .ne. 0 ) THEN
175 write(*,*)
176 write(*,*) '**** Fatal Error while Solving for T=',t
177 write(*,*)
178 call flog( "Errors encountered during later Solve.", 1 )
179 elseif ( stacalls == 0 .or. solcalls == 0 ) then
180 call flog( "Status or Solution routine was not called during later Solve", 1 )
181 else if ( mstat /= 2 .or. sstat /= 1 ) then
182 call flog( "Incorrect Model or Solver Status during later solve", 1 )
183 ENDIF
184 Enddo
185 write(*,*)
186 write(*,*) 'End of Pinadd2 Model. Return code=',coi_error
187
188 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
189
190 call flog( "Successful Solve", 0 )
191
192end Program pinadd2
193!
194! =====================================================================
195! Define information about the model structure
196!
197
198!> Define information about the model
199!!
200!! @include{doc} readMatrix_params.dox
201Integer Function pin_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
202 colsta, rowno, value, nlflag, n, m, nz, usrmem )
203#if defined(itl)
204!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_ReadMatrix
205#endif
206 Use pinadd2data
207 implicit none
208 integer, intent (in) :: n ! number of variables
209 integer, intent (in) :: m ! number of constraints
210 integer, intent (in) :: nz ! number of nonzeros
211 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
212 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
213 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
214 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
215 ! Defined during restarts
216 integer, intent (out), dimension(m) :: type ! vector of equation types
217 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
218 ! Defined during restarts
219 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
220 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
221 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
222 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
223 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
224 real*8 usrmem(*) ! optional user memory
225
226 Integer :: it, is, i, icol, iz, iold
227!
228! Define the information for the columns.
229!
230! We should not supply status information, vsta.
231!
232! We order the variables as follows:
233! td, cs, s, d, r, p, and rev. All variables for period 1 appears
234! first followed by all variables for period 2 etc.
235!
236! td, cs, s, and d have lower bounds of 0, r and p have lower
237! bounds of 1, and rev has no lower bound.
238! All have infinite upper bounds (default).
239! The initial value of td is 18, s is 7, cs is 7*t, d is td-s,
240! p is 14, and r is r(t-1)-d. No initial value for rev.
241!
242 do it = 1, t
243 is = vpp*(it-1)
244 lower(is+1) = 0.d0
245 lower(is+2) = 0.d0
246 lower(is+3) = 0.d0
247 lower(is+4) = 0.d0
248 lower(is+5) = 1.d0
249 lower(is+6) = 1.d0
250 curr(is+1) = 18.d0
251 curr(is+2) = 7.d0*it
252 curr(is+3) = 7.d0
253 curr(is+4) = curr(is+1) - curr(is+3)
254 if ( it .gt. 1 ) then
255 curr(is+5) = curr(is+5-vpp) - curr(is+4)
256 else
257 curr(is+5) = 500.d0 - curr(is+4)
258 endif
259 curr(is+6) = 14.d0
260 enddo
261 If ( t > tmin ) Then
262!
263! This is a restart: Use the initial values from last solve for
264! the variables in the first periods and extrapolate the last
265! period using a linear extrapolation between the last two
266!
267 iold = vpp*(t-1)
268 curr(1:iold) = xkeep(1:iold)
269 do i = 1, vpp
270 curr(iold+i) = curr(iold+i-vpp) + (curr(iold+i-vpp)-curr(iold+i-2*vpp))
271 enddo
272!
273! The variables from the last solve are given the old status and
274! the variables in the new period are given those in the last
275! pariod. Similarly with the Equation status:
276!
277 vsta(1:iold) = xstas(1:iold)
278 do i = 1, vpp
279 vsta(iold+i) = xstas(iold+i-vpp)
280 enddo
281 iold = 6*(t-1)+1
282 esta(1:iold) = estat(1:iold)
283 do i = 1, epp
284 esta(iold+i) = estat(iold+i-epp)
285 enddo
286 endif
287!
288! Define the information for the rows
289!
290! We order the constraints as follows: The objective is first,
291! followed by tddef, sdef, csdef, ddef, rdef, and revdef for
292! the first period, the same for the second period, etc.
293!
294! The objective is a nonbinding constraint:
295!
296 type(1) = 3
297!
298! All others are equalities:
299!
300 do i = 2, m
301 type(i) = 0
302 enddo
303!
304! Right hand sides: In all periods except the first, only tddef
305! has a nonzero right hand side of 1+2.3*1.015**(t-1).
306! In the initial period there are contributions from lagged
307! variables in the constraints that have lagged variables.
308!
309 do it = 1, t
310 is = 1 + 6*(it-1)
311 rhs(is+1) = 1.d0+2.3d0*1.015d0**(it-1)
312 enddo
313!
314! tddef: + 0.87*td(0)
315!
316 rhs(2) = rhs(2) + 0.87d0*18.d0
317!
318! sdef: +0.75*s(0)
319!
320 rhs(3) = 0.75d0*6.5d0
321!
322! csdef: +1*cs(0)
323!
324 rhs(4) = 0.d0
325!
326! rdef: +1*r(0)
327!
328 rhs(6) = 500.d0
329!
330! Define the structure and content of the Jacobian:
331! To help define the Jacobian pattern and values it can be useful to
332! make a picture of the Jacobian. We describe the variables for one
333! period and the constraints they are part of:
334!
335! td cs s d r p rev
336! Obj (1+r)**(1-t)
337! Period t:
338! tddef 1.0 0.13
339! sdef NL 1.0 NL
340! csdef 1.0 -1.0
341! ddef -1.0 1.0 1.0
342! rdef 1.0 1.0
343! revdef NL NL NL 1.0
344! Period t+1:
345! tddef -0.87
346! sdef -0.75
347! csdef -1.0
348! ddef
349! rdef -1.0
350! revdef
351!
352! The Jacobian has to be sorted column-wise so we will just define
353! the elements column by column according to the table above:
354!
355 iz = 1
356 icol = 1
357 do it = 1, t
358!
359! is points to the position before the first equation for the period
360!
361 is = 1 + 6*(it-1)
362!
363! Column td:
364!
365 colsta(icol) = iz
366 icol = icol + 1
367 rowno(iz) = is+1
368 value(iz) = +1.d0
369 nlflag(iz) = 0
370 iz = iz + 1
371 rowno(iz) = is+4
372 value(iz) = -1.d0
373 nlflag(iz) = 0
374 iz = iz + 1
375 if ( it .lt. t ) then
376 rowno(iz) = is+7
377 value(iz) = -0.87d0
378 nlflag(iz) = 0
379 iz = iz + 1
380 endif
381!
382! Column cs
383!
384 colsta(icol) = iz
385 icol = icol + 1
386 rowno(iz) = is+2
387 nlflag(iz) = 1
388 iz = iz + 1
389 rowno(iz) = is+3
390 value(iz) = +1.d0
391 nlflag(iz) = 0
392 iz = iz + 1
393 if ( it .lt. t ) then
394 rowno(iz) = is+9
395 value(iz) = -1.d0
396 nlflag(iz) = 0
397 iz = iz + 1
398 endif
399!
400! Column s
401!
402 colsta(icol) = iz
403 icol = icol + 1
404 rowno(iz) = is+2
405 value(iz) = +1.d0
406 nlflag(iz) = 0
407 iz = iz + 1
408 rowno(iz) = is+3
409 value(iz) = -1.d0
410 nlflag(iz) = 0
411 iz = iz + 1
412 rowno(iz) = is+4
413 value(iz) = +1.d0
414 nlflag(iz) = 0
415 iz = iz + 1
416 if ( it .lt. t ) then
417 rowno(iz) = is+8
418 value(iz) = -0.75d0
419 nlflag(iz) = 0
420 iz = iz + 1
421 endif
422!
423! Column d:
424!
425 colsta(icol) = iz
426 icol = icol + 1
427 rowno(iz) = is+4
428 value(iz) = +1.d0
429 nlflag(iz) = 0
430 iz = iz + 1
431 rowno(iz) = is+5
432 value(iz) = +1.d0
433 nlflag(iz) = 0
434 iz = iz + 1
435 rowno(iz) = is+6
436 nlflag(iz) = 1
437 iz = iz + 1
438!
439! Column r:
440!
441 colsta(icol) = iz
442 icol = icol + 1
443 rowno(iz) = is+5
444 value(iz) = +1.d0
445 nlflag(iz) = 0
446 iz = iz + 1
447 rowno(iz) = is+6
448 nlflag(iz) = 1
449 iz = iz + 1
450 if ( it .lt. t ) then
451 rowno(iz) = is+11
452 value(iz) = -1.d0
453 nlflag(iz) = 0
454 iz = iz + 1
455 endif
456!
457! Column p:
458!
459 colsta(icol) = iz
460 icol = icol + 1
461 rowno(iz) = is+1
462 value(iz) = +0.13d0
463 nlflag(iz) = 0
464 iz = iz + 1
465 rowno(iz) = is+2
466 nlflag(iz) = 1
467 iz = iz + 1
468 rowno(iz) = is+6
469 nlflag(iz) = 1
470 iz = iz + 1
471!
472! Column rev:
473!
474 colsta(icol) = iz
475 icol = icol + 1
476 rowno(iz) = +1
477 value(iz) = 1.05d0**(1-it)
478 nlflag(iz) = 0
479 iz = iz + 1
480 rowno(iz) = is+6
481 value(iz) = 1.d0
482 nlflag(iz) = 0
483 iz = iz + 1
484 enddo
485 colsta(icol) = iz
486
488
489end Function pin_readmatrix
490!
491! =====================================================================
492! Compute nonlinear terms and non-constant Jacobian elements
493!
494
495!> Compute nonlinear terms and non-constant Jacobian elements
496!!
497!! @include{doc} fdeval_params.dox
498Integer Function pin_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
499 n, nz, thread, usrmem )
500#if defined(itl)
501!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_FDEval
502#endif
503 Use pinadd2data
504 implicit none
505 integer, intent (in) :: n ! number of variables
506 integer, intent (in) :: rowno ! number of the row to be evaluated
507 integer, intent (in) :: nz ! number of nonzeros in this row
508 real*8, intent (in), dimension(n) :: x ! vector of current solution values
509 real*8, intent (in out) :: g ! constraint value
510 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
511 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
512 ! in this row. Ffor information only.
513 integer, intent (in) :: mode ! evaluation mode: 1 = function value
514 ! 2 = derivatives, 3 = both
515 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
516 ! as errcnt is incremented
517 integer, intent (in out) :: errcnt ! error counter to be incremented in case
518 ! of function evaluation errors.
519 integer, intent (in) :: thread
520 real*8 usrmem(*) ! optional user memory
521
522 integer :: it, is
523 real*8 :: h1, h2
524!
525! Compute the number of the period
526!
527 it = (rowno+4) / epp
528 is = vpp*(it-1)
529 if ( rowno == (it-1)*epp+3 ) then
530!
531! sdef equation. Nonlinear term = -(1.1+0.1*p)*1.02**(-cs/7)
532!
533 h1 = (1.1d0+0.1d0*x(is+6))
534 h2 = 1.02d0**(-x(is+2)/7.d0)
535 if ( mode == 1 .or. mode == 3 ) then
536 g = -h1*h2
537 endif
538 if ( mode == 2 .or. mode == 3 ) then
539 jac(is+2) = h1*h2*log(1.02d0)/7.d0
540 jac(is+6) = -h2*0.1d0
541 endif
542 elseif ( rowno == (it-1)*epp+7 ) then
543!
544! revdef equation. Nonlinear term = -d*(p-250/r)
545!
546 if ( mode == 1 .or. mode == 3 ) then
547 g = -x(is+4)*(x(is+6)-250.d0/x(is+5))
548 endif
549 if ( mode == 2 .or. mode == 3 ) then
550 jac(is+4) = -(x(is+6)-250.d0/x(is+5))
551 jac(is+5) = -x(is+4)*250d0/x(is+5)**2
552 jac(is+6) = -x(is+4)
553 endif
554 else
555!
556! Error - this equation is not nonlinear
557!
558 write(*,*)
559 write(*,*) 'Error. FDEval called with rowno=',rowno
560 write(*,*)
561 pin_fdeval = 1
562 Return
563 endif
564 pin_fdeval = 0
565
566end Function pin_fdeval
567
568Integer Function pin_solution( XVAL, XMAR, XBAS, XSTA, YVAL, YMAR, YBAS, YSTA, N, M, USRMEM )
569#if defined(itl)
570!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_Solution
571#endif
572
573 Use pinadd2data
574 Use proginfo
575 IMPLICIT NONE
576 INTEGER, Intent(IN) :: n, m
577 INTEGER, Intent(IN), Dimension(N) :: xbas, xsta
578 INTEGER, Intent(IN), Dimension(M) :: ybas, ysta
579 real*8, Intent(IN), Dimension(N) :: xval, xmar
580 real*8, Intent(IN), Dimension(M) :: yval, ymar
581 real*8, Intent(IN OUT) :: usrmem(*)
582 character*6, parameter, dimension(7) :: vname = (/'td ','cs ','s ','d ','r ','p ','rev '/)
583 character*6, parameter, dimension(6) :: ename = (/'tddef ','sdef ','csdef ','ddef ','rdef ','revdef'/)
584
585 INTEGER :: i, it, i1
586 CHARACTER*5, Parameter, Dimension(4) :: stat = (/ 'Lower','Upper','Basic','Super' /)
587
588 solcalls = solcalls + 1
589 If ( t < tmax ) Then
590 Write(*,"(A,i3)") 'Saving primal solution and status information for T =',t
591 xkeep(1:n) = xval(1:n)
592 xstas(1:n) = xbas(1:n)
593 estat(1:m) = ybas(1:m)
594 pin_solution = 0
595 Return
596 Endif
597
598 WRITE(10,"(/' Variable Solution value Reduced cost B-stat'/)")
599 i = 0
600 do it = 1, t
601 DO i1 = 1, vpp
602 i = i + 1
603 WRITE(10,"(1X,A6,i2,1p,E20.6,E16.6,4X,A5 )") vname(i1), it, xval(i), xmar(i), stat(1+xbas(i))
604 ENDDO
605 enddo
606
607 WRITE(10,"(/' Constrnt Activity level Marginal cost B-stat'/)")
608 i = 1
609 WRITE(10,"(1x,'Objective',1P,E19.6,E16.6,4X,A5 )") yval(i), ymar(i), stat(1+ybas(i))
610 do it = 1, t
611 do i1 = 1, epp
612 i = i + 1
613 WRITE(10,"(1x,A6,i2,1P,E20.6,E16.6,4X,A5 )") ename(i1),it, yval(i), ymar(i), stat(1+ybas(i))
614 enddo
615 ENDDO
616
617 pin_solution = 0
618
619END Function pin_solution
620
621
622!> Specify the structure of the Lagrangian of the Hessian
623!!
624!! @include{doc} 2DLagrStr_params.dox
625Integer Function pin_2dlagrstr( HSRW, HSCL, NODRV, N, M, NHESS, UsrMem )
626#if defined(itl)
627!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_2DLagrStr
628#endif
629 USE pinadd2data
630 Implicit None
631
632 Integer, Intent (IN) :: n, m, nhess
633 Integer, Intent (IN OUT) :: nodrv
634 Integer, Dimension(NHess), Intent (Out) :: hsrw, hscl
635 real*8, Intent(IN OUT) :: usrmem(*)
636
637 Integer :: it, is, ic
638!
639! There are two nonlinear constraints, Sdef and RevDef and they have
640! the following Hessians (for each time period):
641!
642! Revdef equation. Nonlinear term = -d*(p-250/r)
643! Hessian (diagonal and lower triangle): A total of 3 nonzero elements per period
644! 4 5 6
645! d r p
646! 4 : d
647! 5 : r -250/r**2 500*d/r**3
648! 6 : p -1
649!
650! Sdef: Nonlinear term = -(1.1+0.1p)*1.02**(-cs/7)
651! Hessian (diagonal and lower triangle): A total of 2 nonzero elements per period
652! 2 6
653! cs p
654! 2 : cs -(1.1+0.1p)*1.02**(-cs/7)*(log(1.02)/7)**2
655! 6 : p 0.1*1.02**(-cs/7)*(log(1.02)72)
656!
657! The two Hessian matrices do not overlap so the total number of nonzeros is
658! 5 per period. The structure using numerical indices for rows and columns and
659! running indices for the Hessian element is:
660!
661! 2 4 5 6
662! 2 1
663! 4
664! 5 3 5
665! 6 2 4
666!
667! and the same with names of variables and contributing equations
668! cs d r p
669! cs sdef
670! d
671! r revdef revdef
672! p sdef revdef
673!
674!
675! Define structure of Hessian
676!
677 if ( n /= vpp*t ) then
678 write(*,*) 'Struct: Number of variables should be=',vpp*t,' but CONOPT uses',n
679 write(*,*) 'Number of periods=',t
680 pin_2dlagrstr = 1; Return
681 stop
682 endif
683 if ( m /= epp*t+1 ) then
684 write(*,*) 'Struct: Number of equations should be=',epp*t+1,' but CONOPT uses',m
685 write(*,*) 'Number of periods=',t
686 pin_2dlagrstr = 1; Return
687 endif
688 Do it = 1, t
689 is = hpp*(it-1)
690 ic = vpp*(it-1)
691 hscl(is+1) = ic+2; hsrw(is+1) = ic+2
692 hscl(is+2) = ic+2; hsrw(is+2) = ic+6
693 hscl(is+3) = ic+4; hsrw(is+3) = ic+5
694 hscl(is+4) = ic+4; hsrw(is+4) = ic+6
695 hscl(is+5) = ic+5; hsrw(is+5) = ic+5
696 Enddo
697
698 pin_2dlagrstr = 0
699
700End Function pin_2dlagrstr
701
702
703!> Compute the Lagrangian of the Hessian
704!!
705!! @include{doc} 2DLagrVal_params.dox
706Integer Function pin_2dlagrval( X, U, HSRW, HSCL, HSVL, NODRV, N, M, NHESS, UsrMem )
707#if defined(itl)
708!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_2DLagrVal
709#endif
710 USE pinadd2data
711 Implicit None
712
713 Integer, Intent (IN) :: n, m, nhess
714 Integer, Intent (IN OUT) :: nodrv
715 real*8, Dimension(N), Intent (IN) :: x
716 real*8, Dimension(M), Intent (IN) :: u
717 Integer, Dimension(Nhess), Intent (IN) :: hsrw, hscl
718 real*8, Dimension(NHess), Intent (Out) :: hsvl
719 real*8, Intent(IN OUT) :: usrmem(*)
720
721 Integer :: it, is, ic, ie
722 real*8 :: cs, d, r, p
723 real*8 :: h1, h2
724!
725! There are two nonlinear constraints, Sdef and RevDef and they have
726! the following Hessians (for each time period):
727!
728! Revdef equation. Nonlinear term = -d*(p-250/r)
729! Hessian (diagonal and lower triangle): A total of 3 nonzero elements per period
730! 4 5 6
731! d r p
732! 4 : d
733! 5 : r -250/r**2 500*d/r**3
734! 6 : p -1
735!
736! Sdef: Nonlinear term = -(1.1+0.1p)*1.02**(-cs/7)
737! Hessian (diagonal and lower triangle): A total of 2 nonzero elements per period
738! 2 6
739! cs p
740! 2 : cs -(1.1+0.1p)*1.02**(-cs/7)*(log(1.02)/7)**2
741! 6 : p 0.1*1.02**(-cs/7)*(log(1.02)72)
742!
743! The two Hessian matrices do not overlap so the total number of nonzeros is
744! 5 per period. The structure using numerical indices for rows and columns and
745! running indices for the Hessian element is:
746!
747! 2 4 5 6
748! 2 1
749! 4
750! 5 3 5
751! 6 2 4
752!
753! and the same with names of variables and contributing equations
754! cs d r p
755! cs sdef
756! d
757! r revdef revdef
758! p sdef revdef
759!
760!
761! Normal Evaluation mode
762!
763 if ( n /= vpp*t ) then
764 write(*,*) 'Eval: Number of variables should be=',vpp*t,' but CONOPT uses',n
765 write(*,*) 'Number of periods=',t
766 pin_2dlagrval = 1; REturn
767 endif
768 if ( m /= epp*t+1 ) then
769 write(*,*) 'Eval: Number of equations should be=',epp*t+1,' but CONOPT uses',m
770 write(*,*) 'Number of periods=',t
771 pin_2dlagrval = 1; Return
772 endif
773 Do it = 1, t
774 is = hpp*(it-1)
775 ic = vpp*(it-1)
776 ie = epp*(it-1) + 1
777 cs = x(ic+2)
778 d = x(ic+4)
779 r = x(ic+5)
780 p = x(ic+6)
781 h1 = 1.1d0+0.1d0*p
782 h2 = 1.02d0**(-cs/7.d0)
783 hsvl(is+1) = -h1*h2*(log(1.02)/7.d0)**2 * u(ie+2) ! Sdef = equation 2
784 hsvl(is+2) = 0.1d0*h2*(log(1.02)/7.d0) * u(ie+2)
785 hsvl(is+3) = -250.d0/r**2 * u(ie+6) ! Revdef = equation 6
786 hsvl(is+4) = -1.d0 * u(ie+6)
787 hsvl(is+5) = 500.d0*d/ r**3 * u(ie+6)
788 enddo
789
790 pin_2dlagrval = 0
791
792End Function pin_2dlagrval
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_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_2dlagrstr(cntvect, coi_2dlagrstr)
define callback routine for providing the structure of the second derivatives of the Lagrangian.
integer function coidef_optfile(cntvect, optfile)
define callback routine for defining an options file.
integer function coidef_2dlagrval(cntvect, coi_2dlagrval)
define callback routine for computing the values of the second derivatives of the Lagrangian.
integer function coidef_inistat(cntvect, inistat)
handling of the initial status values.
integer function coidef_debug2d(cntvect, debug2d)
turn debugging of 2nd derivatives on and off.
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_numhess(cntvect, numhess)
defines the Number of Hessian Nonzeros.
Definition coistart.f90:513
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 t
Definition pinadd2.f90:15
integer, parameter tmax
Definition pinadd2.f90:16
integer, dimension(tmax *vpp) xstas
Definition pinadd2.f90:21
integer, parameter epp
Definition pinadd2.f90:18
integer, parameter hpp
Definition pinadd2.f90:19
integer, dimension(tmax *epp) estat
Definition pinadd2.f90:22
integer, parameter tmin
Definition pinadd2.f90:16
integer, parameter vpp
Definition pinadd2.f90:17
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 pinadd2
Main program. A simple setup and call of CONOPT.
Definition pinadd2.f90:27
integer function pin_2dlagrstr(hsrw, hscl, nodrv, n, m, nhess, usrmem)
Specify the structure of the Lagrangian of the Hessian.
Definition pinadd2.f90:626
integer function pin_2dlagrval(x, u, hsrw, hscl, hsvl, nodrv, n, m, nhess, usrmem)
Compute the Lagrangian of the Hessian.
Definition pinadd2.f90:707