LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine sbdt02 ( integer  M,
integer  N,
real, dimension( ldb, * )  B,
integer  LDB,
real, dimension( ldc, * )  C,
integer  LDC,
real, dimension( ldu, * )  U,
integer  LDU,
real, dimension( * )  WORK,
real  RESID 
)

SBDT02

Purpose:
 SBDT02 tests the change of basis C = U' * B by computing the residual

    RESID = norm( B - U * C ) / ( max(m,n) * norm(B) * EPS ),

 where B and C are M by N matrices, U is an M by M orthogonal matrix,
 and EPS is the machine precision.
Parameters
[in]M
          M is INTEGER
          The number of rows of the matrices B and C and the order of
          the matrix Q.
[in]N
          N is INTEGER
          The number of columns of the matrices B and C.
[in]B
          B is REAL array, dimension (LDB,N)
          The m by n matrix B.
[in]LDB
          LDB is INTEGER
          The leading dimension of the array B.  LDB >= max(1,M).
[in]C
          C is REAL array, dimension (LDC,N)
          The m by n matrix C, assumed to contain U' * B.
[in]LDC
          LDC is INTEGER
          The leading dimension of the array C.  LDC >= max(1,M).
[in]U
          U is REAL array, dimension (LDU,M)
          The m by m orthogonal matrix U.
[in]LDU
          LDU is INTEGER
          The leading dimension of the array U.  LDU >= max(1,M).
[out]WORK
          WORK is REAL array, dimension (M)
[out]RESID
          RESID is REAL
          RESID = norm( B - U * C ) / ( max(m,n) * norm(B) * EPS ),
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 113 of file sbdt02.f.

113 *
114 * -- LAPACK test routine (version 3.4.0) --
115 * -- LAPACK is a software package provided by Univ. of Tennessee, --
116 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
117 * November 2011
118 *
119 * .. Scalar Arguments ..
120  INTEGER ldb, ldc, ldu, m, n
121  REAL resid
122 * ..
123 * .. Array Arguments ..
124  REAL b( ldb, * ), c( ldc, * ), u( ldu, * ),
125  $ work( * )
126 * ..
127 *
128 * ======================================================================
129 *
130 * .. Parameters ..
131  REAL zero, one
132  parameter ( zero = 0.0e+0, one = 1.0e+0 )
133 * ..
134 * .. Local Scalars ..
135  INTEGER j
136  REAL bnorm, eps, realmn
137 * ..
138 * .. External Functions ..
139  REAL sasum, slamch, slange
140  EXTERNAL sasum, slamch, slange
141 * ..
142 * .. External Subroutines ..
143  EXTERNAL scopy, sgemv
144 * ..
145 * .. Intrinsic Functions ..
146  INTRINSIC max, min, real
147 * ..
148 * .. Executable Statements ..
149 *
150 * Quick return if possible
151 *
152  resid = zero
153  IF( m.LE.0 .OR. n.LE.0 )
154  $ RETURN
155  realmn = REAL( MAX( M, N ) )
156  eps = slamch( 'Precision' )
157 *
158 * Compute norm( B - U * C )
159 *
160  DO 10 j = 1, n
161  CALL scopy( m, b( 1, j ), 1, work, 1 )
162  CALL sgemv( 'No transpose', m, m, -one, u, ldu, c( 1, j ), 1,
163  $ one, work, 1 )
164  resid = max( resid, sasum( m, work, 1 ) )
165  10 CONTINUE
166 *
167 * Compute norm of B.
168 *
169  bnorm = slange( '1', m, n, b, ldb, work )
170 *
171  IF( bnorm.LE.zero ) THEN
172  IF( resid.NE.zero )
173  $ resid = one / eps
174  ELSE
175  IF( bnorm.GE.resid ) THEN
176  resid = ( resid / bnorm ) / ( realmn*eps )
177  ELSE
178  IF( bnorm.LT.one ) THEN
179  resid = ( min( resid, realmn*bnorm ) / bnorm ) /
180  $ ( realmn*eps )
181  ELSE
182  resid = min( resid / bnorm, realmn ) / ( realmn*eps )
183  END IF
184  END IF
185  END IF
186  RETURN
187 *
188 * End of SBDT02
189 *
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: