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

◆ claqp2()

subroutine claqp2 ( integer m,
integer n,
integer offset,
complex, dimension( lda, * ) a,
integer lda,
integer, dimension( * ) jpvt,
complex, dimension( * ) tau,
real, dimension( * ) vn1,
real, dimension( * ) vn2,
complex, dimension( * ) work )

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

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

Purpose:
!>
!> CLAQP2 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 COMPLEX 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 COMPLEX array, dimension (min(M,N))
!>          The scalar factors of the elementary reflectors.
!> 
[in,out]VN1
!>          VN1 is REAL array, dimension (N)
!>          The vector with the partial column norms.
!> 
[in,out]VN2
!>          VN2 is REAL array, dimension (N)
!>          The vector with the exact column norms.
!> 
[out]WORK
!>          WORK is COMPLEX 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 143 of file claqp2.f.

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