CONOPT
Loading...
Searching...
No Matches
mono03.f90
Go to the documentation of this file.
1!> @file mono03.f90
2!! @ingroup FORT1THREAD_EXAMPLES
3!!
4!!
5!! Monotone function to bound conversion example 03
6!!
7!! Note that without the lower bound on x1 the sqrt function is not
8!! monotone and the inequality is not converted into a bound.
9!!
10!! Also note that the bound is not binding and that the derivative
11!! at 0 is infinite.
12!!
13!! This is a CONOPT implementation of the GAMS model:
14!!
15!! @verbatim
16!! variable x1
17!! equation e1;
18!!
19!! e1 .. sqrt(x1) =G= -2;
20!!
21!! x1.l = 1;
22!! x1.lo = 0;
23!! model mono / all /;
24!! Option domlim = 1000;
25!! solve mono using nlp minimizing x1;
26!! @endverbatim
27!!
28!!
29!!
30!! For more information about the individual callbacks, please have a look at the source code.
31
32!> Main program. A simple setup and call of CONOPT
33!!
34Program mono03
35
36 Use proginfo
37 Use coidef
38 implicit None
39!
40! Declare the user callback routines as Integer, External:
41!
42 Integer, External :: mono_readmatrix ! Mandatory Matrix definition routine defined below
43 Integer, External :: mono_fdeval ! Function and Derivative evaluation routine
44 ! needed a nonlinear model.
45 Integer, External :: mono_fdinterval ! Function and Derivative evaluation routine
46 ! needed a nonlinear model.
47 Integer, External :: std_status ! Standard callback for displaying solution status
48 Integer, External :: std_solution ! Standard callback for displaying solution values
49 Integer, External :: std_message ! Standard callback for managing messages
50 Integer, External :: std_errmsg ! Standard callback for managing error messages
51 Integer, External :: std_triord ! Standard callback for Monongular order
52#if defined(itl)
53!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Mono_ReadMatrix
54!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Mono_FDEval
55!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Mono_FDInterval
56!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Status
57!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Solution
58!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Message
59!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_ErrMsg
60!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_TriOrd
61#endif
62!
63! Control vector
64!
65 INTEGER :: numcallback
66 INTEGER, Dimension(:), Pointer :: cntvect
67 INTEGER :: coi_error
68
69 call startup
70!
71! Create and initialize a Control Vector
72!
73 numcallback = coidef_size()
74 Allocate( cntvect(numcallback) )
75 coi_error = coidef_inifort( cntvect )
76!
77! Tell CONOPT about the size of the model by populating the Control Vector:
78!
79 coi_error = max( coi_error, coidef_numvar( cntvect, 1 ) ) ! # variables
80 coi_error = max( coi_error, coidef_numcon( cntvect, 1 ) ) ! # constraints
81 coi_error = max( coi_error, coidef_numnz( cntvect, 1 ) ) ! # nonzeros in the Jacobian
82 coi_error = max( coi_error, coidef_numnlnz( cntvect, 1 ) ) ! # of which are nonlinear
83 coi_error = max( coi_error, coidef_optdir( cntvect, -1 ) ) ! Minimize
84 coi_error = max( coi_error, coidef_objvar( cntvect, 1 ) ) ! Objective is variable 3
85 coi_error = max( coi_error, coidef_optfile( cntvect, 'Mono03.opt' ) )
86!
87! Tell CONOPT about the callback routines:
88!
89 coi_error = max( coi_error, coidef_readmatrix( cntvect, mono_readmatrix ) )
90 coi_error = max( coi_error, coidef_fdeval( cntvect, mono_fdeval ) )
91 coi_error = max( coi_error, coidef_fdinterval( cntvect, mono_fdinterval ) )
92 coi_error = max( coi_error, coidef_status( cntvect, std_status ) )
93 coi_error = max( coi_error, coidef_solution( cntvect, std_solution ) )
94 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
95 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
96 coi_error = max( coi_error, coidef_triord( cntvect, std_triord ) )
97
98#if defined(LICENSE_INT_1) && defined(LICENSE_INT_2) && defined(LICENSE_INT_3) && defined(LICENSE_TEXT)
99 coi_error = max( coi_error, coidef_license( cntvect, license_int_1, license_int_2, license_int_3, license_text) )
100#endif
101
102 If ( coi_error .ne. 0 ) THEN
103 write(*,*)
104 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
105 write(*,*)
106 call flog( "Skipping Solve due to setup errors", 1 )
107 ENDIF
108!
109! Save the solution so we can check the duals:
110!
111 do_allocate = .true.
112!
113! Start CONOPT:
114!
115 coi_error = coi_solve( cntvect )
116
117 write(*,*)
118 write(*,*) 'End of Mono03 example. Return code=',coi_error
119
120 If ( coi_error /= 0 ) then
121 call flog( "Errors encountered during solution", 1 )
122 elseif ( stacalls == 0 .or. solcalls == 0 ) then
123 call flog( "Status or Solution routine was not called", 1 )
124 elseif ( sstat /= 1 .or. mstat /= 1 ) then
125 call flog( "Solver and Model Status was not as expected (1,1)", 1 )
126 elseif ( abs( obj-0.0d0 ) > 0.000001d0 ) then
127 call flog( "Incorrect objective returned", 1 )
128 Else
129 Call checkdual( 'Mono03', minimize )
130 endif
131
132 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
133
134 call flog( "Successful Solve", 0 )
135
136End Program mono03
137!
138! ============================================================================
139! Define information about the model:
140!
141
142!> Define information about the model
143!!
144!! @include{doc} readMatrix_params.dox
145Integer Function mono_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
146 colsta, rowno, value, nlflag, n, m, nz, &
147 usrmem )
148#if defined(itl)
149!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Mono_ReadMatrix
150#endif
151 implicit none
152 integer, intent (in) :: n ! number of variables
153 integer, intent (in) :: m ! number of constraints
154 integer, intent (in) :: nz ! number of nonzeros
155 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
156 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
157 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
158 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
159 ! (not defined here)
160 integer, intent (out), dimension(m) :: type ! vector of equation types
161 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
162 ! (not defined here)
163 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
164 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
165 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
166 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
167 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
168 real*8 usrmem(*) ! optional user memory
169!
170! Information about Variables:
171! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
172! Default: the status information in Vsta is not used.
173!
174! The model uses defaults
175!
176! Information about Constraints:
177! Default: Rhs = 0
178! Default: the status information in Esta and the function
179! value in FV are not used.
180! Default: Type: There is no default.
181! 0 = Equality,
182! 1 = Greater than or equal,
183! 2 = Less than or equal,
184! 3 = Non binding.
185!
186! Constraint 1: e1
187! Rhs = -2.0 and type Greater than or Equal
188!
189 rhs(1) = -2.0d0
190 type(1) = 1
191!
192 lower(1) = 0.0d0
193 curr(1) = 1.0d0
194!
195! Information about the Jacobian. We use the standard method with
196! Rowno, Value, Nlflag and Colsta and we do not use Colno.
197!
198! Colsta = Start of column indices (No Defaults):
199! Rowno = Row indices
200! Value = Value of derivative (by default only linear
201! derivatives are used)
202! Nlflag = 0 for linear and 1 for nonlinear derivative
203! (not needed for completely linear models)
204!
205! Indices
206! x(1)
207! 1: 1
208!
209 colsta(1) = 1
210 colsta(2) = 2
211 rowno(1) = 1
212!
213! Nonlinearity Structure: L = 0 are linear and NL = 1 are nonlinear
214! x(1)
215! 1: NL
216!
217 nlflag(1) = 1
218!
219! Value (Linear only)
220! x(1)
221! 1: NL
222!
223 mono_readmatrix = 0 ! Return value means OK
224
225end Function mono_readmatrix
226!
227!==========================================================================
228! Compute nonlinear terms and non-constant Jacobian elements
229!
230
231!> Compute nonlinear terms and non-constant Jacobian elements
232!!
233!! @include{doc} fdeval_params.dox
234Integer Function mono_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
235 n, nz, thread, usrmem )
236#if defined(itl)
237!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Mono_FDEval
238#endif
239 implicit none
240 integer, intent (in) :: n ! number of variables
241 integer, intent (in) :: rowno ! number of the row to be evaluated
242 integer, intent (in) :: nz ! number of nonzeros in this row
243 real*8, intent (in), dimension(n) :: x ! vector of current solution values
244 real*8, intent (in out) :: g ! constraint value
245 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
246 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
247 ! in this row. Ffor information only.
248 integer, intent (in) :: mode ! evaluation mode: 1 = function value
249 ! 2 = derivatives, 3 = both
250 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
251 ! as errcnt is incremented
252 integer, intent (in out) :: errcnt ! error counter to be incremented in case
253 ! of function evaluation errors.
254 integer, intent (in) :: thread
255 real*8 usrmem(*) ! optional user memory
256
257 real*8 :: sq
258!
259! Report an error for bad points
260!
261 mono_fdeval = 0 ! OK unless error found later
262 If ( x(1) < 0.0d0 ) then
263 errcnt = errcnt + 1
264 return
265 endif
266!
267! Row 1: e1
268!
269 if ( rowno .eq. 1 ) then
270 sq = sqrt(x(1))
271!
272! Mode = 1 or 3. G = log(x1)
273!
274 if ( mode .eq. 1 .or. mode .eq. 3 ) then
275 g = sq
276 endif
277!
278! Mode = 2 or 3: Derivative values:
279!
280 if ( mode .eq. 2 .or. mode .eq. 3 ) then
281 jac(1) = 0.5d0/max(sq,1.d-20)
282 endif
283 else
284!
285! There are no other rows:
286!
287 mono_fdeval = 1
288 endif
289
290end Function mono_fdeval
291
292
293!> Evaluating nonlinear functions and derivatives on an interval. Used in preprocessing
294!!
295!! @include{doc} fdinterval_params.dox
296Integer Function mono_fdinterval( XMIN, XMAX, GMIN, GMAX, &
297 JMIN, JMAX, ROWNO, JCNM, &
298 MODE, PINF, N, NJ, USRMEM )
299#if defined(itl)
300!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Mono_FDInterval
301#endif
302 Implicit None
303 INTEGER, Intent(IN) :: rowno, mode, n, nj
304 INTEGER, Dimension(NJ), Intent(IN) :: jcnm
305 real*8, Dimension(N), Intent(IN) :: xmin, xmax
306 real*8, Intent(IN OUT) :: gmin, gmax
307 real*8, Dimension(N), Intent(IN OUT) :: jmin, jmax
308 real*8, Intent(IN) :: pinf
309 real*8, Intent(IN OUT) :: usrmem(*)
310
311!
312! Row 1: e1
313!
314 write(10,*) 'Enter Mono_FDInterval. Row=',rowno,' Mode=',mode
315 write(10,*) 'Xmin=',xmin
316 write(10,*) 'Xmax=',xmax
317 if ( rowno .eq. 1 ) then
318!
319! Mode = 1 or 3. G = log(x1)
320!
321 if ( mode .eq. 1 .or. mode .eq. 3 ) then
322 If ( xmin(1) < 0.0d0 ) then
323 gmin = -pinf
324 else
325 gmin = sqrt(xmin(1))
326 endif
327 If ( xmax(1) < 0.0d0 ) then
328 gmax = -pinf
329 else
330 gmax = sqrt(xmax(1))
331 endif
332 write(10,*) 'Gmin=',gmin,' Gmax=',gmax
333 endif
334!
335! Mode = 2 or 3: Derivative values:
336!
337 if ( mode .eq. 2 .or. mode .eq. 3 ) then
338 If ( xmin(1) < 0.0d0 ) then
339 jmin(1) = -pinf
340 jmax(1) = +pinf
341 else
342 jmin(1) = 1.0d0/max(sqrt(xmax(1)),1.d-20)
343 jmax(1) = 1.0d0/max(sqrt(xmin(1)),1.d-20)
344 endif
345 write(10,*) 'Jmin=',jmin
346 write(10,*) 'Jmax=',jmax
347 endif
349 else
350!
351! There are no other rows:
352!
354 endif
355
356end Function mono_fdinterval
integer function std_solution(xval, xmar, xbas, xsta, yval, ymar, ybas, ysta, n, m, usrmem)
Definition comdecl.f90:128
integer function std_status(modsta, solsta, iter, objval, usrmem)
Definition comdecl.f90:82
subroutine checkdual(case, minmax)
Definition comdecl.f90:365
integer function std_message(smsg, dmsg, nmsg, llen, usrmem, msgv)
Definition comdecl.f90:203
integer function std_triord(mode, type, status, irow, icol, inf, value, resid, usrmem)
Definition comdecl.f90:291
integer function std_errmsg(rowno, colno, posno, msglen, usrmem, msg)
Definition comdecl.f90:248
integer function coidef_fdeval(cntvect, coi_fdeval)
define callback routine for performing function and derivative evaluations.
integer function coidef_errmsg(cntvect, coi_errmsg)
define callback routine for returning error messages for row, column or Jacobian elements.
integer function coidef_message(cntvect, coi_message)
define callback routine for handling messages returned during the solution process.
integer function coidef_readmatrix(cntvect, coi_readmatrix)
define callback routine for providing the matrix data to CONOPT.
integer function coidef_status(cntvect, coi_status)
define callback routine for returning the completion status.
integer function coidef_solution(cntvect, coi_solution)
define callback routine for returning the final solution values.
integer function coidef_optfile(cntvect, optfile)
define callback routine for defining an options file.
integer function coidef_triord(cntvect, coi_triord)
define callback routine for providing the triangular order information.
integer function coidef_fdinterval(cntvect, coi_fdinterval)
define callback routine for performing function and derivative evaluations on intervals.
integer function coidef_license(cntvect, licint1, licint2, licint3, licstring)
define the License Information.
Definition coistart.f90:680
integer function coidef_numvar(cntvect, numvar)
defines the number of variables in the model.
Definition coistart.f90:358
integer function coidef_numnz(cntvect, numnz)
defines the number of nonzero elements in the Jacobian.
Definition coistart.f90:437
integer function coidef_optdir(cntvect, optdir)
defines the Optimization Direction.
Definition coistart.f90:552
integer function coidef_numnlnz(cntvect, numnlnz)
defines the Number of Nonlinear Nonzeros.
Definition coistart.f90:476
integer function coidef_numcon(cntvect, numcon)
defines the number of constraints in the model.
Definition coistart.f90:398
integer function coidef_objvar(cntvect, objvar)
defines the Objective Variable.
Definition coistart.f90:586
integer function coidef_size()
returns the size the Control Vector must have, measured in standard Integer units.
Definition coistart.f90:176
integer function coidef_inifort(cntvect)
initialisation method for Fortran applications.
Definition coistart.f90:314
integer function coi_solve(cntvect)
method for starting the solving process of CONOPT.
Definition coistart.f90:14
integer function mono_fdinterval(xmin, xmax, gmin, gmax, jmin, jmax, rowno, jcnm, mode, pinf, n, nj, usrmem)
Evaluating nonlinear functions and derivatives on an interval. Used in preprocessing.
Definition mono01.f90:281
integer function mono_readmatrix(lower, curr, upper, vsta, type, rhs, esta, colsta, rowno, value, nlflag, n, m, nz, usrmem)
Define information about the model.
Definition mono01.f90:140
integer function mono_fdeval(x, g, jac, rowno, jcnm, mode, ignerr, errcnt, n, nz, thread, usrmem)
Compute nonlinear terms and non-constant Jacobian elements.
Definition mono01.f90:228
program mono03
Main program. A simple setup and call of CONOPT.
Definition mono03.f90:34
#define nj
Definition mp_trans.c:46
real *8 obj
Definition comdecl.f90:10
integer solcalls
Definition comdecl.f90:9
integer sstat
Definition comdecl.f90:12
integer, parameter minimize
Definition comdecl.f90:25
integer stacalls
Definition comdecl.f90:8
subroutine flog(msg, code)
Definition comdecl.f90:56
logical do_allocate
Definition comdecl.f90:21
integer mstat
Definition comdecl.f90:11
subroutine startup
Definition comdecl.f90:35