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