CONOPT
Loading...
Searching...
No Matches
ident11.f90
Go to the documentation of this file.
1!> @file ident11.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), ey(i), objdef;
15!! e(i) .. w(i)*sum(j,a(j)*x(j)) - y(i) =L= 0;
16!! ey(i) .. y(i) =E= abs(w(i));
17!! objdef .. obj =E= sum(j,x(j));
18!! model m / all /; solve m using nlp minimizing obj;
19!! @endverbatim
20!!
21!! The left hand sides of the constraints are all proportional but they are this time
22!! inequalities. Two of them should be changed into a range-set and the rest should be
23!! made redundant.
24!!
25!! The model is similar to ident09, but we minimize and constraint 4 becomes the binding
26!! constraint, but not the one used. Duals must therefore be transferred.
27!!
28!!
29!! For more information about the individual callbacks, please have a look at the source code.
30
31!> Main program. A simple setup and call of CONOPT
32!!
33Program ident11
34
35 Use proginfo
36 Use coidef
37 Use ident
38 implicit None
39!
40! Declare the user callback routines as Integer, External:
41!
42 Integer, External :: ident_readmatrix ! Mandatory Matrix definition routine defined below
43 Integer, External :: std_status ! Standard callback for displaying solution status
44 Integer, External :: std_solution ! Standard callback for displaying solution values
45 Integer, External :: std_message ! Standard callback for managing messages
46 Integer, External :: std_errmsg ! Standard callback for managing error messages
47#if defined(itl)
48!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Ident_ReadMatrix
49!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Status
50!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Solution
51!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Message
52!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_ErrMsg
53#endif
54!
55! Control vector
56!
57 INTEGER :: numcallback
58 INTEGER, Dimension(:), Pointer :: cntvect
59 INTEGER :: coi_error
60
61 call startup
62!
63! Create and initialize a Control Vector
64!
65 numcallback = coidef_size()
66 Allocate( cntvect(numcallback) )
67 coi_error = coidef_inifort( cntvect )
68!
69! Tell CONOPT about the size of the model by populating the Control Vector:
70!
71 coi_error = max( coi_error, coidef_numvar( cntvect, ncol+nrow ) )
72 coi_error = max( coi_error, coidef_numcon( cntvect, 2*nrow+1 ) )
73 coi_error = max( coi_error, coidef_numnz( cntvect, (nrow+1)*ncol+2*nrow ) )
74 coi_error = max( coi_error, coidef_numnlnz( cntvect, 0 ) )
75 coi_error = max( coi_error, coidef_optdir( cntvect, -1 ) ) ! minimize
76 coi_error = max( coi_error, coidef_objcon( cntvect, 2*nrow + 1 ) ) ! Objective is last constraint
77 coi_error = max( coi_error, coidef_optfile( cntvect, 'ident11.opt' ) )
78!
79! Tell CONOPT about the callback routines:
80!
81 coi_error = max( coi_error, coidef_readmatrix( cntvect, ident_readmatrix ) )
82 coi_error = max( coi_error, coidef_status( cntvect, std_status ) )
83 coi_error = max( coi_error, coidef_solution( cntvect, std_solution ) )
84 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
85 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
86
87#if defined(LICENSE_INT_1) && defined(LICENSE_INT_2) && defined(LICENSE_INT_3) && defined(LICENSE_TEXT)
88 coi_error = max( coi_error, coidef_license( cntvect, license_int_1, license_int_2, license_int_3, license_text) )
89#endif
90
91 If ( coi_error .ne. 0 ) THEN
92 write(*,*)
93 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
94 write(*,*)
95 call flog( "Skipping Solve due to setup errors", 1 )
96 ENDIF
97!
98! Save the solution so we can check the duals:
99!
100 do_allocate = .true.
101!
102! Start CONOPT:
103!
104 coi_error = coi_solve( cntvect )
105
106 write(*,*)
107 write(*,*) 'End of Ident example 1. Return code=',coi_error
108
109 If ( coi_error /= 0 ) then
110 call flog( "Errors encountered during solution", 1 )
111 elseif ( stacalls == 0 .or. solcalls == 0 ) then
112 call flog( "Status or Solution routine was not called", 1 )
113 elseif ( .not. ( sstat == 1 .and. mstat == 1 ) ) then
114 call flog( "Solver or Model status was not as expected (1,1)", 1 )
115 elseif ( abs( obj - 0.0d0 ) > 1.d-7 ) then
116 call flog( "Incorrect objective returned", 1 )
117 Else
118 Call checkdual( 'Ident11', minimize )
119 endif
120
121 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
122
123 call flog( "Successful Solve", 0 )
124
125End Program ident11
126!
127! ============================================================================
128! Define information about the model:
129!
130
131!> Define information about the model
132!!
133!! @include{doc} readMatrix_params.dox
134Integer Function ident_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
135 colsta, rowno, value, nlflag, n, m, nz, &
136 usrmem )
137#if defined(itl)
138!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Ident_ReadMatrix
139#endif
140 Use ident
141 implicit none
142 integer, intent (in) :: n ! number of variables
143 integer, intent (in) :: m ! number of constraints
144 integer, intent (in) :: nz ! number of nonzeros
145 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
146 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
147 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
148 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
149 ! (not defined here)
150 integer, intent (out), dimension(m) :: type ! vector of equation types
151 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
152 ! (not defined here)
153 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
154 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
155 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
156 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
157 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
158 real*8 usrmem(*) ! optional user memory
159
160 real*8, dimension(Nrow) :: w
161 real*8, dimension(Ncol) :: a
162 Integer :: i, j, k
163!
164! Information about Variables:
165! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
166! Default: the status information in Vsta is not used.
167!
168 do j = 1, ncol ! Only bounds on the x-variables
169 lower(j) = 0.0d0
170 a(j) = sqrt(1.0d0*j)
171 enddo
172!
173! Information about Constraints:
174! Default: Rhs = 0
175! Default: the status information in Esta and the function
176! value in FV are not used.
177! Default: Type: There is no default.
178! 0 = Equality,
179! 1 = Greater than or equal,
180! 2 = Less than or equal,
181! 3 = Non binding.
182!
183! Constraints 1 to Nrow:
184! Rhs = 0 and type Less than
185! Constraints Nrow+1 to 2*Nrow:
186! Rhs = w(i) and type Equality
187!
188 do i = 1, nrow
189 w(i) = (-1)**(i+1)*sqrt(1.0d0*i);
190 type(i) = 2
191 rhs(nrow+i) = abs(w(i))
192 type(nrow+i) = 0
193 enddo
194!
195! Constraint Nrow + 1 (Objective)
196! Rhs = 0 and type Non binding
197!
198 type(2*nrow+1) = 3
199!
200! Information about the Jacobian. We use the standard method with
201! Rowno, Value, Nlflag and Colsta and we do not use Colno.
202!
203! Colsta = Start of column indices (No Defaults):
204! Rowno = Row indices
205! Value = Value of derivative (by default only linear
206! derivatives are used)
207! Nlflag = 0 for linear and 1 for nonlinear derivative
208! (not needed for completely linear models)
209!
210!
211! Indices
212! x(j) y(i)
213! e(i): L=w(i)*a(j) -1
214! ey(i): 1
215! obj: L=1
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 value(k) = 1.0d0
228 k = k + 1
229 enddo
230 do i = 1, nrow
231 j = ncol+i
232 colsta(j) = k
233 rowno(k) = i
234 nlflag(k) = 0
235 value(k) = -1.0d0
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
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_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
program ident11
Main program. A simple setup and call of CONOPT.
Definition ident11.f90:33
real *8 obj
Definition comdecl.f90:10
integer solcalls
Definition comdecl.f90:9
integer sstat
Definition comdecl.f90:12
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 mstat
Definition comdecl.f90:11
subroutine startup
Definition comdecl.f90:35