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