001:       SUBROUTINE CORE_CGETRF( M, N, IB, A, LDA, IPIV, INFO )
002: 
003: *********************************************************************
004: *     PLASMA core_blas routine (version 2.1.0)                      *
005: *     Author: Hatem Ltaief                                          *
006: *     Release Date: November, 15th 2009                             *
007: *     PLASMA is a software package provided by Univ. of Tennessee,  *
008: *     Univ. of California Berkeley and Univ. of Colorado Denver.    *
009: *********************************************************************
010: *
011: *     .. Scalar Arguments ..
012:       INTEGER            INFO, LDA, M, N, IB
013: *     ..
014: *     .. Array Arguments ..
015:       COMPLEX            A( LDA, * )
016:       INTEGER            IPIV( * )
017: *     ..
018: *
019: *  Purpose
020: *  =======
021: *
022: *  CORE_CGETRF computes an LU factorization of a general M-by-N tile A
023: *  using partial pivoting with row interchanges.
024: *
025: *  The factorization has the form
026: *     A = P * L * U
027: *  where P is a permutation matrix, L is lower triangular with unit
028: *  diagonal elements (lower trapezoidal if m > n), and U is upper
029: *  triangular (upper trapezoidal if m < n).
030: *
031: *  This is the right-looking Level 2.5 BLAS version of the algorithm.
032: *
033: *  Arguments
034: *  =========
035: *
036: *  M       (input) INTEGER
037: *          The number of rows of the tile A.  M >= 0.
038: *
039: *  N       (input) INTEGER
040: *          The number of columns of the tile A.  N >= 0.
041: *
042: *  A       (input/output) COMPLEX array, dimension (LDA,N)
043: *          On entry, the M-by-N tile to be factored.
044: *          On exit, the factors L and U from the factorization
045: *          A = P*L*U; the unit diagonal elements of L are not stored.
046: *
047: *  LDA     (input) INTEGER
048: *          The leading dimension of the array A.  LDA >= max(1,M).
049: *
050: *  IPIV    (output) INTEGER array, dimension (min(M,N))
051: *          The pivot indices; for 1 <= i <= min(M,N), row i of the
052: *          tile was interchanged with row IPIV(i).
053: *
054: *  INFO    (output) INTEGER
055: *          = 0: successful exit
056: *          < 0: if INFO = -k, the k-th argument had an illegal value
057: *          > 0: if INFO = k, U(k,k) is exactly zero. The factorization
058: *               has been completed, but the factor U is exactly
059: *               singular, and division by zero will occur if it is used
060: *               to solve a system of equations.
061: *
062: *  =====================================================================
063: *
064: *     .. Local Scalars ..
065:       REAL               SFMIN 
066:       INTEGER            I, J, K, SB, IINFO
067: *     ..
068: *     .. External Functions ..
069:       REAL               SLAMCH
070:       INTEGER            IDAMAX
071:       EXTERNAL           SLAMCH, IDAMAX
072: *     ..
073: *     .. External Subroutines ..
074:       EXTERNAL           CGETF2, CORE_CGESSM, XERBLA
075: *     ..
076: *     .. Intrinsic Functions ..
077:       INTRINSIC          MAX, MIN
078: *     ..
079: *     Test the input parameters.
080:       INFO = 0
081:       IF( M.LT.0 ) THEN
082:          INFO = -1
083:       ELSE IF( N.LT.0 ) THEN
084:          INFO = -2
085:       ELSE IF( IB.LT.0 ) THEN
086:          INFO = -3
087:       ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
088:          INFO = -5
089:       END IF
090:       IF( INFO.NE.0 ) THEN
091:          CALL XERBLA( 'CORE_CGETRF', -INFO )
092:          RETURN
093:       END IF
094: *
095: *     Quick return if possible.
096: *
097:       IF( M.EQ.0 .OR. N.EQ.0 .OR. IB.EQ.0 )
098:      $   RETURN
099: *
100: *     Compute machine safe minimum.
101: *
102:       SFMIN = SLAMCH('S')
103: *
104:       K = MIN( M, N )
105: *
106:       DO 10 I = 1, K, IB
107:             SB = MIN( K-I+1, IB )
108: *
109: *           Factor diagonal and subdiagonal blocks and test for exact
110: *           singularity.
111: *
112:             CALL CGETF2( M-I+1, SB, A( I, I ), LDA,
113:      $                   IPIV( I ), IINFO )
114: *
115: *           Adjust INFO and the pivot indices.
116: *
117:             IF( INFO.EQ.0 .AND. IINFO.GT.0 )
118:      $         INFO = IINFO + I-1
119: *
120:             IF( I+SB.LE.N ) THEN
121:                CALL CORE_CGESSM( M-I+1, N-( I+SB-1 ), SB, SB,
122:      $                           IPIV( I ), A( I, I ),
123:      $                           LDA, A( I, I+SB ), LDA,
124:      $                           IINFO)
125:             END IF
126: *
127:             DO 20 J = I, I+SB-1
128:                IPIV( J ) = I + IPIV( J ) -1
129:    20       CONTINUE
130:    10 CONTINUE
131: *
132:       RETURN
133: *
134: *     End of CORE_CGETRF.
135: *
136:       END
137: