LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dbdt02.f
Go to the documentation of this file.
1*> \brief \b DBDT02
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 DBDT02( M, N, B, LDB, C, LDC, U, LDU, WORK, RESID )
12*
13* .. Scalar Arguments ..
14* INTEGER LDB, LDC, LDU, M, N
15* DOUBLE PRECISION RESID
16* ..
17* .. Array Arguments ..
18* DOUBLE PRECISION B( LDB, * ), C( LDC, * ), U( LDU, * ),
19* $ WORK( * )
20* ..
21*
22*
23*> \par Purpose:
24* =============
25*>
26*> \verbatim
27*>
28*> DBDT02 tests the change of basis C = U**H * B by computing the
29*> residual
30*>
31*> RESID = norm(B - U * C) / ( max(m,n) * norm(B) * EPS ),
32*>
33*> where B and C are M by N matrices, U is an M by M orthogonal matrix,
34*> and EPS is the machine precision.
35*> \endverbatim
36*
37* Arguments:
38* ==========
39*
40*> \param[in] M
41*> \verbatim
42*> M is INTEGER
43*> The number of rows of the matrices B and C and the order of
44*> the matrix Q.
45*> \endverbatim
46*>
47*> \param[in] N
48*> \verbatim
49*> N is INTEGER
50*> The number of columns of the matrices B and C.
51*> \endverbatim
52*>
53*> \param[in] B
54*> \verbatim
55*> B is DOUBLE PRECISION array, dimension (LDB,N)
56*> The m by n matrix B.
57*> \endverbatim
58*>
59*> \param[in] LDB
60*> \verbatim
61*> LDB is INTEGER
62*> The leading dimension of the array B. LDB >= max(1,M).
63*> \endverbatim
64*>
65*> \param[in] C
66*> \verbatim
67*> C is DOUBLE PRECISION array, dimension (LDC,N)
68*> The m by n matrix C, assumed to contain U**H * B.
69*> \endverbatim
70*>
71*> \param[in] LDC
72*> \verbatim
73*> LDC is INTEGER
74*> The leading dimension of the array C. LDC >= max(1,M).
75*> \endverbatim
76*>
77*> \param[in] U
78*> \verbatim
79*> U is DOUBLE PRECISION array, dimension (LDU,M)
80*> The m by m orthogonal matrix U.
81*> \endverbatim
82*>
83*> \param[in] LDU
84*> \verbatim
85*> LDU is INTEGER
86*> The leading dimension of the array U. LDU >= max(1,M).
87*> \endverbatim
88*>
89*> \param[out] WORK
90*> \verbatim
91*> WORK is DOUBLE PRECISION array, dimension (M)
92*> \endverbatim
93*>
94*> \param[out] RESID
95*> \verbatim
96*> RESID is DOUBLE PRECISION
97*> RESID = norm(B - U * C) / ( max(m,n) * norm(B) * EPS ),
98*> \endverbatim
99*
100* Authors:
101* ========
102*
103*> \author Univ. of Tennessee
104*> \author Univ. of California Berkeley
105*> \author Univ. of Colorado Denver
106*> \author NAG Ltd.
107*
108*> \ingroup double_eig
109*
110* =====================================================================
111 SUBROUTINE dbdt02( M, N, B, LDB, C, LDC, U, LDU, WORK, RESID )
112*
113* -- LAPACK test routine --
114* -- LAPACK is a software package provided by Univ. of Tennessee, --
115* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
116*
117* .. Scalar Arguments ..
118 INTEGER LDB, LDC, LDU, M, N
119 DOUBLE PRECISION RESID
120* ..
121* .. Array Arguments ..
122 DOUBLE PRECISION B( LDB, * ), C( LDC, * ), U( LDU, * ),
123 $ WORK( * )
124* ..
125*
126* ======================================================================
127*
128* .. Parameters ..
129 DOUBLE PRECISION ZERO, ONE
130 parameter( zero = 0.0d+0, one = 1.0d+0 )
131* ..
132* .. Local Scalars ..
133 INTEGER J
134 DOUBLE PRECISION BNORM, EPS, REALMN
135* ..
136* .. External Functions ..
137 DOUBLE PRECISION DASUM, DLAMCH, DLANGE
138 EXTERNAL dasum, dlamch, dlange
139* ..
140* .. External Subroutines ..
141 EXTERNAL dcopy, dgemv
142* ..
143* .. Intrinsic Functions ..
144 INTRINSIC dble, max, min
145* ..
146* .. Executable Statements ..
147*
148* Quick return if possible
149*
150 resid = zero
151 IF( m.LE.0 .OR. n.LE.0 )
152 $ RETURN
153 realmn = dble( max( m, n ) )
154 eps = dlamch( 'Precision' )
155*
156* Compute norm(B - U * C)
157*
158 DO 10 j = 1, n
159 CALL dcopy( m, b( 1, j ), 1, work, 1 )
160 CALL dgemv( 'No transpose', m, m, -one, u, ldu, c( 1, j ), 1,
161 $ one, work, 1 )
162 resid = max( resid, dasum( m, work, 1 ) )
163 10 CONTINUE
164*
165* Compute norm of B.
166*
167 bnorm = dlange( '1', m, n, b, ldb, work )
168*
169 IF( bnorm.LE.zero ) THEN
170 IF( resid.NE.zero )
171 $ resid = one / eps
172 ELSE
173 IF( bnorm.GE.resid ) THEN
174 resid = ( resid / bnorm ) / ( realmn*eps )
175 ELSE
176 IF( bnorm.LT.one ) THEN
177 resid = ( min( resid, realmn*bnorm ) / bnorm ) /
178 $ ( realmn*eps )
179 ELSE
180 resid = min( resid / bnorm, realmn ) / ( realmn*eps )
181 END IF
182 END IF
183 END IF
184 RETURN
185*
186* End of DBDT02
187*
188 END
subroutine dbdt02(m, n, b, ldb, c, ldc, u, ldu, work, resid)
DBDT02
Definition dbdt02.f:112
subroutine dcopy(n, dx, incx, dy, incy)
DCOPY
Definition dcopy.f:82
subroutine dgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
DGEMV
Definition dgemv.f:158