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