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