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