Annotation of rpl/lapack/lapack/dgeqpf.f, revision 1.10

1.10    ! bertrand    1: *> \brief \b DGEQPF
        !             2: *
        !             3: *  =========== DOCUMENTATION ===========
        !             4: *
        !             5: * Online html documentation available at 
        !             6: *            http://www.netlib.org/lapack/explore-html/ 
        !             7: *
        !             8: *> \htmlonly
        !             9: *> Download DGEQPF + dependencies 
        !            10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dgeqpf.f"> 
        !            11: *> [TGZ]</a> 
        !            12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dgeqpf.f"> 
        !            13: *> [ZIP]</a> 
        !            14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgeqpf.f"> 
        !            15: *> [TXT]</a>
        !            16: *> \endhtmlonly 
        !            17: *
        !            18: *  Definition:
        !            19: *  ===========
        !            20: *
        !            21: *       SUBROUTINE DGEQPF( M, N, A, LDA, JPVT, TAU, WORK, INFO )
        !            22: * 
        !            23: *       .. Scalar Arguments ..
        !            24: *       INTEGER            INFO, LDA, M, N
        !            25: *       ..
        !            26: *       .. Array Arguments ..
        !            27: *       INTEGER            JPVT( * )
        !            28: *       DOUBLE PRECISION   A( LDA, * ), TAU( * ), WORK( * )
        !            29: *       ..
        !            30: *  
        !            31: *
        !            32: *> \par Purpose:
        !            33: *  =============
        !            34: *>
        !            35: *> \verbatim
        !            36: *>
        !            37: *> This routine is deprecated and has been replaced by routine DGEQP3.
        !            38: *>
        !            39: *> DGEQPF computes a QR factorization with column pivoting of a
        !            40: *> real M-by-N matrix A: A*P = Q*R.
        !            41: *> \endverbatim
        !            42: *
        !            43: *  Arguments:
        !            44: *  ==========
        !            45: *
        !            46: *> \param[in] M
        !            47: *> \verbatim
        !            48: *>          M is INTEGER
        !            49: *>          The number of rows of the matrix A. M >= 0.
        !            50: *> \endverbatim
        !            51: *>
        !            52: *> \param[in] N
        !            53: *> \verbatim
        !            54: *>          N is INTEGER
        !            55: *>          The number of columns of the matrix A. N >= 0
        !            56: *> \endverbatim
        !            57: *>
        !            58: *> \param[in,out] A
        !            59: *> \verbatim
        !            60: *>          A is DOUBLE PRECISION array, dimension (LDA,N)
        !            61: *>          On entry, the M-by-N matrix A.
        !            62: *>          On exit, the upper triangle of the array contains the
        !            63: *>          min(M,N)-by-N upper triangular matrix R; the elements
        !            64: *>          below the diagonal, together with the array TAU,
        !            65: *>          represent the orthogonal matrix Q as a product of
        !            66: *>          min(m,n) elementary reflectors.
        !            67: *> \endverbatim
        !            68: *>
        !            69: *> \param[in] LDA
        !            70: *> \verbatim
        !            71: *>          LDA is INTEGER
        !            72: *>          The leading dimension of the array A. LDA >= max(1,M).
        !            73: *> \endverbatim
        !            74: *>
        !            75: *> \param[in,out] JPVT
        !            76: *> \verbatim
        !            77: *>          JPVT is INTEGER array, dimension (N)
        !            78: *>          On entry, if JPVT(i) .ne. 0, the i-th column of A is permuted
        !            79: *>          to the front of A*P (a leading column); if JPVT(i) = 0,
        !            80: *>          the i-th column of A is a free column.
        !            81: *>          On exit, if JPVT(i) = k, then the i-th column of A*P
        !            82: *>          was the k-th column of A.
        !            83: *> \endverbatim
        !            84: *>
        !            85: *> \param[out] TAU
        !            86: *> \verbatim
        !            87: *>          TAU is DOUBLE PRECISION array, dimension (min(M,N))
        !            88: *>          The scalar factors of the elementary reflectors.
        !            89: *> \endverbatim
        !            90: *>
        !            91: *> \param[out] WORK
        !            92: *> \verbatim
        !            93: *>          WORK is DOUBLE PRECISION array, dimension (3*N)
        !            94: *> \endverbatim
        !            95: *>
        !            96: *> \param[out] INFO
        !            97: *> \verbatim
        !            98: *>          INFO is INTEGER
        !            99: *>          = 0:  successful exit
        !           100: *>          < 0:  if INFO = -i, the i-th argument had an illegal value
        !           101: *> \endverbatim
        !           102: *
        !           103: *  Authors:
        !           104: *  ========
        !           105: *
        !           106: *> \author Univ. of Tennessee 
        !           107: *> \author Univ. of California Berkeley 
        !           108: *> \author Univ. of Colorado Denver 
        !           109: *> \author NAG Ltd. 
        !           110: *
        !           111: *> \date November 2011
        !           112: *
        !           113: *> \ingroup doubleGEcomputational
        !           114: *
        !           115: *> \par Further Details:
        !           116: *  =====================
        !           117: *>
        !           118: *> \verbatim
        !           119: *>
        !           120: *>  The matrix Q is represented as a product of elementary reflectors
        !           121: *>
        !           122: *>     Q = H(1) H(2) . . . H(n)
        !           123: *>
        !           124: *>  Each H(i) has the form
        !           125: *>
        !           126: *>     H = I - tau * v * v**T
        !           127: *>
        !           128: *>  where tau is a real scalar, and v is a real vector with
        !           129: *>  v(1:i-1) = 0 and v(i) = 1; v(i+1:m) is stored on exit in A(i+1:m,i).
        !           130: *>
        !           131: *>  The matrix P is represented in jpvt as follows: If
        !           132: *>     jpvt(j) = i
        !           133: *>  then the jth column of P is the ith canonical unit vector.
        !           134: *>
        !           135: *>  Partial column norm updating strategy modified by
        !           136: *>    Z. Drmac and Z. Bujanovic, Dept. of Mathematics,
        !           137: *>    University of Zagreb, Croatia.
        !           138: *>  -- April 2011                                                      --
        !           139: *>  For more details see LAPACK Working Note 176.
        !           140: *> \endverbatim
        !           141: *>
        !           142: *  =====================================================================
1.1       bertrand  143:       SUBROUTINE DGEQPF( M, N, A, LDA, JPVT, TAU, WORK, INFO )
                    144: *
1.10    ! bertrand  145: *  -- LAPACK computational routine (version 3.4.0) --
1.1       bertrand  146: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
                    147: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
1.10    ! bertrand  148: *     November 2011
1.1       bertrand  149: *
                    150: *     .. Scalar Arguments ..
                    151:       INTEGER            INFO, LDA, M, N
                    152: *     ..
                    153: *     .. Array Arguments ..
                    154:       INTEGER            JPVT( * )
                    155:       DOUBLE PRECISION   A( LDA, * ), TAU( * ), WORK( * )
                    156: *     ..
                    157: *
                    158: *  =====================================================================
                    159: *
                    160: *     .. Parameters ..
                    161:       DOUBLE PRECISION   ZERO, ONE
                    162:       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
                    163: *     ..
                    164: *     .. Local Scalars ..
                    165:       INTEGER            I, ITEMP, J, MA, MN, PVT
                    166:       DOUBLE PRECISION   AII, TEMP, TEMP2, TOL3Z
                    167: *     ..
                    168: *     .. External Subroutines ..
1.5       bertrand  169:       EXTERNAL           DGEQR2, DLARF, DLARFG, DORM2R, DSWAP, XERBLA
1.1       bertrand  170: *     ..
                    171: *     .. Intrinsic Functions ..
                    172:       INTRINSIC          ABS, MAX, MIN, SQRT
                    173: *     ..
                    174: *     .. External Functions ..
                    175:       INTEGER            IDAMAX
                    176:       DOUBLE PRECISION   DLAMCH, DNRM2
                    177:       EXTERNAL           IDAMAX, DLAMCH, DNRM2
                    178: *     ..
                    179: *     .. Executable Statements ..
                    180: *
                    181: *     Test the input arguments
                    182: *
                    183:       INFO = 0
                    184:       IF( M.LT.0 ) THEN
                    185:          INFO = -1
                    186:       ELSE IF( N.LT.0 ) THEN
                    187:          INFO = -2
                    188:       ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
                    189:          INFO = -4
                    190:       END IF
                    191:       IF( INFO.NE.0 ) THEN
                    192:          CALL XERBLA( 'DGEQPF', -INFO )
                    193:          RETURN
                    194:       END IF
                    195: *
                    196:       MN = MIN( M, N )
                    197:       TOL3Z = SQRT(DLAMCH('Epsilon'))
                    198: *
                    199: *     Move initial columns up front
                    200: *
                    201:       ITEMP = 1
                    202:       DO 10 I = 1, N
                    203:          IF( JPVT( I ).NE.0 ) THEN
                    204:             IF( I.NE.ITEMP ) THEN
                    205:                CALL DSWAP( M, A( 1, I ), 1, A( 1, ITEMP ), 1 )
                    206:                JPVT( I ) = JPVT( ITEMP )
                    207:                JPVT( ITEMP ) = I
                    208:             ELSE
                    209:                JPVT( I ) = I
                    210:             END IF
                    211:             ITEMP = ITEMP + 1
                    212:          ELSE
                    213:             JPVT( I ) = I
                    214:          END IF
                    215:    10 CONTINUE
                    216:       ITEMP = ITEMP - 1
                    217: *
                    218: *     Compute the QR factorization and update remaining columns
                    219: *
                    220:       IF( ITEMP.GT.0 ) THEN
                    221:          MA = MIN( ITEMP, M )
                    222:          CALL DGEQR2( M, MA, A, LDA, TAU, WORK, INFO )
                    223:          IF( MA.LT.N ) THEN
                    224:             CALL DORM2R( 'Left', 'Transpose', M, N-MA, MA, A, LDA, TAU,
                    225:      $                   A( 1, MA+1 ), LDA, WORK, INFO )
                    226:          END IF
                    227:       END IF
                    228: *
                    229:       IF( ITEMP.LT.MN ) THEN
                    230: *
                    231: *        Initialize partial column norms. The first n elements of
                    232: *        work store the exact column norms.
                    233: *
                    234:          DO 20 I = ITEMP + 1, N
                    235:             WORK( I ) = DNRM2( M-ITEMP, A( ITEMP+1, I ), 1 )
                    236:             WORK( N+I ) = WORK( I )
                    237:    20    CONTINUE
                    238: *
                    239: *        Compute factorization
                    240: *
                    241:          DO 40 I = ITEMP + 1, MN
                    242: *
                    243: *           Determine ith pivot column and swap if necessary
                    244: *
                    245:             PVT = ( I-1 ) + IDAMAX( N-I+1, WORK( I ), 1 )
                    246: *
                    247:             IF( PVT.NE.I ) THEN
                    248:                CALL DSWAP( M, A( 1, PVT ), 1, A( 1, I ), 1 )
                    249:                ITEMP = JPVT( PVT )
                    250:                JPVT( PVT ) = JPVT( I )
                    251:                JPVT( I ) = ITEMP
                    252:                WORK( PVT ) = WORK( I )
                    253:                WORK( N+PVT ) = WORK( N+I )
                    254:             END IF
                    255: *
                    256: *           Generate elementary reflector H(i)
                    257: *
                    258:             IF( I.LT.M ) THEN
1.5       bertrand  259:                CALL DLARFG( M-I+1, A( I, I ), A( I+1, I ), 1, TAU( I ) )
1.1       bertrand  260:             ELSE
1.5       bertrand  261:                CALL DLARFG( 1, A( M, M ), A( M, M ), 1, TAU( M ) )
1.1       bertrand  262:             END IF
                    263: *
                    264:             IF( I.LT.N ) THEN
                    265: *
                    266: *              Apply H(i) to A(i:m,i+1:n) from the left
                    267: *
                    268:                AII = A( I, I )
                    269:                A( I, I ) = ONE
                    270:                CALL DLARF( 'LEFT', M-I+1, N-I, A( I, I ), 1, TAU( I ),
                    271:      $                     A( I, I+1 ), LDA, WORK( 2*N+1 ) )
                    272:                A( I, I ) = AII
                    273:             END IF
                    274: *
                    275: *           Update partial column norms
                    276: *
                    277:             DO 30 J = I + 1, N
                    278:                IF( WORK( J ).NE.ZERO ) THEN
                    279: *
                    280: *                 NOTE: The following 4 lines follow from the analysis in
                    281: *                 Lapack Working Note 176.
                    282: *                 
                    283:                   TEMP = ABS( A( I, J ) ) / WORK( J )
                    284:                   TEMP = MAX( ZERO, ( ONE+TEMP )*( ONE-TEMP ) )
                    285:                   TEMP2 = TEMP*( WORK( J ) / WORK( N+J ) )**2
                    286:                   IF( TEMP2 .LE. TOL3Z ) THEN 
                    287:                      IF( M-I.GT.0 ) THEN
                    288:                         WORK( J ) = DNRM2( M-I, A( I+1, J ), 1 )
                    289:                         WORK( N+J ) = WORK( J )
                    290:                      ELSE
                    291:                         WORK( J ) = ZERO
                    292:                         WORK( N+J ) = ZERO
                    293:                      END IF
                    294:                   ELSE
                    295:                      WORK( J ) = WORK( J )*SQRT( TEMP )
                    296:                   END IF
                    297:                END IF
                    298:    30       CONTINUE
                    299: *
                    300:    40    CONTINUE
                    301:       END IF
                    302:       RETURN
                    303: *
                    304: *     End of DGEQPF
                    305: *
                    306:       END

CVSweb interface <joel.bertrand@systella.fr>