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