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