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