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