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#if defined(_WIN32) && !defined(_WIN64)
26#define dec_directives_win32
27#endif
28
29!> Main program. A simple setup and call of CONOPT
30!!
31Program ident01
32
34 Use conopt
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#ifdef dec_directives_win32
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, Dimension(:), Pointer :: cntvect
56 INTEGER :: coi_error
57
58 call startup
59!
60! Create and initialize a Control Vector
61!
62 coi_error = coi_create( cntvect )
63!
64! Tell CONOPT about the size of the model by populating the Control Vector:
65!
66 coi_error = max( coi_error, coidef_numvar( cntvect, ncol ) )
67 coi_error = max( coi_error, coidef_numcon( cntvect, nrow+1 ) )
68 coi_error = max( coi_error, coidef_numnz( cntvect, (nrow+1)*ncol ) )
69 coi_error = max( coi_error, coidef_numnlnz( cntvect, 0 ) )
70 coi_error = max( coi_error, coidef_optdir( cntvect, +1 ) ) ! maximize
71 coi_error = max( coi_error, coidef_objcon( cntvect, nrow + 1 ) ) ! Objective is last constraint
72 coi_error = max( coi_error, coidef_optfile( cntvect, 'ident01.opt' ) )
73!
74! Tell CONOPT about the callback routines:
75!
76 coi_error = max( coi_error, coidef_readmatrix( cntvect, ident_readmatrix ) )
77 coi_error = max( coi_error, coidef_status( cntvect, std_status ) )
78 coi_error = max( coi_error, coidef_solution( cntvect, std_solution ) )
79 coi_error = max( coi_error, coidef_message( cntvect, std_message ) )
80 coi_error = max( coi_error, coidef_errmsg( cntvect, std_errmsg ) )
81
82#if defined(CONOPT_LICENSE_INT_1) && defined(CONOPT_LICENSE_INT_2) && defined(CONOPT_LICENSE_INT_3) && defined(CONOPT_LICENSE_TEXT)
83 coi_error = max( coi_error, coidef_license( cntvect, conopt_license_int_1, conopt_license_int_2, conopt_license_int_3, conopt_license_text) )
84#endif
85
86 If ( coi_error .ne. 0 ) THEN
87 write(*,*)
88 write(*,*) '**** Fatal Error while loading CONOPT Callback routines.'
89 write(*,*)
90 call flog( "Skipping Solve due to setup errors", 1 )
91 ENDIF
92!
93! Save the solution so we can check the duals:
94!
95 do_allocate = .true.
96!
97! Start CONOPT:
98!
99 coi_error = coi_solve( cntvect )
100
101 write(*,*)
102 write(*,*) 'End of Ident example 1. Return code=',coi_error
103
104 If ( coi_error /= 0 ) then
105 call flog( "Errors encountered during solution", 1 )
106 elseif ( stacalls == 0 .or. solcalls == 0 ) then
107 call flog( "Status or Solution routine was not called", 1 )
108 elseif ( .not. ( sstat == 1 .and. mstat == 1 ) ) then
109 call flog( "Solver or Model status was not as expected (1,1)", 1 )
110 elseif ( abs( obj - 1.0d0 ) > 1.d-7 ) then
111 call flog( "Incorrect objective returned", 1 )
112 Else
113 Call checkdual( 'Ident01', maximize )
114 endif
115
116 if ( coi_free(cntvect) /= 0 ) call flog( "Error while freeing control vector",1)
117
118 call flog( "Successful Solve", 0 )
119
120End Program ident01
121!
122! ============================================================================
123! Define information about the model:
124!
125
126!> Define information about the model
127!!
128!! @include{doc} readMatrix_params.dox
129Integer Function ident_readmatrix( lower, curr, upper, vsta, type, rhs, esta, &
130 colsta, rowno, value, nlflag, n, m, nz, &
131 usrmem )
132#ifdef dec_directives_win32
133!DEC$ ATTRIBUTES STDCALL, REFERENCE, NOMIXED_STR_LEN_ARG :: Ident_ReadMatrix
134#endif
135 Use ident
136 implicit none
137 integer, intent (in) :: n ! number of variables
138 integer, intent (in) :: m ! number of constraints
139 integer, intent (in) :: nz ! number of nonzeros
140 real*8, intent (in out), dimension(n) :: lower ! vector of lower bounds
141 real*8, intent (in out), dimension(n) :: curr ! vector of initial values
142 real*8, intent (in out), dimension(n) :: upper ! vector of upper bounds
143 integer, intent (in out), dimension(n) :: vsta ! vector of initial variable status
144 ! (not defined here)
145 integer, intent (out), dimension(m) :: type ! vector of equation types
146 integer, intent (in out), dimension(m) :: esta ! vector of initial equation status
147 ! (not defined here)
148 real*8, intent (in out), dimension(m) :: rhs ! vector of right hand sides
149 integer, intent (in out), dimension(n+1) :: colsta ! vector with start of column indices
150 integer, intent (out), dimension(nz) :: rowno ! vector of row numbers
151 integer, intent (in out), dimension(nz) :: nlflag ! vector of nonlinearity flags
152 real*8, intent (in out), dimension(nz) :: value ! vector of matrix values
153 real*8 usrmem(*) ! optional user memory
154
155 real*8, dimension(Nrow) :: w
156 real*8, dimension(Ncol) :: a
157 Integer :: i, j, k
158!
159! Information about Variables:
160! Default: Lower = -Inf, Curr = 0, and Upper = +inf.
161! Default: the status information in Vsta is not used.
162!
163 do j = 1, ncol
164 lower(j) = 0.0d0
165 a(j) = sqrt(1.0d0*j)
166 enddo
167!
168! Information about Constraints:
169! Default: Rhs = 0
170! Default: the status information in Esta and the function
171! value in FV are not used.
172! Default: Type: There is no default.
173! 0 = Equality,
174! 1 = Greater than or equal,
175! 2 = Less than or equal,
176! 3 = Non binding.
177!
178! Constraints 1 to Nrow:
179! Rhs = Obs(i) and type Equality
180!
181 do i = 1, nrow
182 w(i) = (-1)**(i+1)*sqrt(1.0d0*i);
183 rhs(i) = w(i)
184 type(i) = 0
185 enddo
186!
187! Constraint Nrow + 1 (Objective)
188! Rhs = 0 and type Non binding
189!
190 type(nrow+1) = 3
191!
192! Information about the Jacobian. CONOPT expects a columnwise
193! representation in Rowno, Value, Nlflag and Colsta.
194!
195! Colsta = Start of column indices (No Defaults):
196! Rowno = Row indices
197! Value = Value of derivative (by default only linear
198! derivatives are used)
199! Nlflag = 0 for linear and 1 for nonlinear derivative
200! (not needed for completely linear models)
201!
202!
203! Indices
204! x(j)
205! i: L=w(i)*a(j)
206! obj: L=1
207!
208 k = 1
209 do j = 1, ncol
210 colsta(j) = k
211 do i = 1, nrow
212 rowno(k) = i
213 nlflag(k) = 0
214 value(k) = w(i)*a(j)
215 k = k + 1
216 enddo
217 rowno(k) = nrow+1
218 value(k) = 1.0d0
219 k = k + 1
220 enddo
221 colsta(ncol+1) = k
222
223 ident_readmatrix = 0 ! Return value means OK
224
225end 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
program ident01
Main program. A simple setup and call of CONOPT.
Definition ident01.f90:33
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
real *8 obj
Definition comdecl.f90:16
integer solcalls
Definition comdecl.f90:15
integer sstat
Definition comdecl.f90:18
integer stacalls
Definition comdecl.f90:14
subroutine flog(msg, code)
Definition comdecl.f90:62
logical do_allocate
Definition comdecl.f90:27
integer, parameter maximize
Definition comdecl.f90:31
integer mstat
Definition comdecl.f90:17
subroutine startup
Definition comdecl.f90:41