LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
slaqp2.f
Go to the documentation of this file.
1 *> \brief \b SLAQP2 computes a QR factorization with column pivoting of the matrix block.
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SLAQP2 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slaqp2.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slaqp2.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slaqp2.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE SLAQP2( M, N, OFFSET, A, LDA, JPVT, TAU, VN1, VN2,
22 * WORK )
23 *
24 * .. Scalar Arguments ..
25 * INTEGER LDA, M, N, OFFSET
26 * ..
27 * .. Array Arguments ..
28 * INTEGER JPVT( * )
29 * REAL A( LDA, * ), TAU( * ), VN1( * ), VN2( * ),
30 * $ WORK( * )
31 * ..
32 *
33 *
34 *> \par Purpose:
35 * =============
36 *>
37 *> \verbatim
38 *>
39 *> SLAQP2 computes a QR factorization with column pivoting of
40 *> the block A(OFFSET+1:M,1:N).
41 *> The block A(1:OFFSET,1:N) is accordingly pivoted, but not factorized.
42 *> \endverbatim
43 *
44 * Arguments:
45 * ==========
46 *
47 *> \param[in] M
48 *> \verbatim
49 *> M is INTEGER
50 *> The number of rows of the matrix A. M >= 0.
51 *> \endverbatim
52 *>
53 *> \param[in] N
54 *> \verbatim
55 *> N is INTEGER
56 *> The number of columns of the matrix A. N >= 0.
57 *> \endverbatim
58 *>
59 *> \param[in] OFFSET
60 *> \verbatim
61 *> OFFSET is INTEGER
62 *> The number of rows of the matrix A that must be pivoted
63 *> but no factorized. OFFSET >= 0.
64 *> \endverbatim
65 *>
66 *> \param[in,out] A
67 *> \verbatim
68 *> A is REAL array, dimension (LDA,N)
69 *> On entry, the M-by-N matrix A.
70 *> On exit, the upper triangle of block A(OFFSET+1:M,1:N) is
71 *> the triangular factor obtained; the elements in block
72 *> A(OFFSET+1:M,1:N) below the diagonal, together with the
73 *> array TAU, represent the orthogonal matrix Q as a product of
74 *> elementary reflectors. Block A(1:OFFSET,1:N) has been
75 *> accordingly pivoted, but no factorized.
76 *> \endverbatim
77 *>
78 *> \param[in] LDA
79 *> \verbatim
80 *> LDA is INTEGER
81 *> The leading dimension of the array A. LDA >= max(1,M).
82 *> \endverbatim
83 *>
84 *> \param[in,out] JPVT
85 *> \verbatim
86 *> JPVT is INTEGER array, dimension (N)
87 *> On entry, if JPVT(i) .ne. 0, the i-th column of A is permuted
88 *> to the front of A*P (a leading column); if JPVT(i) = 0,
89 *> the i-th column of A is a free column.
90 *> On exit, if JPVT(i) = k, then the i-th column of A*P
91 *> was the k-th column of A.
92 *> \endverbatim
93 *>
94 *> \param[out] TAU
95 *> \verbatim
96 *> TAU is REAL array, dimension (min(M,N))
97 *> The scalar factors of the elementary reflectors.
98 *> \endverbatim
99 *>
100 *> \param[in,out] VN1
101 *> \verbatim
102 *> VN1 is REAL array, dimension (N)
103 *> The vector with the partial column norms.
104 *> \endverbatim
105 *>
106 *> \param[in,out] VN2
107 *> \verbatim
108 *> VN2 is REAL array, dimension (N)
109 *> The vector with the exact column norms.
110 *> \endverbatim
111 *>
112 *> \param[out] WORK
113 *> \verbatim
114 *> WORK is REAL array, dimension (N)
115 *> \endverbatim
116 *
117 * Authors:
118 * ========
119 *
120 *> \author Univ. of Tennessee
121 *> \author Univ. of California Berkeley
122 *> \author Univ. of Colorado Denver
123 *> \author NAG Ltd.
124 *
125 *> \date September 2012
126 *
127 *> \ingroup realOTHERauxiliary
128 *
129 *> \par Contributors:
130 * ==================
131 *>
132 *> G. Quintana-Orti, Depto. de Informatica, Universidad Jaime I, Spain
133 *> X. Sun, Computer Science Dept., Duke University, USA
134 *> \n
135 *> Partial column norm updating strategy modified on April 2011
136 *> Z. Drmac and Z. Bujanovic, Dept. of Mathematics,
137 *> University of Zagreb, Croatia.
138 *
139 *> \par References:
140 * ================
141 *>
142 *> LAPACK Working Note 176
143 *
144 *> \htmlonly
145 *> <a href="http://www.netlib.org/lapack/lawnspdf/lawn176.pdf">[PDF]</a>
146 *> \endhtmlonly
147 *
148 * =====================================================================
149  SUBROUTINE slaqp2( M, N, OFFSET, A, LDA, JPVT, TAU, VN1, VN2,
150  $ work )
151 *
152 * -- LAPACK auxiliary routine (version 3.4.2) --
153 * -- LAPACK is a software package provided by Univ. of Tennessee, --
154 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
155 * September 2012
156 *
157 * .. Scalar Arguments ..
158  INTEGER LDA, M, N, OFFSET
159 * ..
160 * .. Array Arguments ..
161  INTEGER JPVT( * )
162  REAL A( lda, * ), TAU( * ), VN1( * ), VN2( * ),
163  $ work( * )
164 * ..
165 *
166 * =====================================================================
167 *
168 * .. Parameters ..
169  REAL ZERO, ONE
170  parameter ( zero = 0.0e+0, one = 1.0e+0 )
171 * ..
172 * .. Local Scalars ..
173  INTEGER I, ITEMP, J, MN, OFFPI, PVT
174  REAL AII, TEMP, TEMP2, TOL3Z
175 * ..
176 * .. External Subroutines ..
177  EXTERNAL slarf, slarfg, sswap
178 * ..
179 * .. Intrinsic Functions ..
180  INTRINSIC abs, max, min, sqrt
181 * ..
182 * .. External Functions ..
183  INTEGER ISAMAX
184  REAL SLAMCH, SNRM2
185  EXTERNAL isamax, slamch, snrm2
186 * ..
187 * .. Executable Statements ..
188 *
189  mn = min( m-offset, n )
190  tol3z = sqrt(slamch('Epsilon'))
191 *
192 * Compute factorization.
193 *
194  DO 20 i = 1, mn
195 *
196  offpi = offset + i
197 *
198 * Determine ith pivot column and swap if necessary.
199 *
200  pvt = ( i-1 ) + isamax( n-i+1, vn1( i ), 1 )
201 *
202  IF( pvt.NE.i ) THEN
203  CALL sswap( m, a( 1, pvt ), 1, a( 1, i ), 1 )
204  itemp = jpvt( pvt )
205  jpvt( pvt ) = jpvt( i )
206  jpvt( i ) = itemp
207  vn1( pvt ) = vn1( i )
208  vn2( pvt ) = vn2( i )
209  END IF
210 *
211 * Generate elementary reflector H(i).
212 *
213  IF( offpi.LT.m ) THEN
214  CALL slarfg( m-offpi+1, a( offpi, i ), a( offpi+1, i ), 1,
215  $ tau( i ) )
216  ELSE
217  CALL slarfg( 1, a( m, i ), a( m, i ), 1, tau( i ) )
218  END IF
219 *
220  IF( i.LT.n ) THEN
221 *
222 * Apply H(i)**T to A(offset+i:m,i+1:n) from the left.
223 *
224  aii = a( offpi, i )
225  a( offpi, i ) = one
226  CALL slarf( 'Left', m-offpi+1, n-i, a( offpi, i ), 1,
227  $ tau( i ), a( offpi, i+1 ), lda, work( 1 ) )
228  a( offpi, i ) = aii
229  END IF
230 *
231 * Update partial column norms.
232 *
233  DO 10 j = i + 1, n
234  IF( vn1( j ).NE.zero ) THEN
235 *
236 * NOTE: The following 4 lines follow from the analysis in
237 * Lapack Working Note 176.
238 *
239  temp = one - ( abs( a( offpi, j ) ) / vn1( j ) )**2
240  temp = max( temp, zero )
241  temp2 = temp*( vn1( j ) / vn2( j ) )**2
242  IF( temp2 .LE. tol3z ) THEN
243  IF( offpi.LT.m ) THEN
244  vn1( j ) = snrm2( m-offpi, a( offpi+1, j ), 1 )
245  vn2( j ) = vn1( j )
246  ELSE
247  vn1( j ) = zero
248  vn2( j ) = zero
249  END IF
250  ELSE
251  vn1( j ) = vn1( j )*sqrt( temp )
252  END IF
253  END IF
254  10 CONTINUE
255 *
256  20 CONTINUE
257 *
258  RETURN
259 *
260 * End of SLAQP2
261 *
262  END
subroutine slaqp2(M, N, OFFSET, A, LDA, JPVT, TAU, VN1, VN2, WORK)
SLAQP2 computes a QR factorization with column pivoting of the matrix block.
Definition: slaqp2.f:151
subroutine slarfg(N, ALPHA, X, INCX, TAU)
SLARFG generates an elementary reflector (Householder matrix).
Definition: slarfg.f:108
subroutine slarf(SIDE, M, N, V, INCV, TAU, C, LDC, WORK)
SLARF applies an elementary reflector to a general rectangular matrix.
Definition: slarf.f:126
subroutine sswap(N, SX, INCX, SY, INCY)
SSWAP
Definition: sswap.f:53