Statistiques
| Révision :

root / src / lapack / double / dlaqp2.f @ 10

Historique | Voir | Annoter | Télécharger (5,52 ko)

1 1 pfleura2
      SUBROUTINE DLAQP2( M, N, OFFSET, A, LDA, JPVT, TAU, VN1, VN2,
2 1 pfleura2
     $                   WORK )
3 1 pfleura2
*
4 1 pfleura2
*  -- LAPACK auxiliary routine (version 3.2.2) --
5 1 pfleura2
*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
6 1 pfleura2
*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
7 1 pfleura2
*     June 2010
8 1 pfleura2
*
9 1 pfleura2
*     .. Scalar Arguments ..
10 1 pfleura2
      INTEGER            LDA, M, N, OFFSET
11 1 pfleura2
*     ..
12 1 pfleura2
*     .. Array Arguments ..
13 1 pfleura2
      INTEGER            JPVT( * )
14 1 pfleura2
      DOUBLE PRECISION   A( LDA, * ), TAU( * ), VN1( * ), VN2( * ),
15 1 pfleura2
     $                   WORK( * )
16 1 pfleura2
*     ..
17 1 pfleura2
*
18 1 pfleura2
*  Purpose
19 1 pfleura2
*  =======
20 1 pfleura2
*
21 1 pfleura2
*  DLAQP2 computes a QR factorization with column pivoting of
22 1 pfleura2
*  the block A(OFFSET+1:M,1:N).
23 1 pfleura2
*  The block A(1:OFFSET,1:N) is accordingly pivoted, but not factorized.
24 1 pfleura2
*
25 1 pfleura2
*  Arguments
26 1 pfleura2
*  =========
27 1 pfleura2
*
28 1 pfleura2
*  M       (input) INTEGER
29 1 pfleura2
*          The number of rows of the matrix A. M >= 0.
30 1 pfleura2
*
31 1 pfleura2
*  N       (input) INTEGER
32 1 pfleura2
*          The number of columns of the matrix A. N >= 0.
33 1 pfleura2
*
34 1 pfleura2
*  OFFSET  (input) INTEGER
35 1 pfleura2
*          The number of rows of the matrix A that must be pivoted
36 1 pfleura2
*          but no factorized. OFFSET >= 0.
37 1 pfleura2
*
38 1 pfleura2
*  A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
39 1 pfleura2
*          On entry, the M-by-N matrix A.
40 1 pfleura2
*          On exit, the upper triangle of block A(OFFSET+1:M,1:N) is
41 1 pfleura2
*          the triangular factor obtained; the elements in block
42 1 pfleura2
*          A(OFFSET+1:M,1:N) below the diagonal, together with the
43 1 pfleura2
*          array TAU, represent the orthogonal matrix Q as a product of
44 1 pfleura2
*          elementary reflectors. Block A(1:OFFSET,1:N) has been
45 1 pfleura2
*          accordingly pivoted, but no factorized.
46 1 pfleura2
*
47 1 pfleura2
*  LDA     (input) INTEGER
48 1 pfleura2
*          The leading dimension of the array A. LDA >= max(1,M).
49 1 pfleura2
*
50 1 pfleura2
*  JPVT    (input/output) INTEGER array, dimension (N)
51 1 pfleura2
*          On entry, if JPVT(i) .ne. 0, the i-th column of A is permuted
52 1 pfleura2
*          to the front of A*P (a leading column); if JPVT(i) = 0,
53 1 pfleura2
*          the i-th column of A is a free column.
54 1 pfleura2
*          On exit, if JPVT(i) = k, then the i-th column of A*P
55 1 pfleura2
*          was the k-th column of A.
56 1 pfleura2
*
57 1 pfleura2
*  TAU     (output) DOUBLE PRECISION array, dimension (min(M,N))
58 1 pfleura2
*          The scalar factors of the elementary reflectors.
59 1 pfleura2
*
60 1 pfleura2
*  VN1     (input/output) DOUBLE PRECISION array, dimension (N)
61 1 pfleura2
*          The vector with the partial column norms.
62 1 pfleura2
*
63 1 pfleura2
*  VN2     (input/output) DOUBLE PRECISION array, dimension (N)
64 1 pfleura2
*          The vector with the exact column norms.
65 1 pfleura2
*
66 1 pfleura2
*  WORK    (workspace) DOUBLE PRECISION array, dimension (N)
67 1 pfleura2
*
68 1 pfleura2
*  Further Details
69 1 pfleura2
*  ===============
70 1 pfleura2
*
71 1 pfleura2
*  Based on contributions by
72 1 pfleura2
*    G. Quintana-Orti, Depto. de Informatica, Universidad Jaime I, Spain
73 1 pfleura2
*    X. Sun, Computer Science Dept., Duke University, USA
74 1 pfleura2
*
75 1 pfleura2
*  Partial column norm updating strategy modified by
76 1 pfleura2
*    Z. Drmac and Z. Bujanovic, Dept. of Mathematics,
77 1 pfleura2
*    University of Zagreb, Croatia.
78 1 pfleura2
*     June 2010
79 1 pfleura2
*  For more details see LAPACK Working Note 176.
80 1 pfleura2
*  =====================================================================
81 1 pfleura2
*
82 1 pfleura2
*     .. Parameters ..
83 1 pfleura2
      DOUBLE PRECISION   ZERO, ONE
84 1 pfleura2
      PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
85 1 pfleura2
*     ..
86 1 pfleura2
*     .. Local Scalars ..
87 1 pfleura2
      INTEGER            I, ITEMP, J, MN, OFFPI, PVT
88 1 pfleura2
      DOUBLE PRECISION   AII, TEMP, TEMP2, TOL3Z
89 1 pfleura2
*     ..
90 1 pfleura2
*     .. External Subroutines ..
91 1 pfleura2
      EXTERNAL           DLARF, DLARFG, DSWAP
92 1 pfleura2
*     ..
93 1 pfleura2
*     .. Intrinsic Functions ..
94 1 pfleura2
      INTRINSIC          ABS, MAX, MIN, SQRT
95 1 pfleura2
*     ..
96 1 pfleura2
*     .. External Functions ..
97 1 pfleura2
      INTEGER            IDAMAX
98 1 pfleura2
      DOUBLE PRECISION   DLAMCH, DNRM2
99 1 pfleura2
      EXTERNAL           IDAMAX, DLAMCH, DNRM2
100 1 pfleura2
*     ..
101 1 pfleura2
*     .. Executable Statements ..
102 1 pfleura2
*
103 1 pfleura2
      MN = MIN( M-OFFSET, N )
104 1 pfleura2
      TOL3Z = SQRT(DLAMCH('Epsilon'))
105 1 pfleura2
*
106 1 pfleura2
*     Compute factorization.
107 1 pfleura2
*
108 1 pfleura2
      DO 20 I = 1, MN
109 1 pfleura2
*
110 1 pfleura2
         OFFPI = OFFSET + I
111 1 pfleura2
*
112 1 pfleura2
*        Determine ith pivot column and swap if necessary.
113 1 pfleura2
*
114 1 pfleura2
         PVT = ( I-1 ) + IDAMAX( N-I+1, VN1( I ), 1 )
115 1 pfleura2
*
116 1 pfleura2
         IF( PVT.NE.I ) THEN
117 1 pfleura2
            CALL DSWAP( M, A( 1, PVT ), 1, A( 1, I ), 1 )
118 1 pfleura2
            ITEMP = JPVT( PVT )
119 1 pfleura2
            JPVT( PVT ) = JPVT( I )
120 1 pfleura2
            JPVT( I ) = ITEMP
121 1 pfleura2
            VN1( PVT ) = VN1( I )
122 1 pfleura2
            VN2( PVT ) = VN2( I )
123 1 pfleura2
         END IF
124 1 pfleura2
*
125 1 pfleura2
*        Generate elementary reflector H(i).
126 1 pfleura2
*
127 1 pfleura2
         IF( OFFPI.LT.M ) THEN
128 1 pfleura2
            CALL DLARFG( M-OFFPI+1, A( OFFPI, I ), A( OFFPI+1, I ), 1,
129 1 pfleura2
     $                   TAU( I ) )
130 1 pfleura2
         ELSE
131 1 pfleura2
            CALL DLARFG( 1, A( M, I ), A( M, I ), 1, TAU( I ) )
132 1 pfleura2
         END IF
133 1 pfleura2
*
134 1 pfleura2
         IF( I.LE.N ) THEN
135 1 pfleura2
*
136 1 pfleura2
*           Apply H(i)' to A(offset+i:m,i+1:n) from the left.
137 1 pfleura2
*
138 1 pfleura2
            AII = A( OFFPI, I )
139 1 pfleura2
            A( OFFPI, I ) = ONE
140 1 pfleura2
            CALL DLARF( 'Left', M-OFFPI+1, N-I, A( OFFPI, I ), 1,
141 1 pfleura2
     $                  TAU( I ), A( OFFPI, I+1 ), LDA, WORK( 1 ) )
142 1 pfleura2
            A( OFFPI, I ) = AII
143 1 pfleura2
         END IF
144 1 pfleura2
*
145 1 pfleura2
*        Update partial column norms.
146 1 pfleura2
*
147 1 pfleura2
         DO 10 J = I + 1, N
148 1 pfleura2
            IF( VN1( J ).NE.ZERO ) THEN
149 1 pfleura2
*
150 1 pfleura2
*              NOTE: The following 4 lines follow from the analysis in
151 1 pfleura2
*              Lapack Working Note 176.
152 1 pfleura2
*
153 1 pfleura2
               TEMP = ONE - ( ABS( A( OFFPI, J ) ) / VN1( J ) )**2
154 1 pfleura2
               TEMP = MAX( TEMP, ZERO )
155 1 pfleura2
               TEMP2 = TEMP*( VN1( J ) / VN2( J ) )**2
156 1 pfleura2
               IF( TEMP2 .LE. TOL3Z ) THEN
157 1 pfleura2
                  IF( OFFPI.LT.M ) THEN
158 1 pfleura2
                     VN1( J ) = DNRM2( M-OFFPI, A( OFFPI+1, J ), 1 )
159 1 pfleura2
                     VN2( J ) = VN1( J )
160 1 pfleura2
                  ELSE
161 1 pfleura2
                     VN1( J ) = ZERO
162 1 pfleura2
                     VN2( J ) = ZERO
163 1 pfleura2
                  END IF
164 1 pfleura2
               ELSE
165 1 pfleura2
                  VN1( J ) = VN1( J )*SQRT( TEMP )
166 1 pfleura2
               END IF
167 1 pfleura2
            END IF
168 1 pfleura2
   10    CONTINUE
169 1 pfleura2
*
170 1 pfleura2
   20 CONTINUE
171 1 pfleura2
*
172 1 pfleura2
      RETURN
173 1 pfleura2
*
174 1 pfleura2
*     End of DLAQP2
175 1 pfleura2
*
176 1 pfleura2
      END