001:       SUBROUTINE ZGESV( N, NRHS, A, LDA, IPIV, B, LDB, INFO )
002: *
003: *  -- LAPACK driver routine (version 3.2) --
004: *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
005: *     November 2006
006: *
007: *     .. Scalar Arguments ..
008:       INTEGER            INFO, LDA, LDB, N, NRHS
009: *     ..
010: *     .. Array Arguments ..
011:       INTEGER            IPIV( * )
012:       COMPLEX*16         A( LDA, * ), B( LDB, * )
013: *     ..
014: *
015: *  Purpose
016: *  =======
017: *
018: *  ZGESV computes the solution to a complex system of linear equations
019: *     A * X = B,
020: *  where A is an N-by-N matrix and X and B are N-by-NRHS matrices.
021: *
022: *  The LU decomposition with partial pivoting and row interchanges is
023: *  used to factor A as
024: *     A = P * L * U,
025: *  where P is a permutation matrix, L is unit lower triangular, and U is
026: *  upper triangular.  The factored form of A is then used to solve the
027: *  system of equations A * X = B.
028: *
029: *  Arguments
030: *  =========
031: *
032: *  N       (input) INTEGER
033: *          The number of linear equations, i.e., the order of the
034: *          matrix A.  N >= 0.
035: *
036: *  NRHS    (input) INTEGER
037: *          The number of right hand sides, i.e., the number of columns
038: *          of the matrix B.  NRHS >= 0.
039: *
040: *  A       (input/output) COMPLEX*16 array, dimension (LDA,N)
041: *          On entry, the N-by-N coefficient matrix A.
042: *          On exit, the factors L and U from the factorization
043: *          A = P*L*U; the unit diagonal elements of L are not stored.
044: *
045: *  LDA     (input) INTEGER
046: *          The leading dimension of the array A.  LDA >= max(1,N).
047: *
048: *  IPIV    (output) INTEGER array, dimension (N)
049: *          The pivot indices that define the permutation matrix P;
050: *          row i of the matrix was interchanged with row IPIV(i).
051: *
052: *  B       (input/output) COMPLEX*16 array, dimension (LDB,NRHS)
053: *          On entry, the N-by-NRHS matrix of right hand side matrix B.
054: *          On exit, if INFO = 0, the N-by-NRHS solution matrix X.
055: *
056: *  LDB     (input) INTEGER
057: *          The leading dimension of the array B.  LDB >= max(1,N).
058: *
059: *  INFO    (output) INTEGER
060: *          = 0:  successful exit
061: *          < 0:  if INFO = -i, the i-th argument had an illegal value
062: *          > 0:  if INFO = i, U(i,i) is exactly zero.  The factorization
063: *                has been completed, but the factor U is exactly
064: *                singular, so the solution could not be computed.
065: *
066: *  =====================================================================
067: *
068: *     .. External Subroutines ..
069:       EXTERNAL           XERBLA, ZGETRF, ZGETRS
070: *     ..
071: *     .. Intrinsic Functions ..
072:       INTRINSIC          MAX
073: *     ..
074: *     .. Executable Statements ..
075: *
076: *     Test the input parameters.
077: *
078:       INFO = 0
079:       IF( N.LT.0 ) THEN
080:          INFO = -1
081:       ELSE IF( NRHS.LT.0 ) THEN
082:          INFO = -2
083:       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
084:          INFO = -4
085:       ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
086:          INFO = -7
087:       END IF
088:       IF( INFO.NE.0 ) THEN
089:          CALL XERBLA( 'ZGESV ', -INFO )
090:          RETURN
091:       END IF
092: *
093: *     Compute the LU factorization of A.
094: *
095:       CALL ZGETRF( N, N, A, LDA, IPIV, INFO )
096:       IF( INFO.EQ.0 ) THEN
097: *
098: *        Solve the system A*X = B, overwriting B with X.
099: *
100:          CALL ZGETRS( 'No transpose', N, NRHS, A, LDA, IPIV, B, LDB,
101:      $                INFO )
102:       END IF
103:       RETURN
104: *
105: *     End of ZGESV
106: *
107:       END
108: