CONOPT
Loading...
Searching...
No Matches
postmo02.f90
Go to the documentation of this file.
1!> @file postmo02.f90
2!! @ingroup FORT1THREAD_EXAMPLES
3!!
4!!
5!! Model with derivatives that become constant after other variables are fixed.
6!! Similar to postmo01 except that the Rhs and Lhs have been reversed so the monotone
7!! terms changes between increasing and decreasing.
8!!
9!! This is a CONOPT implementation of the GAMS model:
10!!
11!! @verbatim
12!! e1: x2 =E= log(x1);
13!! e2: x1 =E= exp(x3);
14!! max x2
15!! 0.01 <= x1 x1.l = 1
16!! -1.0 <= x2 <= 1; x2.l = 0
17!! x3.l = 0;
18!! @endverbatim
19!!
20!! The bounds on x2 prevent e1 from being posttriangular immediately. However, due to
21!! the monotonicity the bounds can be transferred to x1. Similarly, the bounds on x1
22!! can be moved to x2 and the model ends with one variable and no constraints.
23!!
24!! The expected solution is x2=1 (at upper bound), `x1=exp(x2)=exp(1)`, and `x3= log(x1) = 1`;
25!!
26!!
27!! For more information about the individual callbacks, please have a look at the source code.
28
29!> Main program. A simple setup and call of CONOPT
30!!
31Program postmo02
32
33 Use proginfo
34 Use coidef
35 implicit None
36!
37! Declare the user callback routines as Integer, External:
38!
39 Integer, External :: con_readmatrix ! Mandatory Matrix definition routine defined below
40 Integer, External :: con_fdeval ! Function and Derivative evaluation routine
41 ! needed a nonlinear model.
42 Integer, External :: con_fdinterval ! Function and Derivative evaluation routine
43 ! optional for a nonlinear model.
44 Integer, External :: std_status ! Standard callback for displaying solution status
45 Integer, External :: std_solution ! Standard callback for displaying solution values
46 Integer, External :: std_message ! Standard callback for managing messages
47 Integer, External :: std_errmsg ! Standard callback for managing error messages
48#if defined(itl)
49!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Con_ReadMatrix
50!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Con_FDEval
51!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Con_FDInterval
52!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Status
53!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Solution
54!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Message
55!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_ErrMsg
56#endif
57!
58! Control vector
59!
60 INTEGER, Dimension(:), Pointer :: cntvect
61 INTEGER :: coi_error
62!
63! Create and initialize a Control Vector
64!
65 call startup
66
67 coi_error = coi_createfort( cntvect )
68!
69! Tell CONOPT about the size of the model by populating the Control Vector:
70!
71 coi_error = max( coi_error, coidef_numvar( cntvect, 3 ) ) ! # variables
72 coi_error = max( coi_error, coidef_numcon( cntvect, 2 ) ) ! # constraints
73 coi_error = max( coi_error, coidef_numnz( cntvect, 4 ) ) ! # nonzeros in the Jacobian
74 coi_error = max( coi_error, coidef_numnlnz( cntvect, 2 ) ) ! # of which are nonlinear
75 coi_error = max( coi_error, coidef_optdir( cntvect, 1 ) ) ! Maximize
76 coi_error = max( coi_error, coidef_objvar( cntvect, 2 ) ) ! Objective is variable 2
77 coi_error = max( coi_error, coidef_optfile( cntvect, 'postmo02.opt' ) )
78!
79! Tell CONOPT about the callback routines:
80!
81 coi_error = max( coi_error, coidef_readmatrix( cntvect, con_readmatrix ) )
82 coi_error = max( coi_error, coidef_fdeval( cntvect, con_fdeval ) )
83 coi_error = max( coi_error, coidef_fdinterval( cntvect, con_fdinterval ) )
84 coi_error = max( coi_error, coidef_status( cntvect, std_status ) )
85 coi_error = max( coi_error, coidef_solution( cntvect, std_solution ) )
86 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
87 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
88
89#if defined(LICENSE_INT_1) && defined(LICENSE_INT_2) && defined(LICENSE_INT_3) && defined(LICENSE_TEXT)
90 coi_error = max( coi_error, coidef_license( cntvect, license_int_1, license_int_2, license_int_3, license_text) )
91#endif
92
93 If ( coi_error .ne. 0 ) THEN
94 write(*,*)
95 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
96 write(*,*)
97 call flog( "Skipping Solve due to setup errors", 1 )
98 ENDIF
99!
100! Save the solution so we can check the duals:
101!
102 do_allocate = .true.
103!
104! Start CONOPT:
105!
106 coi_error = coi_solve( cntvect )
107
108 write(*,*)
109 write(*,*) 'End of postmo02 example. Return code=',coi_error
110
111 If ( coi_error /= 0 ) then
112 call flog( "Errors encountered during solution", 1 )
113 elseif ( stacalls == 0 .or. solcalls == 0 ) then
114 call flog( "Status or Solution routine was not called", 1 )
115 elseif ( sstat /= 1 .or. mstat /= 2 ) then
116 call flog( "Solver and Model Status was not as expected (1,2)", 1 )
117 elseif ( abs( obj-1.0d0 ) > 0.000001d0 ) then
118 call flog( "Incorrect objective returned", 1 )
119 Else
120 Call checkdual( 'postmo02', maximize )
121 endif
122
123 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
124
125 call flog( "Successful Solve", 0 )
126
127End Program postmo02
128!
129! ============================================================================
130! Define information about the model:
131!
132
133!> Define information about the model
134!!
135!! @include{doc} readMatrix_params.dox
136Integer Function con_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
137 colsta, rowno, value, nlflag, n, m, nz, &
138 usrmem )
139#if defined(itl)
140!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Con_ReadMatrix
141#endif
142 implicit none
143 integer, intent (in) :: n ! number of variables
144 integer, intent (in) :: m ! number of constraints
145 integer, intent (in) :: nz ! number of nonzeros
146 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
147 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
148 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
149 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
150 ! (not defined here)
151 integer, intent (out), dimension(m) :: type ! vector of equation types
152 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
153 ! (not defined here)
154 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
155 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
156 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
157 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
158 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
159 real*8 usrmem(*) ! optional user memory
160!
161! Information about Variables:
162! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
163! Default: the status information in Vsta is not used.
164!
165 lower(1) = 0.01d0; curr(1) = 1.0d0
166 lower(2) = -1.0d0; curr(2) = 0.0d0; upper(2) = 1.0d0
167 curr(3) = 0.0d0
168!
169! Information about Constraints:
170! Default: Rhs = 0
171! Default: the status information in Esta and the function
172! value in FV are not used.
173! Default: Type: There is no default.
174! 0 = Equality,
175! 1 = Greater than or equal,
176! 2 = Less than or equal,
177! 3 = Non binding.
178!
179 type(1) = 0
180 type(2) = 0
181!
182! Information about the Jacobian. We use the standard method with
183! Rowno, Value, Nlflag and Colsta and we do not use Colno.
184!
185! Colsta = Start of column indices (No Defaults):
186! Rowno = Row indices
187! Value = Value of derivative (by default only linear
188! derivatives are used)
189! Nlflag = 0 for linear and 1 for nonlinear derivative
190! (not needed for completely linear models)
191!
192! Indices
193! x(1) x(2) x(3)
194! 1: 1 3
195! 2: 2 4
196! e1: log(x1) =E= x2;
197! e2: exp(x3) =E= x1;
198!
199 colsta(1) = 1
200 colsta(2) = 3
201 colsta(3) = 4
202 colsta(4) = 5
203 rowno(1) = 1
204 rowno(2) = 2
205 rowno(3) = 1
206 rowno(4) = 2
207!
208! Nonlinearity Structure: L = 0 are linear and NL = 1 are nonlinear
209! x(1) x(2) x(3)
210! 1: NL L
211! 2: L NL
212!
213 nlflag(1) = 1
214 nlflag(2) = 0
215 nlflag(3) = 0
216 nlflag(4) = 1
217!
218! Value (Linear only)
219! x(1) x(2) x(3)
220! 1: NL +1.0
221! 2: +1.0 NL
222!
223 value(2) = +1.d0
224 value(3) = +1.d0
225
226 con_readmatrix = 0 ! Return value means OK
227
228end Function con_readmatrix
229!
230!==========================================================================
231! Compute nonlinear terms and non-constant Jacobian elements
232!
233
234!> Compute nonlinear terms and non-constant Jacobian elements
235!!
236!! @include{doc} fdeval_params.dox
237Integer Function con_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
238 n, nz, thread, usrmem )
239#if defined(itl)
240!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Con_FDEval
241#endif
242 implicit none
243 integer, intent (in) :: n ! number of variables
244 integer, intent (in) :: rowno ! number of the row to be evaluated
245 integer, intent (in) :: nz ! number of nonzeros in this row
246 real*8, intent (in), dimension(n) :: x ! vector of current solution values
247 real*8, intent (in out) :: g ! constraint value
248 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
249 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
250 ! in this row. Ffor information only.
251 integer, intent (in) :: mode ! evaluation mode: 1 = function value
252 ! 2 = derivatives, 3 = both
253 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
254 ! as errcnt is incremented
255 integer, intent (in out) :: errcnt ! error counter to be incremented in case
256 ! of function evaluation errors.
257 integer, intent (in) :: thread
258 real*8 usrmem(*) ! optional user memory
259 if ( rowno .eq. 1 ) then
260!
261! e1: x2 =E= log(x1)
262!
263! Mode = 1 or 3: Function value
264!
265 if ( mode .eq. 1 .or. mode .eq. 3 ) then
266 g = -log(x(1))
267 endif
268!
269! Mode = 2 or 3: Derivatives
270!
271 if ( mode .eq. 2 .or. mode .eq. 3 ) then
272 jac(1) = -1.0d0/x(1)
273 endif
274 con_fdeval = 0
275 else if ( rowno .eq. 2 ) then
276!
277! e2: x1 =E= exp(x3);
278!
279! Mode = 1 or 3: Function value
280!
281 if ( mode .eq. 1 .or. mode .eq. 3 ) then
282 g = -exp(x(3))
283 endif
284!
285! Mode = 2 or 3: Derivatives
286!
287 if ( mode .eq. 2 .or. mode .eq. 3 ) then
288 jac(3) = -exp(x(3))
289 endif
290 con_fdeval = 0
291 Else
292 con_fdeval = 1 ! Should not happen
293 endif
294
295end Function con_fdeval
296
297
298!> Evaluating nonlinear functions and derivatives on an interval. Used in preprocessing
299!!
300!! @include{doc} fdinterval_params.dox
301Integer Function con_fdinterval( XMIN, XMAX, GMIN, GMAX, &
302 JMIN, JMAX, ROWNO, JCNM, &
303 MODE, PINF, N, NJ, USRMEM )
304#if defined(itl)
305!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Con_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 if ( rowno .eq. 1 ) then
317!
318! e1: x2 =E= log(x1)
319!
320! Mode = 1 or 3. Function value
321!
322 if ( mode .eq. 1 .or. mode .eq. 3 ) then
323 gmin = -log(xmax(1))
324 gmax = -log(xmin(1))
325 endif
326!
327! Mode = 2 or 3: Derivative values:
328!
329 if ( mode .eq. 2 .or. mode .eq. 3 ) then
330 jmin(1) = -1.0d0/xmin(1)
331 jmax(1) = -1.0d0/xmax(1)
332 endif
334 else if ( rowno .eq. 2 ) then
335!
336! e2: x1 =E= exp(x3);
337!
338! Mode = 1 or 3. Function value
339!
340 if ( mode .eq. 1 .or. mode .eq. 3 ) then
341 gmin = -exp(xmax(3))
342 gmax = -exp(xmin(3))
343 endif
344!
345! Mode = 2 or 3: Derivative values:
346!
347 if ( mode .eq. 2 .or. mode .eq. 3 ) then
348 jmin(3) = -exp(xmax(3))
349 jmax(3) = -exp(xmin(3))
350 endif
352 else
353!
354! There are no other rows:
355!
357 endif
358
359end Function con_fdinterval
integer function std_solution(xval, xmar, xbas, xsta, yval, ymar, ybas, ysta, n, m, usrmem)
Definition comdecl.f90:128
integer function std_status(modsta, solsta, iter, objval, usrmem)
Definition comdecl.f90:82
subroutine checkdual(case, minmax)
Definition comdecl.f90:365
integer function std_message(smsg, dmsg, nmsg, llen, usrmem, msgv)
Definition comdecl.f90:203
integer function std_errmsg(rowno, colno, posno, msglen, usrmem, msg)
Definition comdecl.f90:248
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:133
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:238
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:291
integer function coidef_fdeval(cntvect, coi_fdeval)
define callback routine for performing function and derivative evaluations.
integer function coidef_errmsg(cntvect, coi_errmsg)
define callback routine for returning error messages for row, column or Jacobian elements.
integer function coidef_message(cntvect, coi_message)
define callback routine for handling messages returned during the solution process.
integer function coidef_readmatrix(cntvect, coi_readmatrix)
define callback routine for providing the matrix data to CONOPT.
integer function coidef_status(cntvect, coi_status)
define callback routine for returning the completion status.
integer function coidef_solution(cntvect, coi_solution)
define callback routine for returning the final solution values.
integer function coidef_optfile(cntvect, optfile)
define callback routine for defining an options file.
integer function coidef_fdinterval(cntvect, coi_fdinterval)
define callback routine for performing function and derivative evaluations on intervals.
integer function coidef_license(cntvect, licint1, licint2, licint3, licstring)
define the License Information.
Definition coistart.f90:680
integer function coidef_numvar(cntvect, numvar)
defines the number of variables in the model.
Definition coistart.f90:358
integer function coidef_numnz(cntvect, numnz)
defines the number of nonzero elements in the Jacobian.
Definition coistart.f90:437
integer function coidef_optdir(cntvect, optdir)
defines the Optimization Direction.
Definition coistart.f90:552
integer function coidef_numnlnz(cntvect, numnlnz)
defines the Number of Nonlinear Nonzeros.
Definition coistart.f90:476
integer function coidef_numcon(cntvect, numcon)
defines the number of constraints in the model.
Definition coistart.f90:398
integer function coidef_objvar(cntvect, objvar)
defines the Objective Variable.
Definition coistart.f90:586
integer function coi_solve(cntvect)
method for starting the solving process of CONOPT.
Definition coistart.f90:14
#define nj
Definition mp_trans.c:46
real *8 obj
Definition comdecl.f90:10
integer solcalls
Definition comdecl.f90:9
integer sstat
Definition comdecl.f90:12
integer stacalls
Definition comdecl.f90:8
subroutine flog(msg, code)
Definition comdecl.f90:56
logical do_allocate
Definition comdecl.f90:21
integer, parameter maximize
Definition comdecl.f90:25
integer mstat
Definition comdecl.f90:11
subroutine startup
Definition comdecl.f90:35
program postmo02
Main program. A simple setup and call of CONOPT.
Definition postmo02.f90:31