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