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