LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zbdt05 ( integer  M,
integer  N,
complex*16, dimension( lda, * )  A,
integer  LDA,
double precision, dimension( * )  S,
integer  NS,
complex*16, dimension( * )  U,
integer  LDU,
complex*16, dimension( ldvt, * )  VT,
integer  LDVT,
complex*16, dimension( * )  WORK,
double precision  RESID 
)
Purpose:

ZBDT05 reconstructs a bidiagonal matrix B from its (partial) 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( S - U' * B * V ) / ( n * norm(B) * EPS ) where VT = V' and EPS is the machine precision.

Parameters
[in]M
          M is INTEGER
          The number of rows of the matrices A and U.
[in]N
          N is INTEGER
          The number of columns of the matrices A and VT.
[in]A
          A is COMPLEX*16 array, dimension (LDA,N)
          The m by n matrix A.

 \param[in] LDA
 \verbatim
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,M).
[in]S
          S is DOUBLE PRECISION array, dimension (NS)
          The singular values from the (partial) SVD of B, sorted in 
          decreasing order.
[in]NS
          NS is INTEGER
          The number of singular values/vectors from the (partial) 
          SVD of B.
[in]U
          U is COMPLEX*16 array, dimension (LDU,NS)
          The n by ns orthogonal matrix U in S = U' * B * V.
[in]LDU
          LDU is INTEGER
          The leading dimension of the array U.  LDU >= max(1,N)
[in]VT
          VT is COMPLEX*16 array, dimension (LDVT,N)
          The n by ns orthogonal matrix V in S = U' * B * V.
[in]LDVT
          LDVT is INTEGER
          The leading dimension of the array VT.
[out]WORK
          WORK is COMPLEX*16 array, dimension (M,N)
[out]RESID
          RESID is DOUBLE PRECISION
          The test ratio:  norm(S - U' * A * V) / ( n * norm(A) * EPS )
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 125 of file zbdt05.f.

125 *
126 * -- LAPACK test routine (version 3.4.0) --
127 * -- LAPACK is a software package provided by Univ. of Tennessee, --
128 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
129 * November 2011
130 *
131 * .. Scalar Arguments ..
132  CHARACTER uplo
133  INTEGER lda, ldu, ldvt, m, n, ns
134  DOUBLE PRECISION resid
135 * ..
136 * .. Array Arguments ..
137  DOUBLE PRECISION s( * )
138  COMPLEX*16 a( lda, * ), u( * ), vt( ldvt, * ), work( * )
139 * ..
140 *
141 * ======================================================================
142 *
143 * .. Parameters ..
144  DOUBLE PRECISION zero, one
145  parameter ( zero = 0.0d+0, one = 1.0d+0 )
146  COMPLEX*16 czero, cone
147  parameter ( czero = ( 0.0d+0, 0.0d+0 ),
148  $ cone = ( 1.0d+0, 0.0d+0 ) )
149 * ..
150 * .. Local Scalars ..
151  INTEGER i, j
152  DOUBLE PRECISION anorm, eps
153 * ..
154 * .. Local Arrays ..
155  DOUBLE PRECISION dum( 1 )
156 * ..
157 * .. External Functions ..
158  LOGICAL lsame
159  INTEGER idamax
160  DOUBLE PRECISION dasum, dlamch, zlange
161  EXTERNAL lsame, idamax, dasum, dlamch, zlange
162  DOUBLE PRECISION dzasum
163 * ..
164 * .. External Subroutines ..
165  EXTERNAL zgemm
166 * ..
167 * .. Intrinsic Functions ..
168  INTRINSIC abs, dble, max, min
169 * ..
170 * .. Executable Statements ..
171 *
172 * Quick return if possible.
173 *
174  resid = zero
175  IF( min( m, n ).LE.0 .OR. ns.LE.0 )
176  $ RETURN
177 *
178  eps = dlamch( 'Precision' )
179  anorm = zlange( 'M', m, n, a, lda, dum )
180 *
181 * Compute U' * A * V.
182 *
183  CALL zgemm( 'N', 'C', m, ns, n, cone, a, lda, vt,
184  $ ldvt, czero, work( 1+ns*ns ), m )
185  CALL zgemm( 'C', 'N', ns, ns, m, -cone, u, ldu, work( 1+ns*ns ),
186  $ m, czero, work, ns )
187 *
188 * norm(S - U' * B * V)
189 *
190  j = 0
191  DO 10 i = 1, ns
192  work( j+i ) = work( j+i ) + dcmplx( s( i ), zero )
193  resid = max( resid, dzasum( ns, work( j+1 ), 1 ) )
194  j = j + ns
195  10 CONTINUE
196 *
197  IF( anorm.LE.zero ) THEN
198  IF( resid.NE.zero )
199  $ resid = one / eps
200  ELSE
201  IF( anorm.GE.resid ) THEN
202  resid = ( resid / anorm ) / ( dble( n )*eps )
203  ELSE
204  IF( anorm.LT.one ) THEN
205  resid = ( min( resid, dble( n )*anorm ) / anorm ) /
206  $ ( dble( n )*eps )
207  ELSE
208  resid = min( resid / anorm, dble( n ) ) /
209  $ ( dble( n )*eps )
210  END IF
211  END IF
212  END IF
213 *
214  RETURN
215 *
216 * End of ZBDT05
217 *
integer function idamax(N, DX, INCX)
IDAMAX
Definition: idamax.f:53
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:65
subroutine zgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
ZGEMM
Definition: zgemm.f:189
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:117
double precision function dzasum(N, ZX, INCX)
DZASUM
Definition: dzasum.f:54
double precision function dasum(N, DX, INCX)
DASUM
Definition: dasum.f:53
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: