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