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