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

◆ zsgt01()

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

ZSGT01

Purpose:
!>
!> CDGT01 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 Hermitian matrix, B is Hermitian positive definite,
!> Z is unitary, 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 Hermitian 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
!>          Hermitian 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.  M >= 0.
!> 
[in]A
!>          A is COMPLEX*16 array, dimension (LDA, N)
!>          The original Hermitian matrix A.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A.  LDA >= max(1,N).
!> 
[in]B
!>          B is COMPLEX*16 array, dimension (LDB, N)
!>          The original Hermitian positive definite matrix B.
!> 
[in]LDB
!>          LDB is INTEGER
!>          The leading dimension of the array B.  LDB >= max(1,N).
!> 
[in]Z
!>          Z is COMPLEX*16 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 COMPLEX*16 array, dimension (N*N)
!> 
[out]RWORK
!>          RWORK is DOUBLE PRECISION array, dimension (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 150 of file zsgt01.f.

152*
153* -- LAPACK test routine --
154* -- LAPACK is a software package provided by Univ. of Tennessee, --
155* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
156*
157* .. Scalar Arguments ..
158 CHARACTER UPLO
159 INTEGER ITYPE, LDA, LDB, LDZ, M, N
160* ..
161* .. Array Arguments ..
162 DOUBLE PRECISION D( * ), RESULT( * ), RWORK( * )
163 COMPLEX*16 A( LDA, * ), B( LDB, * ), WORK( * ),
164 $ Z( LDZ, * )
165* ..
166*
167* =====================================================================
168*
169* .. Parameters ..
170 DOUBLE PRECISION ZERO, ONE
171 parameter( zero = 0.0d+0, one = 1.0d+0 )
172 COMPLEX*16 CZERO, CONE
173 parameter( czero = ( 0.0d+0, 0.0d+0 ),
174 $ cone = ( 1.0d+0, 0.0d+0 ) )
175* ..
176* .. Local Scalars ..
177 INTEGER I
178 DOUBLE PRECISION ANORM, ULP
179* ..
180* .. External Functions ..
181 DOUBLE PRECISION DLAMCH, ZLANGE, ZLANHE
182 EXTERNAL dlamch, zlange, zlanhe
183* ..
184* .. External Subroutines ..
185 EXTERNAL zdscal, zhemm
186* ..
187* .. Executable Statements ..
188*
189 result( 1 ) = zero
190 IF( n.LE.0 )
191 $ RETURN
192*
193 ulp = dlamch( 'Epsilon' )
194*
195* Compute product of 1-norms of A and Z.
196*
197 anorm = zlanhe( '1', uplo, n, a, lda, rwork )*
198 $ zlange( '1', n, m, z, ldz, rwork )
199 IF( anorm.EQ.zero )
200 $ anorm = one
201*
202 IF( itype.EQ.1 ) THEN
203*
204* Norm of AZ - BZD
205*
206 CALL zhemm( 'Left', uplo, n, m, cone, a, lda, z, ldz, czero,
207 $ work, n )
208 DO 10 i = 1, m
209 CALL zdscal( n, d( i ), z( 1, i ), 1 )
210 10 CONTINUE
211 CALL zhemm( 'Left', uplo, n, m, cone, b, ldb, z, ldz, -cone,
212 $ work, n )
213*
214 result( 1 ) = ( zlange( '1', n, m, work, n, rwork ) / anorm ) /
215 $ ( n*ulp )
216*
217 ELSE IF( itype.EQ.2 ) THEN
218*
219* Norm of ABZ - ZD
220*
221 CALL zhemm( 'Left', uplo, n, m, cone, b, ldb, z, ldz, czero,
222 $ work, n )
223 DO 20 i = 1, m
224 CALL zdscal( n, d( i ), z( 1, i ), 1 )
225 20 CONTINUE
226 CALL zhemm( 'Left', uplo, n, m, cone, a, lda, work, n, -cone,
227 $ z, ldz )
228*
229 result( 1 ) = ( zlange( '1', n, m, z, ldz, rwork ) / anorm ) /
230 $ ( n*ulp )
231*
232 ELSE IF( itype.EQ.3 ) THEN
233*
234* Norm of BAZ - ZD
235*
236 CALL zhemm( 'Left', uplo, n, m, cone, a, lda, z, ldz, czero,
237 $ work, n )
238 DO 30 i = 1, m
239 CALL zdscal( n, d( i ), z( 1, i ), 1 )
240 30 CONTINUE
241 CALL zhemm( 'Left', uplo, n, m, cone, b, ldb, work, n, -cone,
242 $ z, ldz )
243*
244 result( 1 ) = ( zlange( '1', n, m, z, ldz, rwork ) / anorm ) /
245 $ ( n*ulp )
246 END IF
247*
248 RETURN
249*
250* End of ZDGT01
251*
subroutine zhemm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)
ZHEMM
Definition zhemm.f:191
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
double precision function zlange(norm, m, n, a, lda, work)
ZLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition zlange.f:113
double precision function zlanhe(norm, uplo, n, a, lda, work)
ZLANHE returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
Definition zlanhe.f:122
subroutine zdscal(n, da, zx, incx)
ZDSCAL
Definition zdscal.f:78
Here is the call graph for this function:
Here is the caller graph for this function: