LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
spbt02.f
Go to the documentation of this file.
1*> \brief \b SPBT02
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* SUBROUTINE SPBT02( UPLO, N, KD, NRHS, A, LDA, X, LDX, B, LDB,
12* RWORK, RESID )
13*
14* .. Scalar Arguments ..
15* CHARACTER UPLO
16* INTEGER KD, LDA, LDB, LDX, N, NRHS
17* REAL RESID
18* ..
19* .. Array Arguments ..
20* REAL A( LDA, * ), B( LDB, * ), RWORK( * ),
21* $ X( LDX, * )
22* ..
23*
24*
25*> \par Purpose:
26* =============
27*>
28*> \verbatim
29*>
30*> SPBT02 computes the residual for a solution of a symmetric banded
31*> system of equations A*x = b:
32*> RESID = norm( B - A*X ) / ( norm(A) * norm(X) * EPS)
33*> where EPS is the machine precision.
34*> \endverbatim
35*
36* Arguments:
37* ==========
38*
39*> \param[in] UPLO
40*> \verbatim
41*> UPLO is CHARACTER*1
42*> Specifies whether the upper or lower triangular part of the
43*> symmetric matrix A is stored:
44*> = 'U': Upper triangular
45*> = 'L': Lower triangular
46*> \endverbatim
47*>
48*> \param[in] N
49*> \verbatim
50*> N is INTEGER
51*> The number of rows and columns of the matrix A. N >= 0.
52*> \endverbatim
53*>
54*> \param[in] KD
55*> \verbatim
56*> KD is INTEGER
57*> The number of super-diagonals of the matrix A if UPLO = 'U',
58*> or the number of sub-diagonals if UPLO = 'L'. KD >= 0.
59*> \endverbatim
60*>
61*> \param[in] NRHS
62*> \verbatim
63*> NRHS is INTEGER
64*> The number of right hand sides. NRHS >= 0.
65*> \endverbatim
66*>
67*> \param[in] A
68*> \verbatim
69*> A is REAL array, dimension (LDA,N)
70*> The original symmetric band matrix A. If UPLO = 'U', the
71*> upper triangular part of A is stored as a band matrix; if
72*> UPLO = 'L', the lower triangular part of A is stored. The
73*> columns of the appropriate triangle are stored in the columns
74*> of A and the diagonals of the triangle are stored in the rows
75*> of A. See SPBTRF for further details.
76*> \endverbatim
77*>
78*> \param[in] LDA
79*> \verbatim
80*> LDA is INTEGER.
81*> The leading dimension of the array A. LDA >= max(1,KD+1).
82*> \endverbatim
83*>
84*> \param[in] X
85*> \verbatim
86*> X is REAL array, dimension (LDX,NRHS)
87*> The computed solution vectors for the system of linear
88*> equations.
89*> \endverbatim
90*>
91*> \param[in] LDX
92*> \verbatim
93*> LDX is INTEGER
94*> The leading dimension of the array X. LDX >= max(1,N).
95*> \endverbatim
96*>
97*> \param[in,out] B
98*> \verbatim
99*> B is REAL array, dimension (LDB,NRHS)
100*> On entry, the right hand side vectors for the system of
101*> linear equations.
102*> On exit, B is overwritten with the difference B - A*X.
103*> \endverbatim
104*>
105*> \param[in] LDB
106*> \verbatim
107*> LDB is INTEGER
108*> The leading dimension of the array B. LDB >= max(1,N).
109*> \endverbatim
110*>
111*> \param[out] RWORK
112*> \verbatim
113*> RWORK is REAL array, dimension (N)
114*> \endverbatim
115*>
116*> \param[out] RESID
117*> \verbatim
118*> RESID is REAL
119*> The maximum over the number of right hand sides of
120*> norm(B - A*X) / ( norm(A) * norm(X) * EPS ).
121*> \endverbatim
122*
123* Authors:
124* ========
125*
126*> \author Univ. of Tennessee
127*> \author Univ. of California Berkeley
128*> \author Univ. of Colorado Denver
129*> \author NAG Ltd.
130*
131*> \ingroup single_lin
132*
133* =====================================================================
134 SUBROUTINE spbt02( UPLO, N, KD, NRHS, A, LDA, X, LDX, B, LDB,
135 $ RWORK, RESID )
136*
137* -- LAPACK test routine --
138* -- LAPACK is a software package provided by Univ. of Tennessee, --
139* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
140*
141* .. Scalar Arguments ..
142 CHARACTER UPLO
143 INTEGER KD, LDA, LDB, LDX, N, NRHS
144 REAL RESID
145* ..
146* .. Array Arguments ..
147 REAL A( LDA, * ), B( LDB, * ), RWORK( * ),
148 $ x( ldx, * )
149* ..
150*
151* =====================================================================
152*
153* .. Parameters ..
154 REAL ZERO, ONE
155 parameter( zero = 0.0e+0, one = 1.0e+0 )
156* ..
157* .. Local Scalars ..
158 INTEGER J
159 REAL ANORM, BNORM, EPS, XNORM
160* ..
161* .. External Functions ..
162 REAL SASUM, SLAMCH, SLANSB
163 EXTERNAL sasum, slamch, slansb
164* ..
165* .. External Subroutines ..
166 EXTERNAL ssbmv
167* ..
168* .. Intrinsic Functions ..
169 INTRINSIC max
170* ..
171* .. Executable Statements ..
172*
173* Quick exit if N = 0 or NRHS = 0.
174*
175 IF( n.LE.0 .OR. nrhs.LE.0 ) THEN
176 resid = zero
177 RETURN
178 END IF
179*
180* Exit with RESID = 1/EPS if ANORM = 0.
181*
182 eps = slamch( 'Epsilon' )
183 anorm = slansb( '1', uplo, n, kd, a, lda, rwork )
184 IF( anorm.LE.zero ) THEN
185 resid = one / eps
186 RETURN
187 END IF
188*
189* Compute B - A*X
190*
191 DO 10 j = 1, nrhs
192 CALL ssbmv( uplo, n, kd, -one, a, lda, x( 1, j ), 1, one,
193 $ b( 1, j ), 1 )
194 10 CONTINUE
195*
196* Compute the maximum over the number of right hand sides of
197* norm( B - A*X ) / ( norm(A) * norm(X) * EPS )
198*
199 resid = zero
200 DO 20 j = 1, nrhs
201 bnorm = sasum( n, b( 1, j ), 1 )
202 xnorm = sasum( n, x( 1, j ), 1 )
203 IF( xnorm.LE.zero ) THEN
204 resid = one / eps
205 ELSE
206 resid = max( resid, ( ( bnorm / anorm ) / xnorm ) / eps )
207 END IF
208 20 CONTINUE
209*
210 RETURN
211*
212* End of SPBT02
213*
214 END
subroutine ssbmv(uplo, n, k, alpha, a, lda, x, incx, beta, y, incy)
SSBMV
Definition ssbmv.f:184
subroutine spbt02(uplo, n, kd, nrhs, a, lda, x, ldx, b, ldb, rwork, resid)
SPBT02
Definition spbt02.f:136