CONOPT
Loading...
Searching...
No Matches
ident04.f90
Go to the documentation of this file.
1!> @file ident04.f90
2!! @ingroup FORT1THREAD_EXAMPLES
3!!
4!!
5!! This is a CONOPT implementation of the GAMS model:
6!! @verbatim
7!! Set i Rows / 1*m/
8!! Set j cols / 1*n/
9!! parameter a(j); a(j) = sqrt(ord(j))
10!! parameter w(i); w(i) = power(-1,ord(i)+1)*sqrt(ord(i));
11!! variable x(j), obj
12!! positive variable x(j);
13!! equation e(i), objdef;
14!! e(i) .. w(i)*sum(j,a(j)*x(j)) =L= w(i);
15!! objdef .. obj =E= sum(j,x(j));
16!! model m / all /; solve m using nlp minimizing obj;
17!! @endverbatim
18!!
19!! The left hand sides of the constraints are all proportional but they are this time
20!! inequalities. The last two (with the largest size) should be singled out and the last
21!! changed into an equality and the rest should be made redundant.
22!!
23!! The model is similar to ident03, but we minimize and constraint 4 becomes the binding
24!! constraint, but not the one used. Duals must therefore be transferred.
25!!
26!!
27!! For more information about the individual callbacks, please have a look at the source code.
28
29#if defined(_WIN32) && !defined(_WIN64)
30#define dec_directives_win32
31#endif
32
33!> Main program. A simple setup and call of CONOPT
34!!
35Program ident04
36
38 Use conopt
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#ifdef dec_directives_win32
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, Dimension(:), Pointer :: cntvect
60 INTEGER :: coi_error
61
62 call startup
63!
64! Create and initialize a Control Vector
65!
66 coi_error = coi_create( cntvect )
67!
68! Tell CONOPT about the size of the model by populating the Control Vector:
69!
70 coi_error = max( coi_error, coidef_numvar( cntvect, ncol ) )
71 coi_error = max( coi_error, coidef_numcon( cntvect, nrow+1 ) )
72 coi_error = max( coi_error, coidef_numnz( cntvect, (nrow+1)*ncol ) )
73 coi_error = max( coi_error, coidef_numnlnz( cntvect, 0 ) )
74 coi_error = max( coi_error, coidef_optdir( cntvect, -1 ) ) ! Minimize
75 coi_error = max( coi_error, coidef_objcon( cntvect, nrow + 1 ) ) ! Objective is last constraint
76 coi_error = max( coi_error, coidef_optfile( cntvect, 'Ident04.opt' ) )
77!
78! Tell CONOPT about the callback routines:
79!
80 coi_error = max( coi_error, coidef_readmatrix( cntvect, ident_readmatrix ) )
81 coi_error = max( coi_error, coidef_status( cntvect, std_status ) )
82 coi_error = max( coi_error, coidef_solution( cntvect, std_solution ) )
83 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
84 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
85
86#if defined(CONOPT_LICENSE_INT_1) && defined(CONOPT_LICENSE_INT_2) && defined(CONOPT_LICENSE_INT_3) && defined(CONOPT_LICENSE_TEXT)
87 coi_error = max( coi_error, coidef_license( cntvect, conopt_license_int_1, conopt_license_int_2, conopt_license_int_3, conopt_license_text) )
88#endif
89
90 If ( coi_error .ne. 0 ) THEN
91 write(*,*)
92 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
93 write(*,*)
94 call flog( "Skipping Solve due to setup errors", 1 )
95 ENDIF
96!
97! Save the solution so we can check the duals:
98!
99 do_allocate = .true.
100!
101! Start CONOPT:
102!
103 coi_error = coi_solve( cntvect )
104
105 write(*,*)
106 write(*,*) 'End of Ident example 1. Return code=',coi_error
107
108 If ( coi_error /= 0 ) then
109 call flog( "Errors encountered during solution", 1 )
110 elseif ( stacalls == 0 .or. solcalls == 0 ) then
111 call flog( "Status or Solution routine was not called", 1 )
112 elseif ( .not. ( sstat == 1 .and. mstat == 1 ) ) then
113 call flog( "Solver or Model status was not as expected (1,1)", 1 )
114 elseif ( abs( obj - sqrt(1.0d0/ncol) ) > 1.d-7 ) then
115 call flog( "Incorrect objective returned", 1 )
116 Else
117 Call checkdual( 'Ident04', minimize )
118 endif
119
120 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
121
122 call flog( "Successful Solve", 0 )
123
124End Program ident04
125!
126! ============================================================================
127! Define information about the model:
128!
129
130!> Define information about the model
131!!
132!! @include{doc} readMatrix_params.dox
133Integer Function ident_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
134 colsta, rowno, value, nlflag, n, m, nz, &
135 usrmem )
136#ifdef dec_directives_win32
137!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Ident_ReadMatrix
138#endif
139 Use ident
140 implicit none
141 integer, intent (in) :: n ! number of variables
142 integer, intent (in) :: m ! number of constraints
143 integer, intent (in) :: nz ! number of nonzeros
144 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
145 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
146 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
147 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
148 ! (not defined here)
149 integer, intent (out), dimension(m) :: type ! vector of equation types
150 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
151 ! (not defined here)
152 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
153 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
154 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
155 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
156 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
157 real*8 usrmem(*) ! optional user memory
158
159 real*8, dimension(Nrow) :: w
160 real*8, dimension(Ncol) :: a
161 Integer :: i, j, k
162!
163! Information about Variables:
164! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
165! Default: the status information in Vsta is not used.
166!
167 do j = 1, ncol
168 lower(j) = 0.0d0
169 a(j) = sqrt(1.0d0*j)
170 enddo
171!
172! Information about Constraints:
173! Default: Rhs = 0
174! Default: the status information in Esta and the function
175! value in FV are not used.
176! Default: Type: There is no default.
177! 0 = Equality,
178! 1 = Greater than or equal,
179! 2 = Less than or equal,
180! 3 = Non binding.
181!
182! Constraints 1 to Nrow:
183! Rhs = Obs(i) and type Equality
184!
185 do i = 1, nrow
186 w(i) = (-1)**(i+1)*sqrt(1.0d0*i);
187 rhs(i) = w(i)
188 type(i) = 2
189 enddo
190!
191! Constraint Nrow + 1 (Objective)
192! Rhs = 0 and type Non binding
193!
194 type(nrow+1) = 3
195!
196! Information about the Jacobian. CONOPT expects a columnwise
197! representation in Rowno, Value, Nlflag and Colsta.
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)
209! i: L=w(i)*a(j)
210! obj: L=1
211!
212 k = 1
213 do j = 1, ncol
214 colsta(j) = k
215 do i = 1, nrow
216 rowno(k) = i
217 nlflag(k) = 0
218 value(k) = w(i)*a(j)
219 k = k + 1
220 enddo
221 rowno(k) = nrow+1
222 value(k) = 1.0d0
223 k = k + 1
224 enddo
225 colsta(ncol+1) = k
226
227 ident_readmatrix = 0 ! Return value means OK
228
229end Function ident_readmatrix
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
subroutine checkdual(case, minmax)
Definition comdecl.f90:394
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_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_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
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:134
program ident04
Main program. A simple setup and call of CONOPT.
Definition ident04.f90:37
real *8 obj
Definition comdecl.f90:16
integer solcalls
Definition comdecl.f90:15
integer sstat
Definition comdecl.f90:18
integer, parameter minimize
Definition comdecl.f90:31
integer stacalls
Definition comdecl.f90:14
subroutine flog(msg, code)
Definition comdecl.f90:62
logical do_allocate
Definition comdecl.f90:27
integer mstat
Definition comdecl.f90:17
subroutine startup
Definition comdecl.f90:41