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