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