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

◆ sget54()

subroutine sget54 ( integer n,
real, dimension( lda, * ) a,
integer lda,
real, dimension( ldb, * ) b,
integer ldb,
real, dimension( lds, * ) s,
integer lds,
real, dimension( ldt, * ) t,
integer ldt,
real, dimension( ldu, * ) u,
integer ldu,
real, dimension( ldv, * ) v,
integer ldv,
real, dimension( * ) work,
real result )

SGET54

Purpose:
!> !> SGET54 checks a generalized decomposition of the form !> !> A = U*S*V' and B = U*T* V' !> !> where ' means transpose and U and V are orthogonal. !> !> 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, SGET54 does nothing. !> It must be at least zero. !>
[in]A
!> A is REAL 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 REAL 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 REAL 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 REAL 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 REAL 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 REAL 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 REAL array, dimension (3*N**2) !>
[out]RESULT
!> RESULT is REAL !> 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 sget54.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 REAL RESULT
164* ..
165* .. Array Arguments ..
166 REAL A( LDA, * ), B( LDB, * ), S( LDS, * ),
167 $ T( LDT, * ), U( LDU, * ), V( LDV, * ),
168 $ WORK( * )
169* ..
170*
171* =====================================================================
172*
173* .. Parameters ..
174 REAL ZERO, ONE
175 parameter( zero = 0.0e+0, one = 1.0e+0 )
176* ..
177* .. Local Scalars ..
178 REAL ABNORM, ULP, UNFL, WNORM
179* ..
180* .. Local Arrays ..
181 REAL DUM( 1 )
182* ..
183* .. External Functions ..
184 REAL SLAMCH, SLANGE
185 EXTERNAL slamch, slange
186* ..
187* .. External Subroutines ..
188 EXTERNAL sgemm, slacpy
189* ..
190* .. Intrinsic Functions ..
191 INTRINSIC max, min, real
192* ..
193* .. Executable Statements ..
194*
195 result = zero
196 IF( n.LE.0 )
197 $ RETURN
198*
199* Constants
200*
201 unfl = slamch( 'Safe minimum' )
202 ulp = slamch( 'Epsilon' )*slamch( 'Base' )
203*
204* compute the norm of (A,B)
205*
206 CALL slacpy( 'Full', n, n, a, lda, work, n )
207 CALL slacpy( 'Full', n, n, b, ldb, work( n*n+1 ), n )
208 abnorm = max( slange( '1', n, 2*n, work, n, dum ), unfl )
209*
210* Compute W1 = A - U*S*V', and put in the array WORK(1:N*N)
211*
212 CALL slacpy( ' ', n, n, a, lda, work, n )
213 CALL sgemm( 'N', 'N', n, n, n, one, u, ldu, s, lds, zero,
214 $ work( n*n+1 ), n )
215*
216 CALL sgemm( 'N', 'C', n, n, n, -one, work( n*n+1 ), n, v, ldv,
217 $ one, work, n )
218*
219* Compute W2 = B - U*T*V', and put in the workarray W(N*N+1:2*N*N)
220*
221 CALL slacpy( ' ', n, n, b, ldb, work( n*n+1 ), n )
222 CALL sgemm( 'N', 'N', n, n, n, one, u, ldu, t, ldt, zero,
223 $ work( 2*n*n+1 ), n )
224*
225 CALL sgemm( 'N', 'C', n, n, n, -one, work( 2*n*n+1 ), n, v, ldv,
226 $ one, work( n*n+1 ), n )
227*
228* Compute norm(W)/ ( ulp*norm((A,B)) )
229*
230 wnorm = slange( '1', n, 2*n, work, n, dum )
231*
232 IF( abnorm.GT.wnorm ) THEN
233 result = ( wnorm / abnorm ) / ( 2*n*ulp )
234 ELSE
235 IF( abnorm.LT.one ) THEN
236 result = ( min( wnorm, 2*n*abnorm ) / abnorm ) / ( 2*n*ulp )
237 ELSE
238 result = min( wnorm / abnorm, real( 2*n ) ) / ( 2*n*ulp )
239 END IF
240 END IF
241*
242 RETURN
243*
244* End of SGET54
245*
subroutine sgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
SGEMM
Definition sgemm.f:188
subroutine slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
Definition slacpy.f:101
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
Here is the call graph for this function:
Here is the caller graph for this function: