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

◆ dlaqp2()

subroutine dlaqp2 ( integer  m,
integer  n,
integer  offset,
double precision, dimension( lda, * )  a,
integer  lda,
integer, dimension( * )  jpvt,
double precision, dimension( * )  tau,
double precision, dimension( * )  vn1,
double precision, dimension( * )  vn2,
double precision, dimension( * )  work 
)

DLAQP2 computes a QR factorization with column pivoting of the matrix block.

Download DLAQP2 + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 DLAQP2 computes a QR factorization with column pivoting of
 the block A(OFFSET+1:M,1:N).
 The block A(1:OFFSET,1:N) is accordingly pivoted, but not factorized.
Parameters
[in]M
          M is INTEGER
          The number of rows of the matrix A. M >= 0.
[in]N
          N is INTEGER
          The number of columns of the matrix A. N >= 0.
[in]OFFSET
          OFFSET is INTEGER
          The number of rows of the matrix A that must be pivoted
          but no factorized. OFFSET >= 0.
[in,out]A
          A is DOUBLE PRECISION array, dimension (LDA,N)
          On entry, the M-by-N matrix A.
          On exit, the upper triangle of block A(OFFSET+1:M,1:N) is
          the triangular factor obtained; the elements in block
          A(OFFSET+1:M,1:N) below the diagonal, together with the
          array TAU, represent the orthogonal matrix Q as a product of
          elementary reflectors. Block A(1:OFFSET,1:N) has been
          accordingly pivoted, but no factorized.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A. LDA >= max(1,M).
[in,out]JPVT
          JPVT is INTEGER array, dimension (N)
          On entry, if JPVT(i) .ne. 0, the i-th column of A is permuted
          to the front of A*P (a leading column); if JPVT(i) = 0,
          the i-th column of A is a free column.
          On exit, if JPVT(i) = k, then the i-th column of A*P
          was the k-th column of A.
[out]TAU
          TAU is DOUBLE PRECISION array, dimension (min(M,N))
          The scalar factors of the elementary reflectors.
[in,out]VN1
          VN1 is DOUBLE PRECISION array, dimension (N)
          The vector with the partial column norms.
[in,out]VN2
          VN2 is DOUBLE PRECISION array, dimension (N)
          The vector with the exact column norms.
[out]WORK
          WORK is DOUBLE PRECISION array, dimension (N)
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Contributors:
G. Quintana-Orti, Depto. de Informatica, Universidad Jaime I, Spain X. Sun, Computer Science Dept., Duke University, USA
Partial column norm updating strategy modified on April 2011 Z. Drmac and Z. Bujanovic, Dept. of Mathematics, University of Zagreb, Croatia.
References:
LAPACK Working Note 176 [PDF]

Definition at line 147 of file dlaqp2.f.

149*
150* -- LAPACK auxiliary routine --
151* -- LAPACK is a software package provided by Univ. of Tennessee, --
152* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
153*
154* .. Scalar Arguments ..
155 INTEGER LDA, M, N, OFFSET
156* ..
157* .. Array Arguments ..
158 INTEGER JPVT( * )
159 DOUBLE PRECISION A( LDA, * ), TAU( * ), VN1( * ), VN2( * ),
160 $ WORK( * )
161* ..
162*
163* =====================================================================
164*
165* .. Parameters ..
166 DOUBLE PRECISION ZERO, ONE
167 parameter( zero = 0.0d+0, one = 1.0d+0 )
168* ..
169* .. Local Scalars ..
170 INTEGER I, ITEMP, J, MN, OFFPI, PVT
171 DOUBLE PRECISION AII, TEMP, TEMP2, TOL3Z
172* ..
173* .. External Subroutines ..
174 EXTERNAL dlarf, dlarfg, dswap
175* ..
176* .. Intrinsic Functions ..
177 INTRINSIC abs, max, min, sqrt
178* ..
179* .. External Functions ..
180 INTEGER IDAMAX
181 DOUBLE PRECISION DLAMCH, DNRM2
182 EXTERNAL idamax, dlamch, dnrm2
183* ..
184* .. Executable Statements ..
185*
186 mn = min( m-offset, n )
187 tol3z = sqrt(dlamch('Epsilon'))
188*
189* Compute factorization.
190*
191 DO 20 i = 1, mn
192*
193 offpi = offset + i
194*
195* Determine ith pivot column and swap if necessary.
196*
197 pvt = ( i-1 ) + idamax( n-i+1, vn1( i ), 1 )
198*
199 IF( pvt.NE.i ) THEN
200 CALL dswap( m, a( 1, pvt ), 1, a( 1, i ), 1 )
201 itemp = jpvt( pvt )
202 jpvt( pvt ) = jpvt( i )
203 jpvt( i ) = itemp
204 vn1( pvt ) = vn1( i )
205 vn2( pvt ) = vn2( i )
206 END IF
207*
208* Generate elementary reflector H(i).
209*
210 IF( offpi.LT.m ) THEN
211 CALL dlarfg( m-offpi+1, a( offpi, i ), a( offpi+1, i ), 1,
212 $ tau( i ) )
213 ELSE
214 CALL dlarfg( 1, a( m, i ), a( m, i ), 1, tau( i ) )
215 END IF
216*
217 IF( i.LT.n ) THEN
218*
219* Apply H(i)**T to A(offset+i:m,i+1:n) from the left.
220*
221 aii = a( offpi, i )
222 a( offpi, i ) = one
223 CALL dlarf( 'Left', m-offpi+1, n-i, a( offpi, i ), 1,
224 $ tau( i ), a( offpi, i+1 ), lda, work( 1 ) )
225 a( offpi, i ) = aii
226 END IF
227*
228* Update partial column norms.
229*
230 DO 10 j = i + 1, n
231 IF( vn1( j ).NE.zero ) THEN
232*
233* NOTE: The following 4 lines follow from the analysis in
234* Lapack Working Note 176.
235*
236 temp = one - ( abs( a( offpi, j ) ) / vn1( j ) )**2
237 temp = max( temp, zero )
238 temp2 = temp*( vn1( j ) / vn2( j ) )**2
239 IF( temp2 .LE. tol3z ) THEN
240 IF( offpi.LT.m ) THEN
241 vn1( j ) = dnrm2( m-offpi, a( offpi+1, j ), 1 )
242 vn2( j ) = vn1( j )
243 ELSE
244 vn1( j ) = zero
245 vn2( j ) = zero
246 END IF
247 ELSE
248 vn1( j ) = vn1( j )*sqrt( temp )
249 END IF
250 END IF
251 10 CONTINUE
252*
253 20 CONTINUE
254*
255 RETURN
256*
257* End of DLAQP2
258*
integer function idamax(n, dx, incx)
IDAMAX
Definition idamax.f:71
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
subroutine dlarf(side, m, n, v, incv, tau, c, ldc, work)
DLARF applies an elementary reflector to a general rectangular matrix.
Definition dlarf.f:124
subroutine dlarfg(n, alpha, x, incx, tau)
DLARFG generates an elementary reflector (Householder matrix).
Definition dlarfg.f:106
real(wp) function dnrm2(n, x, incx)
DNRM2
Definition dnrm2.f90:89
subroutine dswap(n, dx, incx, dy, incy)
DSWAP
Definition dswap.f:82
Here is the call graph for this function:
Here is the caller graph for this function: