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