CONOPT
Loading...
Searching...
No Matches
square3.f90
Go to the documentation of this file.
1!> @file square3.f90
2!! @ingroup FORT1THREAD_EXAMPLES
3!!
4!!
5!! A square model where we pretend that the second and third constraints are completely
6!! nonlinear.
7!!
8!! \f{eqnarray*}{
9!! &x1 + x2 = 10 \\
10!! &x1 - x2 = 0\\
11!! &x1 + x2 \leq 9
12!! \f}
13!!
14!! The model is almost like square2 but the initial values are the
15!! values that satisfies the first two constriants but violates the
16!! last.
17!!
18!!
19!! For more information about the individual callbacks, please have a look at the source code.
20
21#if defined(_WIN32) && !defined(_WIN64)
22#define dec_directives_win32
23#endif
24
25!> Main program. A simple setup and call of CONOPT
26!!
27Program square
28
30 Use conopt
31 implicit None
32!
33! Declare the user callback routines as Integer, External:
34!
35 Integer, External :: sq_readmatrix ! Mandatory Matrix definition routine defined below
36 Integer, External :: sq_fdeval ! Function and Derivative evaluation routine
37 ! needed a nonlinear model.
38 Integer, External :: std_status ! Standard callback for displaying solution status
39 Integer, External :: std_solution ! Standard callback for displaying solution values
40 Integer, External :: std_message ! Standard callback for managing messages
41 Integer, External :: std_errmsg ! Standard callback for managing error messages
42#ifdef dec_directives_win32
43!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Sq_ReadMatrix
44!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Sq_FDEval
45!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Status
46!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Solution
47!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Message
48!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_ErrMsg
49#endif
50!
51! Control vector
52!
53 INTEGER, Dimension(:), Pointer :: cntvect
54 INTEGER :: coi_error
55
56 call startup
57!
58! Create and initialize a Control Vector
59!
60 coi_error = coi_create( cntvect )
61!
62! Tell CONOPT about the size of the model by populating the Control Vector:
63!
64 coi_error = max( coi_error, coidef_numvar( cntvect, 2 ) ) ! 2 variables
65 coi_error = max( coi_error, coidef_numcon( cntvect, 3 ) ) ! 3 constraints
66 coi_error = max( coi_error, coidef_numnz( cntvect, 6 ) ) ! 6 nonzeros in the Jacobian
67 coi_error = max( coi_error, coidef_numnlnz( cntvect, 4 ) ) ! 4 of which are nonlinear
68 coi_error = max( coi_error, coidef_square( cntvect, 1 ) ) ! 1 means Square system
69 coi_error = max( coi_error, coidef_optfile( cntvect, 'square3.opt' ) )
70!
71! Tell CONOPT about the callback routines:
72!
73 coi_error = max( coi_error, coidef_readmatrix( cntvect, sq_readmatrix ) )
74 coi_error = max( coi_error, coidef_fdeval( cntvect, sq_fdeval ) )
75 coi_error = max( coi_error, coidef_status( cntvect, std_status ) )
76 coi_error = max( coi_error, coidef_solution( cntvect, std_solution ) )
77 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
78 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
79
80#if defined(CONOPT_LICENSE_INT_1) && defined(CONOPT_LICENSE_INT_2) && defined(CONOPT_LICENSE_INT_3) && defined(CONOPT_LICENSE_TEXT)
81 coi_error = max( coi_error, coidef_license( cntvect, conopt_license_int_1, conopt_license_int_2, conopt_license_int_3, conopt_license_text) )
82#endif
83
84 If ( coi_error .ne. 0 ) THEN
85 write(*,*)
86 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
87 write(*,*)
88 call flog( "Skipping Solve due to setup errors", 1 )
89 ENDIF
90!
91! Start CONOPT:
92!
93 coi_error = coi_solve( cntvect )
94
95 write(*,*)
96 write(*,*) 'End of Square3 example. Return code=',coi_error
97
98 If ( coi_error /= 0 ) then
99 call flog( "Errors encountered during solution", 1 )
100 elseif ( stacalls == 0 .or. solcalls == 0 ) then
101 call flog( "Status or Solution routine was not called", 1 )
102 elseif ( sstat /= 1 .or. mstat < 4 .or. mstat > 5 ) then
103 call flog( "Solver or Model status not as expected (1,4) or (1,5)", 1 )
104 endif
105
106 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
107
108 call flog( "Successful Solve", 0 )
109
110End Program square
111!
112! ============================================================================
113! Define information about the model:
114!
115
116!> Define information about the model
117!!
118!! @include{doc} readMatrix_params.dox
119Integer Function sq_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
120 colsta, rowno, value, nlflag, n, m, nz, &
121 usrmem )
122#ifdef dec_directives_win32
123!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Sq_ReadMatrix
124#endif
125 implicit none
126 integer, intent (in) :: n ! number of variables
127 integer, intent (in) :: m ! number of constraints
128 integer, intent (in) :: nz ! number of nonzeros
129 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
130 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
131 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
132 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
133 ! (not defined here)
134 integer, intent (out), dimension(m) :: type ! vector of equation types
135 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
136 ! (not defined here)
137 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
138 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
139 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
140 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
141 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
142 real*8 usrmem(*) ! optional user memory
143!
144! Information about Variables:
145! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
146! Default: the status information in Vsta is not used.
147!
148! Initial x1 = x2 = 5:
149!
150 curr(1) = 5.0d0
151 curr(2) = 5.0d0
152!
153! Information about Constraints:
154! Default: Rhs = 0
155! Default: the status information in Esta and the function
156! value in FV are not used.
157! Default: Type: There is no default.
158! 0 = Equality,
159! 1 = Greater than or equal,
160! 2 = Less than or equal,
161! 3 = Non binding.
162!
163! Constraint 1
164! Rhs = 10 and type Equal
165!
166 rhs(1) = 10.d0
167 type(1) = 0
168!
169! Constraint 2
170! Rhs = 0 and type Equality
171!
172 type(2) = 0
173!
174! Constraint 3
175! Rhs = 9 and type Less than
176!
177 rhs(3) = 9.d0
178 type(3) = 2
179!
180! Information about the Jacobian. CONOPT expects a columnwise
181! representation in Rowno, Value, Nlflag and Colsta.
182!
183! Colsta = Start of column indices (No Defaults):
184! Rowno = Row indices
185! Value = Value of derivative (by default only linear
186! derivatives are used)
187! Nlflag = 0 for linear and 1 for nonlinear derivative
188! (not needed for completely linear models)
189!
190! Indices
191! x(1) x(2)
192! 1: 1 4
193! 2: 2 5
194! 3: 2 6
195!
196 colsta(1) = 1
197 colsta(2) = 4
198 colsta(3) = 7
199 rowno(1) = 1
200 rowno(2) = 2
201 rowno(3) = 3
202 rowno(4) = 1
203 rowno(5) = 2
204 rowno(6) = 3
205!
206! Nonlinearity Structure: L = 0 are linear and NL = 1 are nonlinear
207! x(1) x(2)
208! 1: L L
209! 2: NL NL
210! 3: NL NL
211!
212 nlflag(1) = 0
213 nlflag(2) = 1
214 nlflag(3) = 1
215 nlflag(4) = 0
216 nlflag(5) = 1
217 nlflag(6) = 1
218!
219! Value (Linear only)
220! x(1) x(2) x(3) x(4)
221! 1: 1 1
222! 2: NL NL
223! 3: NL NL
224!
225 value(1) = 1.d0
226 value(4) = 1.d0
228 sq_readmatrix = 0 ! Return value means OK
229
230end Function sq_readmatrix
231!
232!==========================================================================
233! Compute nonlinear terms and non-constant Jacobian elements
234!
235
236!> Compute nonlinear terms and non-constant Jacobian elements
237!!
238!! @include{doc} fdeval_params.dox
239Integer Function sq_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
240 n, nz, thread, usrmem )
241#ifdef dec_directives_win32
242!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Sq_FDEval
243#endif
244 implicit none
245 integer, intent (in) :: n ! number of variables
246 integer, intent (in) :: rowno ! number of the row to be evaluated
247 integer, intent (in) :: nz ! number of nonzeros in this row
248 real*8, intent (in), dimension(n) :: x ! vector of current solution values
249 real*8, intent (in out) :: g ! constraint value
250 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
251 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
252 ! in this row. Ffor information only.
253 integer, intent (in) :: mode ! evaluation mode: 1 = function value
254 ! 2 = derivatives, 3 = both
255 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
256 ! as errcnt is incremented
257 integer, intent (in out) :: errcnt ! error counter to be incremented in case
258 ! of function evaluation errors.
259 integer, intent (in) :: thread
260 real*8 usrmem(*) ! optional user memory
261!
262! Row 1: Is declared as linear and should not be called.
263!
264 if ( rowno .eq. 1 ) then
265 sq_fdeval = 1
266 return
267!
268! Row 2: x1 + x2 assumed to be nonlinear
269!
270 elseif ( rowno .eq. 2 ) then
271!
272! Mode = 1 or 3: Function value
273!
274 if ( mode .eq. 1 .or. mode .eq. 3 ) then
275 g = x(1) - x(2)
276 endif
277!
278! Mode = 2 or 3: Derivatives
279!
280 if ( mode .eq. 2 .or. mode .eq. 3 ) then
281 jac(1) = 1.d0
282 jac(2) = -1.d0
283 endif
284 elseif ( rowno .eq. 3 ) then
285!
286! Mode = 1 or 3: Function value
287!
288 if ( mode .eq. 1 .or. mode .eq. 3 ) then
289 g = x(1) + x(2)
290 endif
291!
292! Mode = 2 or 3: Derivatives
293!
294 if ( mode .eq. 2 .or. mode .eq. 3 ) then
295 jac(1) = 1.d0
296 jac(2) = 1.d0
297 endif
298 endif
299 sq_fdeval = 0
300
301end Function sq_fdeval
integer function std_solution(xval, xmar, xbas, xsta, yval, ymar, ybas, ysta, n, m, usrmem)
Definition comdecl.f90:132
integer function std_status(modsta, solsta, iter, objval, usrmem)
Definition comdecl.f90:88
integer function std_message(smsg, dmsg, nmsg, llen, usrmem, msgv)
Definition comdecl.f90:205
integer function std_errmsg(rowno, colno, posno, msglen, usrmem, msg)
Definition comdecl.f90:248
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_license(cntvect, licint1, licint2, licint3, licstring)
define the License Information.
Definition conopt.f90:293
integer(c_int) function coidef_square(cntvect, square)
square models.
Definition conopt.f90:447
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_numnz(cntvect, numnz)
defines the number of nonzero elements in the Jacobian.
Definition conopt.f90:144
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
integer solcalls
Definition comdecl.f90:15
integer sstat
Definition comdecl.f90:18
integer stacalls
Definition comdecl.f90:14
subroutine flog(msg, code)
Definition comdecl.f90:62
integer mstat
Definition comdecl.f90:17
subroutine startup
Definition comdecl.f90:41
integer function sq_fdeval(x, g, jac, rowno, jcnm, mode, ignerr, errcnt, n, nz, thread, usrmem)
Compute nonlinear terms and non-constant Jacobian elements.
Definition square.f90:237
integer function sq_readmatrix(lower, curr, upper, vsta, type, rhs, esta, colsta, rowno, value, nlflag, n, m, nz, usrmem)
Define information about the model.
Definition square.f90:139
program square
Main program. A simple setup and call of CONOPT.
Definition square.f90:23