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