CONOPT
Loading...
Searching...
No Matches
fvforall2.f90
Go to the documentation of this file.
1!> @file fvforall2.f90
2!! @ingroup FORT1THREAD_EXAMPLES
3!!
4!!
5!! This is the pindyck example rewritten to use the FVforAll2
6!! way of defining nonlinear functions. All functions, linear as
7!! well as nonlinear, will be called.
8!!
9!! The example is similar to FVforAll2, but constant terms are not
10!! put in the right hand side but instead added to the function
11!! values. This is possible since all constraints, including linear,
12!! are called.
13!!
14!!
15!! For more information about the individual callbacks, please have a look at the source code.
16
17#if defined(_WIN32) && !defined(_WIN64)
18#define dec_directives_win32
19#endif
20
21!> Main program. A simple setup and call of CONOPT
22!!
23Program fvforall2
24 Use proginfo
26 Use data_t
27 Implicit none
28!
29! Declare the user callback routines as Integer, External:
30!
31 Integer, External :: pin_readmatrix ! Mandatory Matrix definition routine defined below
32 Integer, External :: pin_fdeval ! Function and Derivative evaluation routine
33 ! needed a nonlinear model.
34 Integer, External :: std_status ! Standard callback for displaying solution status
35 Integer, External :: pin_solution ! Specialized callback for displaying solution values
36 Integer, External :: std_message ! Standard callback for managing messages
37 Integer, External :: std_errmsg ! Standard callback for managing error messages
38#ifdef dec_directives_win32
39!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_ReadMatrix
40!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_FDEval
41!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Status
42!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_Solution
43!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Message
44!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_ErrMsg
45#endif
46!
47! Control vector
48!
49 INTEGER, Dimension(:), Pointer :: cntvect
50 INTEGER :: coi_error
51!
52! Other variables
53!
54 INTEGER :: major, minor, patch
55
56 call startup
57!
58! Create and initialize a Control Vector
59!
60 coi_error = coi_create( cntvect )
61
62! Write which version of CONOPT we are using.
63
64 call coiget_version( major, minor, patch )
65 write(*,"('Solving Pindyck Model using CONOPT version ',i2,'.',i2,'.',i2)") major, minor, patch
66!
67! Define the number of time periods, T.
68!
69 t = 16
70!
71! Tell CONOPT about the size of the model by populating the Control Vector:
72!
73! Number of variables (excl. slacks): 7 per period
74!
75 coi_error = max( coi_error, coidef_numvar( cntvect, 7 * t ) )
76!
77! Number of equations: 1 objective + 6 per period
78!
79 coi_error = max( coi_error, coidef_numcon( cntvect, 1 + 6 * t ) )
80!
81! Number of nonzeros in the Jacobian. See the counting in ReadMatrix below:
82! For each period there is 1 in the objective, 16 for unlagged
83! variables and 4 for lagged variables.
84!
85 coi_error = max( coi_error, coidef_numnz( cntvect, 17 * t + 4 * (t-1) ) )
86!
87! Number of nonlinear nonzeros. 5 unlagged for each period.
88!
89 coi_error = max( coi_error, coidef_numnlnz( cntvect, 5 * t ) )
90!
91! Direction: +1 = maximization.
92!
93 coi_error = max( coi_error, coidef_optdir( cntvect, 1 ) )
94!
95! Objective: Constraint no 1
96!
97 coi_error = max( coi_error, coidef_objcon( cntvect, 1 ) )
98!
99! Define that all functions should be called.
100!
101 coi_error = max( coi_error, coidef_fvforall( cntvect, +1 ) )
102!
103! Turn function debugging on in the initial point to check if it is consistent
104! with FVforAll2:
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 FVforAll2 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( 'FVforAll2', 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 fvforall2
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! All right hand sides have been included in the function values.
246!
247! Define the structure and content of the Jacobian:
248! To help define the Jacobian pattern and values it can be useful to
249! make a picture of the Jacobian. We describe the variables for one
250! period and the constraints they are part of:
251!
252! td cs s d r p rev
253! Obj (1+r)**(1-t)
254! Period t:
255! tddef 1.0 0.13
256! sdef NL 1.0 NL
257! csdef 1.0 -1.0
258! ddef -1.0 1.0 1.0
259! rdef 1.0 1.0
260! revdef NL NL NL 1.0
261! Period t+1:
262! tddef -0.87
263! sdef -0.75
264! csdef -1.0
265! ddef
266! rdef -1.0
267! revdef
268!
269! The Jacobian has to be sorted column-wise so we will just define
270! the elements column by column according to the table above:
271!
272 iz = 1
273 icol = 1
274 do it = 1, t
275!
276! is points to the position before the first equation for the period
277!
278 is = 1 + 6*(it-1)
279!
280! Column td:
281!
282 colsta(icol) = iz
283 icol = icol + 1
284 rowno(iz) = is+1
285 value(iz) = +1.d0
286 nlflag(iz) = 0
287 iz = iz + 1
288 rowno(iz) = is+4
289 value(iz) = -1.d0
290 nlflag(iz) = 0
291 iz = iz + 1
292 if ( it .lt. t ) then
293 rowno(iz) = is+7
294 value(iz) = -0.87d0
295 nlflag(iz) = 0
296 iz = iz + 1
297 endif
298!
299! Column cs
300!
301 colsta(icol) = iz
302 icol = icol + 1
303 rowno(iz) = is+2
304 nlflag(iz) = 1
305 iz = iz + 1
306 rowno(iz) = is+3
307 value(iz) = +1.d0
308 nlflag(iz) = 0
309 iz = iz + 1
310 if ( it .lt. t ) then
311 rowno(iz) = is+9
312 value(iz) = -1.d0
313 nlflag(iz) = 0
314 iz = iz + 1
315 endif
316!
317! Column s
318!
319 colsta(icol) = iz
320 icol = icol + 1
321 rowno(iz) = is+2
322 value(iz) = +1.d0
323 nlflag(iz) = 0
324 iz = iz + 1
325 rowno(iz) = is+3
326 value(iz) = -1.d0
327 nlflag(iz) = 0
328 iz = iz + 1
329 rowno(iz) = is+4
330 value(iz) = +1.d0
331 nlflag(iz) = 0
332 iz = iz + 1
333 if ( it .lt. t ) then
334 rowno(iz) = is+8
335 value(iz) = -0.75d0
336 nlflag(iz) = 0
337 iz = iz + 1
338 endif
339!
340! Column d:
341!
342 colsta(icol) = iz
343 icol = icol + 1
344 rowno(iz) = is+4
345 value(iz) = +1.d0
346 nlflag(iz) = 0
347 iz = iz + 1
348 rowno(iz) = is+5
349 value(iz) = +1.d0
350 nlflag(iz) = 0
351 iz = iz + 1
352 rowno(iz) = is+6
353 nlflag(iz) = 1
354 iz = iz + 1
355!
356! Column r:
357!
358 colsta(icol) = iz
359 icol = icol + 1
360 rowno(iz) = is+5
361 value(iz) = +1.d0
362 nlflag(iz) = 0
363 iz = iz + 1
364 rowno(iz) = is+6
365 nlflag(iz) = 1
366 iz = iz + 1
367 if ( it .lt. t ) then
368 rowno(iz) = is+11
369 value(iz) = -1.d0
370 nlflag(iz) = 0
371 iz = iz + 1
372 endif
373!
374! Column p:
375!
376 colsta(icol) = iz
377 icol = icol + 1
378 rowno(iz) = is+1
379 value(iz) = +0.13d0
380 nlflag(iz) = 0
381 iz = iz + 1
382 rowno(iz) = is+2
383 nlflag(iz) = 1
384 iz = iz + 1
385 rowno(iz) = is+6
386 nlflag(iz) = 1
387 iz = iz + 1
388!
389! Column rev:
390!
391 colsta(icol) = iz
392 icol = icol + 1
393 rowno(iz) = +1
394 value(iz) = 1.05d0**(1-it)
395 nlflag(iz) = 0
396 iz = iz + 1
397 rowno(iz) = is+6
398 value(iz) = 1.d0
399 nlflag(iz) = 0
400 iz = iz + 1
401 enddo
402 colsta(icol) = iz
405
406end Function pin_readmatrix
407!
408! =====================================================================
409! Compute nonlinear terms and non-constant Jacobian elements
410!
411
412!> Compute nonlinear terms and non-constant Jacobian elements
413!!
414!! @include{doc} fdeval_params.dox
415Integer Function pin_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
416 n, nz, thread, usrmem )
417#ifdef dec_directives_win32
418!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_FDEval
419#endif
420 Use data_t
421 implicit none
422 integer, intent (in) :: n ! number of variables
423 integer, intent (in) :: rowno ! number of the row to be evaluated
424 integer, intent (in) :: nz ! number of nonzeros in this row
425 real*8, intent (in), dimension(n) :: x ! vector of current solution values
426 real*8, intent (in out) :: g ! constraint value
427 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
428 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
429 ! in this row. Ffor information only.
430 integer, intent (in) :: mode ! evaluation mode: 1 = function value
431 ! 2 = derivatives, 3 = both
432 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
433 ! as errcnt is incremented
434 integer, intent (in out) :: errcnt ! error counter to be incremented in case
435 ! of function evaluation errors.
436 integer, intent (in) :: thread
437 real*8 usrmem(*) ! optional user memory
438
439 integer it, is
440 real*8 h1, h2
441!
442! Compute the number of the period
443!
444 pin_fdeval = 0
445 it = (rowno+4) / 6
446 is = 7*(it-1)
447 if ( rowno == 1 ) then
448!
449! This is the linear objective
450!
451 if ( mode == 1 .or. mode == 3 ) then
452 g = 0.0d0
453 endif
454 else if ( rowno == (it-1)*6+2 ) then
455!
456! tddef equation. All terms: rhs = 1+2.3*1.015**(t-1).
457! In the initial period there are contributions from lagged
458! variables in the constraints that have lagged variables.
459!
460 if ( mode == 1 .or. mode == 3 ) then
461 g = -( 1.d0+2.3d0*1.015d0**(it-1) )
462 if ( it == 1 ) g = g - 0.87d0*18.d0
463 endif
464 else if ( rowno == (it-1)*6+3 ) then
465!
466! sdef equation. NL Terms: -(1.1+0.1*p)*1.02**(-cs/7)
467! rhs = 0.75d0*6.5d0
468!
469 h1 = (1.1d0+0.1d0*x(is+6))
470 h2 = 1.02d0**(-x(is+2)/7.d0)
471 if ( mode == 1 .or. mode == 3 ) then
472 g = -h1*h2
473 if ( it == 1 ) g = g - 0.75d0*6.5d0
474 endif
475 if ( mode == 2 .or. mode == 3 ) then
476 jac(is+2) = h1*h2*log(1.02d0)/7.d0
477 jac(is+6) = -h2*0.1d0
478 endif
479 elseif ( rowno == (it-1)*6+4 ) then
480!
481! csdef: rhs = +1*cs(0) = 0
482!
483 if ( mode == 1 .or. mode == 3 ) then
484 g = 0.0d0
485 endif
486 elseif ( rowno == (it-1)*6+6 ) then
487!
488! rdef: +1*r(0)
489!
490 if ( mode == 1 .or. mode == 3 ) then
491 g = 0.0d0
492 if ( it == 1 ) g = g - 500.d0
493 endif
494 elseif ( rowno == (it-1)*6+7 ) then
495!
496! revdef equation. NL term: d*(p-250/r)
497!
498 if ( mode == 1 .or. mode == 3 ) then
499 g = -x(is+4)*(x(is+6)-250.d0/x(is+5))
500 endif
501 if ( mode == 2 .or. mode == 3 ) then
502 jac(is+4) = -(x(is+6)-250.d0/x(is+5))
503 jac(is+5) = -x(is+4)*250d0/x(is+5)**2
504 jac(is+6) = -x(is+4)
505 endif
506 else
507!
508! This is a linear constraint so we return function value zero and
509! no derivatives.
510!
511 if ( mode == 1 .or. mode == 3 ) then
512 g = 0.0d0
513 endif
514 endif
515
516end Function pin_fdeval
517
518Integer Function pin_solution( XVAL, XMAR, XBAS, XSTA, YVAL, YMAR, YBAS, YSTA, N, M, USRMEM )
519#ifdef dec_directives_win32
520!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_Solution
521#endif
522!
523! Specialized solution callback routine with names for variables and constraints
524!
525 Use proginfo
526 Use data_t
527 IMPLICIT NONE
528 INTEGER, Intent(IN) :: n, m
529 INTEGER, Intent(IN), Dimension(N) :: xbas, xsta
530 INTEGER, Intent(IN), Dimension(M) :: ybas, ysta
531 real*8, Intent(IN), Dimension(N) :: xval, xmar
532 real*8, Intent(IN), Dimension(M) :: yval, ymar
533 real*8, Intent(IN OUT) :: usrmem(*)
534 character*6, parameter, dimension(7) :: vname = (/'td ','cs ','s ','d ','r ','p ','rev '/)
535 character*6, parameter, dimension(6) :: ename = (/'tddef ','sdef ','csdef ','ddef ','rdef ','revdef'/)
536
537 INTEGER :: i, it, i1
538 CHARACTER*5, Parameter, Dimension(4) :: stat = (/ 'Lower','Upper','Basic','Super' /)
539
540 WRITE(10,"(/' Variable Solution value Reduced cost B-stat'/)")
541 i = 0
542 do it = 1, t
543 DO i1 = 1, 7
544 i = i + 1
545 WRITE(10,"(1X,A6,i2,1p,E20.6,E16.6,4X,A5 )") vname(i1), it, xval(i), xmar(i), stat(1+xbas(i))
546 ENDDO
547 enddo
548
549 WRITE(10,"(/' Constrnt Activity level Marginal cost B-stat'/)")
550 i = 1
551 WRITE(10,"(1x,'Objective',1P,E19.6,E16.6,4X,A5 )") yval(i), ymar(i), stat(1+ybas(i))
552 do it = 1, t
553 do i1 = 1, 6
554 i = i + 1
555 WRITE(10,"(1x,A6,i2,1P,E20.6,E16.6,4X,A5 )") ename(i1),it, yval(i), ymar(i), stat(1+ybas(i))
556 enddo
557 ENDDO
558
559 solcalls = solcalls + 1
560 pin_solution = 0
561
562END 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 fvforall2
Main program. A simple setup and call of CONOPT.
Definition fvforall2.f90:25
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_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