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

◆ zget54()

subroutine zget54 ( integer n,
complex*16, dimension( lda, * ) a,
integer lda,
complex*16, dimension( ldb, * ) b,
integer ldb,
complex*16, dimension( lds, * ) s,
integer lds,
complex*16, dimension( ldt, * ) t,
integer ldt,
complex*16, dimension( ldu, * ) u,
integer ldu,
complex*16, dimension( ldv, * ) v,
integer ldv,
complex*16, dimension( * ) work,
double precision result )

ZGET54

Purpose:
!>
!> ZGET54 checks a generalized decomposition of the form
!>
!>          A = U*S*V'  and B = U*T* V'
!>
!> where ' means conjugate transpose and U and V are unitary.
!>
!> Specifically,
!>
!>   RESULT = ||( A - U*S*V', B - U*T*V' )|| / (||( A, B )||*n*ulp )
!> 
Parameters
[in]N
!>          N is INTEGER
!>          The size of the matrix.  If it is zero, DGET54 does nothing.
!>          It must be at least zero.
!> 
[in]A
!>          A is COMPLEX*16 array, dimension (LDA, N)
!>          The original (unfactored) matrix A.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of A.  It must be at least 1
!>          and at least N.
!> 
[in]B
!>          B is COMPLEX*16 array, dimension (LDB, N)
!>          The original (unfactored) matrix B.
!> 
[in]LDB
!>          LDB is INTEGER
!>          The leading dimension of B.  It must be at least 1
!>          and at least N.
!> 
[in]S
!>          S is COMPLEX*16 array, dimension (LDS, N)
!>          The factored matrix S.
!> 
[in]LDS
!>          LDS is INTEGER
!>          The leading dimension of S.  It must be at least 1
!>          and at least N.
!> 
[in]T
!>          T is COMPLEX*16 array, dimension (LDT, N)
!>          The factored matrix T.
!> 
[in]LDT
!>          LDT is INTEGER
!>          The leading dimension of T.  It must be at least 1
!>          and at least N.
!> 
[in]U
!>          U is COMPLEX*16 array, dimension (LDU, N)
!>          The orthogonal matrix on the left-hand side in the
!>          decomposition.
!> 
[in]LDU
!>          LDU is INTEGER
!>          The leading dimension of U.  LDU must be at least N and
!>          at least 1.
!> 
[in]V
!>          V is COMPLEX*16 array, dimension (LDV, N)
!>          The orthogonal matrix on the left-hand side in the
!>          decomposition.
!> 
[in]LDV
!>          LDV is INTEGER
!>          The leading dimension of V.  LDV must be at least N and
!>          at least 1.
!> 
[out]WORK
!>          WORK is COMPLEX*16 array, dimension (3*N**2)
!> 
[out]RESULT
!>          RESULT is DOUBLE PRECISION
!>          The value RESULT, It is currently limited to 1/ulp, to
!>          avoid overflow. Errors are flagged by RESULT=10/ulp.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 154 of file zget54.f.

156*
157* -- LAPACK test routine --
158* -- LAPACK is a software package provided by Univ. of Tennessee, --
159* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
160*
161* .. Scalar Arguments ..
162 INTEGER LDA, LDB, LDS, LDT, LDU, LDV, N
163 DOUBLE PRECISION RESULT
164* ..
165* .. Array Arguments ..
166 COMPLEX*16 A( LDA, * ), B( LDB, * ), S( LDS, * ),
167 $ T( LDT, * ), U( LDU, * ), V( LDV, * ),
168 $ WORK( * )
169* ..
170*
171* =====================================================================
172*
173* .. Parameters ..
174 DOUBLE PRECISION ZERO, ONE
175 parameter( zero = 0.0d+0, one = 1.0d+0 )
176 COMPLEX*16 CZERO, CONE
177 parameter( czero = ( 0.0d+0, 0.0d+0 ),
178 $ cone = ( 1.0d+0, 0.0d+0 ) )
179* ..
180* .. Local Scalars ..
181 DOUBLE PRECISION ABNORM, ULP, UNFL, WNORM
182* ..
183* .. Local Arrays ..
184 DOUBLE PRECISION DUM( 1 )
185* ..
186* .. External Functions ..
187 DOUBLE PRECISION DLAMCH, ZLANGE
188 EXTERNAL dlamch, zlange
189* ..
190* .. External Subroutines ..
191 EXTERNAL zgemm, zlacpy
192* ..
193* .. Intrinsic Functions ..
194 INTRINSIC dble, max, min
195* ..
196* .. Executable Statements ..
197*
198 result = zero
199 IF( n.LE.0 )
200 $ RETURN
201*
202* Constants
203*
204 unfl = dlamch( 'Safe minimum' )
205 ulp = dlamch( 'Epsilon' )*dlamch( 'Base' )
206*
207* compute the norm of (A,B)
208*
209 CALL zlacpy( 'Full', n, n, a, lda, work, n )
210 CALL zlacpy( 'Full', n, n, b, ldb, work( n*n+1 ), n )
211 abnorm = max( zlange( '1', n, 2*n, work, n, dum ), unfl )
212*
213* Compute W1 = A - U*S*V', and put in the array WORK(1:N*N)
214*
215 CALL zlacpy( ' ', n, n, a, lda, work, n )
216 CALL zgemm( 'N', 'N', n, n, n, cone, u, ldu, s, lds, czero,
217 $ work( n*n+1 ), n )
218*
219 CALL zgemm( 'N', 'C', n, n, n, -cone, work( n*n+1 ), n, v, ldv,
220 $ cone, work, n )
221*
222* Compute W2 = B - U*T*V', and put in the workarray W(N*N+1:2*N*N)
223*
224 CALL zlacpy( ' ', n, n, b, ldb, work( n*n+1 ), n )
225 CALL zgemm( 'N', 'N', n, n, n, cone, u, ldu, t, ldt, czero,
226 $ work( 2*n*n+1 ), n )
227*
228 CALL zgemm( 'N', 'C', n, n, n, -cone, work( 2*n*n+1 ), n, v, ldv,
229 $ cone, work( n*n+1 ), n )
230*
231* Compute norm(W)/ ( ulp*norm((A,B)) )
232*
233 wnorm = zlange( '1', n, 2*n, work, n, dum )
234*
235 IF( abnorm.GT.wnorm ) THEN
236 result = ( wnorm / abnorm ) / ( 2*n*ulp )
237 ELSE
238 IF( abnorm.LT.one ) THEN
239 result = ( min( wnorm, 2*n*abnorm ) / abnorm ) / ( 2*n*ulp )
240 ELSE
241 result = min( wnorm / abnorm, dble( 2*n ) ) / ( 2*n*ulp )
242 END IF
243 END IF
244*
245 RETURN
246*
247* End of ZGET54
248*
subroutine zgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
ZGEMM
Definition zgemm.f:188
subroutine zlacpy(uplo, m, n, a, lda, b, ldb)
ZLACPY copies all or part of one two-dimensional array to another.
Definition zlacpy.f:101
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
Here is the call graph for this function:
Here is the caller graph for this function: