CONOPT
Loading...
Searching...
No Matches
ident09.f90
Go to the documentation of this file.
1!> @file ident09.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 maximizing obj;
19!! @endverbatim
20!!
21!! The model is similar to ident08 with the right hand side on ey(i) with an absolute value.
22!! The ey constraints define y and after y is fixed we have the ident03 back.
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 ident09
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 :: std_status ! Standard callback for displaying solution status
40 Integer, External :: std_solution ! Standard callback for displaying solution values
41 Integer, External :: std_message ! Standard callback for managing messages
42 Integer, External :: std_errmsg ! Standard callback for managing error messages
43#if defined(itl)
44!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Ident_ReadMatrix
45!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Status
46!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Solution
47!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_Message
48!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Std_ErrMsg
49#endif
50!
51! Control vector
52!
53 INTEGER :: numcallback
54 INTEGER, Dimension(:), Pointer :: cntvect
55 INTEGER :: coi_error
56
57 call startup
58!
59! Create and initialize a Control Vector
60!
61 numcallback = coidef_size()
62 Allocate( cntvect(numcallback) )
63 coi_error = coidef_inifort( cntvect )
64!
65! Tell CONOPT about the size of the model by populating the Control Vector:
66!
67 coi_error = max( coi_error, coidef_numvar( cntvect, ncol+nrow ) )
68 coi_error = max( coi_error, coidef_numcon( cntvect, 2*nrow+1 ) )
69 coi_error = max( coi_error, coidef_numnz( cntvect, (nrow+1)*ncol+2*nrow ) )
70 coi_error = max( coi_error, coidef_numnlnz( cntvect, 0 ) )
71 coi_error = max( coi_error, coidef_optdir( cntvect, +1 ) ) ! maximize
72 coi_error = max( coi_error, coidef_objcon( cntvect, 2*nrow + 1 ) ) ! Objective is last constraint
73 coi_error = max( coi_error, coidef_optfile( cntvect, 'ident09.opt' ) )
74!
75! Tell CONOPT about the callback routines:
76!
77 coi_error = max( coi_error, coidef_readmatrix( cntvect, ident_readmatrix ) )
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(LICENSE_INT_1) && defined(LICENSE_INT_2) && defined(LICENSE_INT_3) && defined(LICENSE_TEXT)
84 coi_error = max( coi_error, coidef_license( cntvect, license_int_1, license_int_2, license_int_3, 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! Save the solution so we can check the duals:
95!
96 do_allocate = .true.
97!
98! Start CONOPT:
99!
100 coi_error = coi_solve( cntvect )
101
102 write(*,*)
103 write(*,*) 'End of Ident example 1. Return code=',coi_error
104
105 If ( coi_error /= 0 ) then
106 call flog( "Errors encountered during solution", 1 )
107 elseif ( stacalls == 0 .or. solcalls == 0 ) then
108 call flog( "Status or Solution routine was not called", 1 )
109 elseif ( .not. ( sstat == 1 .and. mstat == 1 ) ) then
110 call flog( "Solver or Model status was not as expected (1,1)", 1 )
111 elseif ( abs( obj - 1.0d0 ) > 1.d-7 ) then
112 call flog( "Incorrect objective returned", 1 )
113 Else
114 Call checkdual( 'Ident09', maximize )
115 endif
116
117 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
118
119 call flog( "Successful Solve", 0 )
120
121End Program ident09
122!
123! ============================================================================
124! Define information about the model:
125!
126
127!> Define information about the model
128!!
129!! @include{doc} readMatrix_params.dox
130Integer Function ident_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
131 colsta, rowno, value, nlflag, n, m, nz, &
132 usrmem )
133#if defined(itl)
134!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Ident_ReadMatrix
135#endif
136 Use ident
137 implicit none
138 integer, intent (in) :: n ! number of variables
139 integer, intent (in) :: m ! number of constraints
140 integer, intent (in) :: nz ! number of nonzeros
141 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
142 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
143 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
144 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
145 ! (not defined here)
146 integer, intent (out), dimension(m) :: type ! vector of equation types
147 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
148 ! (not defined here)
149 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
150 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
151 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
152 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
153 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
154 real*8 usrmem(*) ! optional user memory
155
156 real*8, dimension(Nrow) :: w
157 real*8, dimension(Ncol) :: a
158 Integer :: i, j, k
159!
160! Information about Variables:
161! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
162! Default: the status information in Vsta is not used.
163!
164 do j = 1, ncol ! Only bounds on the x-variables
165 lower(j) = 0.0d0
166 a(j) = sqrt(1.0d0*j)
167 enddo
168!
169! Information about Constraints:
170! Default: Rhs = 0
171! Default: the status information in Esta and the function
172! value in FV are not used.
173! Default: Type: There is no default.
174! 0 = Equality,
175! 1 = Greater than or equal,
176! 2 = Less than or equal,
177! 3 = Non binding.
178!
179! Constraints 1 to Nrow:
180! Rhs = 0 and type Less than
181! Constraints Nrow+1 to 2*Nrow:
182! Rhs = abs(w(i)) and type Equality
183!
184 do i = 1, nrow
185 w(i) = (-1)**(i+1)*sqrt(1.0d0*i);
186 type(i) = 2
187 rhs(nrow+i) = abs(w(i))
188 type(nrow+i) = 0
189 enddo
190!
191! Constraint Nrow + 1 (Objective)
192! Rhs = 0 and type Non binding
193!
194 type(2*nrow+1) = 3
195!
196! Information about the Jacobian. We use the standard method with
197! Rowno, Value, Nlflag and Colsta and we do not use Colno.
198!
199! Colsta = Start of column indices (No Defaults):
200! Rowno = Row indices
201! Value = Value of derivative (by default only linear
202! derivatives are used)
203! Nlflag = 0 for linear and 1 for nonlinear derivative
204! (not needed for completely linear models)
205!
206!
207! Indices
208! x(j) y(i)
209! e(i): L=w(i)*a(j) -1
210! ey(i): 1
211! obj: L=1
212!
213 k = 1
214 do j = 1, ncol
215 colsta(j) = k
216 do i = 1, nrow
217 rowno(k) = i
218 nlflag(k) = 0
219 value(k) = w(i)*a(j)
220 k = k + 1
221 enddo
222 rowno(k) = 2*nrow+1
223 value(k) = 1.0d0
224 k = k + 1
225 enddo
226 do i = 1, nrow
227 j = ncol+i
228 colsta(j) = k
229 rowno(k) = i
230 nlflag(k) = 0
231 value(k) = -1.0d0
232 k = k + 1
233 rowno(k) = nrow+i
234 nlflag(k) = 0
235 value(k) = +1.0d0
236 k = k + 1
237 enddo
238 colsta(ncol+nrow+1) = k
239
240 ident_readmatrix = 0 ! Return value means OK
241
242end 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 ident09
Main program. A simple setup and call of CONOPT.
Definition ident09.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