~ubuntu-branches/ubuntu/vivid/atlas/vivid

« back to all changes in this revision

Viewing changes to interfaces/lapack/F77/src/zgesv.f

  • Committer: Bazaar Package Importer
  • Author(s): Camm Maguire
  • Date: 2002-04-13 10:07:52 UTC
  • Revision ID: james.westby@ubuntu.com-20020413100752-va9zm0rd4gpurdkq
Tags: upstream-3.2.1ln
ImportĀ upstreamĀ versionĀ 3.2.1ln

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
      SUBROUTINE ZGESV( N, NRHS, A, LDA, IPIV, B, LDB, INFO )
 
2
*
 
3
*  -- LAPACK driver routine (version 3.0) --
 
4
*     Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
 
5
*     Courant Institute, Argonne National Lab, and Rice University
 
6
*     March 31, 1993 
 
7
*
 
8
*  -- Modified by R. Clint Whaley for ATLAS Fortran77 LAPACK interface,
 
9
*     November, 1999.
 
10
*
 
11
*     .. Scalar Arguments ..
 
12
      INTEGER INFO, LDA, LDB, N, NRHS
 
13
*     ..
 
14
*     .. Array Arguments ..
 
15
      INTEGER IPIV( * )
 
16
      COMPLEX*16 A( LDA, * ), B( LDB, * )
 
17
*     ..
 
18
*
 
19
*  Purpose
 
20
*  =======
 
21
*
 
22
*  ZGESV computes the solution to a complex system of linear equations
 
23
*     A * X = B,
 
24
*  where A is an N-by-N matrix and X and B are N-by-NRHS matrices.
 
25
*
 
26
*  The LU decomposition with partial pivoting and row interchanges is
 
27
*  used to factor A as
 
28
*     A = P * L * U,
 
29
*  where P is a permutation matrix, L is unit lower triangular, and U is
 
30
*  upper triangular.  The factored form of A is then used to solve the
 
31
*  system of equations A * X = B.
 
32
*
 
33
*  Arguments
 
34
*  =========
 
35
*
 
36
*  N       (input) INTEGER
 
37
*          The number of linear equations, i.e., the order of the
 
38
*          matrix A.  N >= 0.
 
39
*
 
40
*  NRHS    (input) INTEGER
 
41
*          The number of right hand sides, i.e., the number of columns
 
42
*          of the matrix B.  NRHS >= 0.
 
43
*
 
44
*  A       (input/output) COMPLEX*16 array, dimension (LDA,N)
 
45
*          On entry, the N-by-N coefficient matrix A.
 
46
*          On exit, the factors L and U from the factorization
 
47
*          A = P*L*U; the unit diagonal elements of L are not stored.
 
48
*
 
49
*  LDA     (input) INTEGER
 
50
*          The leading dimension of the array A.  LDA >= max(1,N).
 
51
*
 
52
*  IPIV    (output) INTEGER array, dimension (N)
 
53
*          The pivot indices that define the permutation matrix P;
 
54
*          row i of the matrix was interchanged with row IPIV(i).
 
55
*
 
56
*  B       (input/output) COMPLEX*16 array, dimension (LDB,NRHS)
 
57
*          On entry, the N-by-NRHS matrix of right hand side matrix B.
 
58
*          On exit, if INFO = 0, the N-by-NRHS solution matrix X.
 
59
*
 
60
*  LDB     (input) INTEGER
 
61
*          The leading dimension of the array B.  LDB >= max(1,N).
 
62
*
 
63
*  INFO    (output) INTEGER
 
64
*          = 0:  successful exit
 
65
*          < 0:  if INFO = -i, the i-th argument had an illegal value
 
66
*          > 0:  if INFO = i, U(i,i) is exactly zero.  The factorization
 
67
*                has been completed, but the factor U is exactly
 
68
*                singular, so the solution could not be computed.
 
69
*
 
70
*  =====================================================================
 
71
*
 
72
*     .. External Subroutines ..
 
73
      EXTERNAL           XERBLA, ATL_F77WRAP_ZGESV
 
74
*     ..
 
75
*     .. Intrinsic Functions ..
 
76
      INTRINSIC          MAX
 
77
*     ..
 
78
*     .. Executable Statements ..
 
79
*
 
80
*     Test the input parameters.
 
81
*
 
82
      INFO = 0
 
83
      IF( N.LT.0 ) THEN
 
84
         INFO = -1
 
85
      ELSE IF( NRHS.LT.0 ) THEN
 
86
         INFO = -2
 
87
      ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
 
88
         INFO = -4
 
89
      ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
 
90
         INFO = -7
 
91
      END IF
 
92
      IF( INFO.NE.0 ) THEN
 
93
         CALL XERBLA( 'ZGESV ', -INFO )
 
94
         RETURN
 
95
      END IF
 
96
*
 
97
      CALL ATL_F77WRAP_ZGESV( N, NRHS, A, LDA, IPIV, B, LDB, INFO )
 
98
*
 
99
      RETURN
 
100
      END