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