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
155end Program fvforall2
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! All right hand sides have been included in the function values.
242!
243! Define the structure and content of the Jacobian:
244! To help define the Jacobian pattern and values it can be useful to
245! make a picture of the Jacobian. We describe the variables for one
246! period and the constraints they are part of:
247!
248! td cs s d r p rev
249! Obj (1+r)**(1-t)
250! Period t:
251! tddef 1.0 0.13
252! sdef NL 1.0 NL
253! csdef 1.0 -1.0
254! ddef -1.0 1.0 1.0
255! rdef 1.0 1.0
256! revdef NL NL NL 1.0
257! Period t+1:
258! tddef -0.87
259! sdef -0.75
260! csdef -1.0
261! ddef
262! rdef -1.0
263! revdef
264!
265! The Jacobian has to be sorted column-wise so we will just define
266! the elements column by column according to the table above:
267!
268 iz = 1
269 icol = 1
270 do it = 1, t
271!
272! is points to the position before the first equation for the period
273!
274 is = 1 + 6*(it-1)
275!
276! Column td:
277!
278 colsta(icol) = iz
279 icol = icol + 1
280 rowno(iz) = is+1
281 value(iz) = +1.d0
282 nlflag(iz) = 0
283 iz = iz + 1
284 rowno(iz) = is+4
285 value(iz) = -1.d0
286 nlflag(iz) = 0
287 iz = iz + 1
288 if ( it .lt. t ) then
289 rowno(iz) = is+7
290 value(iz) = -0.87d0
291 nlflag(iz) = 0
292 iz = iz + 1
293 endif
294!
295! Column cs
296!
297 colsta(icol) = iz
298 icol = icol + 1
299 rowno(iz) = is+2
300 nlflag(iz) = 1
301 iz = iz + 1
302 rowno(iz) = is+3
303 value(iz) = +1.d0
304 nlflag(iz) = 0
305 iz = iz + 1
306 if ( it .lt. t ) then
307 rowno(iz) = is+9
308 value(iz) = -1.d0
309 nlflag(iz) = 0
310 iz = iz + 1
311 endif
312!
313! Column s
314!
315 colsta(icol) = iz
316 icol = icol + 1
317 rowno(iz) = is+2
318 value(iz) = +1.d0
319 nlflag(iz) = 0
320 iz = iz + 1
321 rowno(iz) = is+3
322 value(iz) = -1.d0
323 nlflag(iz) = 0
324 iz = iz + 1
325 rowno(iz) = is+4
326 value(iz) = +1.d0
327 nlflag(iz) = 0
328 iz = iz + 1
329 if ( it .lt. t ) then
330 rowno(iz) = is+8
331 value(iz) = -0.75d0
332 nlflag(iz) = 0
333 iz = iz + 1
334 endif
335!
336! Column d:
337!
338 colsta(icol) = iz
339 icol = icol + 1
340 rowno(iz) = is+4
341 value(iz) = +1.d0
342 nlflag(iz) = 0
343 iz = iz + 1
344 rowno(iz) = is+5
345 value(iz) = +1.d0
346 nlflag(iz) = 0
347 iz = iz + 1
348 rowno(iz) = is+6
349 nlflag(iz) = 1
350 iz = iz + 1
351!
352! Column r:
353!
354 colsta(icol) = iz
355 icol = icol + 1
356 rowno(iz) = is+5
357 value(iz) = +1.d0
358 nlflag(iz) = 0
359 iz = iz + 1
360 rowno(iz) = is+6
361 nlflag(iz) = 1
362 iz = iz + 1
363 if ( it .lt. t ) then
364 rowno(iz) = is+11
365 value(iz) = -1.d0
366 nlflag(iz) = 0
367 iz = iz + 1
368 endif
369!
370! Column p:
371!
372 colsta(icol) = iz
373 icol = icol + 1
374 rowno(iz) = is+1
375 value(iz) = +0.13d0
376 nlflag(iz) = 0
377 iz = iz + 1
378 rowno(iz) = is+2
379 nlflag(iz) = 1
380 iz = iz + 1
381 rowno(iz) = is+6
382 nlflag(iz) = 1
383 iz = iz + 1
384!
385! Column rev:
386!
387 colsta(icol) = iz
388 icol = icol + 1
389 rowno(iz) = +1
390 value(iz) = 1.05d0**(1-it)
391 nlflag(iz) = 0
392 iz = iz + 1
393 rowno(iz) = is+6
394 value(iz) = 1.d0
395 nlflag(iz) = 0
396 iz = iz + 1
397 enddo
398 colsta(icol) = iz
401
402end Function pin_readmatrix
403!
404! =====================================================================
405! Compute nonlinear terms and non-constant Jacobian elements
406!
407
408!> Compute nonlinear terms and non-constant Jacobian elements
409!!
410!! @include{doc} fdeval_params.dox
411Integer Function pin_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
412 n, nz, thread, usrmem )
413#ifdef dec_directives_win32
414!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_FDEval
415#endif
416 Use data_t
417 implicit none
418 integer, intent (in) :: n ! number of variables
419 integer, intent (in) :: rowno ! number of the row to be evaluated
420 integer, intent (in) :: nz ! number of nonzeros in this row
421 real*8, intent (in), dimension(n) :: x ! vector of current solution values
422 real*8, intent (in out) :: g ! constraint value
423 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
424 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
425 ! in this row. Ffor information only.
426 integer, intent (in) :: mode ! evaluation mode: 1 = function value
427 ! 2 = derivatives, 3 = both
428 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
429 ! as errcnt is incremented
430 integer, intent (in out) :: errcnt ! error counter to be incremented in case
431 ! of function evaluation errors.
432 integer, intent (in) :: thread
433 real*8 usrmem(*) ! optional user memory
434
435 integer it, is
436 real*8 h1, h2
437!
438! Compute the number of the period
439!
440 pin_fdeval = 0
441 it = (rowno+4) / 6
442 is = 7*(it-1)
443 if ( rowno == 1 ) then
444!
445! This is the linear objective
446!
447 if ( mode == 1 .or. mode == 3 ) then
448 g = 0.0d0
449 endif
450 else if ( rowno == (it-1)*6+2 ) then
451!
452! tddef equation. All terms: rhs = 1+2.3*1.015**(t-1).
453! In the initial period there are contributions from lagged
454! variables in the constraints that have lagged variables.
455!
456 if ( mode == 1 .or. mode == 3 ) then
457 g = -( 1.d0+2.3d0*1.015d0**(it-1) )
458 if ( it == 1 ) g = g - 0.87d0*18.d0
459 endif
460 else if ( rowno == (it-1)*6+3 ) then
461!
462! sdef equation. NL Terms: -(1.1+0.1*p)*1.02**(-cs/7)
463! rhs = 0.75d0*6.5d0
464!
465 h1 = (1.1d0+0.1d0*x(is+6))
466 h2 = 1.02d0**(-x(is+2)/7.d0)
467 if ( mode == 1 .or. mode == 3 ) then
468 g = -h1*h2
469 if ( it == 1 ) g = g - 0.75d0*6.5d0
470 endif
471 if ( mode == 2 .or. mode == 3 ) then
472 jac(is+2) = h1*h2*log(1.02d0)/7.d0
473 jac(is+6) = -h2*0.1d0
474 endif
475 elseif ( rowno == (it-1)*6+4 ) then
476!
477! csdef: rhs = +1*cs(0) = 0
478!
479 if ( mode == 1 .or. mode == 3 ) then
480 g = 0.0d0
481 endif
482 elseif ( rowno == (it-1)*6+6 ) then
483!
484! rdef: +1*r(0)
485!
486 if ( mode == 1 .or. mode == 3 ) then
487 g = 0.0d0
488 if ( it == 1 ) g = g - 500.d0
489 endif
490 elseif ( rowno == (it-1)*6+7 ) then
491!
492! revdef equation. NL term: d*(p-250/r)
493!
494 if ( mode == 1 .or. mode == 3 ) then
495 g = -x(is+4)*(x(is+6)-250.d0/x(is+5))
496 endif
497 if ( mode == 2 .or. mode == 3 ) then
498 jac(is+4) = -(x(is+6)-250.d0/x(is+5))
499 jac(is+5) = -x(is+4)*250d0/x(is+5)**2
500 jac(is+6) = -x(is+4)
501 endif
502 else
503!
504! This is a linear constraint so we return function value zero and
505! no derivatives.
506!
507 if ( mode == 1 .or. mode == 3 ) then
508 g = 0.0d0
509 endif
510 endif
511
512end Function pin_fdeval
513
514Integer Function pin_solution( XVAL, XMAR, XBAS, XSTA, YVAL, YMAR, YBAS, YSTA, N, M, USRMEM )
515#ifdef dec_directives_win32
516!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Pin_Solution
517#endif
518!
519! Specialized solution callback routine with names for variables and constraints
520!
521 Use proginfo
522 Use data_t
523 IMPLICIT NONE
524 INTEGER, Intent(IN) :: n, m
525 INTEGER, Intent(IN), Dimension(N) :: xbas, xsta
526 INTEGER, Intent(IN), Dimension(M) :: ybas, ysta
527 real*8, Intent(IN), Dimension(N) :: xval, xmar
528 real*8, Intent(IN), Dimension(M) :: yval, ymar
529 real*8, Intent(IN OUT) :: usrmem(*)
530 character*6, parameter, dimension(7) :: vname = (/'td ','cs ','s ','d ','r ','p ','rev '/)
531 character*6, parameter, dimension(6) :: ename = (/'tddef ','sdef ','csdef ','ddef ','rdef ','revdef'/)
532
533 INTEGER :: i, it, i1
534 CHARACTER*5, Parameter, Dimension(4) :: stat = (/ 'Lower','Upper','Basic','Super' /)
535
536 WRITE(10,"(/' Variable Solution value Reduced cost B-stat'/)")
537 i = 0
538 do it = 1, t
539 DO i1 = 1, 7
540 i = i + 1
541 WRITE(10,"(1X,A6,i2,1p,E20.6,E16.6,4X,A5 )") vname(i1), it, xval(i), xmar(i), stat(1+xbas(i))
542 ENDDO
543 enddo
544
545 WRITE(10,"(/' Constrnt Activity level Marginal cost B-stat'/)")
546 i = 1
547 WRITE(10,"(1x,'Objective',1P,E19.6,E16.6,4X,A5 )") yval(i), ymar(i), stat(1+ybas(i))
548 do it = 1, t
549 do i1 = 1, 6
550 i = i + 1
551 WRITE(10,"(1x,A6,i2,1P,E20.6,E16.6,4X,A5 )") ename(i1),it, yval(i), ymar(i), stat(1+ybas(i))
552 enddo
553 ENDDO
554
555 solcalls = solcalls + 1
556 pin_solution = 0
557
558END 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 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
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