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