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