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