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