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