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