LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cbdt01.f
Go to the documentation of this file.
1 *> \brief \b CBDT01
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 CBDT01( M, N, KD, A, LDA, Q, LDQ, D, E, PT, LDPT, WORK,
12 * RWORK, RESID )
13 *
14 * .. Scalar Arguments ..
15 * INTEGER KD, LDA, LDPT, LDQ, M, N
16 * REAL RESID
17 * ..
18 * .. Array Arguments ..
19 * REAL D( * ), E( * ), RWORK( * )
20 * COMPLEX A( LDA, * ), PT( LDPT, * ), Q( LDQ, * ),
21 * $ WORK( * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> CBDT01 reconstructs a general matrix A from its bidiagonal form
31 *> A = Q * B * P'
32 *> where Q (m by min(m,n)) and P' (min(m,n) by n) are unitary
33 *> matrices and B is bidiagonal.
34 *>
35 *> The test ratio to test the reduction is
36 *> RESID = norm( A - Q * B * PT ) / ( n * norm(A) * EPS )
37 *> where PT = P' and EPS is the machine precision.
38 *> \endverbatim
39 *
40 * Arguments:
41 * ==========
42 *
43 *> \param[in] M
44 *> \verbatim
45 *> M is INTEGER
46 *> The number of rows of the matrices A and Q.
47 *> \endverbatim
48 *>
49 *> \param[in] N
50 *> \verbatim
51 *> N is INTEGER
52 *> The number of columns of the matrices A and P'.
53 *> \endverbatim
54 *>
55 *> \param[in] KD
56 *> \verbatim
57 *> KD is INTEGER
58 *> If KD = 0, B is diagonal and the array E is not referenced.
59 *> If KD = 1, the reduction was performed by xGEBRD; B is upper
60 *> bidiagonal if M >= N, and lower bidiagonal if M < N.
61 *> If KD = -1, the reduction was performed by xGBBRD; B is
62 *> always upper bidiagonal.
63 *> \endverbatim
64 *>
65 *> \param[in] A
66 *> \verbatim
67 *> A is COMPLEX array, dimension (LDA,N)
68 *> The m by n matrix A.
69 *> \endverbatim
70 *>
71 *> \param[in] LDA
72 *> \verbatim
73 *> LDA is INTEGER
74 *> The leading dimension of the array A. LDA >= max(1,M).
75 *> \endverbatim
76 *>
77 *> \param[in] Q
78 *> \verbatim
79 *> Q is COMPLEX array, dimension (LDQ,N)
80 *> The m by min(m,n) unitary matrix Q in the reduction
81 *> A = Q * B * P'.
82 *> \endverbatim
83 *>
84 *> \param[in] LDQ
85 *> \verbatim
86 *> LDQ is INTEGER
87 *> The leading dimension of the array Q. LDQ >= max(1,M).
88 *> \endverbatim
89 *>
90 *> \param[in] D
91 *> \verbatim
92 *> D is REAL array, dimension (min(M,N))
93 *> The diagonal elements of the bidiagonal matrix B.
94 *> \endverbatim
95 *>
96 *> \param[in] E
97 *> \verbatim
98 *> E is REAL array, dimension (min(M,N)-1)
99 *> The superdiagonal elements of the bidiagonal matrix B if
100 *> m >= n, or the subdiagonal elements of B if m < n.
101 *> \endverbatim
102 *>
103 *> \param[in] PT
104 *> \verbatim
105 *> PT is COMPLEX array, dimension (LDPT,N)
106 *> The min(m,n) by n unitary matrix P' in the reduction
107 *> A = Q * B * P'.
108 *> \endverbatim
109 *>
110 *> \param[in] LDPT
111 *> \verbatim
112 *> LDPT is INTEGER
113 *> The leading dimension of the array PT.
114 *> LDPT >= max(1,min(M,N)).
115 *> \endverbatim
116 *>
117 *> \param[out] WORK
118 *> \verbatim
119 *> WORK is COMPLEX array, dimension (M+N)
120 *> \endverbatim
121 *>
122 *> \param[out] RWORK
123 *> \verbatim
124 *> RWORK is REAL array, dimension (M)
125 *> \endverbatim
126 *>
127 *> \param[out] RESID
128 *> \verbatim
129 *> RESID is REAL
130 *> The test ratio: norm(A - Q * B * P') / ( n * norm(A) * EPS )
131 *> \endverbatim
132 *
133 * Authors:
134 * ========
135 *
136 *> \author Univ. of Tennessee
137 *> \author Univ. of California Berkeley
138 *> \author Univ. of Colorado Denver
139 *> \author NAG Ltd.
140 *
141 *> \date November 2011
142 *
143 *> \ingroup complex_eig
144 *
145 * =====================================================================
146  SUBROUTINE cbdt01( M, N, KD, A, LDA, Q, LDQ, D, E, PT, LDPT, WORK,
147  $ rwork, resid )
148 *
149 * -- LAPACK test routine (version 3.4.0) --
150 * -- LAPACK is a software package provided by Univ. of Tennessee, --
151 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
152 * November 2011
153 *
154 * .. Scalar Arguments ..
155  INTEGER KD, LDA, LDPT, LDQ, M, N
156  REAL RESID
157 * ..
158 * .. Array Arguments ..
159  REAL D( * ), E( * ), RWORK( * )
160  COMPLEX A( lda, * ), PT( ldpt, * ), Q( ldq, * ),
161  $ work( * )
162 * ..
163 *
164 * =====================================================================
165 *
166 * .. Parameters ..
167  REAL ZERO, ONE
168  parameter ( zero = 0.0e+0, one = 1.0e+0 )
169 * ..
170 * .. Local Scalars ..
171  INTEGER I, J
172  REAL ANORM, EPS
173 * ..
174 * .. External Functions ..
175  REAL CLANGE, SCASUM, SLAMCH
176  EXTERNAL clange, scasum, slamch
177 * ..
178 * .. External Subroutines ..
179  EXTERNAL ccopy, cgemv
180 * ..
181 * .. Intrinsic Functions ..
182  INTRINSIC cmplx, max, min, real
183 * ..
184 * .. Executable Statements ..
185 *
186 * Quick return if possible
187 *
188  IF( m.LE.0 .OR. n.LE.0 ) THEN
189  resid = zero
190  RETURN
191  END IF
192 *
193 * Compute A - Q * B * P' one column at a time.
194 *
195  resid = zero
196  IF( kd.NE.0 ) THEN
197 *
198 * B is bidiagonal.
199 *
200  IF( kd.NE.0 .AND. m.GE.n ) THEN
201 *
202 * B is upper bidiagonal and M >= N.
203 *
204  DO 20 j = 1, n
205  CALL ccopy( m, a( 1, j ), 1, work, 1 )
206  DO 10 i = 1, n - 1
207  work( m+i ) = d( i )*pt( i, j ) + e( i )*pt( i+1, j )
208  10 CONTINUE
209  work( m+n ) = d( n )*pt( n, j )
210  CALL cgemv( 'No transpose', m, n, -cmplx( one ), q, ldq,
211  $ work( m+1 ), 1, cmplx( one ), work, 1 )
212  resid = max( resid, scasum( m, work, 1 ) )
213  20 CONTINUE
214  ELSE IF( kd.LT.0 ) THEN
215 *
216 * B is upper bidiagonal and M < N.
217 *
218  DO 40 j = 1, n
219  CALL ccopy( m, a( 1, j ), 1, work, 1 )
220  DO 30 i = 1, m - 1
221  work( m+i ) = d( i )*pt( i, j ) + e( i )*pt( i+1, j )
222  30 CONTINUE
223  work( m+m ) = d( m )*pt( m, j )
224  CALL cgemv( 'No transpose', m, m, -cmplx( one ), q, ldq,
225  $ work( m+1 ), 1, cmplx( one ), work, 1 )
226  resid = max( resid, scasum( m, work, 1 ) )
227  40 CONTINUE
228  ELSE
229 *
230 * B is lower bidiagonal.
231 *
232  DO 60 j = 1, n
233  CALL ccopy( m, a( 1, j ), 1, work, 1 )
234  work( m+1 ) = d( 1 )*pt( 1, j )
235  DO 50 i = 2, m
236  work( m+i ) = e( i-1 )*pt( i-1, j ) +
237  $ d( i )*pt( i, j )
238  50 CONTINUE
239  CALL cgemv( 'No transpose', m, m, -cmplx( one ), q, ldq,
240  $ work( m+1 ), 1, cmplx( one ), work, 1 )
241  resid = max( resid, scasum( m, work, 1 ) )
242  60 CONTINUE
243  END IF
244  ELSE
245 *
246 * B is diagonal.
247 *
248  IF( m.GE.n ) THEN
249  DO 80 j = 1, n
250  CALL ccopy( m, a( 1, j ), 1, work, 1 )
251  DO 70 i = 1, n
252  work( m+i ) = d( i )*pt( i, j )
253  70 CONTINUE
254  CALL cgemv( 'No transpose', m, n, -cmplx( one ), q, ldq,
255  $ work( m+1 ), 1, cmplx( one ), work, 1 )
256  resid = max( resid, scasum( m, work, 1 ) )
257  80 CONTINUE
258  ELSE
259  DO 100 j = 1, n
260  CALL ccopy( m, a( 1, j ), 1, work, 1 )
261  DO 90 i = 1, m
262  work( m+i ) = d( i )*pt( i, j )
263  90 CONTINUE
264  CALL cgemv( 'No transpose', m, m, -cmplx( one ), q, ldq,
265  $ work( m+1 ), 1, cmplx( one ), work, 1 )
266  resid = max( resid, scasum( m, work, 1 ) )
267  100 CONTINUE
268  END IF
269  END IF
270 *
271 * Compute norm(A - Q * B * P') / ( n * norm(A) * EPS )
272 *
273  anorm = clange( '1', m, n, a, lda, rwork )
274  eps = slamch( 'Precision' )
275 *
276  IF( anorm.LE.zero ) THEN
277  IF( resid.NE.zero )
278  $ resid = one / eps
279  ELSE
280  IF( anorm.GE.resid ) THEN
281  resid = ( resid / anorm ) / ( REAL( n )*EPS )
282  ELSE
283  IF( anorm.LT.one ) THEN
284  resid = ( min( resid, REAL( n )*ANORM ) / anorm ) /
285  $ ( REAL( n )*EPS )
286  ELSE
287  resid = min( resid / anorm, REAL( N ) ) /
288  $ ( REAL( n )*EPS )
289  END IF
290  END IF
291  END IF
292 *
293  RETURN
294 *
295 * End of CBDT01
296 *
297  END
subroutine cbdt01(M, N, KD, A, LDA, Q, LDQ, D, E, PT, LDPT, WORK, RWORK, RESID)
CBDT01
Definition: cbdt01.f:148
subroutine cgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
CGEMV
Definition: cgemv.f:160
subroutine ccopy(N, CX, INCX, CY, INCY)
CCOPY
Definition: ccopy.f:52