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

« back to all changes in this revision

Viewing changes to interfaces/lapack/F77/src/dposv.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 DPOSV( UPLO, N, NRHS, A, LDA, 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
      CHARACTER UPLO
 
13
      INTEGER   INFO, LDA, LDB, N, NRHS
 
14
*     ..
 
15
*     .. Array Arguments ..
 
16
      DOUBLE PRECISION A( LDA, * ), B( LDB, * )
 
17
*     ..
 
18
*
 
19
*  Purpose
 
20
*  =======
 
21
*
 
22
*  DPOSV computes the solution to a real system of linear equations
 
23
*     A * X = B,
 
24
*  where A is an N-by-N symmetric positive definite matrix and X and B
 
25
*  are N-by-NRHS matrices.
 
26
*
 
27
*  The Cholesky decomposition is used to factor A as
 
28
*     A = U**T* U,  if UPLO = 'U', or
 
29
*     A = L * L**T,  if UPLO = 'L',
 
30
*  where U is an upper triangular matrix and  L is a lower triangular
 
31
*  matrix.  The factored form of A is then used to solve the system of
 
32
*  equations A * X = B.
 
33
*
 
34
*  Arguments
 
35
*  =========
 
36
*
 
37
*  UPLO    (input) CHARACTER*1
 
38
*          = 'U':  Upper triangle of A is stored;
 
39
*          = 'L':  Lower triangle of A is stored.
 
40
*
 
41
*  N       (input) INTEGER
 
42
*          The number of linear equations, i.e., the order of the
 
43
*          matrix A.  N >= 0.
 
44
*
 
45
*  NRHS    (input) INTEGER
 
46
*          The number of right hand sides, i.e., the number of columns
 
47
*          of the matrix B.  NRHS >= 0.
 
48
*
 
49
*  A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
 
50
*          On entry, the symmetric matrix A.  If UPLO = 'U', the leading
 
51
*          N-by-N upper triangular part of A contains the upper
 
52
*          triangular part of the matrix A, and the strictly lower
 
53
*          triangular part of A is not referenced.  If UPLO = 'L', the
 
54
*          leading N-by-N lower triangular part of A contains the lower
 
55
*          triangular part of the matrix A, and the strictly upper
 
56
*          triangular part of A is not referenced.
 
57
*
 
58
*          On exit, if INFO = 0, the factor U or L from the Cholesky
 
59
*          factorization A = U**T*U or A = L*L**T.
 
60
*
 
61
*  LDA     (input) INTEGER
 
62
*          The leading dimension of the array A.  LDA >= max(1,N).
 
63
*
 
64
*  B       (input/output) DOUBLE PRECISION array, dimension (LDB,NRHS)
 
65
*          On entry, the N-by-NRHS right hand side matrix B.
 
66
*          On exit, if INFO = 0, the N-by-NRHS solution matrix X.
 
67
*
 
68
*  LDB     (input) INTEGER
 
69
*          The leading dimension of the array B.  LDB >= max(1,N).
 
70
*
 
71
*  INFO    (output) INTEGER
 
72
*          = 0:  successful exit
 
73
*          < 0:  if INFO = -i, the i-th argument had an illegal value
 
74
*          > 0:  if INFO = i, the leading minor of order i of A is not
 
75
*                positive definite, so the factorization could not be
 
76
*                completed, and the solution has not been computed.
 
77
*
 
78
*  =====================================================================
 
79
*
 
80
*     ..
 
81
*     .. Parameters ..
 
82
      INTEGER ATLASROWMAJOR, ATLASCOLMAJOR
 
83
      PARAMETER (ATLASROWMAJOR=101, ATLASCOLMAJOR=102)
 
84
      INTEGER ATLASNOTRANS, ATLASTRANS, ATLASCONJTRANS
 
85
      PARAMETER (ATLASNOTRANS=111, ATLASTRANS=112, ATLASCONJTRANS=113)
 
86
      INTEGER ATLASUPPER, ATLASLOWER
 
87
      PARAMETER (ATLASUPPER=121, ATLASLOWER=122)
 
88
      INTEGER ATLASNONUNIT, ATLASUNIT
 
89
      PARAMETER (ATLASNONUNIT=131, ATLASUNIT=132)
 
90
      INTEGER ATLASLEFT, ATLASRIGHT
 
91
      PARAMETER (ATLASLEFT=141, ATLASRIGHT=142)
 
92
*     ..
 
93
*     .. Local Scalars ..
 
94
      INTEGER            IUPLO
 
95
*     ..
 
96
*     .. External Functions ..
 
97
      LOGICAL            LSAME
 
98
      EXTERNAL           LSAME
 
99
*     ..
 
100
*     .. External Subroutines ..
 
101
      EXTERNAL           XERBLA, ATL_F77WRAP_DPOSV
 
102
*     ..
 
103
*     .. Intrinsic Functions ..
 
104
      INTRINSIC          MAX
 
105
*     ..
 
106
*     .. Executable Statements ..
 
107
*
 
108
*     Test the input parameters.
 
109
*
 
110
      INFO = 0
 
111
      IF( .NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
 
112
         INFO = -1
 
113
      ELSE IF( N.LT.0 ) THEN
 
114
         INFO = -2
 
115
      ELSE IF( NRHS.LT.0 ) THEN
 
116
         INFO = -3
 
117
      ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
 
118
         INFO = -5
 
119
      ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
 
120
         INFO = -7
 
121
      END IF
 
122
      IF( INFO.NE.0 ) THEN
 
123
         CALL XERBLA( 'DPOSV ', -INFO )
 
124
         RETURN
 
125
      END IF
 
126
*
 
127
      IF ( LSAME(UPLO, 'U') ) THEN
 
128
         IUPLO = ATLASUPPER
 
129
      ELSE
 
130
         IUPLO = ATLASLOWER
 
131
      ENDIF
 
132
*
 
133
      CALL ATL_F77WRAP_DPOSV( IUPLO, N, NRHS, A, LDA, B, LDB, INFO )
 
134
*
 
135
      RETURN
 
136
      END