LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zbdt05.f
Go to the documentation of this file.
1 * =========== DOCUMENTATION ===========
2 *
3 * Online html documentation available at
4 * http://www.netlib.org/lapack/explore-html/
5 *
6 * Definition:
7 * ===========
8 *
9 * SUBROUTINE ZBDT05( M, N, A, LDA, S, NS, U, LDU,
10 * VT, LDVT, WORK, RESID )
11 *
12 * .. Scalar Arguments ..
13 * INTEGER LDA, LDU, LDVT, N, NS
14 * DOUBLE PRECISION RESID
15 * ..
16 * .. Array Arguments ..
17 * DOUBLE PRECISION S( * )
18 * COMPLEX*16 A( LDA, * ), U( * ), VT( LDVT, * ), WORK( * )
19 * ..
20 *
21 *> \par Purpose:
22 * =============
23 *>
24 *> \verbatim
25 *>
26 *> ZBDT05 reconstructs a bidiagonal matrix B from its (partial) SVD:
27 *> S = U' * B * V
28 *> where U and V are orthogonal matrices and S is diagonal.
29 *>
30 *> The test ratio to test the singular value decomposition is
31 *> RESID = norm( S - U' * B * V ) / ( n * norm(B) * EPS )
32 *> where VT = V' and EPS is the machine precision.
33 *> \endverbatim
34 *
35 * Arguments:
36 * ==========
37 *
38 *> \param[in] M
39 *> \verbatim
40 *> M is INTEGER
41 *> The number of rows of the matrices A and U.
42 *> \endverbatim
43 *>
44 *> \param[in] N
45 *> \verbatim
46 *> N is INTEGER
47 *> The number of columns of the matrices A and VT.
48 *> \endverbatim
49 *>
50 *> \param[in] A
51 *> \verbatim
52 *> A is COMPLEX*16 array, dimension (LDA,N)
53 *> The m by n matrix A.
54 *>
55 *> \param[in] LDA
56 *> \verbatim
57 *> LDA is INTEGER
58 *> The leading dimension of the array A. LDA >= max(1,M).
59 *> \endverbatim
60 *>
61 *> \param[in] S
62 *> \verbatim
63 *> S is DOUBLE PRECISION array, dimension (NS)
64 *> The singular values from the (partial) SVD of B, sorted in
65 *> decreasing order.
66 *> \endverbatim
67 *>
68 *> \param[in] NS
69 *> \verbatim
70 *> NS is INTEGER
71 *> The number of singular values/vectors from the (partial)
72 *> SVD of B.
73 *> \endverbatim
74 *>
75 *> \param[in] U
76 *> \verbatim
77 *> U is COMPLEX*16 array, dimension (LDU,NS)
78 *> The n by ns orthogonal matrix U in S = U' * B * V.
79 *> \endverbatim
80 *>
81 *> \param[in] LDU
82 *> \verbatim
83 *> LDU is INTEGER
84 *> The leading dimension of the array U. LDU >= max(1,N)
85 *> \endverbatim
86 *>
87 *> \param[in] VT
88 *> \verbatim
89 *> VT is COMPLEX*16 array, dimension (LDVT,N)
90 *> The n by ns orthogonal matrix V in S = U' * B * V.
91 *> \endverbatim
92 *>
93 *> \param[in] LDVT
94 *> \verbatim
95 *> LDVT is INTEGER
96 *> The leading dimension of the array VT.
97 *> \endverbatim
98 *>
99 *> \param[out] WORK
100 *> \verbatim
101 *> WORK is COMPLEX*16 array, dimension (M,N)
102 *> \endverbatim
103 *>
104 *> \param[out] RESID
105 *> \verbatim
106 *> RESID is DOUBLE PRECISION
107 *> The test ratio: norm(S - U' * A * V) / ( n * norm(A) * EPS )
108 *> \endverbatim
109 *
110 * Authors:
111 * ========
112 *
113 *> \author Univ. of Tennessee
114 *> \author Univ. of California Berkeley
115 *> \author Univ. of Colorado Denver
116 *> \author NAG Ltd.
117 *
118 *> \date November 2011
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 (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 *
218  END
subroutine zgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
ZGEMM
Definition: zgemm.f:189
subroutine zbdt05(M, N, A, LDA, S, NS, U, LDU, VT, LDVT, WORK, RESID)
Definition: zbdt05.f:125