LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zbdt05.f
Go to the documentation of this file.
1*> \brief \b ZBDT05
2* =========== DOCUMENTATION ===========
3*
4* Online html documentation available at
5* http://www.netlib.org/lapack/explore-html/
6*
7* Definition:
8* ===========
9*
10* SUBROUTINE ZBDT05( M, N, A, LDA, S, NS, U, LDU,
11* VT, LDVT, WORK, RESID )
12*
13* .. Scalar Arguments ..
14* INTEGER LDA, LDU, LDVT, N, NS
15* DOUBLE PRECISION RESID
16* ..
17* .. Array Arguments ..
18* DOUBLE PRECISION S( * )
19* COMPLEX*16 A( LDA, * ), U( * ), VT( LDVT, * ), WORK( * )
20* ..
21*
22*> \par Purpose:
23* =============
24*>
25*> \verbatim
26*>
27*> ZBDT05 reconstructs a bidiagonal matrix B from its (partial) SVD:
28*> S = U' * B * V
29*> where U and V are orthogonal matrices and S is diagonal.
30*>
31*> The test ratio to test the singular value decomposition is
32*> RESID = norm( S - U' * B * V ) / ( n * norm(B) * EPS )
33*> where VT = V' and EPS is the machine precision.
34*> \endverbatim
35*
36* Arguments:
37* ==========
38*
39*> \param[in] M
40*> \verbatim
41*> M is INTEGER
42*> The number of rows of the matrices A and U.
43*> \endverbatim
44*>
45*> \param[in] N
46*> \verbatim
47*> N is INTEGER
48*> The number of columns of the matrices A and VT.
49*> \endverbatim
50*>
51*> \param[in] A
52*> \verbatim
53*> A is COMPLEX*16 array, dimension (LDA,N)
54*> The m by n matrix A.
55*> \endverbatim
56*>
57*> \param[in] LDA
58*> \verbatim
59*> LDA is INTEGER
60*> The leading dimension of the array A. LDA >= max(1,M).
61*> \endverbatim
62*>
63*> \param[in] S
64*> \verbatim
65*> S is DOUBLE PRECISION array, dimension (NS)
66*> The singular values from the (partial) SVD of B, sorted in
67*> decreasing order.
68*> \endverbatim
69*>
70*> \param[in] NS
71*> \verbatim
72*> NS is INTEGER
73*> The number of singular values/vectors from the (partial)
74*> SVD of B.
75*> \endverbatim
76*>
77*> \param[in] U
78*> \verbatim
79*> U is COMPLEX*16 array, dimension (LDU,NS)
80*> The n by ns orthogonal matrix U in S = U' * B * V.
81*> \endverbatim
82*>
83*> \param[in] LDU
84*> \verbatim
85*> LDU is INTEGER
86*> The leading dimension of the array U. LDU >= max(1,N)
87*> \endverbatim
88*>
89*> \param[in] VT
90*> \verbatim
91*> VT is COMPLEX*16 array, dimension (LDVT,N)
92*> The n by ns orthogonal matrix V in S = U' * B * V.
93*> \endverbatim
94*>
95*> \param[in] LDVT
96*> \verbatim
97*> LDVT is INTEGER
98*> The leading dimension of the array VT.
99*> \endverbatim
100*>
101*> \param[out] WORK
102*> \verbatim
103*> WORK is COMPLEX*16 array, dimension (M,N)
104*> \endverbatim
105*>
106*> \param[out] RESID
107*> \verbatim
108*> RESID is DOUBLE PRECISION
109*> The test ratio: norm(S - U' * A * V) / ( n * norm(A) * EPS )
110*> \endverbatim
111*
112* Authors:
113* ========
114*
115*> \author Univ. of Tennessee
116*> \author Univ. of California Berkeley
117*> \author Univ. of Colorado Denver
118*> \author NAG Ltd.
119*
120*> \ingroup double_eig
121*
122* =====================================================================
123 SUBROUTINE zbdt05( M, N, A, LDA, S, NS, U, LDU,
124 $ VT, LDVT, WORK, RESID )
125*
126* -- LAPACK test routine --
127* -- LAPACK is a software package provided by Univ. of Tennessee, --
128* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
129*
130* .. Scalar Arguments ..
131 INTEGER LDA, LDU, LDVT, M, N, NS
132 DOUBLE PRECISION RESID
133* ..
134* .. Array Arguments ..
135 DOUBLE PRECISION S( * )
136 COMPLEX*16 A( LDA, * ), U( * ), VT( LDVT, * ), WORK( * )
137* ..
138*
139* ======================================================================
140*
141* .. Parameters ..
142 DOUBLE PRECISION ZERO, ONE
143 parameter( zero = 0.0d+0, one = 1.0d+0 )
144 COMPLEX*16 CZERO, CONE
145 parameter( czero = ( 0.0d+0, 0.0d+0 ),
146 $ cone = ( 1.0d+0, 0.0d+0 ) )
147* ..
148* .. Local Scalars ..
149 INTEGER I, J
150 DOUBLE PRECISION ANORM, EPS
151* ..
152* .. Local Arrays ..
153 DOUBLE PRECISION DUM( 1 )
154* ..
155* .. External Functions ..
156 LOGICAL LSAME
157 INTEGER IDAMAX
158 DOUBLE PRECISION DASUM, DZASUM, DLAMCH, ZLANGE
159 EXTERNAL lsame, idamax, dasum, dzasum, dlamch, zlange
160* ..
161* .. External Subroutines ..
162 EXTERNAL zgemm
163* ..
164* .. Intrinsic Functions ..
165 INTRINSIC abs, dble, max, min
166* ..
167* .. Executable Statements ..
168*
169* Quick return if possible.
170*
171 resid = zero
172 IF( min( m, n ).LE.0 .OR. ns.LE.0 )
173 $ RETURN
174*
175 eps = dlamch( 'Precision' )
176 anorm = zlange( 'M', m, n, a, lda, dum )
177*
178* Compute U' * A * V.
179*
180 CALL zgemm( 'N', 'C', m, ns, n, cone, a, lda, vt,
181 $ ldvt, czero, work( 1+ns*ns ), m )
182 CALL zgemm( 'C', 'N', ns, ns, m, -cone, u, ldu, work( 1+ns*ns ),
183 $ m, czero, work, ns )
184*
185* norm(S - U' * B * V)
186*
187 j = 0
188 DO 10 i = 1, ns
189 work( j+i ) = work( j+i ) + dcmplx( s( i ), zero )
190 resid = max( resid, dzasum( ns, work( j+1 ), 1 ) )
191 j = j + ns
192 10 CONTINUE
193*
194 IF( anorm.LE.zero ) THEN
195 IF( resid.NE.zero )
196 $ resid = one / eps
197 ELSE
198 IF( anorm.GE.resid ) THEN
199 resid = ( resid / anorm ) / ( dble( n )*eps )
200 ELSE
201 IF( anorm.LT.one ) THEN
202 resid = ( min( resid, dble( n )*anorm ) / anorm ) /
203 $ ( dble( n )*eps )
204 ELSE
205 resid = min( resid / anorm, dble( n ) ) /
206 $ ( dble( n )*eps )
207 END IF
208 END IF
209 END IF
210*
211 RETURN
212*
213* End of ZBDT05
214*
215 END
subroutine zgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
ZGEMM
Definition zgemm.f:188
subroutine zbdt05(m, n, a, lda, s, ns, u, ldu, vt, ldvt, work, resid)
ZBDT05
Definition zbdt05.f:125