CONOPT
Loading...
Searching...
No Matches
largebnd.f90
Go to the documentation of this file.
1!> @file largebnd.f90
2!! @ingroup FORT1THREAD_EXAMPLES
3!!
4!!
5!! This is the standard Tutorial model with a little twist:
6!! We assign some of the upper bounds a value above the maximum value of
7!! Rtmaxv.
8!! Earlier this would be a fatal error. Now the bounds are projected on
9!! the legal interval, a message is issued, and the model solved.
10!!
11!!
12!! For more information about the individual callbacks, please have a look at the source code.
13
14
15!> Main program. A simple setup and call of CONOPT
16!!
17Program tutorial
18
19 Use proginfo
20 Use coidef
21 implicit None
22!
23! Declare the user callback routines as Integer, External:
24!
25 Integer, External :: tut_readmatrix ! Mandatory Matrix definition routine defined below
26 Integer, External :: tut_fdeval ! Function and Derivative evaluation routine
27 ! needed a nonlinear model.
28 Integer, External :: std_status ! Standard callback for displaying solution status
29 Integer, External :: std_solution ! Standard callback for displaying solution values
30 Integer, External :: std_message ! Standard callback for managing messages
31 Integer, External :: std_errmsg ! Standard callback for managing error messages
32#if defined(itl)
33!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Tut_ReadMatrix
34!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Tut_FDEval
35!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Status
36!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Solution
37!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Message
38!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_ErrMsg
39#endif
40!
41! Control vector
42!
43 INTEGER :: numcallback
44 INTEGER, Dimension(:), Pointer :: cntvect
45 INTEGER :: coi_error
46
47 call startup
48!
49! Create and initialize a Control Vector
50!
51 numcallback = coidef_size()
52 Allocate( cntvect(numcallback) )
53 coi_error = coidef_inifort( cntvect )
54!
55! Tell CONOPT about the size of the model by populating the Control Vector:
56!
57 coi_error = max( coi_error, coidef_numvar( cntvect, 4 ) ) ! 4 variables
58 coi_error = max( coi_error, coidef_numcon( cntvect, 3 ) ) ! 3 constraints
59 coi_error = max( coi_error, coidef_numnz( cntvect, 9 ) ) ! 9 nonzeros in the Jacobian
60 coi_error = max( coi_error, coidef_numnlnz( cntvect, 4 ) ) ! 4 of which are nonlinear
61 coi_error = max( coi_error, coidef_optdir( cntvect, 1 ) ) ! Maximize
62 coi_error = max( coi_error, coidef_objcon( cntvect, 1 ) ) ! Objective is constraint 1
63 coi_error = max( coi_error, coidef_optfile( cntvect, 'tutorial.opt' ) )
64!
65! Tell CONOPT about the callback routines:
66!
67 coi_error = max( coi_error, coidef_readmatrix( cntvect, tut_readmatrix ) )
68 coi_error = max( coi_error, coidef_fdeval( cntvect, tut_fdeval ) )
69 coi_error = max( coi_error, coidef_status( cntvect, std_status ) )
70 coi_error = max( coi_error, coidef_solution( cntvect, std_solution ) )
71 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
72 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
73
74#if defined(LICENSE_INT_1) && defined(LICENSE_INT_2) && defined(LICENSE_INT_3) && defined(LICENSE_TEXT)
75 coi_error = max( coi_error, coidef_license( cntvect, license_int_1, license_int_2, license_int_3, license_text) )
76#endif
77
78 If ( coi_error .ne. 0 ) THEN
79 write(*,*)
80 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
81 write(*,*)
82 call flog( "Skipping Solve due to setup errors", 1 )
83 ENDIF
84!
85! Start CONOPT:
86!
87 coi_error = coi_solve( cntvect )
88
89 write(*,*)
90 write(*,*) 'End of LargeBnd example. Return code=',coi_error
91!
92! The large bound example should solve like the original tutorial.
93!
94 If ( coi_error /= 0 ) then
95 call flog( "Errors encountered during solution", 1 )
96 elseif ( stacalls == 0 .or. solcalls == 0 ) then
97 call flog( "Status or Solution routine was not called", 1 )
98 elseif ( sstat /= 1 .or. mstat /= 2 ) then
99 call flog( "Solver and Model Status was not as expected (1,2)", 1 )
100 elseif ( abs( obj-0.572943d0 ) > 0.000001d0 ) then
101 call flog( "Incorrect objective returned", 1 )
102 Else
103 Call checkdual( 'largebnd', maximize )
104 endif
105
106 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
107
108 call flog( "Successful Solve", 0 )
109
110End Program tutorial
111!
112! ============================================================================
113! Define information about the model:
114!
115
116!> Define information about the model
117!!
118!! @include{doc} readMatrix_params.dox
119Integer Function tut_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
120 colsta, rowno, value, nlflag, n, m, nz, &
121 usrmem )
122#if defined(itl)
123!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Tut_ReadMatrix
124#endif
125 implicit none
126 integer, intent (in) :: n ! number of variables
127 integer, intent (in) :: m ! number of constraints
128 integer, intent (in) :: nz ! number of nonzeros
129 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
130 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
131 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
132 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
133 ! (not defined here)
134 integer, intent (out), dimension(m) :: type ! vector of equation types
135 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
136 ! (not defined here)
137 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
138 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
139 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
140 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
141 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
142 real*8 usrmem(*) ! optional user memory
143!
144! Information about Variables:
145! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
146! Default: the status information in Vsta is not used.
147!
148! Lower bound on L = X(1) = 0.1 and initial value = 0.5:
149!
150 lower(1) = 0.1d0
151 curr(1) = 0.5d0
152!
153! Lower bound on INP = X(2) = 0.1 and initial value = 0.5:
154!
155 lower(2) = 0.1d0
156 curr(2) = 0.5d0
157!
158! Lower bound on OUT = X(3) and P = X(4) are both 0 and the
159! default initial value of 0 is used:
160!
161 lower(3) = 0.d0
162 lower(4) = 0.d0
163!
164!****SPECIAL***** Try to assign the upper bounds a value above Rtmaxv
165!
166 upper(1) = 1.e20
167 upper(2) = 1.e21
168 upper(3) = 1.e22
169 upper(4) = 1.e23
170!
171! Information about Constraints:
172! Default: Rhs = 0
173! Default: the status information in Esta and the function
174! value in FV are not used.
175! Default: Type: There is no default.
176! 0 = Equality,
177! 1 = Greater than or equal,
178! 2 = Less than or equal,
179! 3 = Non binding.
180!
181! Constraint 1 (Objective)
182! Rhs = -0.1 and type Non binding
183!
184 rhs(1) = -0.1d0
185 type(1) = 3
186!
187! Constraint 2 (Production Function)
188! Rhs = 0 and type Equality
189!
190 type(2) = 0
191!
192! Constraint 3 (Price equation)
193! Rhs = 4.0 and type Equality
194!
195 rhs(3) = 4.d0
196 type(3) = 0
197!
198! Information about the Jacobian. We use the standard method with
199! Rowno, Value, Nlflag and Colsta and we do not use Colno.
200!
201! Colsta = Start of column indices (No Defaults):
202! Rowno = Row indices
203! Value = Value of derivative (by default only linear
204! derivatives are used)
205! Nlflag = 0 for linear and 1 for nonlinear derivative
206! (not needed for completely linear models)
207!
208! Indices
209! x(1) x(2) x(3) x(4)
210! 1: 1 3 5 8
211! 2: 2 4 6
212! 3: 7 9
213!
214 colsta(1) = 1
215 colsta(2) = 3
216 colsta(3) = 5
217 colsta(4) = 8
218 colsta(5) = 10
219 rowno(1) = 1
220 rowno(2) = 2
221 rowno(3) = 1
222 rowno(4) = 2
223 rowno(5) = 1
224 rowno(6) = 2
225 rowno(7) = 3
226 rowno(8) = 1
227 rowno(9) = 3
228!
229! Nonlinearity Structure: L = 0 are linear and NL = 1 are nonlinear
230! x(1) x(2) x(3) x(4)
231! 1: L L NL NL
232! 2: NL NL L
233! 3: L L
234!
235 nlflag(1) = 0
236 nlflag(2) = 1
237 nlflag(3) = 0
238 nlflag(4) = 1
239 nlflag(5) = 1
240 nlflag(6) = 0
241 nlflag(7) = 0
242 nlflag(8) = 1
243 nlflag(9) = 0
244!
245! Value (Linear only)
246! x(1) x(2) x(3) x(4)
247! 1: -1 -1 NL NL
248! 2: NL NL -1
249! 3: 1 2
250!
251 value(1) = -1.d0
252 value(3) = -1.d0
253 value(6) = -1.d0
254 value(7) = 1.d0
255 value(9) = 2.d0
256
257 tut_readmatrix = 0 ! Return value means OK
258
259end Function tut_readmatrix
260!
261!==========================================================================
262! Compute nonlinear terms and non-constant Jacobian elements
263!
264
265!> Compute nonlinear terms and non-constant Jacobian elements
266!!
267!! @include{doc} fdeval_params.dox
268Integer Function tut_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
269 n, nz, thread, usrmem )
270#if defined(itl)
271!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Tut_FDEval
272#endif
273 implicit none
274 integer, intent (in) :: n ! number of variables
275 integer, intent (in) :: rowno ! number of the row to be evaluated
276 integer, intent (in) :: nz ! number of nonzeros in this row
277 real*8, intent (in), dimension(n) :: x ! vector of current solution values
278 real*8, intent (in out) :: g ! constraint value
279 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
280 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
281 ! in this row. Ffor information only.
282 integer, intent (in) :: mode ! evaluation mode: 1 = function value
283 ! 2 = derivatives, 3 = both
284 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
285 ! as errcnt is incremented
286 integer, intent (in out) :: errcnt ! error counter to be incremented in case
287 ! of function evaluation errors.
288 integer, intent (in) :: thread
289 real*8 usrmem(*) ! optional user memory
290!
291! Declare local copies of the optimization variables. This is
292! just for convenience to make the expressions easier to read.
293!
294 real*8 :: l, inp, out, p
295!
296! Declare parameters and their data values.
297!
298 real*8, parameter :: w = 1.0d0
299 real*8, parameter :: l0 = 0.1d0
300 real*8, parameter :: pinp = 1.0d0
301 real*8, parameter :: al = 0.16d0
302 real*8, parameter :: ak = 2.0d0
303 real*8, parameter :: ainp = 0.16d0
304 real*8, parameter :: rho = 1.0d0
305 real*8, parameter :: k = 4.0d0
306 real*8 :: hold1, hold2, hold3 ! Intermediate results
307!
308! Move the optimization variables from the X vector to a set
309! of local variables with the same names as the variables in
310! the model description. This is not necessary, but it should make
311! the equations easier to recognize.
312!
313 l = x(1)
314 inp = x(2)
315 out = x(3)
316 p = x(4)
317!
318! Row 1: the objective function is nonlinear
319!
320 if ( rowno .eq. 1 ) then
321!
322! Mode = 1 or 3. Function value: G = P * Out
323!
324 if ( mode .eq. 1 .or. mode .eq. 3 ) then
325 g = p * out
326 endif
327!
328! Mode = 2 or 3: Derivative values:
329!
330 if ( mode .eq. 2 .or. mode .eq. 3 ) then
331 jac(3) = p ! derivative w.r.t. Out = X(3)
332 jac(4) = out ! derivative w.r.t. P = X(4)
333 endif
334!
335! Row 2: The production function is nonlinear
336!
337 elseif ( rowno .eq. 2 ) then
338!
339! Compute some common terms
340!
341 hold1 = (al*l**(-rho) + ak*k**(-rho) + ainp*inp**(-rho))
342 hold2 = hold1 ** ( -1.d0/rho )
343!
344! Mode = 1 or 3: Function value
345!
346 if ( mode .eq. 1 .or. mode .eq. 3 ) then
347 g = hold2
348 endif
349!
350! Mode = 2 or 3: Derivatives
351!
352 if ( mode .eq. 2 .or. mode .eq. 3 ) then
353 hold3 = hold2 / hold1
354 jac(1) = hold3 * al * l ** (-rho-1.d0) ! derivative w.r.t. L = X(1)
355 jac(2) = hold3 * ainp * inp ** (-rho-1.d0) ! derivative w.r.t. Inp = X(2)
356 endif
357!
358! Row = 3: The row is linear and will not be called.
359!
360 endif
361 tut_fdeval = 0
362
363end Function tut_fdeval
Main program. A simple setup and call of CONOPT.
Definition tutorial.java:14
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_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_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_objcon(cntvect, objcon)
defines the Objective Constraint.
Definition coistart.f90:629
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_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
real *8 obj
Definition comdecl.f90:10
integer solcalls
Definition comdecl.f90:9
integer sstat
Definition comdecl.f90:12
integer stacalls
Definition comdecl.f90:8
subroutine flog(msg, code)
Definition comdecl.f90:56
integer, parameter maximize
Definition comdecl.f90:25
integer mstat
Definition comdecl.f90:11
subroutine startup
Definition comdecl.f90:35
integer function tut_readmatrix(lower, curr, upper, vsta, type, rhs, esta, colsta, rowno, value, nlflag, n, m, nz, usrmem)
Define information about the model.
Definition tutorial.f90:109
integer function tut_fdeval(x, g, jac, rowno, jcnm, mode, ignerr, errcnt, n, nz, thread, usrmem)
Compute nonlinear terms and non-constant Jacobian elements.
Definition tutorial.f90:245