LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dqrt11.f
Go to the documentation of this file.
1*> \brief \b DQRT11
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* DOUBLE PRECISION FUNCTION DQRT11( M, K, A, LDA, TAU, WORK, LWORK )
12*
13* .. Scalar Arguments ..
14* INTEGER K, LDA, LWORK, M
15* ..
16* .. Array Arguments ..
17* DOUBLE PRECISION A( LDA, * ), TAU( * ), WORK( LWORK )
18* ..
19*
20*
21*> \par Purpose:
22* =============
23*>
24*> \verbatim
25*>
26*> DQRT11 computes the test ratio
27*>
28*> || Q'*Q - I || / (eps * m)
29*>
30*> where the orthogonal matrix Q is represented as a product of
31*> elementary transformations. Each transformation has the form
32*>
33*> H(k) = I - tau(k) v(k) v(k)'
34*>
35*> where tau(k) is stored in TAU(k) and v(k) is an m-vector of the form
36*> [ 0 ... 0 1 x(k) ]', where x(k) is a vector of length m-k stored
37*> in A(k+1:m,k).
38*> \endverbatim
39*
40* Arguments:
41* ==========
42*
43*> \param[in] M
44*> \verbatim
45*> M is INTEGER
46*> The number of rows of the matrix A.
47*> \endverbatim
48*>
49*> \param[in] K
50*> \verbatim
51*> K is INTEGER
52*> The number of columns of A whose subdiagonal entries
53*> contain information about orthogonal transformations.
54*> \endverbatim
55*>
56*> \param[in] A
57*> \verbatim
58*> A is DOUBLE PRECISION array, dimension (LDA,K)
59*> The (possibly partial) output of a QR reduction routine.
60*> \endverbatim
61*>
62*> \param[in] LDA
63*> \verbatim
64*> LDA is INTEGER
65*> The leading dimension of the array A.
66*> \endverbatim
67*>
68*> \param[in] TAU
69*> \verbatim
70*> TAU is DOUBLE PRECISION array, dimension (K)
71*> The scaling factors tau for the elementary transformations as
72*> computed by the QR factorization routine.
73*> \endverbatim
74*>
75*> \param[out] WORK
76*> \verbatim
77*> WORK is DOUBLE PRECISION array, dimension (LWORK)
78*> \endverbatim
79*>
80*> \param[in] LWORK
81*> \verbatim
82*> LWORK is INTEGER
83*> The length of the array WORK. LWORK >= M*M + M.
84*> \endverbatim
85*
86* Authors:
87* ========
88*
89*> \author Univ. of Tennessee
90*> \author Univ. of California Berkeley
91*> \author Univ. of Colorado Denver
92*> \author NAG Ltd.
93*
94*> \ingroup double_lin
95*
96* =====================================================================
97 DOUBLE PRECISION FUNCTION dqrt11( M, K, A, LDA, TAU, WORK, LWORK )
98*
99* -- LAPACK test routine --
100* -- LAPACK is a software package provided by Univ. of Tennessee, --
101* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
102*
103* .. Scalar Arguments ..
104 INTEGER k, lda, lwork, m
105* ..
106* .. Array Arguments ..
107 DOUBLE PRECISION a( lda, * ), tau( * ), work( lwork )
108* ..
109*
110* =====================================================================
111*
112* .. Parameters ..
113 DOUBLE PRECISION zero, one
114 parameter( zero = 0.0d0, one = 1.0d0 )
115* ..
116* .. Local Scalars ..
117 INTEGER info, j
118* ..
119* .. External Functions ..
120 DOUBLE PRECISION dlamch, dlange
121 EXTERNAL dlamch, dlange
122* ..
123* .. External Subroutines ..
124 EXTERNAL dlaset, dorm2r, xerbla
125* ..
126* .. Intrinsic Functions ..
127 INTRINSIC dble
128* ..
129* .. Local Arrays ..
130 DOUBLE PRECISION rdummy( 1 )
131* ..
132* .. Executable Statements ..
133*
134 dqrt11 = zero
135*
136* Test for sufficient workspace
137*
138 IF( lwork.LT.m*m+m ) THEN
139 CALL xerbla( 'DQRT11', 7 )
140 RETURN
141 END IF
142*
143* Quick return if possible
144*
145 IF( m.LE.0 )
146 $ RETURN
147*
148 CALL dlaset( 'Full', m, m, zero, one, work, m )
149*
150* Form Q
151*
152 CALL dorm2r( 'Left', 'No transpose', m, m, k, a, lda, tau, work,
153 $ m, work( m*m+1 ), info )
154*
155* Form Q'*Q
156*
157 CALL dorm2r( 'Left', 'Transpose', m, m, k, a, lda, tau, work, m,
158 $ work( m*m+1 ), info )
159*
160 DO j = 1, m
161 work( ( j-1 )*m+j ) = work( ( j-1 )*m+j ) - one
162 END DO
163*
164 dqrt11 = dlange( 'One-norm', m, m, work, m, rdummy ) /
165 $ ( dble( m )*dlamch( 'Epsilon' ) )
166*
167 RETURN
168*
169* End of DQRT11
170*
171 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
double precision function dqrt11(m, k, a, lda, tau, work, lwork)
DQRT11
Definition dqrt11.f:98
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
double precision function dlange(norm, m, n, a, lda, work)
DLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition dlange.f:114
subroutine dlaset(uplo, m, n, alpha, beta, a, lda)
DLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
Definition dlaset.f:110
subroutine dorm2r(side, trans, m, n, k, a, lda, tau, c, ldc, work, info)
DORM2R multiplies a general matrix by the orthogonal matrix from a QR factorization determined by sge...
Definition dorm2r.f:159