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

◆ dsgt01()

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

DSGT01

Purpose:
 DDGT01 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 DOUBLE PRECISION array, dimension (M)
          The computed eigenvalues of the generalized eigenproblem.
[out]WORK
          WORK is DOUBLE PRECISION array, dimension (N*N)
[out]RESULT
          RESULT is DOUBLE PRECISION 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 dsgt01.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 DOUBLE PRECISION A( LDA, * ), B( LDB, * ), D( * ), RESULT( * ),
157 $ WORK( * ), Z( LDZ, * )
158* ..
159*
160* =====================================================================
161*
162* .. Parameters ..
163 DOUBLE PRECISION ZERO, ONE
164 parameter( zero = 0.0d0, one = 1.0d0 )
165* ..
166* .. Local Scalars ..
167 INTEGER I
168 DOUBLE PRECISION ANORM, ULP
169* ..
170* .. External Functions ..
171 DOUBLE PRECISION DLAMCH, DLANGE, DLANSY
172 EXTERNAL dlamch, dlange, dlansy
173* ..
174* .. External Subroutines ..
175 EXTERNAL dscal, dsymm
176* ..
177* .. Executable Statements ..
178*
179 result( 1 ) = zero
180 IF( n.LE.0 )
181 $ RETURN
182*
183 ulp = dlamch( 'Epsilon' )
184*
185* Compute product of 1-norms of A and Z.
186*
187 anorm = dlansy( '1', uplo, n, a, lda, work )*
188 $ dlange( '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 dsymm( 'Left', uplo, n, m, one, a, lda, z, ldz, zero,
197 $ work, n )
198 DO 10 i = 1, m
199 CALL dscal( n, d( i ), z( 1, i ), 1 )
200 10 CONTINUE
201 CALL dsymm( 'Left', uplo, n, m, one, b, ldb, z, ldz, -one,
202 $ work, n )
203*
204 result( 1 ) = ( dlange( '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 dsymm( 'Left', uplo, n, m, one, b, ldb, z, ldz, zero,
212 $ work, n )
213 DO 20 i = 1, m
214 CALL dscal( n, d( i ), z( 1, i ), 1 )
215 20 CONTINUE
216 CALL dsymm( 'Left', uplo, n, m, one, a, lda, work, n, -one, z,
217 $ ldz )
218*
219 result( 1 ) = ( dlange( '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 dsymm( 'Left', uplo, n, m, one, a, lda, z, ldz, zero,
227 $ work, n )
228 DO 30 i = 1, m
229 CALL dscal( n, d( i ), z( 1, i ), 1 )
230 30 CONTINUE
231 CALL dsymm( 'Left', uplo, n, m, one, b, ldb, work, n, -one, z,
232 $ ldz )
233*
234 result( 1 ) = ( dlange( '1', n, m, z, ldz, work ) / anorm ) /
235 $ ( n*ulp )
236 END IF
237*
238 RETURN
239*
240* End of DSGT01
241*
subroutine dsymm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)
DSYMM
Definition dsymm.f:189
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
double precision function dlange(norm, m, n, a, lda, work)
DLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition dlange.f:114
double precision function dlansy(norm, uplo, n, a, lda, work)
DLANSY returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
Definition dlansy.f:122
subroutine dscal(n, da, dx, incx)
DSCAL
Definition dscal.f:79
Here is the call graph for this function:
Here is the caller graph for this function: