LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Modules Pages

◆ ssgt01()

subroutine ssgt01 ( integer itype,
character uplo,
integer n,
integer m,
real, dimension( lda, * ) a,
integer lda,
real, dimension( ldb, * ) b,
integer ldb,
real, dimension( ldz, * ) z,
integer ldz,
real, dimension( * ) d,
real, dimension( * ) work,
real, dimension( * ) result )

SSGT01

Purpose:
!> !> SSGT01 checks a decomposition of the form !> !> A Z = B Z D or !> A B Z = Z D or !> B A Z = Z D !> !> where A is a symmetric matrix, B is !> symmetric positive definite, Z is orthogonal, and D is diagonal. !> !> One of the following test ratios is computed: !> !> ITYPE = 1: RESULT(1) = | A Z - B Z D | / ( |A| |Z| n ulp ) !> !> ITYPE = 2: RESULT(1) = | A B Z - Z D | / ( |A| |Z| n ulp ) !> !> ITYPE = 3: RESULT(1) = | B A Z - Z D | / ( |A| |Z| n ulp ) !>
Parameters
[in]ITYPE
!> ITYPE is INTEGER !> The form of the symmetric generalized eigenproblem. !> = 1: A*z = (lambda)*B*z !> = 2: A*B*z = (lambda)*z !> = 3: B*A*z = (lambda)*z !>
[in]UPLO
!> UPLO is CHARACTER*1 !> Specifies whether the upper or lower triangular part of the !> symmetric matrices A and B is stored. !> = 'U': Upper triangular !> = 'L': Lower triangular !>
[in]N
!> N is INTEGER !> The order of the matrix A. N >= 0. !>
[in]M
!> M is INTEGER !> The number of eigenvalues found. 0 <= M <= N. !>
[in]A
!> A is REAL array, dimension (LDA, N) !> The original symmetric matrix A. !>
[in]LDA
!> LDA is INTEGER !> The leading dimension of the array A. LDA >= max(1,N). !>
[in]B
!> B is REAL array, dimension (LDB, N) !> The original symmetric positive definite matrix B. !>
[in]LDB
!> LDB is INTEGER !> The leading dimension of the array B. LDB >= max(1,N). !>
[in]Z
!> Z is REAL array, dimension (LDZ, M) !> The computed eigenvectors of the generalized eigenproblem. !>
[in]LDZ
!> LDZ is INTEGER !> The leading dimension of the array Z. LDZ >= max(1,N). !>
[in]D
!> D is REAL array, dimension (M) !> The computed eigenvalues of the generalized eigenproblem. !>
[out]WORK
!> WORK is REAL array, dimension (N*N) !>
[out]RESULT
!> RESULT is REAL array, dimension (1) !> The test ratio as described above. !>
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 144 of file ssgt01.f.

146*
147* -- LAPACK test routine --
148* -- LAPACK is a software package provided by Univ. of Tennessee, --
149* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
150*
151* .. Scalar Arguments ..
152 CHARACTER UPLO
153 INTEGER ITYPE, LDA, LDB, LDZ, M, N
154* ..
155* .. Array Arguments ..
156 REAL A( LDA, * ), B( LDB, * ), D( * ), RESULT( * ),
157 $ WORK( * ), Z( LDZ, * )
158* ..
159*
160* =====================================================================
161*
162* .. Parameters ..
163 REAL ZERO, ONE
164 parameter( zero = 0.0e0, one = 1.0e0 )
165* ..
166* .. Local Scalars ..
167 INTEGER I
168 REAL ANORM, ULP
169* ..
170* .. External Functions ..
171 REAL SLAMCH, SLANGE, SLANSY
172 EXTERNAL slamch, slange, slansy
173* ..
174* .. External Subroutines ..
175 EXTERNAL sscal, ssymm
176* ..
177* .. Executable Statements ..
178*
179 result( 1 ) = zero
180 IF( n.LE.0 )
181 $ RETURN
182*
183 ulp = slamch( 'Epsilon' )
184*
185* Compute product of 1-norms of A and Z.
186*
187 anorm = slansy( '1', uplo, n, a, lda, work )*
188 $ slange( '1', n, m, z, ldz, work )
189 IF( anorm.EQ.zero )
190 $ anorm = one
191*
192 IF( itype.EQ.1 ) THEN
193*
194* Norm of AZ - BZD
195*
196 CALL ssymm( 'Left', uplo, n, m, one, a, lda, z, ldz, zero,
197 $ work, n )
198 DO 10 i = 1, m
199 CALL sscal( n, d( i ), z( 1, i ), 1 )
200 10 CONTINUE
201 CALL ssymm( 'Left', uplo, n, m, one, b, ldb, z, ldz, -one,
202 $ work, n )
203*
204 result( 1 ) = ( slange( '1', n, m, work, n, work ) / anorm ) /
205 $ ( n*ulp )
206*
207 ELSE IF( itype.EQ.2 ) THEN
208*
209* Norm of ABZ - ZD
210*
211 CALL ssymm( 'Left', uplo, n, m, one, b, ldb, z, ldz, zero,
212 $ work, n )
213 DO 20 i = 1, m
214 CALL sscal( n, d( i ), z( 1, i ), 1 )
215 20 CONTINUE
216 CALL ssymm( 'Left', uplo, n, m, one, a, lda, work, n, -one, z,
217 $ ldz )
218*
219 result( 1 ) = ( slange( '1', n, m, z, ldz, work ) / anorm ) /
220 $ ( n*ulp )
221*
222 ELSE IF( itype.EQ.3 ) THEN
223*
224* Norm of BAZ - ZD
225*
226 CALL ssymm( 'Left', uplo, n, m, one, a, lda, z, ldz, zero,
227 $ work, n )
228 DO 30 i = 1, m
229 CALL sscal( n, d( i ), z( 1, i ), 1 )
230 30 CONTINUE
231 CALL ssymm( 'Left', uplo, n, m, one, b, ldb, work, n, -one, z,
232 $ ldz )
233*
234 result( 1 ) = ( slange( '1', n, m, z, ldz, work ) / anorm ) /
235 $ ( n*ulp )
236 END IF
237*
238 RETURN
239*
240* End of SSGT01
241*
subroutine ssymm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)
SSYMM
Definition ssymm.f:189
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:112
real function slansy(norm, uplo, n, a, lda, work)
SLANSY returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
Definition slansy.f:120
subroutine sscal(n, sa, sx, incx)
SSCAL
Definition sscal.f:79
Here is the call graph for this function:
Here is the caller graph for this function: