CONOPT
Loading...
Searching...
No Matches
evalerr01.f90
Go to the documentation of this file.
1!> @file evalerr01.f90
2!! @ingroup FORT1THREAD_EXAMPLES
3!!
4!!
5!! Model with function evaluation errors -- 01
6!!
7!! This is a CONOPT implementation of the GAMS model:
8!!
9!! @verbatim
10!! variable x1, x2, x3, x4 ;
11!! equation e1, e2, e3 ;
12!!
13!! e1 .. x1 + x2 =E= 1;
14!!
15!! e2 .. x1*log(x1) + x2*log(x2) + x3 - x4 =E= 0;
16!!
17!! e3 .. x1 + 2*x2 - sqr(x3) =E= 0;
18!!
19!! x1.l = 0.5; x2.l = 0.5;
20!!
21!! model EvalErr01 / all /;
22!!
23!! solve EvalErr01 using nlp minimizing x4;
24!! @endverbatim
25!!
26!! The expected behavior is as follows:
27!! 1. x4 is a post-triangular variable in eq2 and is ignored until a
28!! feasible solution is found to the remaining constraints.
29!! 2. The initial value of x3 is zero so the term sqr(x3) has derivative zero.
30!! The initial basis will therefore consist of x1 and x2.
31!! 3. Solving e1 and e3 w.r.t. x1 and x2 gives x1 = 2 and x2 = -1.
32!! 4. Entering these values into e2 gives a log error.
33!! 5. We should therefore expect Sstat = 5 (Domain violation) and
34!! Mstat = 6 (Intermediate Infeasible).
35!!
36!!
37!! For more information about the individual callbacks, please have a look at the source code.
38
39!> Main program. A simple setup and call of CONOPT
40!!
41Program evalerr01
42
43 Use proginfo
44 Use coidef
45 implicit None
46!
47! Declare the user callback routines as Integer, External:
48!
49 Integer, External :: eval_readmatrix ! Mandatory Matrix definition routine defined below
50 Integer, External :: eval_fdeval ! Function and Derivative evaluation routine
51 ! needed a nonlinear model.
52 Integer, External :: std_status ! Standard callback for displaying solution status
53 Integer, External :: std_solution ! Standard callback for displaying solution values
54 Integer, External :: std_message ! Standard callback for managing messages
55 Integer, External :: std_errmsg ! Standard callback for managing error messages
56 Integer, External :: std_triord ! Standard callback for triangular order
57#if defined(itl)
58!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Eval_ReadMatrix
59!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Eval_FDEval
60!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Status
61!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Solution
62!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Message
63!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_ErrMsg
64!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_TriOrd
65#endif
66!
67! Control vector
68!
69 INTEGER :: numcallback
70 INTEGER, Dimension(:), Pointer :: cntvect
71 INTEGER :: coi_error
72
73 call startup
74!
75! Create and initialize a Control Vector
76!
77 numcallback = coidef_size()
78 Allocate( cntvect(numcallback) )
79 coi_error = coidef_inifort( cntvect )
80!
81! Tell CONOPT about the size of the model by populating the Control Vector:
82!
83 coi_error = max( coi_error, coidef_numvar( cntvect, 4 ) ) ! # variables
84 coi_error = max( coi_error, coidef_numcon( cntvect, 3 ) ) ! # constraints
85 coi_error = max( coi_error, coidef_numnz( cntvect, 9 ) ) ! # nonzeros in the Jacobian
86 coi_error = max( coi_error, coidef_numnlnz( cntvect, 3 ) ) ! of which are nonlinear
87 coi_error = max( coi_error, coidef_optdir( cntvect, -1 ) ) ! Minimize
88 coi_error = max( coi_error, coidef_objvar( cntvect, 4 ) ) ! # of Objective variable
89 coi_error = max( coi_error, coidef_optfile( cntvect, 'evalerr01.opt' ) )
90 coi_error = max( coi_error, coidef_errlim( cntvect, 1000 ) ) ! Allow function evaluation errors
91!
92! Tell CONOPT about the callback routines:
93!
94 coi_error = max( coi_error, coidef_readmatrix( cntvect, eval_readmatrix ) )
95 coi_error = max( coi_error, coidef_fdeval( cntvect, eval_fdeval ) )
96 coi_error = max( coi_error, coidef_status( cntvect, std_status ) )
97 coi_error = max( coi_error, coidef_solution( cntvect, std_solution ) )
98 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
99 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
100 coi_error = max( coi_error, coidef_triord( cntvect, std_triord ) )
101
102#if defined(LICENSE_INT_1) && defined(LICENSE_INT_2) && defined(LICENSE_INT_3) && defined(LICENSE_TEXT)
103 coi_error = max( coi_error, coidef_license( cntvect, license_int_1, license_int_2, license_int_3, license_text) )
104#endif
105
106 If ( coi_error .ne. 0 ) THEN
107 write(*,*)
108 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
109 write(*,*)
110 call flog( "Skipping Solve due to setup errors", 1 )
111 ENDIF
112!
113! Save the solution so we can check the duals:
114!
115 do_allocate = .true.
116!
117! Start CONOPT:
118!
119 coi_error = coi_solve( cntvect )
120
121 write(*,*)
122 write(*,*) 'End of Evalerr01 example. Return code=',coi_error
123
124 If ( coi_error /= 0 ) then
125 call flog( "Errors encountered during solution", 1 )
126 elseif ( stacalls == 0 .or. solcalls == 0 ) then
127 call flog( "Status or Solution routine was not called", 1 )
128 elseif ( sstat /= 5 .or. mstat /= 6 ) then
129 call flog( "Solver and Model Status was not as expected (5,6)", 1 )
130 endif
131
132 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
133
134 call flog( "Successful Solve", 0 )
135
136End Program evalerr01
137!
138! ============================================================================
139! Define information about the model:
140!
141
142!> Define information about the model
143!!
144!! @include{doc} readMatrix_params.dox
145Integer Function eval_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
146 colsta, rowno, value, nlflag, n, m, nz, &
147 usrmem )
148#if defined(itl)
149!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Eval_ReadMatrix
150#endif
151 implicit none
152 integer, intent (in) :: n ! number of variables
153 integer, intent (in) :: m ! number of constraints
154 integer, intent (in) :: nz ! number of nonzeros
155 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
156 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
157 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
158 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
159 ! (not defined here)
160 integer, intent (out), dimension(m) :: type ! vector of equation types
161 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
162 ! (not defined here)
163 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
164 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
165 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
166 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
167 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
168 real*8 usrmem(*) ! optional user memory
169!
170! Information about Variables:
171! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
172! Default: the status information in Vsta is not used.
173!
174! The model uses defaults
175!
176! Information about Constraints:
177! Default: Rhs = 0
178! Default: the status information in Esta and the function
179! value in FV are not used.
180! Default: Type: There is no default.
181! 0 = Equality,
182! 1 = Greater than or equal,
183! 2 = Less than or equal,
184! 3 = Non binding.
185!
186! Constraint 1: e1
187! Rhs = 1.0 and type Equality
188!
189 rhs(1) = 1.0d0
190 type(1) = 0
191!
192! Constraint 2: e2
193! Rhs = 0.0 and type Equality
194!
195 type(2) = 0
196!
197! Constraint 3: e3
198! Rhs = 0.0 and type Equality
199!
200 type(3) = 0
201!
202! Initial values
203!
204 curr(1) = 0.5d0
205 curr(2) = 0.5d0
206!
207! Information about the Jacobian. We use the standard method with
208! Rowno, Value, Nlflag and Colsta and we do not use Colno.
209!
210! Colsta = Start of column indices (No Defaults):
211! Rowno = Row indices
212! Value = Value of derivative (by default only linear
213! derivatives are used)
214! Nlflag = 0 for linear and 1 for nonlinear derivative
215! (not needed for completely linear models)
216!
217! Indices
218! x(1) x(2) x(3) x(4)
219! 1: 1 4
220! 2: 2 5 7 9
221! 3: 3 6 8
222!
223 colsta(1) = 1
224 colsta(2) = 4
225 colsta(3) = 7
226 colsta(4) = 9
227 colsta(5) = 10
228 rowno(1) = 1
229 rowno(2) = 2
230 rowno(3) = 3
231 rowno(4) = 1
232 rowno(5) = 2
233 rowno(6) = 3
234 rowno(7) = 2
235 rowno(8) = 3
236 rowno(9) = 2
237!
238! Nonlinearity Structure: L = 0 are linear and NL = 1 are nonlinear
239! x(1) x(2) x(3) x(4)
240! 1: L L
241! 2: NL NL L L
242! 3: L L NL
243!
244 nlflag(1) = 0
245 nlflag(2) = 1
246 nlflag(3) = 0
247 nlflag(4) = 0
248 nlflag(5) = 1
249 nlflag(6) = 0
250 nlflag(7) = 0
251 nlflag(8) = 1
252 nlflag(9) = 0
253!
254! Value (Linear only)
255! x(1) x(2) x(3) x(4)
256! 1: 1.0 1.0
257! 2: NL NL 1.0 -1.0
258! 3: 1.0 2.0 NL
259!
260 value(1) = 1.d0
261 value(3) = 1.d0
262 value(4) = 1.d0
263 value(6) = 2.d0
264 value(7) = 1.d0
265 value(9) = -1.d0
266
267 eval_readmatrix = 0 ! Return value means OK
268
269end Function eval_readmatrix
270!
271!==========================================================================
272! Compute nonlinear terms and non-constant Jacobian elements
273!
274
275!> Compute nonlinear terms and non-constant Jacobian elements
276!!
277!! @include{doc} fdeval_params.dox
278Integer Function eval_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
279 n, nz, thread, usrmem )
280#if defined(itl)
281!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Eval_FDEval
282#endif
283 implicit none
284 integer, intent (in) :: n ! number of variables
285 integer, intent (in) :: rowno ! number of the row to be evaluated
286 integer, intent (in) :: nz ! number of nonzeros in this row
287 real*8, intent (in), dimension(n) :: x ! vector of current solution values
288 real*8, intent (in out) :: g ! constraint value
289 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
290 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
291 ! in this row. Ffor information only.
292 integer, intent (in) :: mode ! evaluation mode: 1 = function value
293 ! 2 = derivatives, 3 = both
294 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
295 ! as errcnt is incremented
296 integer, intent (in out) :: errcnt ! error counter to be incremented in case
297 ! of function evaluation errors.
298 integer, intent (in) :: thread
299 real*8 usrmem(*) ! optional user memory
300
301 eval_fdeval = 0
302!
303! Row 2: e2
304!
305 if ( rowno .eq. 2 ) then
306!
307! Mode = 1 or 3. G = x1*log(x1) + x2*log(x2)
308!
309 if ( x(1) <= 1.e-12 .or. x(2) <= 1.e-12 ) then
310 errcnt = errcnt + 1
311 Return
312 Endif
313 if ( mode .eq. 1 .or. mode .eq. 3 ) then
314 g = x(1)*log(x(1)) + x(2)*log(x(2))
315 endif
316!
317! Mode = 2 or 3: Derivative values:
318!
319 if ( mode .eq. 2 .or. mode .eq. 3 ) then
320 jac(1) = log(x(1)) + 1.0d0
321 jac(2) = log(x(2)) + 1.0d0
322 endif
323 else if ( rowno .eq. 3 ) then
324!
325! Mode = 1 or 3. G = sqr(x3)
326!
327 if ( mode .eq. 1 .or. mode .eq. 3 ) then
328 g = x(3)*x(3)
329 endif
330!
331! Mode = 2 or 3: Derivative values:
332!
333 if ( mode .eq. 2 .or. mode .eq. 3 ) then
334 jac(3) = x(3)+x(3)
335 endif
336!
337! Row 1: The row is linear and will not be called
338!
339 else
340 eval_fdeval = 1
341 endif
342
343end Function eval_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_triord(mode, type, status, irow, icol, inf, value, resid, usrmem)
Definition comdecl.f90:291
integer function std_errmsg(rowno, colno, posno, msglen, usrmem, msg)
Definition comdecl.f90:248
integer function eval_fdeval(x, g, jac, rowno, jcnm, mode, ignerr, errcnt, n, nz, thread, usrmem)
Compute nonlinear terms and non-constant Jacobian elements.
program evalerr01
Main program. A simple setup and call of CONOPT.
Definition evalerr01.f90:41
integer function eval_readmatrix(lower, curr, upper, vsta, type, rhs, esta, colsta, rowno, value, nlflag, n, m, nz, usrmem)
Define information about the model.
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_triord(cntvect, coi_triord)
define callback routine for providing the triangular order information.
integer function coidef_license(cntvect, licint1, licint2, licint3, licstring)
define the License Information.
Definition coistart.f90:680
integer function coidef_errlim(cntvect, errlim)
define the Error Limit.
Definition coistart.f90:890
integer function coidef_numvar(cntvect, numvar)
defines the number of variables in the model.
Definition coistart.f90:358
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_objvar(cntvect, objvar)
defines the Objective Variable.
Definition coistart.f90:586
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
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
logical do_allocate
Definition comdecl.f90:21
integer mstat
Definition comdecl.f90:11
subroutine startup
Definition comdecl.f90:35