CONOPT
Loading...
Searching...
No Matches
vpost01.f90
Go to the documentation of this file.
1!> @file vpost01.f90
2!! @ingroup FORT1THREAD_EXAMPLES
3!!
4!!
5!! This is a CONOPT implementation of the GAMS model:
6!!
7!! @verbatim
8!! set i / i1*i5 /
9!! b / b1*b2 /
10!! parameter a(i,b)
11!! positive variable x(i), y(i), z(i), v(b), obj;
12!! equation e1(i), e2(i), e3(i), objdef
13!! e1(i) .. x(i) + sum(b, a(i,b)*v(b)) =E= 1*ord(i);
14!! e2(i) .. x(i) + y(i) - sum(b, a(i,b)*v(b)) =E= 2*ord(i);
15!! e3(i) .. x(i) + y(i) + z(i) + sum(b, a(i,b)*v(b)) =E= 3*ord(i);
16!! objdef .. obj =E= sum(b, ord(b)*v(b) );
17!! x.up(i) = 10; y.up(i) = 20; z.up(i) = 30; v.up(b) = 40;
18!! @endverbatim
19!!
20!! For fixed values of the variables v the model is recursive. Used to
21!! test various initialization procedures.
22!!
23!!
24!! For more information about the individual callbacks, please have a look at the source code.
25
27 integer, Parameter :: ni = 5
28 integer, Parameter :: nb = 2
29 real*8, Dimension(Ni,Nb) :: a
30End Module vpost01data
31
32!> Main program. A simple setup and call of CONOPT
33!!
34Program vpost01
35
36 Use proginfo
37 Use coidef
38 Use vpost01data
39 implicit None
40!
41! Declare the user callback routines as Integer, External:
42!
43 Integer, External :: vp_readmatrix ! Mandatory Matrix definition routine defined below
44 Integer, External :: vp_fdeval ! Function and Derivative evaluation routine
45 ! needed a nonlinear model.
46 Integer, External :: std_status ! Standard callback for displaying solution status
47 Integer, External :: std_solution ! Standard callback for displaying solution values
48 Integer, External :: std_message ! Standard callback for managing messages
49 Integer, External :: std_errmsg ! Standard callback for managing error messages
50#if defined(itl)
51!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: VP_ReadMatrix
52!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: VP_FDEval
53!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Status
54!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Solution
55!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Message
56!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_ErrMsg
57#endif
58!
59! Control vector
60!
61 INTEGER :: numcallback
62 INTEGER, Dimension(:), Pointer :: cntvect
63 INTEGER :: coi_error
64!
65! Misc local variables
66!
67 Integer :: i, k
68!
69! Initialize Vpost01Data for the model
70!
71 do i = 1, ni
72 do k = 1, nb
73 a(i,k) = 0.1d0*i/ni*k*(-1)**(i+k)
74 enddo
75 enddo
76!
77! Create and initialize a Control Vector
78!
79 call startup
80
81 numcallback = coidef_size()
82 Allocate( cntvect(numcallback) )
83 coi_error = coidef_inifort( cntvect )
84!
85! Tell CONOPT about the size of the model by populating the Control Vector:
86!
87 coi_error = max( coi_error, coidef_numvar( cntvect, 3*ni+nb ) ) ! # variables
88 coi_error = max( coi_error, coidef_numcon( cntvect, 3*ni+1 ) ) ! # constraints
89 coi_error = max( coi_error, coidef_numnz( cntvect, ni*(6+3*nb)+nb ) ) ! # nonzeros in the Jacobian
90 coi_error = max( coi_error, coidef_numnlnz( cntvect, 0 ) ) ! # of which are nonlinear
91 coi_error = max( coi_error, coidef_optdir( cntvect, 1 ) ) ! Maximize
92 coi_error = max( coi_error, coidef_objcon( cntvect, 3*ni+1 ) ) ! Objective is constraint #
93 coi_error = max( coi_error, coidef_optfile( cntvect, 'vpost01.opt' ) )
94!
95! Tell CONOPT about the callback routines:
96!
97 coi_error = max( coi_error, coidef_readmatrix( cntvect, vp_readmatrix ) )
98 coi_error = max( coi_error, coidef_fdeval( cntvect, vp_fdeval ) )
99 coi_error = max( coi_error, coidef_status( cntvect, std_status ) )
100 coi_error = max( coi_error, coidef_solution( cntvect, std_solution ) )
101 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
102 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
103
104#if defined(LICENSE_INT_1) && defined(LICENSE_INT_2) && defined(LICENSE_INT_3) && defined(LICENSE_TEXT)
105 coi_error = max( coi_error, coidef_license( cntvect, license_int_1, license_int_2, license_int_3, license_text) )
106#endif
107
108 If ( coi_error .ne. 0 ) THEN
109 write(*,*)
110 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
111 write(*,*)
112 call flog( "Skipping Solve due to setup errors", 1 )
113 ENDIF
114!
115! Save the solution so we can check the duals:
116!
117 do_allocate = .true.
118!
119! Start CONOPT:
120!
121 coi_error = coi_solve( cntvect )
122
123 write(*,*)
124 write(*,*) 'End of Vpost01 example. Return code=',coi_error
125
126 If ( coi_error /= 0 ) then
127 call flog( "Errors encountered during solution", 1 )
128 elseif ( stacalls == 0 .or. solcalls == 0 ) then
129 call flog( "Status or Solution routine was not called", 1 )
130 elseif ( sstat /= 1 .or. mstat /= 1 ) then
131 call flog( "Solver and Model Status was not as expected (1,1)", 1 )
132 Else
133 do i = 1, ni
134 if ( abs(uprim(i)-i) > 1.e-7 .or. abs(uprim(ni+i)-2*i) > 1.e-7 .or. &
135 abs(uprim(ni+ni+i)-3*i) > 1.e-7 ) Then
136 call flog( "Incorrect activity level for an equation.", 1 )
137 endif
138 enddo
139 Call checkdual( 'Vpost01', maximize )
140 endif
141
142 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
143
144 call flog( "Successful Solve", 0 )
145
146End Program vpost01
147!
148! ============================================================================
149! Define information about the model:
150!
151
152!> Define information about the model
153!!
154!! @include{doc} readMatrix_params.dox
155Integer Function vp_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
156 colsta, rowno, value, nlflag, n, m, nz, &
157 usrmem )
158#if defined(itl)
159!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: VP_ReadMatrix
160#endif
161 use vpost01data
162 implicit none
163 integer, intent (in) :: n ! number of variables
164 integer, intent (in) :: m ! number of constraints
165 integer, intent (in) :: nz ! number of nonzeros
166 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
167 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
168 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
169 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
170 ! (not defined here)
171 integer, intent (out), dimension(m) :: type ! vector of equation types
172 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
173 ! (not defined here)
174 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
175 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
176 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
177 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
178 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
179 real*8 usrmem(*) ! optional user memory
180!
181 integer i, j, k
182!
183! Information about Variables:
184! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
185! Default: the status information in Vsta is not used.
186!
187! Lower bound = 0 on all variables
188!
189 do i = 1, n
190 lower(i) = 0.0d0
191 enddo
192 do i = 1, ni
193 upper(i) = 10.0d0
194 upper(ni+i) = 20.0d0
195 upper(ni+ni+i) = 30.0d0
196 enddo
197 do j = 1, nb
198 upper(3*ni+j) = 40.d0
199 enddo
200!
201! Information about Constraints:
202! Default: Rhs = 0
203! Default: the status information in Esta and the function
204! value in FV are not used.
205! Default: Type: There is no default.
206! 0 = Equality,
207! 1 = Greater than or equal,
208! 2 = Less than or equal,
209! 3 = Non binding.
210!
211 do i = 1, ni
212 rhs(i) = i
213 rhs(ni+i) = 2*i
214 rhs(ni+ni+i) = 3*i
215 enddo
216 do i = 1, 3*ni
217 type(i) = 0
218 enddo
219!
220! Constraint 3*ni+1 (Objective)
221! Rhs = 0 and type Non binding
222!
223 type(3*ni+1) = 3
224! positive variable x(i), y(i), z(i), v(b), obj;
225! equation e1(i), e2(i), e3(i), objdef
226! e1(i) .. x(i) + sum(b, a(i,b)*v(b)) =E= 1*ord(i);
227! e2(i) .. x(i) + y(i) - sum(b, a(i,b)*v(b)) =E= 2*ord(i);
228! e3(i) .. x(i) + y(i) + z(i) + sum(b, a(i,b)*v(b)) =E= 3*ord(i);
229! objdef .. obj =E= sum(b, ord(b)*v(b) );
230!
231! Information about the Jacobian. We use the standard method with
232! Rowno, Value, Nlflag and Colsta and we do not use Colno.
233!
234! Colsta = Start of column indices (No Defaults):
235! Rowno = Row indices
236! Value = Value of derivative (by default only linear
237! derivatives are used)
238! Nlflag = 0 for linear and 1 for nonlinear derivative
239! (not needed for completely linear models)
240!
241 k = 1
242 do i = 1, ni ! x variables
243 colsta(i) = k
244 rowno(k) = i
245 value(k) = 1.d0
246 k = k + 1
247 rowno(k) = ni+i
248 value(k) = 1.d0
249 k = k + 1
250 rowno(k) = ni+ni+i
251 value(k) = 1.d0
252 k = k + 1
253 enddo
254 do i = 1, ni ! y variables
255 colsta(ni+i) = k
256 rowno(k) = ni+i
257 value(k) = 1.d0
258 k = k + 1
259 rowno(k) = ni+ni+i
260 value(k) = 1.d0
261 k = k + 1
262 enddo
263 do i = 1, ni ! z variables
264 colsta(ni+ni+i) = k
265 rowno(k) = ni+ni+i
266 value(k) = 1.d0
267 k = k + 1
268 enddo
269 do j = 1, nb
270 colsta(3*ni+j) = k
271 do i = 1, ni
272 rowno(k) = i
273 value(k) = a(i,j)
274 k = k + 1
275 enddo
276 do i = 1, ni
277 rowno(k) = ni+i
278 value(k) = -a(i,j)
279 k = k + 1
280 enddo
281 do i = 1, ni
282 rowno(k) = ni+ni+i
283 value(k) = a(i,j)
284 k = k + 1
285 enddo
286 rowno(k) = 3*ni+1
287 value(k) = j
288 k = k + 1
289 enddo
290 colsta(3*ni+nb+1) = k
291
292 vp_readmatrix = 0 ! Return value means OK
293
294end Function vp_readmatrix
295!
296!==========================================================================
297! Compute nonlinear terms and non-constant Jacobian elements
298!
299
300!> Compute nonlinear terms and non-constant Jacobian elements
301!!
302!! @include{doc} fdeval_params.dox
303Integer Function vp_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
304 n, nz, thread, usrmem )
305#if defined(itl)
306!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: VP_FDEval
307#endif
308 implicit none
309 integer, intent (in) :: n ! number of variables
310 integer, intent (in) :: rowno ! number of the row to be evaluated
311 integer, intent (in) :: nz ! number of nonzeros in this row
312 real*8, intent (in), dimension(n) :: x ! vector of current solution values
313 real*8, intent (in out) :: g ! constraint value
314 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
315 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
316 ! in this row. Ffor information only.
317 integer, intent (in) :: mode ! evaluation mode: 1 = function value
318 ! 2 = derivatives, 3 = both
319 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
320 ! as errcnt is incremented
321 integer, intent (in out) :: errcnt ! error counter to be incremented in case
322 ! of function evaluation errors.
323 integer, intent (in) :: thread
324 real*8 usrmem(*) ! optional user memory
325
326 vp_fdeval = 1 ! this routine should never be called for a linear model
327
328end Function vp_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_errmsg(rowno, colno, posno, msglen, usrmem, msg)
Definition comdecl.f90:248
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_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_objcon(cntvect, objcon)
defines the Objective Constraint.
Definition coistart.f90:629
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_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
#define ni
Definition mp_trans.c:45
integer solcalls
Definition comdecl.f90:9
integer sstat
Definition comdecl.f90:12
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
real *8, dimension(:), pointer uprim
Definition comdecl.f90:18
integer mstat
Definition comdecl.f90:11
subroutine startup
Definition comdecl.f90:35
integer, parameter nb
Definition vpost01.f90:28
real *8, dimension(ni, nb) a
Definition vpost01.f90:29
integer function vp_readmatrix(lower, curr, upper, vsta, type, rhs, esta, colsta, rowno, value, nlflag, n, m, nz, usrmem)
Define information about the model.
Definition vpost01.f90:158
integer function vp_fdeval(x, g, jac, rowno, jcnm, mode, ignerr, errcnt, n, nz, thread, usrmem)
Compute nonlinear terms and non-constant Jacobian elements.
Definition vpost01.f90:305
program vpost01
Main program. A simple setup and call of CONOPT.
Definition vpost01.f90:34