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