LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine sbdt05 ( integer  M,
integer  N,
real, dimension( lda, * )  A,
integer  LDA,
real, dimension( * )  S,
integer  NS,
real, dimension( ldu, * )  U,
integer  LDU,
real, dimension( ldvt, * )  VT,
integer  LDVT,
real, dimension( * )  WORK,
real  RESID 
)
Purpose:

SBDT05 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 REAL 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 REAL 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 REAL 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 REAL 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 REAL array, dimension (M,N)
[out]RESID
          RESID is REAL
          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 126 of file sbdt05.f.

126 *
127 * -- LAPACK test routine (version 3.4.0) --
128 * -- LAPACK is a software package provided by Univ. of Tennessee, --
129 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
130 * November 2011
131 *
132 * .. Scalar Arguments ..
133  CHARACTER uplo
134  INTEGER lda, ldu, ldvt, m, n, ns
135  REAL resid
136 * ..
137 * .. Array Arguments ..
138  REAL a( lda, * ), s( * ), u( ldu, * ),
139  $ vt( ldvt, * ), work( * )
140 * ..
141 *
142 * ======================================================================
143 *
144 * .. Parameters ..
145  REAL zero, one
146  parameter ( zero = 0.0e+0, one = 1.0e+0 )
147 * ..
148 * .. Local Scalars ..
149  INTEGER i, j
150  REAL anorm, eps
151 * ..
152 * .. External Functions ..
153  LOGICAL lsame
154  INTEGER isamax
155  REAL sasum, slamch, slange
156  EXTERNAL lsame, isamax, sasum, slamch, slange
157 * ..
158 * .. External Subroutines ..
159  EXTERNAL sgemm
160 * ..
161 * .. Intrinsic Functions ..
162  INTRINSIC abs, REAL, max, min
163 * ..
164 * .. Executable Statements ..
165 *
166 * Quick return if possible.
167 *
168  resid = zero
169  IF( min( m, n ).LE.0 .OR. ns.LE.0 )
170  $ RETURN
171 *
172  eps = slamch( 'Precision' )
173  anorm = slange( 'M', m, n, a, lda, work )
174 *
175 * Compute U' * A * V.
176 *
177  CALL sgemm( 'N', 'T', m, ns, n, one, a, lda, vt,
178  $ ldvt, zero, work( 1+ns*ns ), m )
179  CALL sgemm( 'T', 'N', ns, ns, m, -one, u, ldu, work( 1+ns*ns ),
180  $ m, zero, work, ns )
181 *
182 * norm(S - U' * B * V)
183 *
184  j = 0
185  DO 10 i = 1, ns
186  work( j+i ) = work( j+i ) + s( i )
187  resid = max( resid, sasum( ns, work( j+1 ), 1 ) )
188  j = j + ns
189  10 CONTINUE
190 *
191  IF( anorm.LE.zero ) THEN
192  IF( resid.NE.zero )
193  $ resid = one / eps
194  ELSE
195  IF( anorm.GE.resid ) THEN
196  resid = ( resid / anorm ) / ( REAL( n )*eps )
197  ELSE
198  IF( anorm.LT.one ) THEN
199  resid = ( min( resid, REAL( n )*anorm ) / anorm ) /
200  $ ( REAL( n )*eps )
201  ELSE
202  resid = min( resid / anorm, REAL( N ) ) /
203  $ ( REAL( n )*eps )
204  END IF
205  END IF
206  END IF
207 *
208  RETURN
209 *
210 * End of SBDT05
211 *
integer function isamax(N, SX, INCX)
ISAMAX
Definition: isamax.f:53
subroutine sgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
SGEMM
Definition: sgemm.f:189
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:116
real function sasum(N, SX, INCX)
SASUM
Definition: sasum.f:54
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69
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: