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

◆ zbdt03()

subroutine zbdt03 ( character  uplo,
integer  n,
integer  kd,
double precision, dimension( * )  d,
double precision, dimension( * )  e,
complex*16, dimension( ldu, * )  u,
integer  ldu,
double precision, dimension( * )  s,
complex*16, dimension( ldvt, * )  vt,
integer  ldvt,
complex*16, dimension( * )  work,
double precision  resid 
)

ZBDT03

Purpose:
 ZBDT03 reconstructs a bidiagonal matrix B from its SVD:
    S = U' * B * V
 where U and V are orthogonal matrices and S is diagonal.

 The test ratio to test the singular value decomposition is
    RESID = norm( B - U * S * VT ) / ( n * norm(B) * EPS )
 where VT = V' and EPS is the machine precision.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          Specifies whether the matrix B is upper or lower bidiagonal.
          = 'U':  Upper bidiagonal
          = 'L':  Lower bidiagonal
[in]N
          N is INTEGER
          The order of the matrix B.
[in]KD
          KD is INTEGER
          The bandwidth of the bidiagonal matrix B.  If KD = 1, the
          matrix B is bidiagonal, and if KD = 0, B is diagonal and E is
          not referenced.  If KD is greater than 1, it is assumed to be
          1, and if KD is less than 0, it is assumed to be 0.
[in]D
          D is DOUBLE PRECISION array, dimension (N)
          The n diagonal elements of the bidiagonal matrix B.
[in]E
          E is DOUBLE PRECISION array, dimension (N-1)
          The (n-1) superdiagonal elements of the bidiagonal matrix B
          if UPLO = 'U', or the (n-1) subdiagonal elements of B if
          UPLO = 'L'.
[in]U
          U is COMPLEX*16 array, dimension (LDU,N)
          The n by n orthogonal matrix U in the reduction B = U'*A*P.
[in]LDU
          LDU is INTEGER
          The leading dimension of the array U.  LDU >= max(1,N)
[in]S
          S is DOUBLE PRECISION array, dimension (N)
          The singular values from the SVD of B, sorted in decreasing
          order.
[in]VT
          VT is COMPLEX*16 array, dimension (LDVT,N)
          The n by n orthogonal matrix V' in the reduction
          B = U * S * V'.
[in]LDVT
          LDVT is INTEGER
          The leading dimension of the array VT.
[out]WORK
          WORK is COMPLEX*16 array, dimension (2*N)
[out]RESID
          RESID is DOUBLE PRECISION
          The test ratio:  norm(B - U * S * V') / ( n * norm(A) * EPS )
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 133 of file zbdt03.f.

135*
136* -- LAPACK test routine --
137* -- LAPACK is a software package provided by Univ. of Tennessee, --
138* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
139*
140* .. Scalar Arguments ..
141 CHARACTER UPLO
142 INTEGER KD, LDU, LDVT, N
143 DOUBLE PRECISION RESID
144* ..
145* .. Array Arguments ..
146 DOUBLE PRECISION D( * ), E( * ), S( * )
147 COMPLEX*16 U( LDU, * ), VT( LDVT, * ), WORK( * )
148* ..
149*
150* ======================================================================
151*
152* .. Parameters ..
153 DOUBLE PRECISION ZERO, ONE
154 parameter( zero = 0.0d+0, one = 1.0d+0 )
155* ..
156* .. Local Scalars ..
157 INTEGER I, J
158 DOUBLE PRECISION BNORM, EPS
159* ..
160* .. External Functions ..
161 LOGICAL LSAME
162 INTEGER IDAMAX
163 DOUBLE PRECISION DLAMCH, DZASUM
164 EXTERNAL lsame, idamax, dlamch, dzasum
165* ..
166* .. External Subroutines ..
167 EXTERNAL zgemv
168* ..
169* .. Intrinsic Functions ..
170 INTRINSIC abs, dble, dcmplx, max, min
171* ..
172* .. Executable Statements ..
173*
174* Quick return if possible
175*
176 resid = zero
177 IF( n.LE.0 )
178 $ RETURN
179*
180* Compute B - U * S * V' one column at a time.
181*
182 bnorm = zero
183 IF( kd.GE.1 ) THEN
184*
185* B is bidiagonal.
186*
187 IF( lsame( uplo, 'U' ) ) THEN
188*
189* B is upper bidiagonal.
190*
191 DO 20 j = 1, n
192 DO 10 i = 1, n
193 work( n+i ) = s( i )*vt( i, j )
194 10 CONTINUE
195 CALL zgemv( 'No transpose', n, n, -dcmplx( one ), u, ldu,
196 $ work( n+1 ), 1, dcmplx( zero ), work, 1 )
197 work( j ) = work( j ) + d( j )
198 IF( j.GT.1 ) THEN
199 work( j-1 ) = work( j-1 ) + e( j-1 )
200 bnorm = max( bnorm, abs( d( j ) )+abs( e( j-1 ) ) )
201 ELSE
202 bnorm = max( bnorm, abs( d( j ) ) )
203 END IF
204 resid = max( resid, dzasum( n, work, 1 ) )
205 20 CONTINUE
206 ELSE
207*
208* B is lower bidiagonal.
209*
210 DO 40 j = 1, n
211 DO 30 i = 1, n
212 work( n+i ) = s( i )*vt( i, j )
213 30 CONTINUE
214 CALL zgemv( 'No transpose', n, n, -dcmplx( one ), u, ldu,
215 $ work( n+1 ), 1, dcmplx( zero ), work, 1 )
216 work( j ) = work( j ) + d( j )
217 IF( j.LT.n ) THEN
218 work( j+1 ) = work( j+1 ) + e( j )
219 bnorm = max( bnorm, abs( d( j ) )+abs( e( j ) ) )
220 ELSE
221 bnorm = max( bnorm, abs( d( j ) ) )
222 END IF
223 resid = max( resid, dzasum( n, work, 1 ) )
224 40 CONTINUE
225 END IF
226 ELSE
227*
228* B is diagonal.
229*
230 DO 60 j = 1, n
231 DO 50 i = 1, n
232 work( n+i ) = s( i )*vt( i, j )
233 50 CONTINUE
234 CALL zgemv( 'No transpose', n, n, -dcmplx( one ), u, ldu,
235 $ work( n+1 ), 1, dcmplx( zero ), work, 1 )
236 work( j ) = work( j ) + d( j )
237 resid = max( resid, dzasum( n, work, 1 ) )
238 60 CONTINUE
239 j = idamax( n, d, 1 )
240 bnorm = abs( d( j ) )
241 END IF
242*
243* Compute norm(B - U * S * V') / ( n * norm(B) * EPS )
244*
245 eps = dlamch( 'Precision' )
246*
247 IF( bnorm.LE.zero ) THEN
248 IF( resid.NE.zero )
249 $ resid = one / eps
250 ELSE
251 IF( bnorm.GE.resid ) THEN
252 resid = ( resid / bnorm ) / ( dble( n )*eps )
253 ELSE
254 IF( bnorm.LT.one ) THEN
255 resid = ( min( resid, dble( n )*bnorm ) / bnorm ) /
256 $ ( dble( n )*eps )
257 ELSE
258 resid = min( resid / bnorm, dble( n ) ) /
259 $ ( dble( n )*eps )
260 END IF
261 END IF
262 END IF
263*
264 RETURN
265*
266* End of ZBDT03
267*
double precision function dzasum(n, zx, incx)
DZASUM
Definition dzasum.f:72
subroutine zgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
ZGEMV
Definition zgemv.f:160
integer function idamax(n, dx, incx)
IDAMAX
Definition idamax.f:71
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: