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