LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
spbt01.f
Go to the documentation of this file.
1*> \brief \b SPBT01
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 SPBT01( UPLO, N, KD, A, LDA, AFAC, LDAFAC, RWORK,
12* RESID )
13*
14* .. Scalar Arguments ..
15* CHARACTER UPLO
16* INTEGER KD, LDA, LDAFAC, N
17* REAL RESID
18* ..
19* .. Array Arguments ..
20* REAL A( LDA, * ), AFAC( LDAFAC, * ), RWORK( * )
21* ..
22*
23*
24*> \par Purpose:
25* =============
26*>
27*> \verbatim
28*>
29*> SPBT01 reconstructs a symmetric positive definite band matrix A from
30*> its L*L' or U'*U factorization and computes the residual
31*> norm( L*L' - A ) / ( N * norm(A) * EPS ) or
32*> norm( U'*U - A ) / ( N * norm(A) * EPS ),
33*> where EPS is the machine epsilon, L' is the conjugate transpose of
34*> L, and U' is the conjugate transpose of U.
35*> \endverbatim
36*
37* Arguments:
38* ==========
39*
40*> \param[in] UPLO
41*> \verbatim
42*> UPLO is CHARACTER*1
43*> Specifies whether the upper or lower triangular part of the
44*> symmetric matrix A is stored:
45*> = 'U': Upper triangular
46*> = 'L': Lower triangular
47*> \endverbatim
48*>
49*> \param[in] N
50*> \verbatim
51*> N is INTEGER
52*> The number of rows and columns of the matrix A. N >= 0.
53*> \endverbatim
54*>
55*> \param[in] KD
56*> \verbatim
57*> KD is INTEGER
58*> The number of super-diagonals of the matrix A if UPLO = 'U',
59*> or the number of sub-diagonals if UPLO = 'L'. KD >= 0.
60*> \endverbatim
61*>
62*> \param[in] A
63*> \verbatim
64*> A is REAL array, dimension (LDA,N)
65*> The original symmetric band matrix A. If UPLO = 'U', the
66*> upper triangular part of A is stored as a band matrix; if
67*> UPLO = 'L', the lower triangular part of A is stored. The
68*> columns of the appropriate triangle are stored in the columns
69*> of A and the diagonals of the triangle are stored in the rows
70*> of A. See SPBTRF for further details.
71*> \endverbatim
72*>
73*> \param[in] LDA
74*> \verbatim
75*> LDA is INTEGER.
76*> The leading dimension of the array A. LDA >= max(1,KD+1).
77*> \endverbatim
78*>
79*> \param[in] AFAC
80*> \verbatim
81*> AFAC is REAL array, dimension (LDAFAC,N)
82*> The factored form of the matrix A. AFAC contains the factor
83*> L or U from the L*L' or U'*U factorization in band storage
84*> format, as computed by SPBTRF.
85*> \endverbatim
86*>
87*> \param[in] LDAFAC
88*> \verbatim
89*> LDAFAC is INTEGER
90*> The leading dimension of the array AFAC.
91*> LDAFAC >= max(1,KD+1).
92*> \endverbatim
93*>
94*> \param[out] RWORK
95*> \verbatim
96*> RWORK is REAL array, dimension (N)
97*> \endverbatim
98*>
99*> \param[out] RESID
100*> \verbatim
101*> RESID is REAL
102*> If UPLO = 'L', norm(L*L' - A) / ( N * norm(A) * EPS )
103*> If UPLO = 'U', norm(U'*U - A) / ( N * norm(A) * EPS )
104*> \endverbatim
105*
106* Authors:
107* ========
108*
109*> \author Univ. of Tennessee
110*> \author Univ. of California Berkeley
111*> \author Univ. of Colorado Denver
112*> \author NAG Ltd.
113*
114*> \ingroup single_lin
115*
116* =====================================================================
117 SUBROUTINE spbt01( UPLO, N, KD, A, LDA, AFAC, LDAFAC, RWORK,
118 $ RESID )
119*
120* -- LAPACK test routine --
121* -- LAPACK is a software package provided by Univ. of Tennessee, --
122* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
123*
124* .. Scalar Arguments ..
125 CHARACTER UPLO
126 INTEGER KD, LDA, LDAFAC, N
127 REAL RESID
128* ..
129* .. Array Arguments ..
130 REAL A( LDA, * ), AFAC( LDAFAC, * ), RWORK( * )
131* ..
132*
133* =====================================================================
134*
135*
136* .. Parameters ..
137 REAL ZERO, ONE
138 parameter( zero = 0.0e+0, one = 1.0e+0 )
139* ..
140* .. Local Scalars ..
141 INTEGER I, J, K, KC, KLEN, ML, MU
142 REAL ANORM, EPS, T
143* ..
144* .. External Functions ..
145 LOGICAL LSAME
146 REAL SDOT, SLAMCH, SLANSB
147 EXTERNAL lsame, sdot, slamch, slansb
148* ..
149* .. External Subroutines ..
150 EXTERNAL sscal, ssyr, strmv
151* ..
152* .. Intrinsic Functions ..
153 INTRINSIC max, min, real
154* ..
155* .. Executable Statements ..
156*
157* Quick exit if N = 0.
158*
159 IF( n.LE.0 ) THEN
160 resid = zero
161 RETURN
162 END IF
163*
164* Exit with RESID = 1/EPS if ANORM = 0.
165*
166 eps = slamch( 'Epsilon' )
167 anorm = slansb( '1', uplo, n, kd, a, lda, rwork )
168 IF( anorm.LE.zero ) THEN
169 resid = one / eps
170 RETURN
171 END IF
172*
173* Compute the product U'*U, overwriting U.
174*
175 IF( lsame( uplo, 'U' ) ) THEN
176 DO 10 k = n, 1, -1
177 kc = max( 1, kd+2-k )
178 klen = kd + 1 - kc
179*
180* Compute the (K,K) element of the result.
181*
182 t = sdot( klen+1, afac( kc, k ), 1, afac( kc, k ), 1 )
183 afac( kd+1, k ) = t
184*
185* Compute the rest of column K.
186*
187 IF( klen.GT.0 )
188 $ CALL strmv( 'Upper', 'Transpose', 'Non-unit', klen,
189 $ afac( kd+1, k-klen ), ldafac-1,
190 $ afac( kc, k ), 1 )
191*
192 10 CONTINUE
193*
194* UPLO = 'L': Compute the product L*L', overwriting L.
195*
196 ELSE
197 DO 20 k = n, 1, -1
198 klen = min( kd, n-k )
199*
200* Add a multiple of column K of the factor L to each of
201* columns K+1 through N.
202*
203 IF( klen.GT.0 )
204 $ CALL ssyr( 'Lower', klen, one, afac( 2, k ), 1,
205 $ afac( 1, k+1 ), ldafac-1 )
206*
207* Scale column K by the diagonal element.
208*
209 t = afac( 1, k )
210 CALL sscal( klen+1, t, afac( 1, k ), 1 )
211*
212 20 CONTINUE
213 END IF
214*
215* Compute the difference L*L' - A or U'*U - A.
216*
217 IF( lsame( uplo, 'U' ) ) THEN
218 DO 40 j = 1, n
219 mu = max( 1, kd+2-j )
220 DO 30 i = mu, kd + 1
221 afac( i, j ) = afac( i, j ) - a( i, j )
222 30 CONTINUE
223 40 CONTINUE
224 ELSE
225 DO 60 j = 1, n
226 ml = min( kd+1, n-j+1 )
227 DO 50 i = 1, ml
228 afac( i, j ) = afac( i, j ) - a( i, j )
229 50 CONTINUE
230 60 CONTINUE
231 END IF
232*
233* Compute norm( L*L' - A ) / ( N * norm(A) * EPS )
234*
235 resid = slansb( 'I', uplo, n, kd, afac, ldafac, rwork )
236*
237 resid = ( ( resid / real( n ) ) / anorm ) / eps
238*
239 RETURN
240*
241* End of SPBT01
242*
243 END
subroutine ssyr(uplo, n, alpha, x, incx, a, lda)
SSYR
Definition ssyr.f:132
subroutine sscal(n, sa, sx, incx)
SSCAL
Definition sscal.f:79
subroutine strmv(uplo, trans, diag, n, a, lda, x, incx)
STRMV
Definition strmv.f:147
subroutine spbt01(uplo, n, kd, a, lda, afac, ldafac, rwork, resid)
SPBT01
Definition spbt01.f:119