CONOPT
Loading...
Searching...
No Matches
mono03.f90
Go to the documentation of this file.
1!> @file mono03.f90
2!! @ingroup FORT1THREAD_EXAMPLES
3!!
4!!
5!! Monotone function to bound conversion example 03
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) =G= -2;
20!!
21!! x1.l = 1;
22!! x1.lo = 0;
23!! model mono / all /;
24!! Option domlim = 1000;
25!! solve mono using nlp minimizing x1;
26!! @endverbatim
27!!
28!!
29!!
30!! For more information about the individual callbacks, please have a look at the source code.
31
32#if defined(_WIN32) && !defined(_WIN64)
33#define dec_directives_win32
34#endif
35
36!> Main program. A simple setup and call of CONOPT
37!!
38Program mono03
39
41 Use conopt
42 implicit None
43!
44! Declare the user callback routines as Integer, External:
45!
46 Integer, External :: mono_readmatrix ! Mandatory Matrix definition routine defined below
47 Integer, External :: mono_fdeval ! Function and Derivative evaluation routine
48 ! needed a nonlinear model.
49 Integer, External :: mono_fdinterval ! Function and Derivative evaluation routine
50 ! needed a nonlinear model.
51 Integer, External :: std_status ! Standard callback for displaying solution status
52 Integer, External :: std_solution ! Standard callback for displaying solution values
53 Integer, External :: std_message ! Standard callback for managing messages
54 Integer, External :: std_errmsg ! Standard callback for managing error messages
55 Integer, External :: std_triord ! Standard callback for Monongular order
56#ifdef dec_directives_win32
57!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Mono_ReadMatrix
58!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Mono_FDEval
59!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Mono_FDInterval
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, Dimension(:), Pointer :: cntvect
70 INTEGER :: coi_error
71
72 call startup
73!
74! Create and initialize a Control Vector
75!
76 coi_error = coi_create( cntvect )
77!
78! Tell CONOPT about the size of the model by populating the Control Vector:
79!
80 coi_error = max( coi_error, coidef_numvar( cntvect, 1 ) ) ! # variables
81 coi_error = max( coi_error, coidef_numcon( cntvect, 1 ) ) ! # constraints
82 coi_error = max( coi_error, coidef_numnz( cntvect, 1 ) ) ! # nonzeros in the Jacobian
83 coi_error = max( coi_error, coidef_numnlnz( cntvect, 1 ) ) ! # of which are nonlinear
84 coi_error = max( coi_error, coidef_optdir( cntvect, -1 ) ) ! Minimize
85 coi_error = max( coi_error, coidef_objvar( cntvect, 1 ) ) ! Objective is variable 3
86 coi_error = max( coi_error, coidef_optfile( cntvect, 'Mono03.opt' ) )
87!
88! Tell CONOPT about the callback routines:
89!
90 coi_error = max( coi_error, coidef_readmatrix( cntvect, mono_readmatrix ) )
91 coi_error = max( coi_error, coidef_fdeval( cntvect, mono_fdeval ) )
92 coi_error = max( coi_error, coidef_fdinterval( cntvect, mono_fdinterval ) )
93 coi_error = max( coi_error, coidef_status( cntvect, std_status ) )
94 coi_error = max( coi_error, coidef_solution( cntvect, std_solution ) )
95 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
96 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
97 coi_error = max( coi_error, coidef_triord( cntvect, std_triord ) )
98
99#if defined(CONOPT_LICENSE_INT_1) && defined(CONOPT_LICENSE_INT_2) && defined(CONOPT_LICENSE_INT_3) && defined(CONOPT_LICENSE_TEXT)
100 coi_error = max( coi_error, coidef_license( cntvect, conopt_license_int_1, conopt_license_int_2, conopt_license_int_3, conopt_license_text) )
101#endif
102
103 If ( coi_error .ne. 0 ) THEN
104 write(*,*)
105 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
106 write(*,*)
107 call flog( "Skipping Solve due to setup errors", 1 )
108 ENDIF
109!
110! Save the solution so we can check the duals:
111!
112 do_allocate = .true.
113!
114! Start CONOPT:
115!
116 coi_error = coi_solve( cntvect )
117
118 write(*,*)
119 write(*,*) 'End of Mono03 example. Return code=',coi_error
120
121 If ( coi_error /= 0 ) then
122 call flog( "Errors encountered during solution", 1 )
123 elseif ( stacalls == 0 .or. solcalls == 0 ) then
124 call flog( "Status or Solution routine was not called", 1 )
125 elseif ( sstat /= 1 .or. mstat /= 1 ) then
126 call flog( "Solver and Model Status was not as expected (1,1)", 1 )
127 elseif ( abs( obj-0.0d0 ) > 0.000001d0 ) then
128 call flog( "Incorrect objective returned", 1 )
129 Else
130 Call checkdual( 'Mono03', minimize )
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!
140
141End Program mono03
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 mono_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 :: Mono_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 = -2.0 and type Greater than or Equal
193!
194 rhs(1) = -2.0d0
195 type(1) = 1
196!
197 lower(1) = 0.0d0
198 curr(1) = 1.0d0
199!
200! Information about the Jacobian. CONOPT expects a columnwise
201! representation in Rowno, Value, Nlflag and Colsta.
202!
203! Colsta = Start of column indices (No Defaults):
204! Rowno = Row indices
205! Value = Value of derivative (by default only linear
206! derivatives are used)
207! Nlflag = 0 for linear and 1 for nonlinear derivative
208! (not needed for completely linear models)
209!
210! Indices
211! x(1)
212! 1: 1
213!
214 colsta(1) = 1
215 colsta(2) = 2
216 rowno(1) = 1
217!
218! Nonlinearity Structure: L = 0 are linear and NL = 1 are nonlinear
219! x(1)
220! 1: NL
221!
222 nlflag(1) = 1
223!
224! Value (Linear only)
225! x(1)
226! 1: NL
227!
228 mono_readmatrix = 0 ! Return value means OK
229
230end Function mono_readmatrix
231!
232!==========================================================================
233! Compute nonlinear terms and non-constant Jacobian elements
234!
235
236!> Compute nonlinear terms and non-constant Jacobian elements
237!!
238!! @include{doc} fdeval_params.dox
239Integer Function mono_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
240 n, nz, thread, usrmem )
241#ifdef dec_directives_win32
242!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Mono_FDEval
243#endif
244 implicit none
245 integer, intent (in) :: n ! number of variables
246 integer, intent (in) :: rowno ! number of the row to be evaluated
247 integer, intent (in) :: nz ! number of nonzeros in this row
248 real*8, intent (in), dimension(n) :: x ! vector of current solution values
249 real*8, intent (in out) :: g ! constraint value
250 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
251 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
252 ! in this row. Ffor information only.
253 integer, intent (in) :: mode ! evaluation mode: 1 = function value
254 ! 2 = derivatives, 3 = both
255 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
256 ! as errcnt is incremented
257 integer, intent (in out) :: errcnt ! error counter to be incremented in case
258 ! of function evaluation errors.
259 integer, intent (in) :: thread
260 real*8 usrmem(*) ! optional user memory
261
262 real*8 :: sq
263!
264! Report an error for bad points
265!
266 mono_fdeval = 0 ! OK unless error found later
267 If ( x(1) < 0.0d0 ) then
268 errcnt = errcnt + 1
269 return
270 endif
271!
272! Row 1: e1
273!
274 if ( rowno .eq. 1 ) then
275 sq = sqrt(x(1))
276!
277! Mode = 1 or 3. G = log(x1)
278!
279 if ( mode .eq. 1 .or. mode .eq. 3 ) then
280 g = sq
281 endif
282!
283! Mode = 2 or 3: Derivative values:
285 if ( mode .eq. 2 .or. mode .eq. 3 ) then
286 jac(1) = 0.5d0/max(sq,1.d-20)
287 endif
288 else
289!
290! There are no other rows:
291!
292 mono_fdeval = 1
293 endif
294
295end Function mono_fdeval
296
297
298!> Evaluating nonlinear functions and derivatives on an interval. Used in preprocessing
299!!
300!! @include{doc} fdinterval_params.dox
301Integer Function mono_fdinterval( XMIN, XMAX, GMIN, GMAX, &
302 JMIN, JMAX, ROWNO, JCNM, &
303 MODE, PINF, N, NJ, USRMEM )
304#ifdef dec_directives_win32
305!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Mono_FDInterval
306#endif
307 Implicit None
308 INTEGER, Intent(IN) :: rowno, mode, n, nj
309 INTEGER, Dimension(NJ), Intent(IN) :: jcnm
310 real*8, Dimension(N), Intent(IN) :: xmin, xmax
311 real*8, Intent(IN OUT) :: gmin, gmax
312 real*8, Dimension(N), Intent(IN OUT) :: jmin, jmax
313 real*8, Intent(IN) :: pinf
314 real*8, Intent(IN OUT) :: usrmem(*)
315
316!
317! Row 1: e1
318!
319 write(10,*) 'Enter Mono_FDInterval. Row=',rowno,' Mode=',mode
320 write(10,*) 'Xmin=',xmin
321 write(10,*) 'Xmax=',xmax
322 if ( rowno .eq. 1 ) then
323!
324! Mode = 1 or 3. G = log(x1)
325!
326 if ( mode .eq. 1 .or. mode .eq. 3 ) then
327 If ( xmin(1) < 0.0d0 ) then
328 gmin = -pinf
329 else
330 gmin = sqrt(xmin(1))
331 endif
332 If ( xmax(1) < 0.0d0 ) then
333 gmax = -pinf
334 else
335 gmax = sqrt(xmax(1))
336 endif
337 write(10,*) 'Gmin=',gmin,' Gmax=',gmax
338 endif
339!
340! Mode = 2 or 3: Derivative values:
341!
342 if ( mode .eq. 2 .or. mode .eq. 3 ) then
343 If ( xmin(1) < 0.0d0 ) then
344 jmin(1) = -pinf
345 jmax(1) = +pinf
346 else
347 jmin(1) = 1.0d0/max(sqrt(xmax(1)),1.d-20)
348 jmax(1) = 1.0d0/max(sqrt(xmin(1)),1.d-20)
349 endif
350 write(10,*) 'Jmin=',jmin
351 write(10,*) 'Jmax=',jmax
352 endif
354 else
355!
356! There are no other rows:
357!
359 endif
360
361end 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 mono03
Main program. A simple setup and call of CONOPT.
Definition mono03.f90:40
#define nj
Definition mp_trans.c:46
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 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
integer mstat
Definition comdecl.f90:17
subroutine startup
Definition comdecl.f90:41