LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zqpt01.f
Go to the documentation of this file.
1*> \brief \b ZQPT01
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 ZQPT01( M, N, K, A, AF, LDA, TAU, JPVT,
12* WORK, LWORK )
13*
14* .. Scalar Arguments ..
15* INTEGER K, LDA, LWORK, M, N
16* ..
17* .. Array Arguments ..
18* INTEGER JPVT( * )
19* COMPLEX*16 A( LDA, * ), AF( LDA, * ), TAU( * ),
20* $ WORK( LWORK )
21* ..
22*
23*
24*> \par Purpose:
25* =============
26*>
27*> \verbatim
28*>
29*> ZQPT01 tests the QR-factorization with pivoting of a matrix A. The
30*> array AF contains the (possibly partial) QR-factorization of A, where
31*> the upper triangle of AF(1:k,1:k) is a partial triangular factor,
32*> the entries below the diagonal in the first k columns are the
33*> Householder vectors, and the rest of AF contains a partially updated
34*> matrix.
35*>
36*> This function returns ||A*P - Q*R|| / ( ||norm(A)||*eps*max(M,N) )
37*> \endverbatim
38*
39* Arguments:
40* ==========
41*
42*> \param[in] M
43*> \verbatim
44*> M is INTEGER
45*> The number of rows of the matrices A and AF.
46*> \endverbatim
47*>
48*> \param[in] N
49*> \verbatim
50*> N is INTEGER
51*> The number of columns of the matrices A and AF.
52*> \endverbatim
53*>
54*> \param[in] K
55*> \verbatim
56*> K is INTEGER
57*> The number of columns of AF that have been reduced
58*> to upper triangular form.
59*> \endverbatim
60*>
61*> \param[in] A
62*> \verbatim
63*> A is COMPLEX*16 array, dimension (LDA, N)
64*> The original matrix A.
65*> \endverbatim
66*>
67*> \param[in] AF
68*> \verbatim
69*> AF is COMPLEX*16 array, dimension (LDA,N)
70*> The (possibly partial) output of ZGEQPF. The upper triangle
71*> of AF(1:k,1:k) is a partial triangular factor, the entries
72*> below the diagonal in the first k columns are the Householder
73*> vectors, and the rest of AF contains a partially updated
74*> matrix.
75*> \endverbatim
76*>
77*> \param[in] LDA
78*> \verbatim
79*> LDA is INTEGER
80*> The leading dimension of the arrays A and AF.
81*> \endverbatim
82*>
83*> \param[in] TAU
84*> \verbatim
85*> TAU is COMPLEX*16 array, dimension (K)
86*> Details of the Householder transformations as returned by
87*> ZGEQPF.
88*> \endverbatim
89*>
90*> \param[in] JPVT
91*> \verbatim
92*> JPVT is INTEGER array, dimension (N)
93*> Pivot information as returned by ZGEQPF.
94*> \endverbatim
95*>
96*> \param[out] WORK
97*> \verbatim
98*> WORK is COMPLEX*16 array, dimension (LWORK)
99*> \endverbatim
100*>
101*> \param[in] LWORK
102*> \verbatim
103*> LWORK is INTEGER
104*> The length of the array WORK. LWORK >= M*N+N.
105*> \endverbatim
106*
107* Authors:
108* ========
109*
110*> \author Univ. of Tennessee
111*> \author Univ. of California Berkeley
112*> \author Univ. of Colorado Denver
113*> \author NAG Ltd.
114*
115*> \ingroup complex16_lin
116*
117* =====================================================================
118 DOUBLE PRECISION FUNCTION zqpt01( M, N, K, A, AF, LDA, TAU, JPVT,
119 $ WORK, LWORK )
120*
121* -- LAPACK test routine --
122* -- LAPACK is a software package provided by Univ. of Tennessee, --
123* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
124*
125* .. Scalar Arguments ..
126 INTEGER k, lda, lwork, m, n
127* ..
128* .. Array Arguments ..
129 INTEGER jpvt( * )
130 COMPLEX*16 a( lda, * ), af( lda, * ), tau( * ),
131 $ work( lwork )
132* ..
133*
134* =====================================================================
135*
136* .. Parameters ..
137 DOUBLE PRECISION zero, one
138 parameter( zero = 0.0d0, one = 1.0d0 )
139* ..
140* .. Local Scalars ..
141 INTEGER i, info, j
142 DOUBLE PRECISION norma
143* ..
144* .. Local Arrays ..
145 DOUBLE PRECISION rwork( 1 )
146* ..
147* .. External Functions ..
148 DOUBLE PRECISION dlamch, zlange
149 EXTERNAL dlamch, zlange
150* ..
151* .. External Subroutines ..
152 EXTERNAL xerbla, zaxpy, zcopy, zunmqr
153* ..
154* .. Intrinsic Functions ..
155 INTRINSIC dble, dcmplx, max, min
156* ..
157* .. Executable Statements ..
158*
159 zqpt01 = zero
160*
161* Test if there is enough workspace
162*
163 IF( lwork.LT.m*n+n ) THEN
164 CALL xerbla( 'ZQPT01', 10 )
165 RETURN
166 END IF
167*
168* Quick return if possible
169*
170 IF( m.LE.0 .OR. n.LE.0 )
171 $ RETURN
172*
173 norma = zlange( 'One-norm', m, n, a, lda, rwork )
174*
175 DO j = 1, k
176 DO i = 1, min( j, m )
177 work( ( j-1 )*m+i ) = af( i, j )
178 END DO
179 DO i = j + 1, m
180 work( ( j-1 )*m+i ) = zero
181 END DO
182 END DO
183 DO j = k + 1, n
184 CALL zcopy( m, af( 1, j ), 1, work( ( j-1 )*m+1 ), 1 )
185 END DO
186*
187 CALL zunmqr( 'Left', 'No transpose', m, n, k, af, lda, tau, work,
188 $ m, work( m*n+1 ), lwork-m*n, info )
189*
190 DO j = 1, n
191*
192* Compare i-th column of QR and jpvt(i)-th column of A
193*
194 CALL zaxpy( m, dcmplx( -one ), a( 1, jpvt( j ) ), 1,
195 $ work( ( j-1 )*m+1 ), 1 )
196 END DO
197*
198 zqpt01 = zlange( 'One-norm', m, n, work, m, rwork ) /
199 $ ( dble( max( m, n ) )*dlamch( 'Epsilon' ) )
200 IF( norma.NE.zero )
201 $ zqpt01 = zqpt01 / norma
202*
203 RETURN
204*
205* End of ZQPT01
206*
207 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zaxpy(n, za, zx, incx, zy, incy)
ZAXPY
Definition zaxpy.f:88
subroutine zcopy(n, zx, incx, zy, incy)
ZCOPY
Definition zcopy.f:81
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
double precision function zlange(norm, m, n, a, lda, work)
ZLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition zlange.f:115
subroutine zunmqr(side, trans, m, n, k, a, lda, tau, c, ldc, work, lwork, info)
ZUNMQR
Definition zunmqr.f:167
double precision function zqpt01(m, n, k, a, af, lda, tau, jpvt, work, lwork)
ZQPT01
Definition zqpt01.f:120