LAPACK  3.9.0
LAPACK: Linear Algebra PACKage

◆ cbdt05()

subroutine cbdt05 ( integer  M,
integer  N,
complex, dimension( lda, * )  A,
integer  LDA,
real, dimension( * )  S,
integer  NS,
complex, dimension( * )  U,
integer  LDU,
complex, dimension( ldvt, * )  VT,
integer  LDVT,
complex, dimension( * )  WORK,
real  RESID 
)

CBDT05

Purpose:
 CBDT05 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 array, dimension (LDA,N)
          The m by n matrix A.
[in]LDA
          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 COMPLEX 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 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 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
December 2016

Definition at line 127 of file cbdt05.f.

127 *
128 * -- LAPACK test routine (version 3.7.0) --
129 * -- LAPACK is a software package provided by Univ. of Tennessee, --
130 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
131 * December 2016
132 *
133 * .. Scalar Arguments ..
134  INTEGER LDA, LDU, LDVT, M, N, NS
135  REAL RESID
136 * ..
137 * .. Array Arguments ..
138  REAL S( * )
139  COMPLEX A( LDA, * ), U( * ), VT( LDVT, * ), WORK( * )
140 * ..
141 *
142 * ======================================================================
143 *
144 * .. Parameters ..
145  REAL ZERO, ONE
146  parameter( zero = 0.0e+0, one = 1.0e+0 )
147  COMPLEX CZERO, CONE
148  parameter( czero = ( 0.0e+0, 0.0e+0 ),
149  $ cone = ( 1.0e+0, 0.0e+0 ) )
150 * ..
151 * .. Local Scalars ..
152  INTEGER I, J
153  REAL ANORM, EPS
154 * ..
155 * .. Local Arrays ..
156  REAL DUM( 1 )
157 * ..
158 * .. External Functions ..
159  LOGICAL LSAME
160  INTEGER ISAMAX
161  REAL SASUM, SLAMCH, CLANGE
162  EXTERNAL lsame, isamax, sasum, slamch, clange
163  REAL SCASUM
164 * ..
165 * .. External Subroutines ..
166  EXTERNAL cgemm
167 * ..
168 * .. Intrinsic Functions ..
169  INTRINSIC abs, real, max, min
170 * ..
171 * .. Executable Statements ..
172 *
173 * Quick return if possible.
174 *
175  resid = zero
176  IF( min( m, n ).LE.0 .OR. ns.LE.0 )
177  $ RETURN
178 *
179  eps = slamch( 'Precision' )
180  anorm = clange( 'M', m, n, a, lda, dum )
181 *
182 * Compute U' * A * V.
183 *
184  CALL cgemm( 'N', 'C', m, ns, n, cone, a, lda, vt,
185  $ ldvt, czero, work( 1+ns*ns ), m )
186  CALL cgemm( 'C', 'N', ns, ns, m, -cone, u, ldu, work( 1+ns*ns ),
187  $ m, czero, work, ns )
188 *
189 * norm(S - U' * B * V)
190 *
191  j = 0
192  DO 10 i = 1, ns
193  work( j+i ) = work( j+i ) + cmplx( s( i ), zero )
194  resid = max( resid, scasum( ns, work( j+1 ), 1 ) )
195  j = j + ns
196  10 CONTINUE
197 *
198  IF( anorm.LE.zero ) THEN
199  IF( resid.NE.zero )
200  $ resid = one / eps
201  ELSE
202  IF( anorm.GE.resid ) THEN
203  resid = ( resid / anorm ) / ( real( n )*eps )
204  ELSE
205  IF( anorm.LT.one ) THEN
206  resid = ( min( resid, real( n )*anorm ) / anorm ) /
207  $ ( real( n )*eps )
208  ELSE
209  resid = min( resid / anorm, real( n ) ) /
210  $ ( real( n )*eps )
211  END IF
212  END IF
213  END IF
214 *
215  RETURN
216 *
217 * End of CBDT05
218 *
Here is the call graph for this function:
Here is the caller graph for this function:
cgemm
subroutine cgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
CGEMM
Definition: cgemm.f:189