CONOPT
Loading...
Searching...
No Matches
ident07.f90
Go to the documentation of this file.
1!> @file ident07.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) =E= 0;
16!! ey(i) .. y(i) =E= 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 derived from ident01 with y(i) introduced as some extra variables.
22!! The ey constraints define y and after y is fixed we have the ident01 back.
23!! The constraints are all proportional and only one should be used in the internal model.
24!! The rest should be made redundant from the start.
25!!
26!!
27!! For more information about the individual callbacks, please have a look at the source code.
28
29!> Main program. A simple setup and call of CONOPT
30!!
31Program ident07
32
33 Use proginfo
34 Use coidef
35 Use ident
36 implicit None
37!
38! Declare the user callback routines as Integer, External:
39!
40 Integer, External :: ident_readmatrix ! Mandatory Matrix definition routine defined below
41 Integer, External :: std_status ! Standard callback for displaying solution status
42 Integer, External :: std_solution ! Standard callback for displaying solution values
43 Integer, External :: std_message ! Standard callback for managing messages
44 Integer, External :: std_errmsg ! Standard callback for managing error messages
45#if defined(itl)
46!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Ident_ReadMatrix
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, 0 ) )
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, 'ident07.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_status( cntvect, std_status ) )
81 coi_error = max( coi_error, coidef_solution( cntvect, std_solution ) )
82 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
83 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
84
85#if defined(LICENSE_INT_1) && defined(LICENSE_INT_2) && defined(LICENSE_INT_3) && defined(LICENSE_TEXT)
86 coi_error = max( coi_error, coidef_license( cntvect, license_int_1, license_int_2, license_int_3, license_text) )
87#endif
88
89 If ( coi_error .ne. 0 ) THEN
90 write(*,*)
91 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
92 write(*,*)
93 call flog( "Skipping Solve due to setup errors", 1 )
94 ENDIF
95!
96! Save the solution so we can check the duals:
97!
98 do_allocate = .true.
99!
100! Start CONOPT:
101!
102 coi_error = coi_solve( cntvect )
103
104 write(*,*)
105 write(*,*) 'End of Ident example 1. Return code=',coi_error
106
107 If ( coi_error /= 0 ) then
108 call flog( "Errors encountered during solution", 1 )
109 elseif ( stacalls == 0 .or. solcalls == 0 ) then
110 call flog( "Status or Solution routine was not called", 1 )
111 elseif ( .not. ( sstat == 1 .and. mstat == 1 ) ) then
112 call flog( "Solver or Model status was not as expected (1,1)", 1 )
113 elseif ( abs( obj - 1.0d0 ) > 1.d-7 ) then
114 call flog( "Incorrect objective returned", 1 )
115 Else
116 Call checkdual( 'Ident07', maximize )
117 endif
118
119 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
120
121 call flog( "Successful Solve", 0 )
122
123End Program ident07
124!
125! ============================================================================
126! Define information about the model:
127!
128
129!> Define information about the model
130!!
131!! @include{doc} readMatrix_params.dox
132Integer Function ident_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
133 colsta, rowno, value, nlflag, n, m, nz, &
134 usrmem )
135#if defined(itl)
136!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Ident_ReadMatrix
137#endif
138 Use ident
139 implicit none
140 integer, intent (in) :: n ! number of variables
141 integer, intent (in) :: m ! number of constraints
142 integer, intent (in) :: nz ! number of nonzeros
143 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
144 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
145 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
146 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
147 ! (not defined here)
148 integer, intent (out), dimension(m) :: type ! vector of equation types
149 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
150 ! (not defined here)
151 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
152 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
153 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
154 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
155 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
156 real*8 usrmem(*) ! optional user memory
157
158 real*8, dimension(Nrow) :: w
159 real*8, dimension(Ncol) :: a
160 Integer :: i, j, k
161!
162! Information about Variables:
163! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
164! Default: the status information in Vsta is not used.
165!
166 do j = 1, ncol ! Only bounds on the x-variables
167 lower(j) = 0.0d0
168 a(j) = sqrt(1.0d0*j)
169 enddo
170!
171! Information about Constraints:
172! Default: Rhs = 0
173! Default: the status information in Esta and the function
174! value in FV are not used.
175! Default: Type: There is no default.
176! 0 = Equality,
177! 1 = Greater than or equal,
178! 2 = Less than or equal,
179! 3 = Non binding.
180!
181! Constraints 1 to Nrow:
182! Rhs = 0 and type Equality
183! Constraints Nrow+1 to 2*Nrow:
184! Rhs = w(i) and type Equality
185!
186 do i = 1, nrow
187 w(i) = (-1)**(i+1)*sqrt(1.0d0*i);
188 type(i) = 0
189 rhs(nrow+i) = w(i)
190 type(nrow+i) = 0
191 enddo
192!
193! Constraint Nrow + 1 (Objective)
194! Rhs = 0 and type Non binding
195!
196 type(2*nrow+1) = 3
197!
198! Information about the Jacobian. We use the standard method with
199! Rowno, Value, Nlflag and Colsta and we do not use Colno.
200!
201! Colsta = Start of column indices (No Defaults):
202! Rowno = Row indices
203! Value = Value of derivative (by default only linear
204! derivatives are used)
205! Nlflag = 0 for linear and 1 for nonlinear derivative
206! (not needed for completely linear models)
207!
208!
209! Indices
210! x(j) y(i)
211! e(i): L=w(i)*a(j) -1
212! ey(i): 1
213! obj: L=1
214!
215 k = 1
216 do j = 1, ncol
217 colsta(j) = k
218 do i = 1, nrow
219 rowno(k) = i
220 nlflag(k) = 0
221 value(k) = w(i)*a(j)
222 k = k + 1
223 enddo
224 rowno(k) = 2*nrow+1
225 value(k) = 1.0d0
226 k = k + 1
227 enddo
228 do i = 1, nrow
229 j = ncol+i
230 colsta(j) = k
231 rowno(k) = i
232 nlflag(k) = 0
233 value(k) = -1.0d0
234 k = k + 1
235 rowno(k) = nrow+i
236 nlflag(k) = 0
237 value(k) = +1.0d0
238 k = k + 1
239 enddo
240 colsta(ncol+nrow+1) = k
241
242 ident_readmatrix = 0 ! Return value means OK
243
244end 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 ident07
Main program. A simple setup and call of CONOPT.
Definition ident07.f90:31
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