LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine cbdt01 ( integer  M,
integer  N,
integer  KD,
complex, dimension( lda, * )  A,
integer  LDA,
complex, dimension( ldq, * )  Q,
integer  LDQ,
real, dimension( * )  D,
real, dimension( * )  E,
complex, dimension( ldpt, * )  PT,
integer  LDPT,
complex, dimension( * )  WORK,
real, dimension( * )  RWORK,
real  RESID 
)

CBDT01

Purpose:
 CBDT01 reconstructs a general matrix A from its bidiagonal form
    A = Q * B * P'
 where Q (m by min(m,n)) and P' (min(m,n) by n) are unitary
 matrices and B is bidiagonal.

 The test ratio to test the reduction is
    RESID = norm( A - Q * B * PT ) / ( n * norm(A) * EPS )
 where PT = P' and EPS is the machine precision.
Parameters
[in]M
          M is INTEGER
          The number of rows of the matrices A and Q.
[in]N
          N is INTEGER
          The number of columns of the matrices A and P'.
[in]KD
          KD is INTEGER
          If KD = 0, B is diagonal and the array E is not referenced.
          If KD = 1, the reduction was performed by xGEBRD; B is upper
          bidiagonal if M >= N, and lower bidiagonal if M < N.
          If KD = -1, the reduction was performed by xGBBRD; B is
          always upper bidiagonal.
[in]A
          A is COMPLEX array, dimension (LDA,N)
          The m by n matrix A.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,M).
[in]Q
          Q is COMPLEX array, dimension (LDQ,N)
          The m by min(m,n) unitary matrix Q in the reduction
          A = Q * B * P'.
[in]LDQ
          LDQ is INTEGER
          The leading dimension of the array Q.  LDQ >= max(1,M).
[in]D
          D is REAL array, dimension (min(M,N))
          The diagonal elements of the bidiagonal matrix B.
[in]E
          E is REAL array, dimension (min(M,N)-1)
          The superdiagonal elements of the bidiagonal matrix B if
          m >= n, or the subdiagonal elements of B if m < n.
[in]PT
          PT is COMPLEX array, dimension (LDPT,N)
          The min(m,n) by n unitary matrix P' in the reduction
          A = Q * B * P'.
[in]LDPT
          LDPT is INTEGER
          The leading dimension of the array PT.
          LDPT >= max(1,min(M,N)).
[out]WORK
          WORK is COMPLEX array, dimension (M+N)
[out]RWORK
          RWORK is REAL array, dimension (M)
[out]RESID
          RESID is REAL
          The test ratio:  norm(A - Q * B * P') / ( n * norm(A) * EPS )
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 148 of file cbdt01.f.

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 *
real function scasum(N, CX, INCX)
SCASUM
Definition: scasum.f:54
real function clange(NORM, M, N, A, LDA, WORK)
CLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition: clange.f:117
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
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69

Here is the call graph for this function:

Here is the caller graph for this function: