LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
cbdt05.f
Go to the documentation of this file.
1 *> \brief \b CBDT05
2 * =========== DOCUMENTATION ===========
3 *
4 * Online html documentation available at
5 * http://www.netlib.org/lapack/explore-html/
6 *
7 * Definition:
8 * ===========
9 *
10 * SUBROUTINE CBDT05( 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 * REAL RESID
16 * ..
17 * .. Array Arguments ..
18 * REAL S( * )
19 * COMPLEX A( LDA, * ), U( * ), VT( LDVT, * ), WORK( * )
20 * ..
21 *
22 *> \par Purpose:
23 * =============
24 *>
25 *> \verbatim
26 *>
27 *> CBDT05 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 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 REAL 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 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 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 array, dimension (M,N)
104 *> \endverbatim
105 *>
106 *> \param[out] RESID
107 *> \verbatim
108 *> RESID is REAL
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 *> \date December 2016
121 *
122 *> \ingroup double_eig
123 *
124 * =====================================================================
125  SUBROUTINE cbdt05( M, N, A, LDA, S, NS, U, LDU,
126  $ VT, LDVT, WORK, RESID )
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 *
219  END
cgemm
subroutine cgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
CGEMM
Definition: cgemm.f:189
cbdt05
subroutine cbdt05(M, N, A, LDA, S, NS, U, LDU, VT, LDVT, WORK, RESID)
CBDT05
Definition: cbdt05.f:127