CONOPT
Loading...
Searching...
No Matches
nleq03.f90
Go to the documentation of this file.
1!> @file nleq03.f90
2!! @ingroup FORT1THREAD_EXAMPLES
3!!
4!!
5!! Nonlinear function to bound conversion example 03
6!!
7!! This is a CONOPT implementation of the GAMS model:
8!!
9!! @verbatim
10!! variable x1
11!! equation e1;
12!!
13!! e1 .. sqr(x) =E= -0.01; ! Infeasible
14!! e1 .. sqr(x) =E= +0.01; ! Feasible, x1 = -0.1 or +0.1
15!! e1 .. sqr(x) =L= -0.01; ! Infeasible
16!! e1 .. sqr(x) =L= +0.01; ! Feasible, x1 = 0.1
17!! e1 .. sqr(x) =G= -0.01; ! Unbounded or x1 = -0.1
18!! e1 .. sqr(x) =G= +0.01; ! Unbounded
19!!
20!! x1.l = 1.0;
21!! model Nleq / all /;
22!! solve Nleq using nlp maximizing x1;
23!! @endverbatim
24!!
25!!
26!!
27!! For more information about the individual callbacks, please have a look at the source code.
28
30 Integer, Parameter :: maxcase = 6
31 real*8, Parameter, dimension(MaxCase) :: caserhs = &
32 (/ -0.01d0, +0.01d0, -0.01d0, +0.01d0,-0.01d0, +0.01d0 /)
33 Integer, Parameter, dimension(MaxCase) :: casetype = &
34 (/ 0, 0, 2, 2, 1, 1 /)
35 Integer, Parameter, dimension(MaxCase) :: casemstat = &
36 (/ 5, 2, 5, 2, 3, 3 /)
37 real*8, Parameter, dimension(MaxCase) :: caseobj = &
38 (/ 0.0d0, 0.0d0, 0.0d0, 0.1d0, 0.0d0, 0.0d0 /)
39 Integer :: casenum
40end module nleq03data
41!> Main program. A simple setup and call of CONOPT
42!!
43Program nleq03
44
45 Use proginfo
46 Use coidef
47 Use nleq03data
48 implicit None
49!
50! Declare the user callback routines as Integer, External:
51!
52 Integer, External :: nleq_readmatrix ! Mandatory Matrix definition routine defined below
53 Integer, External :: nleq_fdeval ! Function and Derivative evaluation routine
54 ! needed a nonlinear model.
55 Integer, External :: std_status ! Standard callback for displaying solution status
56 Integer, External :: std_solution ! Standard callback for displaying solution values
57 Integer, External :: std_message ! Standard callback for managing messages
58 Integer, External :: std_errmsg ! Standard callback for managing error messages
59 Integer, External :: std_triord ! Standard callback for Nleqngular order
60#if defined(itl)
61!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Nleq_ReadMatrix
62!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Nleq_FDEval
63!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Status
64!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Solution
65!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Message
66!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_ErrMsg
67!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_TriOrd
68#endif
69!
70! Control vector
71!
72 INTEGER :: numcallback
73 INTEGER, Dimension(:), Pointer :: cntvect
74 INTEGER :: coi_error
75
76 call startup
77!
78! Create and initialize a Control Vector
79!
80 numcallback = coidef_size()
81 Allocate( cntvect(numcallback) )
82 coi_error = coidef_inifort( cntvect )
83!
84! Tell CONOPT about the size of the model by populating the Control Vector:
85!
86 coi_error = max( coi_error, coidef_numvar( cntvect, 1 ) ) ! # variables
87 coi_error = max( coi_error, coidef_numcon( cntvect, 1 ) ) ! # constraints
88 coi_error = max( coi_error, coidef_numnz( cntvect, 1 ) ) ! # nonzeros in the Jacobian
89 coi_error = max( coi_error, coidef_numnlnz( cntvect, 1 ) ) ! # of which are nonlinear
90 coi_error = max( coi_error, coidef_optdir( cntvect, +1 ) ) ! Maximize
91 coi_error = max( coi_error, coidef_objvar( cntvect, 1 ) ) ! Objective is variable 3
92 coi_error = max( coi_error, coidef_optfile( cntvect, 'Nleq03.opt' ) )
93!
94! Tell CONOPT about the callback routines:
95!
96 coi_error = max( coi_error, coidef_readmatrix( cntvect, nleq_readmatrix ) )
97 coi_error = max( coi_error, coidef_fdeval( cntvect, nleq_fdeval ) )
98 coi_error = max( coi_error, coidef_status( cntvect, std_status ) )
99 coi_error = max( coi_error, coidef_solution( cntvect, std_solution ) )
100 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
101 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
102 coi_error = max( coi_error, coidef_triord( cntvect, std_triord ) )
103
104#if defined(LICENSE_INT_1) && defined(LICENSE_INT_2) && defined(LICENSE_INT_3) && defined(LICENSE_TEXT)
105 coi_error = max( coi_error, coidef_license( cntvect, license_int_1, license_int_2, license_int_3, license_text) )
106#endif
107
108 If ( coi_error .ne. 0 ) THEN
109 write(*,*)
110 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
111 write(*,*)
112 call flog( "Skipping Solve due to setup errors", 1 )
113 ENDIF
114!
115! Save the solution so we can check the duals:
116!
117 do_allocate = .true.
118 DO casenum = 1, maxcase
119!
120! Start CONOPT:
121!
122 coi_error = coi_solve( cntvect )
123
124 write(*,*)
125 write(*,*) 'End of Nleq03 example case=',casenum,'. Return code=',coi_error
126
127 If ( coi_error /= 0 ) then
128 call flog( "Errors encountered during solution", 1 )
129 elseif ( stacalls == 0 .or. solcalls == 0 ) then
130 call flog( "Status or Solution routine was not called", 1 )
131 elseif ( sstat /= 1 .or. mstat /= casemstat(casenum) ) then
132 call flog( "Solver and Model Status was not as expected", 1 )
133 elseif ( mstat == 1 .and. caseobj(casenum) /= 0.0d0 .and. abs( obj-caseobj(casenum) ) > 0.000001d0 ) then
134 call flog( "Incorrect objective returned", 1 )
135 Elseif ( mstat == 1 ) Then
136 Call checkdual( 'Nleq03', maximize )
137 Elseif ( mstat == 4 ) Then
138 Call checkdual( 'Nleq03', infeasible )
139 endif
140
141 EndDo ! end Casenum loop
142
143 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
144
145 call flog( "Successful Solve", 0 )
146
147End Program nleq03
148!
149! ============================================================================
150! Define information about the model:
151!
152
153!> Define information about the model
154!!
155!! @include{doc} readMatrix_params.dox
156Integer Function nleq_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
157 colsta, rowno, value, nlflag, n, m, nz, &
158 usrmem )
159#if defined(itl)
160!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Nleq_ReadMatrix
161#endif
162 Use nleq03data
163 implicit none
164 integer, intent (in) :: n ! number of variables
165 integer, intent (in) :: m ! number of constraints
166 integer, intent (in) :: nz ! number of nonzeros
167 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
168 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
169 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
170 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
171 ! (not defined here)
172 integer, intent (out), dimension(m) :: type ! vector of equation types
173 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
174 ! (not defined here)
175 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
176 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
177 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
178 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
179 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
180 real*8 usrmem(*) ! optional user memory
181!
182! Information about Variables:
183! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
184! Default: the status information in Vsta is not used.
185!
186! The model uses defaults
187!
188! Information about Constraints:
189! Default: Rhs = 0
190! Default: the status information in Esta and the function
191! value in FV are not used.
192! Default: Type: There is no default.
193! 0 = Equality,
194! 1 = Greater than or equal,
195! 2 = Less than or equal,
196! 3 = Non binding.
197!
198! Constraint 1: e1
199! Rhs and type depends on case
200!
201 rhs(1) = caserhs(casenum)
202 type(1) = casetype(casenum)
203!
204 curr(1) = 1.0d0
205!
206! Information about the Jacobian. We use the standard method with
207! Rowno, Value, Nlflag and Colsta and we do not use Colno.
208!
209! Colsta = Start of column indices (No Defaults):
210! Rowno = Row indices
211! Value = Value of derivative (by default only linear
212! derivatives are used)
213! Nlflag = 0 for linear and 1 for nonlinear derivative
214! (not needed for completely linear models)
215!
216! Indices
217! x(1)
218! 1: 1
219!
220 colsta(1) = 1
221 colsta(2) = 2
222 rowno(1) = 1
223!
224! Nonlinearity Structure: L = 0 are linear and NL = 1 are nonlinear
225! x(1)
226! 1: NL
227!
228 nlflag(1) = 1
229!
230! Value (Linear only)
231! x(1)
232! 1: NL
233!
234 nleq_readmatrix = 0 ! Return value means OK
235
236end Function nleq_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 nleq_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
246 n, nz, thread, usrmem )
247#if defined(itl)
248!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Nleq_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!
268! Row 1: e1
269!
270 if ( rowno .eq. 1 ) then
271!
272! Mode = 1 or 3. G = log(x1)
273!
274 if ( mode .eq. 1 .or. mode .eq. 3 ) then
275 g = x(1)*x(1)
276 endif
277!
278! Mode = 2 or 3: Derivative values:
279!
280 if ( mode .eq. 2 .or. mode .eq. 3 ) then
281 jac(1) = 2.0d0*x(1)
282 endif
283 nleq_fdeval = 0
284 else
285!
286! There are no other rows:
287!
288 nleq_fdeval = 1
289 endif
290
291end Function nleq_fdeval
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_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, parameter maxcase
Definition nleq03.f90:30
integer, dimension(maxcase), parameter casemstat
Definition nleq03.f90:35
real *8, dimension(maxcase), parameter caserhs
Definition nleq03.f90:31
integer, dimension(maxcase), parameter casetype
Definition nleq03.f90:33
real *8, dimension(maxcase), parameter caseobj
Definition nleq03.f90:37
integer casenum
Definition nleq03.f90:39
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
integer function nleq_fdeval(x, g, jac, rowno, jcnm, mode, ignerr, errcnt, n, nz, thread, usrmem)
Compute nonlinear terms and non-constant Jacobian elements.
Definition nleq01.f90:261
integer function nleq_readmatrix(lower, curr, upper, vsta, type, rhs, esta, colsta, rowno, value, nlflag, n, m, nz, usrmem)
Define information about the model.
Definition nleq01.f90:173
program nleq03
Main program. A simple setup and call of CONOPT.
Definition nleq03.f90:43