CONOPT
Loading...
Searching...
No Matches
objnotn.f90
Go to the documentation of this file.
1!> @file objnotn.f90
2!! @ingroup FORT1THREAD_EXAMPLES
3!!
4!!
5!! Objective constraint is not type `=N=`. Test the error message.
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 objnotn
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_objcon( cntvect, 1 ) ) ! Objective is constraint 1
59 coi_error = max( coi_error, coidef_optfile( cntvect, 'objnotn.opt' ) )
60!
61! Tell CONOPT about the callback routines:
62!
63 coi_error = max( coi_error, coidef_readmatrix( cntvect, tut_readmatrix ) )
64 coi_error = max( coi_error, coidef_fdeval( cntvect, tut_fdeval ) )
65 coi_error = max( coi_error, coidef_status( cntvect, std_status ) )
66 coi_error = max( coi_error, coidef_solution( cntvect, std_solution ) )
67 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
68 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
69
70#if defined(CONOPT_LICENSE_INT_1) && defined(CONOPT_LICENSE_INT_2) && defined(CONOPT_LICENSE_INT_3) && defined(CONOPT_LICENSE_TEXT)
71 coi_error = max( coi_error, coidef_license( cntvect, conopt_license_int_1, conopt_license_int_2, conopt_license_int_3, conopt_license_text) )
72#endif
73
74 If ( coi_error .ne. 0 ) THEN
75 write(*,*)
76 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
77 write(*,*)
78 call flog( "Skipping Solve due to setup errors", 1 )
79 ENDIF
80!
81! Save the solution so we can check the duals:
82!
83 do_allocate = .true.
84!
85! Start CONOPT:
86!
87 coi_error = coi_solve( cntvect )
88
89 write(*,*)
90 write(*,*) 'End of objnotn example. Return code=',coi_error
91
92 If ( coi_error /= 400 ) then
93 call flog( "COI_Solve did not return 400 as expected.", 1 )
94 endif
95
96 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
97
98 call flog( "Successful bad objective row check", 0 )
99!
100! Free solution memory
101!
102 call finalize
103
104End Program objnotn
105!
106! ============================================================================
107! Define information about the model:
108!
109
110!> Define information about the model
111!!
112!! @include{doc} readMatrix_params.dox
113Integer Function tut_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
114 colsta, rowno, value, nlflag, n, m, nz, &
115 usrmem )
116#ifdef dec_directives_win32
117!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Tut_ReadMatrix
118#endif
119 implicit none
120 integer, intent (in) :: n ! number of variables
121 integer, intent (in) :: m ! number of constraints
122 integer, intent (in) :: nz ! number of nonzeros
123 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
124 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
125 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
126 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
127 ! (not defined here)
128 integer, intent (out), dimension(m) :: type ! vector of equation types
129 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
130 ! (not defined here)
131 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
132 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
133 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
134 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
135 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
136 real*8 usrmem(*) ! optional user memory
137!
138! Information about Variables:
139! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
140! Default: the status information in Vsta is not used.
141!
142! Lower bound on L = X(1) = 0.1 and initial value = 0.5:
143!
144 lower(1) = 0.1d0
145 curr(1) = 0.5d0
146!
147! Lower bound on INP = X(2) = 0.1 and initial value = 0.5:
148!
149 lower(2) = 0.1d0
150 curr(2) = 0.5d0
151!
152! Lower bound on OUT = X(3) and P = X(4) are both 0 and the
153! default initial value of 0 is used:
154!
155 lower(3) = 0.d0
156 lower(4) = 0.d0
157!
158! Information about Constraints:
159! Default: Rhs = 0
160! Default: the status information in Esta and the function
161! value in FV are not used.
162! Default: Type: There is no default.
163! 0 = Equality,
164! 1 = Greater than or equal,
165! 2 = Less than or equal,
166! 3 = Non binding.
167!
168! Constraint 1 (Objective)
169! Rhs = -0.1 and type Non binding
170!
171 rhs(1) = -0.1d0
172 type(1) = 2 ! Changed. Check that we get an error
173!
174! Constraint 2 (Production Function)
175! Rhs = 0 and type Equality
176!
177 type(2) = 0
178!
179! Constraint 3 (Price equation)
180! Rhs = 4.0 and type Equality
181!
182 rhs(3) = 4.d0
183 type(3) = 0
184!
185! Information about the Jacobian. CONOPT expects a columnwise
186! representation in Rowno, Value, Nlflag and Colsta.
187!
188! Colsta = Start of column indices (No Defaults):
189! Rowno = Row indices
190! Value = Value of derivative (by default only linear
191! derivatives are used)
192! Nlflag = 0 for linear and 1 for nonlinear derivative
193! (not needed for completely linear models)
194!
195! Indices
196! x(1) x(2) x(3) x(4)
197! 1: 1 3 5 8
198! 2: 2 4 6
199! 3: 7 9
200!
201 colsta(1) = 1
202 colsta(2) = 3
203 colsta(3) = 5
204 colsta(4) = 8
205 colsta(5) = 10
206 rowno(1) = 1
207 rowno(2) = 2
208 rowno(3) = 1
209 rowno(4) = 2
210 rowno(5) = 1
211 rowno(6) = 2
212 rowno(7) = 3
213 rowno(8) = 1
214 rowno(9) = 3
215!
216! Nonlinearity Structure: L = 0 are linear and NL = 1 are nonlinear
217! x(1) x(2) x(3) x(4)
218! 1: L L NL NL
219! 2: NL NL L
220! 3: L L
221!
222 nlflag(1) = 0
223 nlflag(2) = 1
224 nlflag(3) = 0
225 nlflag(4) = 1
226 nlflag(5) = 1
227 nlflag(6) = 0
228 nlflag(7) = 0
229 nlflag(8) = 1
230 nlflag(9) = 0
231!
232! Value (Linear only)
233! x(1) x(2) x(3) x(4)
234! 1: -1 -1 NL NL
235! 2: NL NL -1
236! 3: 1 2
237!
238 value(1) = -1.d0
239 value(3) = -1.d0
240 value(6) = -1.d0
241 value(7) = 1.d0
242 value(9) = 2.d0
244 tut_readmatrix = 0 ! Return value means OK
245
246end Function tut_readmatrix
247!
248!==========================================================================
249! Compute nonlinear terms and non-constant Jacobian elements
250!
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#ifdef dec_directives_win32
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
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, parameter :: k = 4.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 inp = x(2)
302 out = x(3)
303 p = x(4)
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(3) = p ! derivative w.r.t. Out = X(3)
319 jac(4) = out ! derivative w.r.t. P = X(4)
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 * ainp * inp ** (-rho-1.d0) ! derivative w.r.t. Inp = X(2)
343 endif
344!
345! Row = 3: The row is linear and will not be called.
346!
347 endif
348 tut_fdeval = 0
349
350end Function tut_fdeval
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
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
subroutine finalize
Definition comdecl.f90:79
subroutine flog(msg, code)
Definition comdecl.f90:62
logical do_allocate
Definition comdecl.f90:27
subroutine startup
Definition comdecl.f90:41
program objnotn
Main program. A simple setup and call of CONOPT.
Definition objnotn.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: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