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