Annotation of rpl/lapack/lapack/dgelq.f, revision 1.5

1.4       bertrand    1: *> \brief \b DGELQ
1.1       bertrand    2: *
                      3: *  Definition:
                      4: *  ===========
                      5: *
                      6: *       SUBROUTINE DGELQ( M, N, A, LDA, T, TSIZE, WORK, LWORK,
                      7: *                         INFO )
                      8: *
                      9: *       .. Scalar Arguments ..
                     10: *       INTEGER           INFO, LDA, M, N, TSIZE, LWORK
                     11: *       ..
                     12: *       .. Array Arguments ..
                     13: *       DOUBLE PRECISION  A( LDA, * ), T( * ), WORK( * )
                     14: *       ..
                     15: *
                     16: *
                     17: *> \par Purpose:
                     18: *  =============
                     19: *>
                     20: *> \verbatim
1.4       bertrand   21: *>
                     22: *> DGELQ computes an LQ factorization of a real M-by-N matrix A:
                     23: *>
                     24: *>    A = ( L 0 ) *  Q
                     25: *>
                     26: *> where:
                     27: *>
                     28: *>    Q is a N-by-N orthogonal matrix;
1.5     ! bertrand   29: *>    L is a lower-triangular M-by-M matrix;
1.4       bertrand   30: *>    0 is a M-by-(N-M) zero matrix, if M < N.
                     31: *>
1.1       bertrand   32: *> \endverbatim
                     33: *
                     34: *  Arguments:
                     35: *  ==========
                     36: *
                     37: *> \param[in] M
                     38: *> \verbatim
                     39: *>          M is INTEGER
                     40: *>          The number of rows of the matrix A.  M >= 0.
                     41: *> \endverbatim
                     42: *>
                     43: *> \param[in] N
                     44: *> \verbatim
                     45: *>          N is INTEGER
                     46: *>          The number of columns of the matrix A.  N >= 0.
                     47: *> \endverbatim
                     48: *>
                     49: *> \param[in,out] A
                     50: *> \verbatim
                     51: *>          A is DOUBLE PRECISION array, dimension (LDA,N)
                     52: *>          On entry, the M-by-N matrix A.
                     53: *>          On exit, the elements on and below the diagonal of the array
                     54: *>          contain the M-by-min(M,N) lower trapezoidal matrix L
                     55: *>          (L is lower triangular if M <= N);
                     56: *>          the elements above the diagonal are used to store part of the 
                     57: *>          data structure to represent Q.
                     58: *> \endverbatim
                     59: *>
                     60: *> \param[in] LDA
                     61: *> \verbatim
                     62: *>          LDA is INTEGER
                     63: *>          The leading dimension of the array A.  LDA >= max(1,M).
                     64: *> \endverbatim
                     65: *>
                     66: *> \param[out] T
                     67: *> \verbatim
                     68: *>          T is DOUBLE PRECISION array, dimension (MAX(5,TSIZE))
                     69: *>          On exit, if INFO = 0, T(1) returns optimal (or either minimal 
                     70: *>          or optimal, if query is assumed) TSIZE. See TSIZE for details.
                     71: *>          Remaining T contains part of the data structure used to represent Q.
                     72: *>          If one wants to apply or construct Q, then one needs to keep T 
                     73: *>          (in addition to A) and pass it to further subroutines.
                     74: *> \endverbatim
                     75: *>
                     76: *> \param[in] TSIZE
                     77: *> \verbatim
                     78: *>          TSIZE is INTEGER
                     79: *>          If TSIZE >= 5, the dimension of the array T.
                     80: *>          If TSIZE = -1 or -2, then a workspace query is assumed. The routine
                     81: *>          only calculates the sizes of the T and WORK arrays, returns these
                     82: *>          values as the first entries of the T and WORK arrays, and no error
                     83: *>          message related to T or WORK is issued by XERBLA.
                     84: *>          If TSIZE = -1, the routine calculates optimal size of T for the 
                     85: *>          optimum performance and returns this value in T(1).
                     86: *>          If TSIZE = -2, the routine calculates minimal size of T and 
                     87: *>          returns this value in T(1).
                     88: *> \endverbatim
                     89: *>
                     90: *> \param[out] WORK
                     91: *> \verbatim
                     92: *>          (workspace) DOUBLE PRECISION array, dimension (MAX(1,LWORK))
                     93: *>          On exit, if INFO = 0, WORK(1) contains optimal (or either minimal
                     94: *>          or optimal, if query was assumed) LWORK.
                     95: *>          See LWORK for details.
                     96: *> \endverbatim
                     97: *>
                     98: *> \param[in] LWORK
                     99: *> \verbatim
                    100: *>          LWORK is INTEGER
                    101: *>          The dimension of the array WORK.
                    102: *>          If LWORK = -1 or -2, then a workspace query is assumed. The routine
                    103: *>          only calculates the sizes of the T and WORK arrays, returns these
                    104: *>          values as the first entries of the T and WORK arrays, and no error
                    105: *>          message related to T or WORK is issued by XERBLA.
                    106: *>          If LWORK = -1, the routine calculates optimal size of WORK for the
                    107: *>          optimal performance and returns this value in WORK(1).
                    108: *>          If LWORK = -2, the routine calculates minimal size of WORK and 
                    109: *>          returns this value in WORK(1).
                    110: *> \endverbatim
                    111: *>
                    112: *> \param[out] INFO
                    113: *> \verbatim
                    114: *>          INFO is INTEGER
                    115: *>          = 0:  successful exit
                    116: *>          < 0:  if INFO = -i, the i-th argument had an illegal value
                    117: *> \endverbatim
                    118: *
                    119: *  Authors:
                    120: *  ========
                    121: *
                    122: *> \author Univ. of Tennessee
                    123: *> \author Univ. of California Berkeley
                    124: *> \author Univ. of Colorado Denver
                    125: *> \author NAG Ltd.
                    126: *
                    127: *> \par Further Details
                    128: *  ====================
                    129: *>
                    130: *> \verbatim
                    131: *>
                    132: *> The goal of the interface is to give maximum freedom to the developers for
                    133: *> creating any LQ factorization algorithm they wish. The triangular 
                    134: *> (trapezoidal) L has to be stored in the lower part of A. The lower part of A
                    135: *> and the array T can be used to store any relevant information for applying or
                    136: *> constructing the Q factor. The WORK array can safely be discarded after exit.
                    137: *>
                    138: *> Caution: One should not expect the sizes of T and WORK to be the same from one 
                    139: *> LAPACK implementation to the other, or even from one execution to the other.
                    140: *> A workspace query (for T and WORK) is needed at each execution. However, 
                    141: *> for a given execution, the size of T and WORK are fixed and will not change 
                    142: *> from one query to the next.
                    143: *>
                    144: *> \endverbatim
                    145: *>
                    146: *> \par Further Details particular to this LAPACK implementation:
                    147: *  ==============================================================
                    148: *>
                    149: *> \verbatim
                    150: *>
                    151: *> These details are particular for this LAPACK implementation. Users should not 
1.4       bertrand  152: *> take them for granted. These details may change in the future, and are not likely
1.1       bertrand  153: *> true for another LAPACK implementation. These details are relevant if one wants
                    154: *> to try to understand the code. They are not part of the interface.
                    155: *>
                    156: *> In this version,
                    157: *>
                    158: *>          T(2): row block size (MB)
                    159: *>          T(3): column block size (NB)
                    160: *>          T(6:TSIZE): data structure needed for Q, computed by
                    161: *>                           DLASWLQ or DGELQT
                    162: *>
                    163: *>  Depending on the matrix dimensions M and N, and row and column
                    164: *>  block sizes MB and NB returned by ILAENV, DGELQ will use either
                    165: *>  DLASWLQ (if the matrix is short-and-wide) or DGELQT to compute
                    166: *>  the LQ factorization.
                    167: *> \endverbatim
                    168: *>
                    169: *  =====================================================================
                    170:       SUBROUTINE DGELQ( M, N, A, LDA, T, TSIZE, WORK, LWORK,
                    171:      $                  INFO )
                    172: *
1.5     ! bertrand  173: *  -- LAPACK computational routine --
1.1       bertrand  174: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
                    175: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd. --
                    176: *
                    177: *     .. Scalar Arguments ..
                    178:       INTEGER            INFO, LDA, M, N, TSIZE, LWORK
                    179: *     ..
                    180: *     .. Array Arguments ..
                    181:       DOUBLE PRECISION   A( LDA, * ), T( * ), WORK( * )
                    182: *     ..
                    183: *
                    184: *  =====================================================================
                    185: *
                    186: *     ..
                    187: *     .. Local Scalars ..
                    188:       LOGICAL            LQUERY, LMINWS, MINT, MINW
1.5     ! bertrand  189:       INTEGER            MB, NB, MINTSZ, NBLCKS, LWMIN, LWOPT, LWREQ
1.1       bertrand  190: *     ..
                    191: *     .. External Functions ..
                    192:       LOGICAL            LSAME
                    193:       EXTERNAL           LSAME
                    194: *     ..
                    195: *     .. External Subroutines ..
                    196:       EXTERNAL           DGELQT, DLASWLQ, XERBLA
                    197: *     ..
                    198: *     .. Intrinsic Functions ..
                    199:       INTRINSIC          MAX, MIN, MOD
                    200: *     ..
                    201: *     .. External Functions ..
                    202:       INTEGER            ILAENV
                    203:       EXTERNAL           ILAENV
                    204: *     ..
                    205: *     .. Executable Statements ..
                    206: *
                    207: *     Test the input arguments
                    208: *
                    209:       INFO = 0
                    210: *
                    211:       LQUERY = ( TSIZE.EQ.-1 .OR. TSIZE.EQ.-2 .OR.
                    212:      $           LWORK.EQ.-1 .OR. LWORK.EQ.-2 )
                    213: *
                    214:       MINT = .FALSE.
                    215:       MINW = .FALSE.
                    216:       IF( TSIZE.EQ.-2 .OR. LWORK.EQ.-2 ) THEN
                    217:         IF( TSIZE.NE.-1 ) MINT = .TRUE.
                    218:         IF( LWORK.NE.-1 ) MINW = .TRUE.
                    219:       END IF
                    220: *
                    221: *     Determine the block size
                    222: *
                    223:       IF( MIN( M, N ).GT.0 ) THEN
                    224:         MB = ILAENV( 1, 'DGELQ ', ' ', M, N, 1, -1 )
                    225:         NB = ILAENV( 1, 'DGELQ ', ' ', M, N, 2, -1 )
                    226:       ELSE
                    227:         MB = 1
                    228:         NB = N
                    229:       END IF
                    230:       IF( MB.GT.MIN( M, N ) .OR. MB.LT.1 ) MB = 1
                    231:       IF( NB.GT.N .OR. NB.LE.M ) NB = N
                    232:       MINTSZ = M + 5
                    233:       IF ( NB.GT.M .AND. N.GT.M ) THEN
                    234:         IF( MOD( N - M, NB - M ).EQ.0 ) THEN
                    235:           NBLCKS = ( N - M ) / ( NB - M )
                    236:         ELSE
                    237:           NBLCKS = ( N - M ) / ( NB - M ) + 1
                    238:         END IF
                    239:       ELSE
                    240:         NBLCKS = 1
                    241:       END IF
                    242: *
                    243: *     Determine if the workspace size satisfies minimal size
                    244: *
1.5     ! bertrand  245:       IF( ( N.LE.M ) .OR. ( NB.LE.M ) .OR. ( NB.GE.N ) ) THEN
        !           246:          LWMIN = MAX( 1, N )
        !           247:          LWOPT = MAX( 1, MB*N )
        !           248:       ELSE
        !           249:          LWMIN = MAX( 1, M )
        !           250:          LWOPT = MAX( 1, MB*M )
        !           251:       END IF
1.1       bertrand  252:       LMINWS = .FALSE.
1.5     ! bertrand  253:       IF( ( TSIZE.LT.MAX( 1, MB*M*NBLCKS + 5 ) .OR. LWORK.LT.LWOPT )
        !           254:      $    .AND. ( LWORK.GE.LWMIN ) .AND. ( TSIZE.GE.MINTSZ )
1.1       bertrand  255:      $    .AND. ( .NOT.LQUERY ) ) THEN
                    256:         IF( TSIZE.LT.MAX( 1, MB*M*NBLCKS + 5 ) ) THEN
                    257:             LMINWS = .TRUE.
                    258:             MB = 1
                    259:             NB = N
                    260:         END IF
1.5     ! bertrand  261:         IF( LWORK.LT.LWOPT ) THEN
1.1       bertrand  262:             LMINWS = .TRUE.
                    263:             MB = 1
                    264:         END IF
                    265:       END IF
1.5     ! bertrand  266:       IF( ( N.LE.M ) .OR. ( NB.LE.M ) .OR. ( NB.GE.N ) ) THEN
        !           267:          LWREQ = MAX( 1, MB*N )
        !           268:       ELSE
        !           269:          LWREQ = MAX( 1, MB*M )
        !           270:       END IF
1.1       bertrand  271: *
                    272:       IF( M.LT.0 ) THEN
                    273:         INFO = -1
                    274:       ELSE IF( N.LT.0 ) THEN
                    275:         INFO = -2
                    276:       ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
                    277:         INFO = -4
                    278:       ELSE IF( TSIZE.LT.MAX( 1, MB*M*NBLCKS + 5 )
                    279:      $   .AND. ( .NOT.LQUERY ) .AND. ( .NOT.LMINWS ) ) THEN
                    280:         INFO = -6
1.5     ! bertrand  281:       ELSE IF( ( LWORK.LT.LWREQ ) .AND .( .NOT.LQUERY )
1.1       bertrand  282:      $   .AND. ( .NOT.LMINWS ) ) THEN
                    283:         INFO = -8
                    284:       END IF
                    285: *
                    286:       IF( INFO.EQ.0 ) THEN
                    287:         IF( MINT ) THEN
                    288:           T( 1 ) = MINTSZ
                    289:         ELSE
                    290:           T( 1 ) = MB*M*NBLCKS + 5
                    291:         END IF
                    292:         T( 2 ) = MB
                    293:         T( 3 ) = NB
                    294:         IF( MINW ) THEN
1.5     ! bertrand  295:           WORK( 1 ) = LWMIN
1.1       bertrand  296:         ELSE
1.5     ! bertrand  297:           WORK( 1 ) = LWREQ
1.1       bertrand  298:         END IF
                    299:       END IF
                    300:       IF( INFO.NE.0 ) THEN
                    301:         CALL XERBLA( 'DGELQ', -INFO )
                    302:         RETURN
                    303:       ELSE IF( LQUERY ) THEN
                    304:         RETURN
                    305:       END IF
                    306: *
                    307: *     Quick return if possible
                    308: *
                    309:       IF( MIN( M, N ).EQ.0 ) THEN
                    310:         RETURN
                    311:       END IF
                    312: *
                    313: *     The LQ Decomposition
                    314: *
                    315:       IF( ( N.LE.M ) .OR. ( NB.LE.M ) .OR. ( NB.GE.N ) ) THEN
                    316:         CALL DGELQT( M, N, MB, A, LDA, T( 6 ), MB, WORK, INFO )
                    317:       ELSE
                    318:         CALL DLASWLQ( M, N, MB, NB, A, LDA, T( 6 ), MB, WORK,
                    319:      $                LWORK, INFO )
                    320:       END IF
                    321: *
1.5     ! bertrand  322:       WORK( 1 ) = LWREQ
1.1       bertrand  323: *
                    324:       RETURN
                    325: *
                    326: *     End of DGELQ
                    327: *
                    328:       END

CVSweb interface <joel.bertrand@systella.fr>