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

SBDT01

Purpose:
 SBDT01 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 orthogonal
 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 REAL 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 REAL array, dimension (LDQ,N)
          The m by min(m,n) orthogonal 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 REAL array, dimension (LDPT,N)
          The min(m,n) by n orthogonal 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 REAL array, dimension (M+N)
[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 142 of file sbdt01.f.

142 *
143 * -- LAPACK test routine (version 3.4.0) --
144 * -- LAPACK is a software package provided by Univ. of Tennessee, --
145 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
146 * November 2011
147 *
148 * .. Scalar Arguments ..
149  INTEGER kd, lda, ldpt, ldq, m, n
150  REAL resid
151 * ..
152 * .. Array Arguments ..
153  REAL a( lda, * ), d( * ), e( * ), pt( ldpt, * ),
154  $ q( ldq, * ), work( * )
155 * ..
156 *
157 * =====================================================================
158 *
159 * .. Parameters ..
160  REAL zero, one
161  parameter ( zero = 0.0e+0, one = 1.0e+0 )
162 * ..
163 * .. Local Scalars ..
164  INTEGER i, j
165  REAL anorm, eps
166 * ..
167 * .. External Functions ..
168  REAL sasum, slamch, slange
169  EXTERNAL sasum, slamch, slange
170 * ..
171 * .. External Subroutines ..
172  EXTERNAL scopy, sgemv
173 * ..
174 * .. Intrinsic Functions ..
175  INTRINSIC max, min, real
176 * ..
177 * .. Executable Statements ..
178 *
179 * Quick return if possible
180 *
181  IF( m.LE.0 .OR. n.LE.0 ) THEN
182  resid = zero
183  RETURN
184  END IF
185 *
186 * Compute A - Q * B * P' one column at a time.
187 *
188  resid = zero
189  IF( kd.NE.0 ) THEN
190 *
191 * B is bidiagonal.
192 *
193  IF( kd.NE.0 .AND. m.GE.n ) THEN
194 *
195 * B is upper bidiagonal and M >= N.
196 *
197  DO 20 j = 1, n
198  CALL scopy( m, a( 1, j ), 1, work, 1 )
199  DO 10 i = 1, n - 1
200  work( m+i ) = d( i )*pt( i, j ) + e( i )*pt( i+1, j )
201  10 CONTINUE
202  work( m+n ) = d( n )*pt( n, j )
203  CALL sgemv( 'No transpose', m, n, -one, q, ldq,
204  $ work( m+1 ), 1, one, work, 1 )
205  resid = max( resid, sasum( m, work, 1 ) )
206  20 CONTINUE
207  ELSE IF( kd.LT.0 ) THEN
208 *
209 * B is upper bidiagonal and M < N.
210 *
211  DO 40 j = 1, n
212  CALL scopy( m, a( 1, j ), 1, work, 1 )
213  DO 30 i = 1, m - 1
214  work( m+i ) = d( i )*pt( i, j ) + e( i )*pt( i+1, j )
215  30 CONTINUE
216  work( m+m ) = d( m )*pt( m, j )
217  CALL sgemv( 'No transpose', m, m, -one, q, ldq,
218  $ work( m+1 ), 1, one, work, 1 )
219  resid = max( resid, sasum( m, work, 1 ) )
220  40 CONTINUE
221  ELSE
222 *
223 * B is lower bidiagonal.
224 *
225  DO 60 j = 1, n
226  CALL scopy( m, a( 1, j ), 1, work, 1 )
227  work( m+1 ) = d( 1 )*pt( 1, j )
228  DO 50 i = 2, m
229  work( m+i ) = e( i-1 )*pt( i-1, j ) +
230  $ d( i )*pt( i, j )
231  50 CONTINUE
232  CALL sgemv( 'No transpose', m, m, -one, q, ldq,
233  $ work( m+1 ), 1, one, work, 1 )
234  resid = max( resid, sasum( m, work, 1 ) )
235  60 CONTINUE
236  END IF
237  ELSE
238 *
239 * B is diagonal.
240 *
241  IF( m.GE.n ) THEN
242  DO 80 j = 1, n
243  CALL scopy( m, a( 1, j ), 1, work, 1 )
244  DO 70 i = 1, n
245  work( m+i ) = d( i )*pt( i, j )
246  70 CONTINUE
247  CALL sgemv( 'No transpose', m, n, -one, q, ldq,
248  $ work( m+1 ), 1, one, work, 1 )
249  resid = max( resid, sasum( m, work, 1 ) )
250  80 CONTINUE
251  ELSE
252  DO 100 j = 1, n
253  CALL scopy( m, a( 1, j ), 1, work, 1 )
254  DO 90 i = 1, m
255  work( m+i ) = d( i )*pt( i, j )
256  90 CONTINUE
257  CALL sgemv( 'No transpose', m, m, -one, q, ldq,
258  $ work( m+1 ), 1, one, work, 1 )
259  resid = max( resid, sasum( m, work, 1 ) )
260  100 CONTINUE
261  END IF
262  END IF
263 *
264 * Compute norm(A - Q * B * P') / ( n * norm(A) * EPS )
265 *
266  anorm = slange( '1', m, n, a, lda, work )
267  eps = slamch( 'Precision' )
268 *
269  IF( anorm.LE.zero ) THEN
270  IF( resid.NE.zero )
271  $ resid = one / eps
272  ELSE
273  IF( anorm.GE.resid ) THEN
274  resid = ( resid / anorm ) / ( REAL( n )*eps )
275  ELSE
276  IF( anorm.LT.one ) THEN
277  resid = ( min( resid, REAL( n )*anorm ) / anorm ) /
278  $ ( REAL( n )*eps )
279  ELSE
280  resid = min( resid / anorm, REAL( N ) ) /
281  $ ( REAL( n )*eps )
282  END IF
283  END IF
284  END IF
285 *
286  RETURN
287 *
288 * End of SBDT01
289 *
subroutine sgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
SGEMV
Definition: sgemv.f:158
real function slange(NORM, M, N, A, LDA, WORK)
SLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition: slange.f:116
real function sasum(N, SX, INCX)
SASUM
Definition: sasum.f:54
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69
subroutine scopy(N, SX, INCX, SY, INCY)
SCOPY
Definition: scopy.f:53

Here is the call graph for this function:

Here is the caller graph for this function: