1       SUBROUTINE ZLAQPS( M, N, OFFSET, NB, KB, A, LDA, JPVT, TAU, VN1,
  2      $                   VN2, AUXV, F, LDF )
  3 *
  4 *  -- LAPACK auxiliary routine (version 3.3.1) --
  5 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  6 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  7 *  -- April 2011                                                      --
  8 *
  9 *     .. Scalar Arguments ..
 10       INTEGER            KB, LDA, LDF, M, N, NB, OFFSET
 11 *     ..
 12 *     .. Array Arguments ..
 13       INTEGER            JPVT( * )
 14       DOUBLE PRECISION   VN1( * ), VN2( * )
 15       COMPLEX*16         A( LDA, * ), AUXV( * ), F( LDF, * ), TAU( * )
 16 *     ..
 17 *
 18 *  Purpose
 19 *  =======
 20 *
 21 *  ZLAQPS computes a step of QR factorization with column pivoting
 22 *  of a complex M-by-N matrix A by using Blas-3.  It tries to factorize
 23 *  NB columns from A starting from the row OFFSET+1, and updates all
 24 *  of the matrix with Blas-3 xGEMM.
 25 *
 26 *  In some cases, due to catastrophic cancellations, it cannot
 27 *  factorize NB columns.  Hence, the actual number of factorized
 28 *  columns is returned in KB.
 29 *
 30 *  Block A(1:OFFSET,1:N) is accordingly pivoted, but not factorized.
 31 *
 32 *  Arguments
 33 *  =========
 34 *
 35 *  M       (input) INTEGER
 36 *          The number of rows of the matrix A. M >= 0.
 37 *
 38 *  N       (input) INTEGER
 39 *          The number of columns of the matrix A. N >= 0
 40 *
 41 *  OFFSET  (input) INTEGER
 42 *          The number of rows of A that have been factorized in
 43 *          previous steps.
 44 *
 45 *  NB      (input) INTEGER
 46 *          The number of columns to factorize.
 47 *
 48 *  KB      (output) INTEGER
 49 *          The number of columns actually factorized.
 50 *
 51 *  A       (input/output) COMPLEX*16 array, dimension (LDA,N)
 52 *          On entry, the M-by-N matrix A.
 53 *          On exit, block A(OFFSET+1:M,1:KB) is the triangular
 54 *          factor obtained and block A(1:OFFSET,1:N) has been
 55 *          accordingly pivoted, but no factorized.
 56 *          The rest of the matrix, block A(OFFSET+1:M,KB+1:N) has
 57 *          been updated.
 58 *
 59 *  LDA     (input) INTEGER
 60 *          The leading dimension of the array A. LDA >= max(1,M).
 61 *
 62 *  JPVT    (input/output) INTEGER array, dimension (N)
 63 *          JPVT(I) = K <==> Column K of the full matrix A has been
 64 *          permuted into position I in AP.
 65 *
 66 *  TAU     (output) COMPLEX*16 array, dimension (KB)
 67 *          The scalar factors of the elementary reflectors.
 68 *
 69 *  VN1     (input/output) DOUBLE PRECISION array, dimension (N)
 70 *          The vector with the partial column norms.
 71 *
 72 *  VN2     (input/output) DOUBLE PRECISION array, dimension (N)
 73 *          The vector with the exact column norms.
 74 *
 75 *  AUXV    (input/output) COMPLEX*16 array, dimension (NB)
 76 *          Auxiliar vector.
 77 *
 78 *  F       (input/output) COMPLEX*16 array, dimension (LDF,NB)
 79 *          Matrix F**H = L * Y**H * A.
 80 *
 81 *  LDF     (input) INTEGER
 82 *          The leading dimension of the array F. LDF >= max(1,N).
 83 *
 84 *  Further Details
 85 *  ===============
 86 *
 87 *  Based on contributions by
 88 *    G. Quintana-Orti, Depto. de Informatica, Universidad Jaime I, Spain
 89 *    X. Sun, Computer Science Dept., Duke University, USA
 90 *
 91 *  Partial column norm updating strategy modified by
 92 *    Z. Drmac and Z. Bujanovic, Dept. of Mathematics,
 93 *    University of Zagreb, Croatia.
 94 *  -- April 2011                                                      --
 95 *  For more details see LAPACK Working Note 176.
 96 *  =====================================================================
 97 *
 98 *     .. Parameters ..
 99       DOUBLE PRECISION   ZERO, ONE
100       COMPLEX*16         CZERO, CONE
101       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0,
102      $                   CZERO = ( 0.0D+00.0D+0 ),
103      $                   CONE = ( 1.0D+00.0D+0 ) )
104 *     ..
105 *     .. Local Scalars ..
106       INTEGER            ITEMP, J, K, LASTRK, LSTICC, PVT, RK
107       DOUBLE PRECISION   TEMP, TEMP2, TOL3Z
108       COMPLEX*16         AKK
109 *     ..
110 *     .. External Subroutines ..
111       EXTERNAL           ZGEMM, ZGEMV, ZLARFG, ZSWAP
112 *     ..
113 *     .. Intrinsic Functions ..
114       INTRINSIC          ABSDBLEDCONJGMAXMINNINTSQRT
115 *     ..
116 *     .. External Functions ..
117       INTEGER            IDAMAX
118       DOUBLE PRECISION   DLAMCH, DZNRM2
119       EXTERNAL           IDAMAX, DLAMCH, DZNRM2
120 *     ..
121 *     .. Executable Statements ..
122 *
123       LASTRK = MIN( M, N+OFFSET )
124       LSTICC = 0
125       K = 0
126       TOL3Z = SQRT(DLAMCH('Epsilon'))
127 *
128 *     Beginning of while loop.
129 *
130    10 CONTINUE
131       IF( ( K.LT.NB ) .AND. ( LSTICC.EQ.0 ) ) THEN
132          K = K + 1
133          RK = OFFSET + K
134 *
135 *        Determine ith pivot column and swap if necessary
136 *
137          PVT = ( K-1 ) + IDAMAX( N-K+1, VN1( K ), 1 )
138          IF( PVT.NE.K ) THEN
139             CALL ZSWAP( M, A( 1, PVT ), 1, A( 1, K ), 1 )
140             CALL ZSWAP( K-1, F( PVT, 1 ), LDF, F( K, 1 ), LDF )
141             ITEMP = JPVT( PVT )
142             JPVT( PVT ) = JPVT( K )
143             JPVT( K ) = ITEMP
144             VN1( PVT ) = VN1( K )
145             VN2( PVT ) = VN2( K )
146          END IF
147 *
148 *        Apply previous Householder reflectors to column K:
149 *        A(RK:M,K) := A(RK:M,K) - A(RK:M,1:K-1)*F(K,1:K-1)**H.
150 *
151          IF( K.GT.1 ) THEN
152             DO 20 J = 1, K - 1
153                F( K, J ) = DCONJG( F( K, J ) )
154    20       CONTINUE
155             CALL ZGEMV( 'No transpose', M-RK+1, K-1-CONE, A( RK, 1 ),
156      $                  LDA, F( K, 1 ), LDF, CONE, A( RK, K ), 1 )
157             DO 30 J = 1, K - 1
158                F( K, J ) = DCONJG( F( K, J ) )
159    30       CONTINUE
160          END IF
161 *
162 *        Generate elementary reflector H(k).
163 *
164          IF( RK.LT.M ) THEN
165             CALL ZLARFG( M-RK+1, A( RK, K ), A( RK+1, K ), 1, TAU( K ) )
166          ELSE
167             CALL ZLARFG( 1, A( RK, K ), A( RK, K ), 1, TAU( K ) )
168          END IF
169 *
170          AKK = A( RK, K )
171          A( RK, K ) = CONE
172 *
173 *        Compute Kth column of F:
174 *
175 *        Compute  F(K+1:N,K) := tau(K)*A(RK:M,K+1:N)**H*A(RK:M,K).
176 *
177          IF( K.LT.N ) THEN
178             CALL ZGEMV( 'Conjugate transpose', M-RK+1, N-K, TAU( K ),
179      $                  A( RK, K+1 ), LDA, A( RK, K ), 1, CZERO,
180      $                  F( K+1, K ), 1 )
181          END IF
182 *
183 *        Padding F(1:K,K) with zeros.
184 *
185          DO 40 J = 1, K
186             F( J, K ) = CZERO
187    40    CONTINUE
188 *
189 *        Incremental updating of F:
190 *        F(1:N,K) := F(1:N,K) - tau(K)*F(1:N,1:K-1)*A(RK:M,1:K-1)**H
191 *                    *A(RK:M,K).
192 *
193          IF( K.GT.1 ) THEN
194             CALL ZGEMV( 'Conjugate transpose', M-RK+1, K-1-TAU( K ),
195      $                  A( RK, 1 ), LDA, A( RK, K ), 1, CZERO,
196      $                  AUXV( 1 ), 1 )
197 *
198             CALL ZGEMV( 'No transpose', N, K-1, CONE, F( 11 ), LDF,
199      $                  AUXV( 1 ), 1, CONE, F( 1, K ), 1 )
200          END IF
201 *
202 *        Update the current row of A:
203 *        A(RK,K+1:N) := A(RK,K+1:N) - A(RK,1:K)*F(K+1:N,1:K)**H.
204 *
205          IF( K.LT.N ) THEN
206             CALL ZGEMM( 'No transpose''Conjugate transpose'1, N-K,
207      $                  K, -CONE, A( RK, 1 ), LDA, F( K+11 ), LDF,
208      $                  CONE, A( RK, K+1 ), LDA )
209          END IF
210 *
211 *        Update partial column norms.
212 *
213          IF( RK.LT.LASTRK ) THEN
214             DO 50 J = K + 1, N
215                IF( VN1( J ).NE.ZERO ) THEN
216 *
217 *                 NOTE: The following 4 lines follow from the analysis in
218 *                 Lapack Working Note 176.
219 *
220                   TEMP = ABS( A( RK, J ) ) / VN1( J )
221                   TEMP = MAX( ZERO, ( ONE+TEMP )*( ONE-TEMP ) )
222                   TEMP2 = TEMP*( VN1( J ) / VN2( J ) )**2
223                   IF( TEMP2 .LE. TOL3Z ) THEN
224                      VN2( J ) = DBLE( LSTICC )
225                      LSTICC = J
226                   ELSE
227                      VN1( J ) = VN1( J )*SQRT( TEMP )
228                   END IF
229                END IF
230    50       CONTINUE
231          END IF
232 *
233          A( RK, K ) = AKK
234 *
235 *        End of while loop.
236 *
237          GO TO 10
238       END IF
239       KB = K
240       RK = OFFSET + KB
241 *
242 *     Apply the block reflector to the rest of the matrix:
243 *     A(OFFSET+KB+1:M,KB+1:N) := A(OFFSET+KB+1:M,KB+1:N) -
244 *                         A(OFFSET+KB+1:M,1:KB)*F(KB+1:N,1:KB)**H.
245 *
246       IF( KB.LT.MIN( N, M-OFFSET ) ) THEN
247          CALL ZGEMM( 'No transpose''Conjugate transpose', M-RK, N-KB,
248      $               KB, -CONE, A( RK+11 ), LDA, F( KB+11 ), LDF,
249      $               CONE, A( RK+1, KB+1 ), LDA )
250       END IF
251 *
252 *     Recomputation of difficult columns.
253 *
254    60 CONTINUE
255       IF( LSTICC.GT.0 ) THEN
256          ITEMP = NINT( VN2( LSTICC ) )
257          VN1( LSTICC ) = DZNRM2( M-RK, A( RK+1, LSTICC ), 1 )
258 *
259 *        NOTE: The computation of VN1( LSTICC ) relies on the fact that 
260 *        SNRM2 does not fail on vectors with norm below the value of
261 *        SQRT(DLAMCH('S')) 
262 *
263          VN2( LSTICC ) = VN1( LSTICC )
264          LSTICC = ITEMP
265          GO TO 60
266       END IF
267 *
268       RETURN
269 *
270 *     End of ZLAQPS
271 *
272       END