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!
155! Free solution memory
156!
157 call finalize
158
159end Program fvboth
160!
161! =====================================================================
162! Define information about the model structure
163!
164
165!> Define information about the model
166!!
167!! @include{doc} readMatrix_params.dox
168Integer Function pin_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
169 colsta, rowno, value, nlflag, n, m, nz, usrmem )
170#ifdef dec_directives_win32
171!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_ReadMatrix
172#endif
173 Use data_t
174 implicit none
175 integer, intent (in) :: n ! number of variables
176 integer, intent (in) :: m ! number of constraints
177 integer, intent (in) :: nz ! number of nonzeros
178 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
179 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
180 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
181 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
182 ! (not defined here)
183 integer, intent (out), dimension(m) :: type ! vector of equation types
184 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
185 ! (not defined here)
186 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
187 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
188 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
189 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
190 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
191 real*8 usrmem(*) ! optional user memory
192
193 Integer :: it, is, i, icol, iz
194!
195! Define the information for the columns.
196!
197! We should not supply status information, vsta.
198!
199! We order the variables as follows:
200! td, cs, s, d, r, p, and rev. All variables for period 1 appears
201! first followed by all variables for period 2 etc.
202!
203! td, cs, s, and d have lower bounds of 0, r and p have lower
204! bounds of 1, and rev has no lower bound.
205! All have infinite upper bounds (default).
206! The initial value of td is 18, s is 7, cs is 7*t, d is td-s,
207! p is 14, and r is r(t-1)-d. No initial value for rev.
208!
209 do it = 1, t
210 is = 7*(it-1)
211 lower(is+1) = 0.d0
212 lower(is+2) = 0.d0
213 lower(is+3) = 0.d0
214 lower(is+4) = 0.d0
215 lower(is+5) = 1.d0
216 lower(is+6) = 1.d0
217 curr(is+1) = 18.d0
218 curr(is+2) = 7.d0*it
219 curr(is+3) = 7.d0
220 curr(is+4) = curr(is+1) - curr(is+3)
221 if ( it .gt. 1 ) then
222 curr(is+5) = curr(is+5-7) - curr(is+4)
223 else
224 curr(is+5) = 500.d0 - curr(is+4)
225 endif
226 curr(is+6) = 14.d0
227 enddo
228!
229! Define the information for the rows
230!
231! We order the constraints as follows: The objective is first,
232! followed by tddef, sdef, csdef, ddef, rdef, and revdef for
233! the first period, the same for the second period, etc.
234!
235! The objective is a nonbinding constraint:
236!
237 type(1) = 3
238!
239! All others are equalities:
240!
241 do i = 2, m
242 type(i) = 0
243 enddo
244!
245! Right hand sides: In all periods except the first, only tddef
246! has a nonzero right hand side of 1+2.3*1.015**(t-1).
247! In the initial period there are contributions from lagged
248! variables in the constraints that have lagged variables.
249!
250 do it = 1, t
251 is = 1 + 6*(it-1)
252 rhs(is+1) = 1.d0+2.3d0*1.015d0**(it-1)
253 enddo
254!
255! tddef: + 0.87*td(0)
256!
257 rhs(2) = rhs(2) + 0.87d0*18.d0
258!
259! sdef: +0.75*s(0)
260!
261 rhs(3) = 0.75d0*6.5d0
262!
263! csdef: +1*cs(0)
264!
265 rhs(4) = 0.d0
266!
267! rdef: +1*r(0)
268!
269 rhs(6) = 500.d0
270!
271! Define the structure and content of the Jacobian:
272! To help define the Jacobian pattern and values it can be useful to
273! make a picture of the Jacobian. We describe the variables for one
274! period and the constraints they are part of:
275!
276! td cs s d r p rev
277! Obj (1+r)**(1-t)
278! Period t:
279! tddef 1.0 0.13
280! sdef NL 1.0 NL
281! csdef 1.0 -1.0
282! ddef -1.0 1.0 1.0
283! rdef 1.0 1.0
284! revdef NL NL NL 1.0
285! Period t+1:
286! tddef -0.87
287! sdef -0.75
288! csdef -1.0
289! ddef
290! rdef -1.0
291! revdef
292!
293! The Jacobian has to be sorted column-wise so we will just define
294! the elements column by column according to the table above:
295!
296 iz = 1
297 icol = 1
298 do it = 1, t
299!
300! is points to the position before the first equation for the period
301!
302 is = 1 + 6*(it-1)
303!
304! Column td:
305!
306 colsta(icol) = iz
307 icol = icol + 1
308 rowno(iz) = is+1
309 value(iz) = +1.d0
310 nlflag(iz) = 0
311 iz = iz + 1
312 rowno(iz) = is+4
313 value(iz) = -1.d0
314 nlflag(iz) = 0
315 iz = iz + 1
316 if ( it .lt. t ) then
317 rowno(iz) = is+7
318 value(iz) = -0.87d0
319 nlflag(iz) = 0
320 iz = iz + 1
321 endif
322!
323! Column cs
324!
325 colsta(icol) = iz
326 icol = icol + 1
327 rowno(iz) = is+2
328 nlflag(iz) = 1
329 iz = iz + 1
330 rowno(iz) = is+3
331 value(iz) = +1.d0
332 nlflag(iz) = 0
333 iz = iz + 1
334 if ( it .lt. t ) then
335 rowno(iz) = is+9
336 value(iz) = -1.d0
337 nlflag(iz) = 0
338 iz = iz + 1
339 endif
340!
341! Column s
342!
343 colsta(icol) = iz
344 icol = icol + 1
345 rowno(iz) = is+2
346 value(iz) = +1.d0
347 nlflag(iz) = 0
348 iz = iz + 1
349 rowno(iz) = is+3
350 value(iz) = -1.d0
351 nlflag(iz) = 0
352 iz = iz + 1
353 rowno(iz) = is+4
354 value(iz) = +1.d0
355 nlflag(iz) = 0
356 iz = iz + 1
357 if ( it .lt. t ) then
358 rowno(iz) = is+8
359 value(iz) = -0.75d0
360 nlflag(iz) = 0
361 iz = iz + 1
362 endif
363!
364! Column d:
365!
366 colsta(icol) = iz
367 icol = icol + 1
368 rowno(iz) = is+4
369 value(iz) = +1.d0
370 nlflag(iz) = 0
371 iz = iz + 1
372 rowno(iz) = is+5
373 value(iz) = +1.d0
374 nlflag(iz) = 0
375 iz = iz + 1
376 rowno(iz) = is+6
377 nlflag(iz) = 1
378 iz = iz + 1
379!
380! Column r:
381!
382 colsta(icol) = iz
383 icol = icol + 1
384 rowno(iz) = is+5
385 value(iz) = +1.d0
386 nlflag(iz) = 0
387 iz = iz + 1
388 rowno(iz) = is+6
389 nlflag(iz) = 1
390 iz = iz + 1
391 if ( it .lt. t ) then
392 rowno(iz) = is+11
393 value(iz) = -1.d0
394 nlflag(iz) = 0
395 iz = iz + 1
396 endif
397!
398! Column p:
399!
400 colsta(icol) = iz
401 icol = icol + 1
402 rowno(iz) = is+1
403 value(iz) = +0.13d0
404 nlflag(iz) = 0
405 iz = iz + 1
406 rowno(iz) = is+2
407 nlflag(iz) = 1
408 iz = iz + 1
409 rowno(iz) = is+6
410 nlflag(iz) = 1
411 iz = iz + 1
412!
413! Column rev:
414!
415 colsta(icol) = iz
416 icol = icol + 1
417 rowno(iz) = +1
418 value(iz) = 1.05d0**(1-it)
419 nlflag(iz) = 0
420 iz = iz + 1
421 rowno(iz) = is+6
422 value(iz) = 1.d0
423 nlflag(iz) = 0
424 iz = iz + 1
425 enddo
426 colsta(icol) = iz
429
430end Function pin_readmatrix
431!
432! =====================================================================
433! Compute nonlinear terms and non-constant Jacobian elements
434!
435
436!> Compute nonlinear terms and non-constant Jacobian elements
437!!
438!! @include{doc} fdeval_params.dox
439Integer Function pin_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
440 n, nz, thread, usrmem )
441#ifdef dec_directives_win32
442!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_FDEval
443#endif
444 Use data_t
445 implicit none
446 integer, intent (in) :: n ! number of variables
447 integer, intent (in) :: rowno ! number of the row to be evaluated
448 integer, intent (in) :: nz ! number of nonzeros in this row
449 real*8, intent (in), dimension(n) :: x ! vector of current solution values
450 real*8, intent (in out) :: g ! constraint value
451 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
452 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
453 ! in this row. Ffor information only.
454 integer, intent (in) :: mode ! evaluation mode: 1 = function value
455 ! 2 = derivatives, 3 = both
456 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
457 ! as errcnt is incremented
458 integer, intent (in out) :: errcnt ! error counter to be incremented in case
459 ! of function evaluation errors.
460 integer, intent (in) :: thread
461 real*8 usrmem(*) ! optional user memory
462
463 integer it, is
464 real*8 h1, h2
465!
466! Compute the number of the period
467!
468 pin_fdeval = 0
469 it = (rowno+4) / 6
470 is = 7*(it-1)
471 if ( rowno == 1 ) then
472!
473! This is the linear objective
474! Obj : sum(t,(1+r)**(1-t)*rev(t)
475!
476 if ( mode == 1 .or. mode == 3 ) then
477 g = 0.0d0
478 do it = 1, t
479 is = 7*(it-1)
480 g = g + x(is+7) * 1.05d0**(1-it)
481 enddo
482 endif
483 else if ( rowno == (it-1)*6+2 ) then
484!
485! tddef equation. All terms: td + 0.13*p -0.87*td(t-1)
486!
487 if ( mode == 1 .or. mode == 3 ) then
488 g = x(is+1) + 0.13d0*x(is+6)
489 if ( it > 1 ) g = g - 0.87d0*x(is+1-7)
490 endif
491 else if ( rowno == (it-1)*6+3 ) then
492!
493! sdef equation. All terms: s - 0.75*s(t-1) -(1.1+0.1*p)*1.02**(-cs/7)
494!
495 h1 = (1.1d0+0.1d0*x(is+6))
496 h2 = 1.02d0**(-x(is+2)/7.d0)
497 if ( mode == 1 .or. mode == 3 ) then
498 g = x(is+3) -h1*h2
499 if ( it > 1 ) g = g - 0.75d0*x(is+3-7) ! 0.75*s(t-1) only it t > 1
500 endif
501 if ( mode == 2 .or. mode == 3 ) then
502 jac(is+2) = h1*h2*log(1.02d0)/7.d0
503 jac(is+6) = -h2*0.1d0
504 endif
505 else if ( rowno == (it-1)*6+4 ) then
506!
507! csdef equation. All terms: cs - s - cs(t-1)
508!
509 if ( mode == 1 .or. mode == 3 ) then
510 g = x(is+2) - x(is+3)
511 if ( it > 1 ) g = g - x(is+2-7)
512 endif
513 else if ( rowno == (it-1)*6+5 ) then
514!
515! ddef equation. All terms: -td + s + d
516!
517 if ( mode == 1 .or. mode == 3 ) then
518 g = -x(is+1) + x(is+3) + x(is+4)
519 endif
520 else if ( rowno == (it-1)*6+6 ) then
521!
522! rdef equation. All terms: d + r - r(t-1)
523!
524 if ( mode == 1 .or. mode == 3 ) then
525 g = x(is+4) + x(is+5)
526 if ( it > 1 ) g = g - x(is+5-7)
527 endif
528 elseif ( rowno == (it-1)*6+7 ) then
529!
530! revdef equation. All terms: rev - d*(p-250/r)
531!
532 if ( mode == 1 .or. mode == 3 ) then
533 g = x(is+7) -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! We should have covered everything above so this is an error.
543!
544 pin_fdeval = 1
545 endif
546
547end Function pin_fdeval
548
549Integer Function pin_solution( XVAL, XMAR, XBAS, XSTA, YVAL, YMAR, YBAS, YSTA, N, M, USRMEM )
550#ifdef dec_directives_win32
551!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_Solution
552#endif
553!
554! Specialized solution callback routine with names for variables and constraints
555!
556 Use proginfo
557 Use data_t
558 IMPLICIT NONE
559 INTEGER, Intent(IN) :: n, m
560 INTEGER, Intent(IN), Dimension(N) :: xbas, xsta
561 INTEGER, Intent(IN), Dimension(M) :: ybas, ysta
562 real*8, Intent(IN), Dimension(N) :: xval, xmar
563 real*8, Intent(IN), Dimension(M) :: yval, ymar
564 real*8, Intent(IN OUT) :: usrmem(*)
565 character*6, parameter, dimension(7) :: vname = (/'td ','cs ','s ','d ','r ','p ','rev '/)
566 character*6, parameter, dimension(6) :: ename = (/'tddef ','sdef ','csdef ','ddef ','rdef ','revdef'/)
567
568 INTEGER :: i, it, i1
569 CHARACTER*5, Parameter, Dimension(4) :: stat = (/ 'Lower','Upper','Basic','Super' /)
570
571 WRITE(10,"(/' Variable Solution value Reduced cost B-stat'/)")
572 i = 0
573 do it = 1, t
574 DO i1 = 1, 7
575 i = i + 1
576 WRITE(10,"(1X,A6,i2,1p,E20.6,E16.6,4X,A5 )") vname(i1), it, xval(i), xmar(i), stat(1+xbas(i))
577 ENDDO
578 enddo
579
580 WRITE(10,"(/' Constrnt Activity level Marginal cost B-stat'/)")
581 i = 1
582 WRITE(10,"(1x,'Objective',1P,E19.6,E16.6,4X,A5 )") yval(i), ymar(i), stat(1+ybas(i))
583 do it = 1, t
584 do i1 = 1, 6
585 i = i + 1
586 WRITE(10,"(1x,A6,i2,1P,E20.6,E16.6,4X,A5 )") ename(i1),it, yval(i), ymar(i), stat(1+ybas(i))
587 enddo
588 ENDDO
589
590 solcalls = solcalls + 1
591 pin_solution = 0
592
593END Function pin_solution
integer function std_status(modsta, solsta, iter, objval, usrmem)
Definition comdecl.f90:126
subroutine checkdual(case, minmax)
Definition comdecl.f90:432
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
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
subroutine finalize
Definition comdecl.f90:79
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