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