CONOPT
Loading...
Searching...
No Matches
postmo03.f90
Go to the documentation of this file.
1!> @file postmo03.f90
2!! @ingroup FORT1THREAD_EXAMPLES
3!!
4!!
5!! Model with derivatives that become constant after other variables are fixed.
6!! The model is similar to postmo01 but the bounds are changed.
7!!
8!! This is a CONOPT implementation of the GAMS model:
9!!
10!! @verbatim
11!! e1: log(x1) =E= x2;
12!! e2: exp(x3) =E= x1;
13!! max x2
14!! 0.01 <= x1 x1.l = 1
15!! -inf <= x2 <= 1; x2.l = 0
16!! -2 <= x3 <= +inf; x3.l = 0;
17!! @endverbatim
18!!
19!! The bounds on x2 prevent e1 from being posttriangular immediately. However, due to
20!! the monotonicity the bounds can be transferred to x1. Similarly, the bounds on x1
21!! can be moved to x2 and the model ends with one variable and no constraints.
22!!
23!! The transfer of bounds work as follows:
24!! e1: the inverval `-inf <= x2 <= 1` is transferred to `0 = exp(-inf) <= x1 <= exp(1) = 2.718`
25!! where only the upper bound is tighter than the input bound.
26!! e2: the inverval `0.01 <= x1 <= exp(1)` from before is transferred to `-4.605 <= x3 <= 1`
27!! where again only the upper bound is tighter that the input bound.
28!!
29!! The expected solution is `x2=1` (at upper bound), `x1=exp(x2)=exp(1)`, and `x3= log(x1) = 1`;
30!!
31!!
32!! For more information about the individual callbacks, please have a look at the source code.
33
34#if defined(_WIN32) && !defined(_WIN64)
35#define dec_directives_win32
36#endif
37
38!> Main program. A simple setup and call of CONOPT
39!!
40Program postmo03
41
43 Use conopt
44 implicit None
45!
46! Declare the user callback routines as Integer, External:
47!
48 Integer, External :: con_readmatrix ! Mandatory Matrix definition routine defined below
49 Integer, External :: con_fdeval ! Function and Derivative evaluation routine
50 ! needed a nonlinear model.
51 Integer, External :: con_fdinterval ! Function and Derivative evaluation routine
52 ! optional for a nonlinear model.
53 Integer, External :: std_status ! Standard callback for displaying solution status
54 Integer, External :: std_solution ! Standard callback for displaying solution values
55 Integer, External :: std_message ! Standard callback for managing messages
56 Integer, External :: std_errmsg ! Standard callback for managing error messages
57#ifdef dec_directives_win32
58!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Con_ReadMatrix
59!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Con_FDEval
60!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Con_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#endif
66!
67! Control vector
68!
69 INTEGER, Dimension(:), Pointer :: cntvect
70 INTEGER :: coi_error
71!
72! Create and initialize a Control Vector
73!
74 call startup
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, 3 ) ) ! # variables
81 coi_error = max( coi_error, coidef_numcon( cntvect, 2 ) ) ! # constraints
82 coi_error = max( coi_error, coidef_numnz( cntvect, 4 ) ) ! # nonzeros in the Jacobian
83 coi_error = max( coi_error, coidef_numnlnz( cntvect, 2 ) ) ! # of which are nonlinear
84 coi_error = max( coi_error, coidef_optdir( cntvect, 1 ) ) ! Maximize
85 coi_error = max( coi_error, coidef_objvar( cntvect, 2 ) ) ! Objective is variable 2
86 coi_error = max( coi_error, coidef_optfile( cntvect, 'postmo03.opt' ) )
87!
88! Tell CONOPT about the callback routines:
89!
90 coi_error = max( coi_error, coidef_readmatrix( cntvect, con_readmatrix ) )
91 coi_error = max( coi_error, coidef_fdeval( cntvect, con_fdeval ) )
92 coi_error = max( coi_error, coidef_fdinterval( cntvect, con_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
98#if defined(CONOPT_LICENSE_INT_1) && defined(CONOPT_LICENSE_INT_2) && defined(CONOPT_LICENSE_INT_3) && defined(CONOPT_LICENSE_TEXT)
99 coi_error = max( coi_error, coidef_license( cntvect, conopt_license_int_1, conopt_license_int_2, conopt_license_int_3, conopt_license_text) )
100#endif
101
102 If ( coi_error .ne. 0 ) THEN
103 write(*,*)
104 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
105 write(*,*)
106 call flog( "Skipping Solve due to setup errors", 1 )
107 ENDIF
108!
109! Save the solution so we can check the duals:
110!
111 do_allocate = .true.
112!
113! Start CONOPT:
114!
115 coi_error = coi_solve( cntvect )
116
117 write(*,*)
118 write(*,*) 'End of postmo03 example. Return code=',coi_error
119
120 If ( coi_error /= 0 ) then
121 call flog( "Errors encountered during solution", 1 )
122 elseif ( stacalls == 0 .or. solcalls == 0 ) then
123 call flog( "Status or Solution routine was not called", 1 )
124 elseif ( sstat /= 1 .or. mstat /= 2 ) then
125 call flog( "Solver and Model Status was not as expected (1,2)", 1 )
126 elseif ( abs( obj-1.0d0 ) > 0.000001d0 ) then
127 call flog( "Incorrect objective returned", 1 )
128 Else
129 Call checkdual( 'postmo03', maximize )
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!
136! Free solution memory
137!
138 call finalize
140End Program postmo03
141!
142! ============================================================================
143! Define information about the model:
144!
145
146!> Define information about the model
147!!
148!! @include{doc} readMatrix_params.dox
149Integer Function con_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
150 colsta, rowno, value, nlflag, n, m, nz, &
151 usrmem )
152#ifdef dec_directives_win32
153!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Con_ReadMatrix
154#endif
155 implicit none
156 integer, intent (in) :: n ! number of variables
157 integer, intent (in) :: m ! number of constraints
158 integer, intent (in) :: nz ! number of nonzeros
159 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
160 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
161 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
162 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
163 ! (not defined here)
164 integer, intent (out), dimension(m) :: type ! vector of equation types
165 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
166 ! (not defined here)
167 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
168 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
169 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
170 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
171 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
172 real*8 usrmem(*) ! optional user memory
173!
174! Information about Variables:
175! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
176! Default: the status information in Vsta is not used.
177!
178 lower(1) = 0.01d0; curr(1) = 1.0d0
179 curr(2) = 0.0d0; upper(2) = 1.0d0
180 lower(3) = -2.0d0; curr(3) = 0.0d0
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 type(1) = 0
193 type(2) = 0
194!
195! Information about the Jacobian. CONOPT expects a columnwise
196! representation in Rowno, Value, Nlflag and Colsta.
197!
198! Colsta = Start of column indices (No Defaults):
199! Rowno = Row indices
200! Value = Value of derivative (by default only linear
201! derivatives are used)
202! Nlflag = 0 for linear and 1 for nonlinear derivative
203! (not needed for completely linear models)
204!
205! Indices
206! x(1) x(2) x(3)
207! 1: 1 3
208! 2: 2 4
209! e1: log(x1) =E= x2;
210! e2: exp(x3) =E= x1;
211!
212 colsta(1) = 1
213 colsta(2) = 3
214 colsta(3) = 4
215 colsta(4) = 5
216 rowno(1) = 1
217 rowno(2) = 2
218 rowno(3) = 1
219 rowno(4) = 2
220!
221! Nonlinearity Structure: L = 0 are linear and NL = 1 are nonlinear
222! x(1) x(2) x(3)
223! 1: NL L
224! 2: L NL
225!
226 nlflag(1) = 1
227 nlflag(2) = 0
228 nlflag(3) = 0
229 nlflag(4) = 1
230!
231! Value (Linear only)
232! x(1) x(2) x(3)
233! 1: NL -1.0
234! 2: -1.0 NL
235!
236 value(2) = -1.d0
237 value(3) = -1.d0
238
239 con_readmatrix = 0 ! Return value means OK
240
241end Function con_readmatrix
242!
243!==========================================================================
244! Compute nonlinear terms and non-constant Jacobian elements
245!
246
247!> Compute nonlinear terms and non-constant Jacobian elements
248!!
249!! @include{doc} fdeval_params.dox
250Integer Function con_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
251 n, nz, thread, usrmem )
252#ifdef dec_directives_win32
253!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Con_FDEval
254#endif
255 implicit none
256 integer, intent (in) :: n ! number of variables
257 integer, intent (in) :: rowno ! number of the row to be evaluated
258 integer, intent (in) :: nz ! number of nonzeros in this row
259 real*8, intent (in), dimension(n) :: x ! vector of current solution values
260 real*8, intent (in out) :: g ! constraint value
261 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
262 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
263 ! in this row. Ffor information only.
264 integer, intent (in) :: mode ! evaluation mode: 1 = function value
265 ! 2 = derivatives, 3 = both
266 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
267 ! as errcnt is incremented
268 integer, intent (in out) :: errcnt ! error counter to be incremented in case
269 ! of function evaluation errors.
270 integer, intent (in) :: thread
271 real*8 usrmem(*) ! optional user memory
272 if ( rowno .eq. 1 ) then
273!
274! e1: log(x1) =E= x2;
275!
276! Mode = 1 or 3: Function value
277!
278 if ( mode .eq. 1 .or. mode .eq. 3 ) then
279 g = log(x(1))
280 endif
281!
282! Mode = 2 or 3: Derivatives
283!
284 if ( mode .eq. 2 .or. mode .eq. 3 ) then
285 jac(1) = 1.0d0/x(1)
286 endif
287 con_fdeval = 0
288 else if ( rowno .eq. 2 ) then
289!
290! e2: exp(x3) =E= x1;
291!
292! Mode = 1 or 3: Function value
293!
294 if ( mode .eq. 1 .or. mode .eq. 3 ) then
295 g = exp(x(3))
296 endif
297!
298! Mode = 2 or 3: Derivatives
299!
300 if ( mode .eq. 2 .or. mode .eq. 3 ) then
301 jac(3) = exp(x(3))
302 endif
303 con_fdeval = 0
304 Else
305 con_fdeval = 1 ! Should not happen
306 endif
307
308end Function con_fdeval
309
310
311!> Evaluating nonlinear functions and derivatives on an interval. Used in preprocessing
312!!
313!! @include{doc} fdinterval_params.dox
314Integer Function con_fdinterval( XMIN, XMAX, GMIN, GMAX, &
315 JMIN, JMAX, ROWNO, JCNM, &
316 MODE, PINF, N, NJ, USRMEM )
317#ifdef dec_directives_win32
318!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Con_FDInterval
319#endif
320 Implicit None
321 INTEGER, Intent(IN) :: rowno, mode, n, nj
322 INTEGER, Dimension(NJ), Intent(IN) :: jcnm
323 real*8, Dimension(N), Intent(IN) :: xmin, xmax
324 real*8, Intent(IN OUT) :: gmin, gmax
325 real*8, Dimension(N), Intent(IN OUT) :: jmin, jmax
326 real*8, Intent(IN) :: pinf
327 real*8, Intent(IN OUT) :: usrmem(*)
328
329 if ( rowno .eq. 1 ) then
330!
331! e1: log(x1) =E= x2;
332!
333! Mode = 1 or 3. Function value
334!
335 if ( mode .eq. 1 .or. mode .eq. 3 ) then
336 gmin = log(xmin(1))
337 gmax = log(xmax(1))
338 endif
339!
340! Mode = 2 or 3: Derivative values:
341!
342 if ( mode .eq. 2 .or. mode .eq. 3 ) then
343 jmin(1) = 1.0d0/xmax(1)
344 jmax(1) = 1.0d0/xmin(1)
345 endif
347 else if ( rowno .eq. 2 ) then
348!
349! e2: exp(x3) =E= x1;
350!
351! Mode = 1 or 3. Function value
352!
353 if ( mode .eq. 1 .or. mode .eq. 3 ) then
354 gmin = exp(xmin(3))
355 gmax = exp(xmax(3))
356 endif
357!
358! Mode = 2 or 3: Derivative values:
359!
360 if ( mode .eq. 2 .or. mode .eq. 3 ) then
361 jmin(3) = exp(xmin(3))
362 jmax(3) = exp(xmax(3))
363 endif
365 else
366!
367! There are no other rows:
368!
370 endif
371
372end Function con_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_errmsg(rowno, colno, posno, msglen, usrmem, msg)
Definition comdecl.f90:286
integer function con_readmatrix(lower, curr, upper, vsta, type, rhs, esta, colsta, rowno, value, nlflag, n, m, nz, usrmem)
Define information about the model.
Definition const01.f90:131
integer function con_fdeval(x, g, jac, rowno, jcnm, mode, ignerr, errcnt, n, nz, thread, usrmem)
Compute nonlinear terms and non-constant Jacobian elements.
Definition const01.f90:233
integer function con_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 const01.f90:283
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_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
#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 stacalls
Definition comdecl.f90:14
subroutine flog(msg, code)
Definition comdecl.f90:62
logical do_allocate
Definition comdecl.f90:27
integer, parameter maximize
Definition comdecl.f90:31
integer mstat
Definition comdecl.f90:17
subroutine startup
Definition comdecl.f90:41
program postmo03
Main program. A simple setup and call of CONOPT.
Definition postmo03.f90:42