LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dqpt01()

double precision function dqpt01 ( integer m,
integer n,
integer k,
double precision, dimension( lda, * ) a,
double precision, dimension( lda, * ) af,
integer lda,
double precision, dimension( * ) tau,
integer, dimension( * ) jpvt,
double precision, dimension( lwork ) work,
integer lwork )

DQPT01

Purpose:
!>
!> DQPT01 tests the QR-factorization with pivoting of a matrix A.  The
!> array AF contains the (possibly partial) QR-factorization of A, where
!> the upper triangle of AF(1:K,1:K) is a partial triangular factor,
!> the entries below the diagonal in the first K columns are the
!> Householder vectors, and the rest of AF contains a partially updated
!> matrix.
!>
!> This function returns ||A*P - Q*R|| / ( ||norm(A)||*eps*max(M,N) ),
!> where || . || is matrix one norm.
!> 
Parameters
[in]M
!>          M is INTEGER
!>          The number of rows of the matrices A and AF.
!> 
[in]N
!>          N is INTEGER
!>          The number of columns of the matrices A and AF.
!> 
[in]K
!>          K is INTEGER
!>          The number of columns of AF that have been reduced
!>          to upper triangular form.
!> 
[in]A
!>          A is DOUBLE PRECISION array, dimension (LDA, N)
!>          The original matrix A.
!> 
[in]AF
!>          AF is DOUBLE PRECISION array, dimension (LDA,N)
!>          The (possibly partial) output of DGEQPF.  The upper triangle
!>          of AF(1:k,1:k) is a partial triangular factor, the entries
!>          below the diagonal in the first k columns are the Householder
!>          vectors, and the rest of AF contains a partially updated
!>          matrix.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the arrays A and AF.
!> 
[in]TAU
!>          TAU is DOUBLE PRECISION array, dimension (K)
!>          Details of the Householder transformations as returned by
!>          DGEQPF.
!> 
[in]JPVT
!>          JPVT is INTEGER array, dimension (N)
!>          Pivot information as returned by DGEQPF.
!> 
[out]WORK
!>          WORK is DOUBLE PRECISION array, dimension (LWORK)
!> 
[in]LWORK
!>          LWORK is INTEGER
!>          The length of the array WORK.  LWORK >= M*N+N.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 119 of file dqpt01.f.

121*
122* -- LAPACK test routine --
123* -- LAPACK is a software package provided by Univ. of Tennessee, --
124* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
125*
126* .. Scalar Arguments ..
127 INTEGER K, LDA, LWORK, M, N
128* ..
129* .. Array Arguments ..
130 INTEGER JPVT( * )
131 DOUBLE PRECISION A( LDA, * ), AF( LDA, * ), TAU( * ),
132 $ WORK( LWORK )
133* ..
134*
135* =====================================================================
136*
137* .. Parameters ..
138 DOUBLE PRECISION ZERO, ONE
139 parameter( zero = 0.0d0, one = 1.0d0 )
140* ..
141* .. Local Scalars ..
142 INTEGER I, INFO, J
143 DOUBLE PRECISION NORMA
144* ..
145* .. Local Arrays ..
146 DOUBLE PRECISION RWORK( 1 )
147* ..
148* .. External Functions ..
149 DOUBLE PRECISION DLAMCH, DLANGE
150 EXTERNAL dlamch, dlange
151* ..
152* .. External Subroutines ..
153 EXTERNAL daxpy, dcopy, dormqr, xerbla
154* ..
155* .. Intrinsic Functions ..
156 INTRINSIC dble, max, min
157* ..
158* .. Executable Statements ..
159*
160 dqpt01 = zero
161*
162* Test if there is enough workspace
163*
164 IF( lwork.LT.m*n+n ) THEN
165 CALL xerbla( 'DQPT01', 10 )
166 RETURN
167 END IF
168*
169* Quick return if possible
170*
171 IF( m.LE.0 .OR. n.LE.0 )
172 $ RETURN
173*
174 norma = dlange( 'One-norm', m, n, a, lda, rwork )
175*
176 DO j = 1, k
177*
178* Copy the upper triangular part of the factor R stored
179* in AF(1:K,1:K) into the work array WORK.
180*
181 DO i = 1, min( j, m )
182 work( ( j-1 )*m+i ) = af( i, j )
183 END DO
184*
185* Zero out the elements below the diagonal in the work array.
186*
187 DO i = j + 1, m
188 work( ( j-1 )*m+i ) = zero
189 END DO
190 END DO
191*
192* Copy columns (K+1,N) from AF into the work array WORK.
193* AF(1:K,K+1:N) contains the rectangular block of the upper trapezoidal
194* factor R, AF(K+1:M,K+1:N) contains the partially updated residual
195* matrix of R.
196*
197 DO j = k + 1, n
198 CALL dcopy( m, af( 1, j ), 1, work( ( j-1 )*m+1 ), 1 )
199 END DO
200*
201 CALL dormqr( 'Left', 'No transpose', m, n, k, af, lda, tau, work,
202 $ m, work( m*n+1 ), lwork-m*n, info )
203*
204 DO j = 1, n
205*
206* Compare J-th column of QR and JPVT(J)-th column of A.
207*
208 CALL daxpy( m, -one, a( 1, jpvt( j ) ), 1, work( ( j-1 )*m+1 ),
209 $ 1 )
210 END DO
211*
212 dqpt01 = dlange( 'One-norm', m, n, work, m, rwork ) /
213 $ ( dble( max( m, n ) )*dlamch( 'Epsilon' ) )
214 IF( norma.NE.zero )
215 $ dqpt01 = dqpt01 / norma
216*
217 RETURN
218*
219* End of DQPT01
220*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
double precision function dqpt01(m, n, k, a, af, lda, tau, jpvt, work, lwork)
DQPT01
Definition dqpt01.f:121
subroutine daxpy(n, da, dx, incx, dy, incy)
DAXPY
Definition daxpy.f:89
subroutine dcopy(n, dx, incx, dy, incy)
DCOPY
Definition dcopy.f:82
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:112
subroutine dormqr(side, trans, m, n, k, a, lda, tau, c, ldc, work, lwork, info)
DORMQR
Definition dormqr.f:165
Here is the call graph for this function:
Here is the caller graph for this function: