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