CONOPT
Loading...
Searching...
No Matches
rosex.f90
Go to the documentation of this file.
1!> @file rosex.f90
2!! @ingroup FORT1THREAD_EXAMPLES
3!!
4!!
5!! Extended Rosenbrock function.
6!!
7!!
8!! For more information about the individual callbacks, please have a look at the source code.
9
10!> Main program. A simple setup and call of CONOPT
11!!
12Program rosex
13
14 Use proginfo
15 Use coidef
16 IMPLICIT NONE
17!
18! Declare the user callback routines as Integer, External:
19!
20 Integer, External :: ros_readmatrix ! Mandatory Matrix definition routine defined below
21 Integer, External :: ros_fdeval ! Function and Derivative evaluation routine
22 ! needed a nonlinear model.
23 Integer, External :: std_status ! Standard callback for displaying solution status
24 Integer, External :: std_solution ! Standard callback for displaying solution values
25 Integer, External :: std_message ! Standard callback for managing messages
26 Integer, External :: std_errmsg ! Standard callback for managing error messages
27#if defined(itl)
28!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Ros_ReadMatrix
29!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Ros_FDEval
30!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Status
31!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Solution
32!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Message
33!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_ErrMsg
34#endif
35!
36! Control vector
37!
38 INTEGER :: numcallback
39 INTEGER, Dimension(:), Pointer :: cntvect
40 INTEGER :: coi_error
41!
42! The model is an unconstrained problem in which the objective is the
43! sum of N identical copies of the Rosenbrock function placed after
44! each other:
45!
46! min sum(i, (1-x(2*i-1))**2+100*(x(2*i)-x(2*i-1)**2)**2)
47!
48! The number of Rosenborck functions
49!
50 Integer :: nr
51 Integer :: miter_ini
52 real*8 :: memused, memini
53!
54! Create and initialize a Control Vector
55!
56 call startup
57
58 numcallback = coidef_size()
59 Allocate( cntvect(numcallback) )
60 coi_error = coidef_inifort( cntvect )
61!
62! Tell CONOPT about the size of the model by populating the Control Vector:
63!
64 nr = 100
65 coi_error = max( coi_error, coidef_numvar( cntvect, 2*nr ) ) ! # variables
66 coi_error = max( coi_error, coidef_numcon( cntvect, 1 ) ) ! # constraints
67 coi_error = max( coi_error, coidef_numnz( cntvect, 2*nr ) ) ! # nonzeros in the Jacobian
68 coi_error = max( coi_error, coidef_numnlnz( cntvect, 2*nr ) ) ! # of which are nonlinear
69 coi_error = max( coi_error, coidef_optdir( cntvect, -1 ) ) ! Minimize
70 coi_error = max( coi_error, coidef_objcon( cntvect, 1 ) ) ! Objective is constraint 1
71 coi_error = max( coi_error, coidef_optfile( cntvect, 'rosex.opt' ) )
72!
73! Tell CONOPT about the callback routines:
74!
75 coi_error = max( coi_error, coidef_readmatrix( cntvect, ros_readmatrix ) )
76 coi_error = max( coi_error, coidef_fdeval( cntvect, ros_fdeval ) )
77 coi_error = max( coi_error, coidef_status( cntvect, std_status ) )
78 coi_error = max( coi_error, coidef_solution( cntvect, std_solution ) )
79 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
80 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
81
82#if defined(LICENSE_INT_1) && defined(LICENSE_INT_2) && defined(LICENSE_INT_3) && defined(LICENSE_TEXT)
83 coi_error = max( coi_error, coidef_license( cntvect, license_int_1, license_int_2, license_int_3, license_text) )
84#endif
85
86 If ( coi_error .ne. 0 ) THEN
87 write(*,*)
88 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
89 write(*,*)
90 call flog( "Skipping Solve due to setup errors", 1 )
91 ENDIF
92!
93! Start CONOPT:
94!
95 coi_error = coi_solve( cntvect )
96 If ( coi_error /= 0 ) then
97 call flog( "Solve 1: Errors encountered during solution", 1 )
98 elseif ( stacalls == 0 .or. solcalls == 0 ) then
99 call flog( "Solve 1: Status or Solution routine was not called", 1 )
100 elseif ( sstat /= 1 .or. mstat /= 2 ) then
101 call flog( "Solve 1: Solver and Model Status was not as expected (1,2)", 1 )
102 elseif ( abs( obj-0.0d0 ) > 0.000001d0 ) then
103 call flog( "Solve 1: Incorrect objective returned", 1 )
104 endif
105
106!
107! Ask for the amount of memory used and the number of iterations
108!
109 memini = coiget_maxheapused( cntvect )
110 miter_ini = miter
111 write(*,*) 'Solve 1 used',memini,' MBytes of memory and',miter_ini,' iterations.'
112 write(10,*) 'Solve 1 used',memini,' MBytes of memory and',miter_ini,' iterations.'
113!
114! Solve a model with a little less memory. We expect to run out of memory or use more iterations
115! We may run with less memory by turning some 2nd order info off, but the solve should be slower. (Not true!!)
116!
117 coi_error = max( coi_error, coidef_maxheap( cntvect, memini-8.d2/1024.d0**2 ) ) ! take 800 reals less
118 coi_error = coi_solve( cntvect )
119 memused = coiget_maxheapused( cntvect )
120 write(*,*) 'Solve 2 used',memused,' MBytes of memory and',miter,' iterations. Return code=',coi_error
121 write(10,*) 'Solve 2 used',memused,' MBytes of memory and',miter,' iterations. Return code=',coi_error
122! if ( Miter <= Miter_Ini .and. (COI_Error < 113 .or. COI_Error > 114) ) then
123! call flog( "Solve 2: Error return was not slower or 113 or 114 (insufficient memory)", 1 )
124! Endif
125!
126! Solve a model with NR increased by one using the same amount of memory.
127! We expect to run out of memory or use more iterations
128!
129 coi_error = 0 ! Reset before next experiment
130 coi_error = max( coi_error, coidef_maxheap( cntvect, memini ) ) ! take the memory from last call
131 nr = nr + 1 ! Increase the number of functions and redefine the quantities that change:
132 coi_error = max( coi_error, coidef_numvar( cntvect, 2*nr ) ) ! # variables
133 coi_error = max( coi_error, coidef_numnz( cntvect, 2*nr ) ) ! # nonzeros in the Jacobian
134 coi_error = max( coi_error, coidef_numnlnz( cntvect, 2*nr ) ) ! # of which are nonlinear
135 coi_error = coi_solve( cntvect )
136 memused = coiget_maxheapused( cntvect )
137 write(*,*) 'Solve 3 used',memused,' MBytes of memory and',miter,' iterations. Return code=',coi_error
138 write(10,*) 'Solve 3 used',memused,' MBytes of memory and',miter,' iterations. Return code=',coi_error
139! if ( Miter <= Miter_Ini .and. (COI_Error < 113 .or. COI_Error > 114) ) then
140! call flog( "Solve 3: Error return was not slower or 113 or 114 (insufficient memory)", 1 )
141! Endif
142!
143! Solve the previous model with a very large amount of memory.
144! We expect to run correctly.
145!
146 coi_error = 0 ! Reset before next experiment
147 coi_error = max( coi_error, coidef_maxheap( cntvect, 1.0d20 ) ) ! Allow a lot of memory
148 coi_error = coi_solve( cntvect )
149 memused = coiget_maxheapused( cntvect )
150 write(*,*) 'Solve 4 used',memused,' MBytes of memory. Return code=',coi_error
151 write(10,*) 'Solve 4 used',memused,' MBytes of memory. Return code=',coi_error
152 If ( coi_error /= 0 ) then
153 call flog( "Solve 4: Errors encountered during solution", 1 )
154 elseif ( stacalls == 0 .or. solcalls == 0 ) then
155 call flog( "Solve 4: Status or Solution routine was not called", 1 )
156 elseif ( sstat /= 1 .or. mstat /= 2 ) then
157 call flog( "Solve 4: Solver and Model Status was not as expected (1,2)", 1 )
158 elseif ( abs( obj-0.0d0 ) > 0.000001d0 ) then
159 call flog( "Solve 4: Incorrect objective returned", 1 )
160 endif
161 write(*,*)
162 write(*,*) 'End of Extended Rosenbrock Function example. Return code=',coi_error
163
164 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
165
166 call flog( "Successful Solve", 0 )
167
168End Program rosex
169!
170! ============================================================================
171! Define information about the model:
172!
173
174!> Define information about the model
175!!
176!! @include{doc} readMatrix_params.dox
177Integer Function ros_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
178 colsta, rowno, value, nlflag, n, m, nz, &
179 usrmem )
180#if defined(itl)
181!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Ros_ReadMatrix
182#endif
183 IMPLICIT NONE
184 integer, intent (in) :: n ! number of variables
185 integer, intent (in) :: m ! number of constraints
186 integer, intent (in) :: nz ! number of nonzeros
187 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
188 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
189 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
190 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
191 ! (not defined here)
192 integer, intent (out), dimension(m) :: type ! vector of equation types
193 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
194 ! (not defined here)
195 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
196 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
197 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
198 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
199 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
200 real*8 usrmem(*) ! optional user memory
201
202 Integer :: nr
203 Integer :: i
204
205 nr = n / 2
206!
207! Information about Variables:
208! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
209! Default: the status information in Vsta is not used.
210!
211 DO i = 1, nr
212 curr(2*i-1) = -1.d0
213 curr(2*i ) = +1.d0
214 enddo
215!
216! Information about Constraints:
217! Default: Rhs = 0
218! Default: the status information in Esta and the function
219! value in FV are not used.
220! Default: Type: There is no default.
221! 0 = Equality,
222! 1 = Greater than or equal,
223! 2 = Less than or equal,
224! 3 = Non binding.
225!
226! Constraint 1 (Objective)
227! Rhs = 0.0 and type Non binding
228!
229 type(1) = 3
230!
231! Information about the Jacobian. We have to define Rowno, Value,
232! Nlflag and Colsta.
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! Indices
242! x(1) x(2) x(3) x(4)
243! 1: 1 2 3 4 etc
244!
245! Nonlinearity Structure: L = 0 are linear and NL = 1 are nonlinear
246! x(1) x(2) x(3) x(4)
247! 1: NL NL NL NL etc
248!
249! Value (Linear only)
250!
251 DO i = 1, nr*2+1
252 colsta(i) = i
253 enddo
254 DO i = 1, nr*2
255 rowno(i) = 1
256 nlflag(i) = 1
257 enddo
258
259 ros_readmatrix = 0 ! Return value means OK
260
261end Function ros_readmatrix
262!
263!==========================================================================
264! Compute nonlinear terms and non-constant Jacobian elements
265!
266
267!> Compute nonlinear terms and non-constant Jacobian elements
268!!
269!! @include{doc} fdeval_params.dox
270Integer Function ros_fdeval( x, g, jac, rowno, jcnm, mode, ignerr, errcnt, &
271 n, nz, thread, usrmem )
272#if defined(itl)
273!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Ros_FDEval
274#endif
275 IMPLICIT NONE
276 integer, intent (in) :: n ! number of variables
277 integer, intent (in) :: rowno ! number of the row to be evaluated
278 integer, intent (in) :: nz ! number of nonzeros in this row
279 real*8, intent (in), dimension(n) :: x ! vector of current solution values
280 real*8, intent (in out) :: g ! constraint value
281 real*8, intent (in out), dimension(n) :: jac ! vector of derivatives for current constraint
282 integer, intent (in), dimension(nz) :: jcnm ! list of variables that appear nonlinearly
283 ! in this row. Ffor information only.
284 integer, intent (in) :: mode ! evaluation mode: 1 = function value
285 ! 2 = derivatives, 3 = both
286 integer, intent (in) :: ignerr ! if 1 then errors can be ignored as long
287 ! as errcnt is incremented
288 integer, intent (in out) :: errcnt ! error counter to be incremented in case
289 ! of function evaluation errors.
290 integer, intent (in) :: thread
291 real*8 usrmem(*) ! optional user memory
292
293 Integer :: nr
294 Integer :: i
295
296 nr = n / 2
297!
298! Row 1: the objective function is nonlinear
299!
300 if ( rowno .eq. 1 ) then
301!
302! Mode = 1 or 3. Function value:
303!
304 if ( mode .eq. 1 .or. mode .eq. 3 ) then
305 g = 0.d0
306 do i = 1, nr
307 g = g + (x(2*i-1)-1.d0)**2 + 1.d2*(x(2*i)-x(2*i-1)**2)**2
308 enddo
309 endif
310!
311! Mode = 2 or 3: Derivative values:
312!
313 if ( mode .eq. 2 .or. mode .eq. 3 ) then
314 do i = 1, nr
315 jac(2*i-1) = 2.d0*(x(2*i-1)-1.d0) - 4.d2*(x(2*i)-x(2*i-1)**2)*x(2*i-1)
316 jac(2*i ) = 2.d2*(x(2*i)-x(2*i-1)**2)
317 enddo
318 endif
319 endif
320 ros_fdeval = 0
321
322end Function ros_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
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_maxheap(cntvect, maxheap)
define Limit on Heap Memory. ""
Definition coistart.f90:988
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
real *8 function coiget_maxheapused(cntvect)
After a model has been solved this method will return the amount of heap memory used.
Definition coistart.f90:126
integer function coi_solve(cntvect)
method for starting the solving process of CONOPT.
Definition coistart.f90:14
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
integer miter
Definition comdecl.f90:13
integer mstat
Definition comdecl.f90:11
subroutine startup
Definition comdecl.f90:35
integer function ros_readmatrix(lower, curr, upper, vsta, type, rhs, esta, colsta, rowno, value, nlflag, n, m, nz, usrmem)
Define information about the model.
Definition roseq.f90:120
integer function ros_fdeval(x, g, jac, rowno, jcnm, mode, ignerr, errcnt, n, nz, thread, usrmem)
Compute nonlinear terms and non-constant Jacobian elements.
Definition roseq.f90:211
program rosex
Main program. A simple setup and call of CONOPT.
Definition rosex.f90:12