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