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!> Main program. A simple setup and call of CONOPT
12!!
13Program tutorialk
14
15 Use proginfo
16 Use coidef
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#if defined(itl)
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 :: numcallback
40 INTEGER, Dimension(:), Pointer :: cntvect
41 INTEGER :: coi_error
42
43 call startup
44!
45! Create and initialize a Control Vector
46!
47 numcallback = coidef_size()
48 Allocate( cntvect(numcallback) )
49 coi_error = coidef_inifort( 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, 5 ) ) ! 5 variables
54 coi_error = max( coi_error, coidef_numcon( cntvect, 3 ) ) ! 3 constraints
55 coi_error = max( coi_error, coidef_numnz( cntvect, 10 ) ) ! 10 nonzeros in the Jacobian
56 coi_error = max( coi_error, coidef_numnlnz( cntvect, 5 ) ) ! 5 of which are nonlinear
57 coi_error = max( coi_error, coidef_optdir( cntvect, 1 ) ) ! Maximize
58 coi_error = max( coi_error, coidef_objcon( cntvect, 1 ) ) ! Objective is constraint 1
59 coi_error = max( coi_error, coidef_debugfv( cntvect, 0 ) ) ! Debug Fdeval on or off
60 coi_error = max( coi_error, coidef_optfile( cntvect, 'tutorial.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(LICENSE_INT_1) && defined(LICENSE_INT_2) && defined(LICENSE_INT_3) && defined(LICENSE_TEXT)
72 coi_error = max( coi_error, coidef_license( cntvect, license_int_1, license_int_2, license_int_3, 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! Start CONOPT:
83!
84 coi_error = coi_solve( cntvect )
85
86 write(*,*)
87 write(*,*) 'End of TutorialK 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 endif
98
99 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
100
101 call flog( "Successful Solve", 0 )
102
103End Program tutorialk
104
105!> Define information about the model
106!!
107!! @include{doc} readMatrix_params.dox
108Integer Function tut_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
109 colsta, rowno, value, nlflag, n, m, nz, &
110 usrmem )
111#if defined(itl)
112!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Tut_ReadMatrix
113#endif
114 implicit none
115 integer, intent (in) :: n ! number of variables
116 integer, intent (in) :: m ! number of constraints
117 integer, intent (in) :: nz ! number of nonzeros
118 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
119 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
120 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
121 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
122 ! (not defined here)
123 integer, intent (out), dimension(m) :: type ! vector of equation types
124 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
125 ! (not defined here)
126 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
127 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
128 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
129 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
130 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
131 real*8 usrmem(*) ! optional user memory
132!
133! Information about Variables:
134! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
135! Default: the status information in Vsta is not used.
136!
137! Lower bound on L = X(1) = 0.1 and initial value = 0.5:
138!
139 lower(1) = 0.1d0
140 curr(1) = 0.5d0
141!
142! Lower bound = Upper bound = Initial value for K = X(2) = 4.0
143!
144 lower(2) = 4.0d0
145 curr(2) = 4.0d0
146 upper(2) = 4.0d0
147!
148! Lower bound on INP = X(3) = 0.1 and initial value = 0.5:
149!
150 lower(3) = 0.1d0
151 curr(3) = 0.5d0
152!
153! Lower bound on OUT = X(4) and P = X(5) are both 0 and the
154! default initial value of 0 is used:
155!
156 lower(4) = 0.d0
157 lower(5) = 0.d0
158!
159! Information about Constraints:
160! Default: Rhs = 0
161! Default: the status information in Esta and the function
162! value in FV are not used.
163! Default: Type: There is no default.
164! 0 = Equality,
165! 1 = Greater than or equal,
166! 2 = Less than or equal,
167! 3 = Non binding.
168!
169! Constraint 1 (Objective)
170! Rhs = -0.1 and type Non binding
171!
172 rhs(1) = -0.1d0
173 type(1) = 3
174!
175! Constraint 2 (Production Function)
176! Rhs = 0 and type Equality
177!
178 type(2) = 0
179!
180! Constraint 3 (Price equation)
181! Rhs = 4.0 and type Equality
182!
183 rhs(3) = 4.d0
184 type(3) = 0
185!
186! Information about the Jacobian. We use the standard method with
187! Rowno, Value, Nlflag and Colsta and we do not use Colno.
188!
189! Colsta = Start of column indices (No Defaults):
190! Rowno = Row indices
191! Value = Value of derivative (by default only linear
192! derivatives are used)
193! Nlflag = 0 for linear and 1 for nonlinear derivative
194! (not needed for completely linear models)
195!
196! Indices
197! x(1) x(2) x(3) x(4) x(5)
198! 1: 1 4 6 9
199! 2: 2 3 5 7
200! 3: 8 10
201!
202 colsta(1) = 1
203 colsta(2) = 3
204 colsta(3) = 4
205 colsta(4) = 6
206 colsta(5) = 9
207 colsta(6) = 11
208 rowno(1) = 1
209 rowno(2) = 2
210 rowno(3) = 2
211 rowno(4) = 1
212 rowno(5) = 2
213 rowno(6) = 1
214 rowno(7) = 2
215 rowno(8) = 3
216 rowno(9) = 1
217 rowno(10) = 3
218!
219! Nonlinearity Structure: L = 0 are linear and NL = 1 are nonlinear
220! x(1) x(2) x(3) x(4) x(5)
221! 1: L L NL NL
222! 2: NL NL NL L
223! 3: L L
224!
225 nlflag(1) = 0
226 nlflag(2) = 1
227 nlflag(3) = 1
228 nlflag(4) = 0
229 nlflag(5) = 1
230 nlflag(6) = 1
231 nlflag(7) = 0
232 nlflag(8) = 0
233 nlflag(9) = 1
234 nlflag(10)= 0
235!
236! Value (Linear only)
237! x(1) x(2) x(3) x(4) x(5)
238! 1: -1 -1 NL NL
239! 2: NL NL NL -1
240! 3: 1 2
241!
242 value(1) = -1.d0
243 value(4) = -1.d0
244 value(7) = -1.d0
245 value(8) = 1.d0
246 value(10) = 2.d0
247
248 tut_readmatrix = 0 ! Return value means OK
249
250end Function tut_readmatrix
251
252!> Compute nonlinear terms and non-constant Jacobian elements
253!!
254!! @include{doc} fdeval_params.dox
255Integer Function tut_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
256 n, nz, thread, usrmem )
257#if defined(itl)
258!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Tut_FDEval
259#endif
260 implicit none
261 integer, intent (in) :: n ! number of variables
262 integer, intent (in) :: rowno ! number of the row to be evaluated
263 integer, intent (in) :: nz ! number of nonzeros in this row
264 real*8, intent (in), dimension(n) :: x ! vector of current solution values
265 real*8, intent (in out) :: g ! constraint value
266 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
267 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
268 ! in this row. Ffor information only.
269 integer, intent (in) :: mode ! evaluation mode: 1 = function value
270 ! 2 = derivatives, 3 = both
271 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
272 ! as errcnt is incremented
273 integer, intent (in out) :: errcnt ! error counter to be incremented in case
274 ! of function evaluation errors.
275 integer, intent (in) :: thread
276 real*8 usrmem(*) ! optional user memory
277!
278! Declare local copies of the optimization variables. This is
279! just for convenience to make the expressions easier to read.
280!
281 real*8 :: l, inp, out, p, k
282!
283! Declare parameters and their data values.
284!
285 real*8, parameter :: w = 1.0d0
286 real*8, parameter :: l0 = 0.1d0
287 real*8, parameter :: pinp = 1.0d0
288 real*8, parameter :: al = 0.16d0
289 real*8, parameter :: ak = 2.0d0
290 real*8, parameter :: ainp = 0.16d0
291 real*8, parameter :: rho = 1.0d0
292 real*8 :: hold1, hold2, hold3 ! Intermediate results
293!
294! Move the optimization variables from the X vector to a set
295! of local variables with the same names as the variables in
296! the model description. This is not necessary, but it should make
297! the equations easier to recognize.
298!
299 l = x(1)
300 k = x(2)
301 inp = x(3)
302 out = x(4)
303 p = x(5)
304!
305! Row 1: the objective function is nonlinear
306!
307 if ( rowno .eq. 1 ) then
308!
309! Mode = 1 or 3. Function value: G = P * Out
310!
311 if ( mode .eq. 1 .or. mode .eq. 3 ) then
312 g = p * out
313 endif
314!
315! Mode = 2 or 3: Derivative values:
316!
317 if ( mode .eq. 2 .or. mode .eq. 3 ) then
318 jac(4) = p ! derivative w.r.t. Out = X(4)
319 jac(5) = out ! derivative w.r.t. P = X(5)
320 endif
321!
322! Row 2: The production function is nonlinear
323!
324 elseif ( rowno .eq. 2 ) then
325!
326! Compute some common terms
327!
328 hold1 = (al*l**(-rho) + ak*k**(-rho) + ainp*inp**(-rho))
329 hold2 = hold1 ** ( -1.d0/rho )
330!
331! Mode = 1 or 3: Function value
332!
333 if ( mode .eq. 1 .or. mode .eq. 3 ) then
334 g = hold2
335 endif
336!
337! Mode = 2 or 3: Derivatives
338!
339 if ( mode .eq. 2 .or. mode .eq. 3 ) then
340 hold3 = hold2 / hold1
341 jac(1) = hold3 * al * l ** (-rho-1.d0) ! derivative w.r.t. L = X(1)
342 jac(2) = hold3 * ak * k ** (-rho-1.d0) ! derivative w.r.t. K = X(2)
343 jac(3) = hold3 * ainp * inp ** (-rho-1.d0) ! derivative w.r.t. Inp = X(3)
344 endif
345!
346! Row = 3: The row is linear and will not be called.
347!
348 endif
349 tut_fdeval = 0
350
351end 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
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_debugfv(cntvect, debugfv)
turn Debugging of FDEval on and off.
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 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
program tutorialk
Main program. A simple setup and call of CONOPT.
Definition tutorialk.f90:13