LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zbdt03.f
Go to the documentation of this file.
1 *> \brief \b ZBDT03
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE ZBDT03( UPLO, N, KD, D, E, U, LDU, S, VT, LDVT, WORK,
12 * RESID )
13 *
14 * .. Scalar Arguments ..
15 * CHARACTER UPLO
16 * INTEGER KD, LDU, LDVT, N
17 * DOUBLE PRECISION RESID
18 * ..
19 * .. Array Arguments ..
20 * DOUBLE PRECISION D( * ), E( * ), S( * )
21 * COMPLEX*16 U( LDU, * ), VT( LDVT, * ), WORK( * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> ZBDT03 reconstructs a bidiagonal matrix B from its SVD:
31 *> S = U' * B * V
32 *> where U and V are orthogonal matrices and S is diagonal.
33 *>
34 *> The test ratio to test the singular value decomposition is
35 *> RESID = norm( B - U * S * VT ) / ( n * norm(B) * EPS )
36 *> where VT = V' and EPS is the machine precision.
37 *> \endverbatim
38 *
39 * Arguments:
40 * ==========
41 *
42 *> \param[in] UPLO
43 *> \verbatim
44 *> UPLO is CHARACTER*1
45 *> Specifies whether the matrix B is upper or lower bidiagonal.
46 *> = 'U': Upper bidiagonal
47 *> = 'L': Lower bidiagonal
48 *> \endverbatim
49 *>
50 *> \param[in] N
51 *> \verbatim
52 *> N is INTEGER
53 *> The order of the matrix B.
54 *> \endverbatim
55 *>
56 *> \param[in] KD
57 *> \verbatim
58 *> KD is INTEGER
59 *> The bandwidth of the bidiagonal matrix B. If KD = 1, the
60 *> matrix B is bidiagonal, and if KD = 0, B is diagonal and E is
61 *> not referenced. If KD is greater than 1, it is assumed to be
62 *> 1, and if KD is less than 0, it is assumed to be 0.
63 *> \endverbatim
64 *>
65 *> \param[in] D
66 *> \verbatim
67 *> D is DOUBLE PRECISION array, dimension (N)
68 *> The n diagonal elements of the bidiagonal matrix B.
69 *> \endverbatim
70 *>
71 *> \param[in] E
72 *> \verbatim
73 *> E is DOUBLE PRECISION array, dimension (N-1)
74 *> The (n-1) superdiagonal elements of the bidiagonal matrix B
75 *> if UPLO = 'U', or the (n-1) subdiagonal elements of B if
76 *> UPLO = 'L'.
77 *> \endverbatim
78 *>
79 *> \param[in] U
80 *> \verbatim
81 *> U is COMPLEX*16 array, dimension (LDU,N)
82 *> The n by n orthogonal matrix U in the reduction B = U'*A*P.
83 *> \endverbatim
84 *>
85 *> \param[in] LDU
86 *> \verbatim
87 *> LDU is INTEGER
88 *> The leading dimension of the array U. LDU >= max(1,N)
89 *> \endverbatim
90 *>
91 *> \param[in] S
92 *> \verbatim
93 *> S is DOUBLE PRECISION array, dimension (N)
94 *> The singular values from the SVD of B, sorted in decreasing
95 *> order.
96 *> \endverbatim
97 *>
98 *> \param[in] VT
99 *> \verbatim
100 *> VT is COMPLEX*16 array, dimension (LDVT,N)
101 *> The n by n orthogonal matrix V' in the reduction
102 *> B = U * S * V'.
103 *> \endverbatim
104 *>
105 *> \param[in] LDVT
106 *> \verbatim
107 *> LDVT is INTEGER
108 *> The leading dimension of the array VT.
109 *> \endverbatim
110 *>
111 *> \param[out] WORK
112 *> \verbatim
113 *> WORK is COMPLEX*16 array, dimension (2*N)
114 *> \endverbatim
115 *>
116 *> \param[out] RESID
117 *> \verbatim
118 *> RESID is DOUBLE PRECISION
119 *> The test ratio: norm(B - U * S * V') / ( n * norm(A) * EPS )
120 *> \endverbatim
121 *
122 * Authors:
123 * ========
124 *
125 *> \author Univ. of Tennessee
126 *> \author Univ. of California Berkeley
127 *> \author Univ. of Colorado Denver
128 *> \author NAG Ltd.
129 *
130 *> \date November 2011
131 *
132 *> \ingroup complex16_eig
133 *
134 * =====================================================================
135  SUBROUTINE zbdt03( UPLO, N, KD, D, E, U, LDU, S, VT, LDVT, WORK,
136  $ resid )
137 *
138 * -- LAPACK test routine (version 3.4.0) --
139 * -- LAPACK is a software package provided by Univ. of Tennessee, --
140 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
141 * November 2011
142 *
143 * .. Scalar Arguments ..
144  CHARACTER uplo
145  INTEGER kd, ldu, ldvt, n
146  DOUBLE PRECISION resid
147 * ..
148 * .. Array Arguments ..
149  DOUBLE PRECISION d( * ), e( * ), s( * )
150  COMPLEX*16 u( ldu, * ), vt( ldvt, * ), work( * )
151 * ..
152 *
153 * ======================================================================
154 *
155 * .. Parameters ..
156  DOUBLE PRECISION zero, one
157  parameter( zero = 0.0d+0, one = 1.0d+0 )
158 * ..
159 * .. Local Scalars ..
160  INTEGER i, j
161  DOUBLE PRECISION bnorm, eps
162 * ..
163 * .. External Functions ..
164  LOGICAL lsame
165  INTEGER idamax
166  DOUBLE PRECISION dlamch, dzasum
167  EXTERNAL lsame, idamax, dlamch, dzasum
168 * ..
169 * .. External Subroutines ..
170  EXTERNAL zgemv
171 * ..
172 * .. Intrinsic Functions ..
173  INTRINSIC abs, dble, dcmplx, max, min
174 * ..
175 * .. Executable Statements ..
176 *
177 * Quick return if possible
178 *
179  resid = zero
180  IF( n.LE.0 )
181  $ return
182 *
183 * Compute B - U * S * V' one column at a time.
184 *
185  bnorm = zero
186  IF( kd.GE.1 ) THEN
187 *
188 * B is bidiagonal.
189 *
190  IF( lsame( uplo, 'U' ) ) THEN
191 *
192 * B is upper bidiagonal.
193 *
194  DO 20 j = 1, n
195  DO 10 i = 1, n
196  work( n+i ) = s( i )*vt( i, j )
197  10 continue
198  CALL zgemv( 'No transpose', n, n, -dcmplx( one ), u, ldu,
199  $ work( n+1 ), 1, dcmplx( zero ), work, 1 )
200  work( j ) = work( j ) + d( j )
201  IF( j.GT.1 ) THEN
202  work( j-1 ) = work( j-1 ) + e( j-1 )
203  bnorm = max( bnorm, abs( d( j ) )+abs( e( j-1 ) ) )
204  ELSE
205  bnorm = max( bnorm, abs( d( j ) ) )
206  END IF
207  resid = max( resid, dzasum( n, work, 1 ) )
208  20 continue
209  ELSE
210 *
211 * B is lower bidiagonal.
212 *
213  DO 40 j = 1, n
214  DO 30 i = 1, n
215  work( n+i ) = s( i )*vt( i, j )
216  30 continue
217  CALL zgemv( 'No transpose', n, n, -dcmplx( one ), u, ldu,
218  $ work( n+1 ), 1, dcmplx( zero ), work, 1 )
219  work( j ) = work( j ) + d( j )
220  IF( j.LT.n ) THEN
221  work( j+1 ) = work( j+1 ) + e( j )
222  bnorm = max( bnorm, abs( d( j ) )+abs( e( j ) ) )
223  ELSE
224  bnorm = max( bnorm, abs( d( j ) ) )
225  END IF
226  resid = max( resid, dzasum( n, work, 1 ) )
227  40 continue
228  END IF
229  ELSE
230 *
231 * B is diagonal.
232 *
233  DO 60 j = 1, n
234  DO 50 i = 1, n
235  work( n+i ) = s( i )*vt( i, j )
236  50 continue
237  CALL zgemv( 'No transpose', n, n, -dcmplx( one ), u, ldu,
238  $ work( n+1 ), 1, dcmplx( zero ), work, 1 )
239  work( j ) = work( j ) + d( j )
240  resid = max( resid, dzasum( n, work, 1 ) )
241  60 continue
242  j = idamax( n, d, 1 )
243  bnorm = abs( d( j ) )
244  END IF
245 *
246 * Compute norm(B - U * S * V') / ( n * norm(B) * EPS )
247 *
248  eps = dlamch( 'Precision' )
249 *
250  IF( bnorm.LE.zero ) THEN
251  IF( resid.NE.zero )
252  $ resid = one / eps
253  ELSE
254  IF( bnorm.GE.resid ) THEN
255  resid = ( resid / bnorm ) / ( dble( n )*eps )
256  ELSE
257  IF( bnorm.LT.one ) THEN
258  resid = ( min( resid, dble( n )*bnorm ) / bnorm ) /
259  $ ( dble( n )*eps )
260  ELSE
261  resid = min( resid / bnorm, dble( n ) ) /
262  $ ( dble( n )*eps )
263  END IF
264  END IF
265  END IF
266 *
267  return
268 *
269 * End of ZBDT03
270 *
271  END