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