LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine dbdt03 ( character  UPLO,
integer  N,
integer  KD,
double precision, dimension( * )  D,
double precision, dimension( * )  E,
double precision, dimension( ldu, * )  U,
integer  LDU,
double precision, dimension( * )  S,
double precision, dimension( ldvt, * )  VT,
integer  LDVT,
double precision, dimension( * )  WORK,
double precision  RESID 
)

DBDT03

Purpose:
 DBDT03 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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.
Date
November 2011

Definition at line 137 of file dbdt03.f.

137 *
138 * -- LAPACK test routine (version 3.4.0) --
139 * -- LAPACK is a software package provided by Univ. of Tennessee, --
140 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
141 * November 2011
142 *
143 * .. Scalar Arguments ..
144  CHARACTER uplo
145  INTEGER kd, ldu, ldvt, n
146  DOUBLE PRECISION resid
147 * ..
148 * .. Array Arguments ..
149  DOUBLE PRECISION d( * ), e( * ), s( * ), u( ldu, * ),
150  $ vt( ldvt, * ), work( * )
151 * ..
152 *
153 * ======================================================================
154 *
155 * .. Parameters ..
156  DOUBLE PRECISION zero, one
157  parameter ( zero = 0.0d+0, one = 1.0d+0 )
158 * ..
159 * .. Local Scalars ..
160  INTEGER i, j
161  DOUBLE PRECISION bnorm, eps
162 * ..
163 * .. External Functions ..
164  LOGICAL lsame
165  INTEGER idamax
166  DOUBLE PRECISION dasum, dlamch
167  EXTERNAL lsame, idamax, dasum, dlamch
168 * ..
169 * .. External Subroutines ..
170  EXTERNAL dgemv
171 * ..
172 * .. Intrinsic Functions ..
173  INTRINSIC abs, dble, max, min
174 * ..
175 * .. Executable Statements ..
176 *
177 * Quick return if possible
178 *
179  resid = zero
180  IF( n.LE.0 )
181  $ RETURN
182 *
183 * Compute B - U * S * V' one column at a time.
184 *
185  bnorm = zero
186  IF( kd.GE.1 ) THEN
187 *
188 * B is bidiagonal.
189 *
190  IF( lsame( uplo, 'U' ) ) THEN
191 *
192 * B is upper bidiagonal.
193 *
194  DO 20 j = 1, n
195  DO 10 i = 1, n
196  work( n+i ) = s( i )*vt( i, j )
197  10 CONTINUE
198  CALL dgemv( 'No transpose', n, n, -one, u, ldu,
199  $ work( n+1 ), 1, zero, work, 1 )
200  work( j ) = work( j ) + d( j )
201  IF( j.GT.1 ) THEN
202  work( j-1 ) = work( j-1 ) + e( j-1 )
203  bnorm = max( bnorm, abs( d( j ) )+abs( e( j-1 ) ) )
204  ELSE
205  bnorm = max( bnorm, abs( d( j ) ) )
206  END IF
207  resid = max( resid, dasum( n, work, 1 ) )
208  20 CONTINUE
209  ELSE
210 *
211 * B is lower bidiagonal.
212 *
213  DO 40 j = 1, n
214  DO 30 i = 1, n
215  work( n+i ) = s( i )*vt( i, j )
216  30 CONTINUE
217  CALL dgemv( 'No transpose', n, n, -one, u, ldu,
218  $ work( n+1 ), 1, zero, work, 1 )
219  work( j ) = work( j ) + d( j )
220  IF( j.LT.n ) THEN
221  work( j+1 ) = work( j+1 ) + e( j )
222  bnorm = max( bnorm, abs( d( j ) )+abs( e( j ) ) )
223  ELSE
224  bnorm = max( bnorm, abs( d( j ) ) )
225  END IF
226  resid = max( resid, dasum( n, work, 1 ) )
227  40 CONTINUE
228  END IF
229  ELSE
230 *
231 * B is diagonal.
232 *
233  DO 60 j = 1, n
234  DO 50 i = 1, n
235  work( n+i ) = s( i )*vt( i, j )
236  50 CONTINUE
237  CALL dgemv( 'No transpose', n, n, -one, u, ldu, work( n+1 ),
238  $ 1, zero, work, 1 )
239  work( j ) = work( j ) + d( j )
240  resid = max( resid, dasum( n, work, 1 ) )
241  60 CONTINUE
242  j = idamax( n, d, 1 )
243  bnorm = abs( d( j ) )
244  END IF
245 *
246 * Compute norm(B - U * S * V') / ( n * norm(B) * EPS )
247 *
248  eps = dlamch( 'Precision' )
249 *
250  IF( bnorm.LE.zero ) THEN
251  IF( resid.NE.zero )
252  $ resid = one / eps
253  ELSE
254  IF( bnorm.GE.resid ) THEN
255  resid = ( resid / bnorm ) / ( dble( n )*eps )
256  ELSE
257  IF( bnorm.LT.one ) THEN
258  resid = ( min( resid, dble( n )*bnorm ) / bnorm ) /
259  $ ( dble( n )*eps )
260  ELSE
261  resid = min( resid / bnorm, dble( n ) ) /
262  $ ( dble( n )*eps )
263  END IF
264  END IF
265  END IF
266 *
267  RETURN
268 *
269 * End of DBDT03
270 *
integer function idamax(N, DX, INCX)
IDAMAX
Definition: idamax.f:53
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:65
subroutine dgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
DGEMV
Definition: dgemv.f:158
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: