LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ ssbt21()

subroutine ssbt21 ( character  uplo,
integer  n,
integer  ka,
integer  ks,
real, dimension( lda, * )  a,
integer  lda,
real, dimension( * )  d,
real, dimension( * )  e,
real, dimension( ldu, * )  u,
integer  ldu,
real, dimension( * )  work,
real, dimension( 2 )  result 
)

SSBT21

Purpose:
 SSBT21  generally checks a decomposition of the form

         A = U S U**T

 where **T means transpose, A is symmetric banded, U is
 orthogonal, and S is diagonal (if KS=0) or symmetric
 tridiagonal (if KS=1).

 Specifically:

         RESULT(1) = | A - U S U**T | / ( |A| n ulp ) and
         RESULT(2) = | I - U U**T | / ( n ulp )
Parameters
[in]UPLO
          UPLO is CHARACTER
          If UPLO='U', the upper triangle of A and V will be used and
          the (strictly) lower triangle will not be referenced.
          If UPLO='L', the lower triangle of A and V will be used and
          the (strictly) upper triangle will not be referenced.
[in]N
          N is INTEGER
          The size of the matrix.  If it is zero, SSBT21 does nothing.
          It must be at least zero.
[in]KA
          KA is INTEGER
          The bandwidth of the matrix A.  It must be at least zero.  If
          it is larger than N-1, then max( 0, N-1 ) will be used.
[in]KS
          KS is INTEGER
          The bandwidth of the matrix S.  It may only be zero or one.
          If zero, then S is diagonal, and E is not referenced.  If
          one, then S is symmetric tri-diagonal.
[in]A
          A is REAL array, dimension (LDA, N)
          The original (unfactored) matrix.  It is assumed to be
          symmetric, and only the upper (UPLO='U') or only the lower
          (UPLO='L') will be referenced.
[in]LDA
          LDA is INTEGER
          The leading dimension of A.  It must be at least 1
          and at least min( KA, N-1 ).
[in]D
          D is REAL array, dimension (N)
          The diagonal of the (symmetric tri-) diagonal matrix S.
[in]E
          E is REAL array, dimension (N-1)
          The off-diagonal of the (symmetric tri-) diagonal matrix S.
          E(1) is the (1,2) and (2,1) element, E(2) is the (2,3) and
          (3,2) element, etc.
          Not referenced if KS=0.
[in]U
          U is REAL array, dimension (LDU, N)
          The orthogonal matrix in the decomposition, expressed as a
          dense matrix (i.e., not as a product of Householder
          transformations, Givens transformations, etc.)
[in]LDU
          LDU is INTEGER
          The leading dimension of U.  LDU must be at least N and
          at least 1.
[out]WORK
          WORK is REAL array, dimension (N**2+N)
[out]RESULT
          RESULT is REAL array, dimension (2)
          The values computed by the two tests described above.  The
          values are currently limited to 1/ulp, to avoid overflow.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 145 of file ssbt21.f.

147*
148* -- LAPACK test routine --
149* -- LAPACK is a software package provided by Univ. of Tennessee, --
150* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
151*
152* .. Scalar Arguments ..
153 CHARACTER UPLO
154 INTEGER KA, KS, LDA, LDU, N
155* ..
156* .. Array Arguments ..
157 REAL A( LDA, * ), D( * ), E( * ), RESULT( 2 ),
158 $ U( LDU, * ), WORK( * )
159* ..
160*
161* =====================================================================
162*
163* .. Parameters ..
164 REAL ZERO, ONE
165 parameter( zero = 0.0e0, one = 1.0e0 )
166* ..
167* .. Local Scalars ..
168 LOGICAL LOWER
169 CHARACTER CUPLO
170 INTEGER IKA, J, JC, JR, LW
171 REAL ANORM, ULP, UNFL, WNORM
172* ..
173* .. External Functions ..
174 LOGICAL LSAME
175 REAL SLAMCH, SLANGE, SLANSB, SLANSP
176 EXTERNAL lsame, slamch, slange, slansb, slansp
177* ..
178* .. External Subroutines ..
179 EXTERNAL sgemm, sspr, sspr2
180* ..
181* .. Intrinsic Functions ..
182 INTRINSIC max, min, real
183* ..
184* .. Executable Statements ..
185*
186* Constants
187*
188 result( 1 ) = zero
189 result( 2 ) = zero
190 IF( n.LE.0 )
191 $ RETURN
192*
193 ika = max( 0, min( n-1, ka ) )
194 lw = ( n*( n+1 ) ) / 2
195*
196 IF( lsame( uplo, 'U' ) ) THEN
197 lower = .false.
198 cuplo = 'U'
199 ELSE
200 lower = .true.
201 cuplo = 'L'
202 END IF
203*
204 unfl = slamch( 'Safe minimum' )
205 ulp = slamch( 'Epsilon' )*slamch( 'Base' )
206*
207* Some Error Checks
208*
209* Do Test 1
210*
211* Norm of A:
212*
213 anorm = max( slansb( '1', cuplo, n, ika, a, lda, work ), unfl )
214*
215* Compute error matrix: Error = A - U S U**T
216*
217* Copy A from SB to SP storage format.
218*
219 j = 0
220 DO 50 jc = 1, n
221 IF( lower ) THEN
222 DO 10 jr = 1, min( ika+1, n+1-jc )
223 j = j + 1
224 work( j ) = a( jr, jc )
225 10 CONTINUE
226 DO 20 jr = ika + 2, n + 1 - jc
227 j = j + 1
228 work( j ) = zero
229 20 CONTINUE
230 ELSE
231 DO 30 jr = ika + 2, jc
232 j = j + 1
233 work( j ) = zero
234 30 CONTINUE
235 DO 40 jr = min( ika, jc-1 ), 0, -1
236 j = j + 1
237 work( j ) = a( ika+1-jr, jc )
238 40 CONTINUE
239 END IF
240 50 CONTINUE
241*
242 DO 60 j = 1, n
243 CALL sspr( cuplo, n, -d( j ), u( 1, j ), 1, work )
244 60 CONTINUE
245*
246 IF( n.GT.1 .AND. ks.EQ.1 ) THEN
247 DO 70 j = 1, n - 1
248 CALL sspr2( cuplo, n, -e( j ), u( 1, j ), 1, u( 1, j+1 ), 1,
249 $ work )
250 70 CONTINUE
251 END IF
252 wnorm = slansp( '1', cuplo, n, work, work( lw+1 ) )
253*
254 IF( anorm.GT.wnorm ) THEN
255 result( 1 ) = ( wnorm / anorm ) / ( n*ulp )
256 ELSE
257 IF( anorm.LT.one ) THEN
258 result( 1 ) = ( min( wnorm, n*anorm ) / anorm ) / ( n*ulp )
259 ELSE
260 result( 1 ) = min( wnorm / anorm, real( n ) ) / ( n*ulp )
261 END IF
262 END IF
263*
264* Do Test 2
265*
266* Compute U U**T - I
267*
268 CALL sgemm( 'N', 'C', n, n, n, one, u, ldu, u, ldu, zero, work,
269 $ n )
270*
271 DO 80 j = 1, n
272 work( ( n+1 )*( j-1 )+1 ) = work( ( n+1 )*( j-1 )+1 ) - one
273 80 CONTINUE
274*
275 result( 2 ) = min( slange( '1', n, n, work, n, work( n**2+1 ) ),
276 $ real( n ) ) / ( n*ulp )
277*
278 RETURN
279*
280* End of SSBT21
281*
subroutine sgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
SGEMM
Definition sgemm.f:188
subroutine sspr2(uplo, n, alpha, x, incx, y, incy, ap)
SSPR2
Definition sspr2.f:142
subroutine sspr(uplo, n, alpha, x, incx, ap)
SSPR
Definition sspr.f:127
real function slamch(cmach)
SLAMCH
Definition slamch.f:68
real function slange(norm, m, n, a, lda, work)
SLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition slange.f:114
real function slansb(norm, uplo, n, k, ab, ldab, work)
SLANSB returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
Definition slansb.f:129
real function slansp(norm, uplo, n, ap, work)
SLANSP returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
Definition slansp.f:114
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: