1       SUBROUTINE DSPSV( UPLO, N, NRHS, AP, IPIV, B, LDB, INFO )
  2 *
  3 *  -- LAPACK driver routine (version 3.3.1) --
  4 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  5 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  6 *  -- April 2011                                                      --
  7 *
  8 *     .. Scalar Arguments ..
  9       CHARACTER          UPLO
 10       INTEGER            INFO, LDB, N, NRHS
 11 *     ..
 12 *     .. Array Arguments ..
 13       INTEGER            IPIV( * )
 14       DOUBLE PRECISION   AP( * ), B( LDB, * )
 15 *     ..
 16 *
 17 *  Purpose
 18 *  =======
 19 *
 20 *  DSPSV computes the solution to a real system of linear equations
 21 *     A * X = B,
 22 *  where A is an N-by-N symmetric matrix stored in packed format and X
 23 *  and B are N-by-NRHS matrices.
 24 *
 25 *  The diagonal pivoting method is used to factor A as
 26 *     A = U * D * U**T,  if UPLO = 'U', or
 27 *     A = L * D * L**T,  if UPLO = 'L',
 28 *  where U (or L) is a product of permutation and unit upper (lower)
 29 *  triangular matrices, D is symmetric and block diagonal with 1-by-1
 30 *  and 2-by-2 diagonal blocks.  The factored form of A is then used to
 31 *  solve the system of equations A * X = B.
 32 *
 33 *  Arguments
 34 *  =========
 35 *
 36 *  UPLO    (input) CHARACTER*1
 37 *          = 'U':  Upper triangle of A is stored;
 38 *          = 'L':  Lower triangle of A is stored.
 39 *
 40 *  N       (input) INTEGER
 41 *          The number of linear equations, i.e., the order of the
 42 *          matrix A.  N >= 0.
 43 *
 44 *  NRHS    (input) INTEGER
 45 *          The number of right hand sides, i.e., the number of columns
 46 *          of the matrix B.  NRHS >= 0.
 47 *
 48 *  AP      (input/output) DOUBLE PRECISION array, dimension (N*(N+1)/2)
 49 *          On entry, the upper or lower triangle of the symmetric matrix
 50 *          A, packed columnwise in a linear array.  The j-th column of A
 51 *          is stored in the array AP as follows:
 52 *          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
 53 *          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
 54 *          See below for further details.
 55 *
 56 *          On exit, the block diagonal matrix D and the multipliers used
 57 *          to obtain the factor U or L from the factorization
 58 *          A = U*D*U**T or A = L*D*L**T as computed by DSPTRF, stored as
 59 *          a packed triangular matrix in the same storage format as A.
 60 *
 61 *  IPIV    (output) INTEGER array, dimension (N)
 62 *          Details of the interchanges and the block structure of D, as
 63 *          determined by DSPTRF.  If IPIV(k) > 0, then rows and columns
 64 *          k and IPIV(k) were interchanged, and D(k,k) is a 1-by-1
 65 *          diagonal block.  If UPLO = 'U' and IPIV(k) = IPIV(k-1) < 0,
 66 *          then rows and columns k-1 and -IPIV(k) were interchanged and
 67 *          D(k-1:k,k-1:k) is a 2-by-2 diagonal block.  If UPLO = 'L' and
 68 *          IPIV(k) = IPIV(k+1) < 0, then rows and columns k+1 and
 69 *          -IPIV(k) were interchanged and D(k:k+1,k:k+1) is a 2-by-2
 70 *          diagonal block.
 71 *
 72 *  B       (input/output) DOUBLE PRECISION array, dimension (LDB,NRHS)
 73 *          On entry, the N-by-NRHS right hand side matrix B.
 74 *          On exit, if INFO = 0, the N-by-NRHS solution matrix X.
 75 *
 76 *  LDB     (input) INTEGER
 77 *          The leading dimension of the array B.  LDB >= max(1,N).
 78 *
 79 *  INFO    (output) INTEGER
 80 *          = 0:  successful exit
 81 *          < 0:  if INFO = -i, the i-th argument had an illegal value
 82 *          > 0:  if INFO = i, D(i,i) is exactly zero.  The factorization
 83 *                has been completed, but the block diagonal matrix D is
 84 *                exactly singular, so the solution could not be
 85 *                computed.
 86 *
 87 *  Further Details
 88 *  ===============
 89 *
 90 *  The packed storage scheme is illustrated by the following example
 91 *  when N = 4, UPLO = 'U':
 92 *
 93 *  Two-dimensional storage of the symmetric matrix A:
 94 *
 95 *     a11 a12 a13 a14
 96 *         a22 a23 a24
 97 *             a33 a34     (aij = aji)
 98 *                 a44
 99 *
100 *  Packed storage of the upper triangle of A:
101 *
102 *  AP = [ a11, a12, a22, a13, a23, a33, a14, a24, a34, a44 ]
103 *
104 *  =====================================================================
105 *
106 *     .. External Functions ..
107       LOGICAL            LSAME
108       EXTERNAL           LSAME
109 *     ..
110 *     .. External Subroutines ..
111       EXTERNAL           DSPTRF, DSPTRS, XERBLA
112 *     ..
113 *     .. Intrinsic Functions ..
114       INTRINSIC          MAX
115 *     ..
116 *     .. Executable Statements ..
117 *
118 *     Test the input parameters.
119 *
120       INFO = 0
121       IF.NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
122          INFO = -1
123       ELSE IF( N.LT.0 ) THEN
124          INFO = -2
125       ELSE IF( NRHS.LT.0 ) THEN
126          INFO = -3
127       ELSE IF( LDB.LT.MAX1, N ) ) THEN
128          INFO = -7
129       END IF
130       IF( INFO.NE.0 ) THEN
131          CALL XERBLA( 'DSPSV '-INFO )
132          RETURN
133       END IF
134 *
135 *     Compute the factorization A = U*D*U**T or A = L*D*L**T.
136 *
137       CALL DSPTRF( UPLO, N, AP, IPIV, INFO )
138       IF( INFO.EQ.0 ) THEN
139 *
140 *        Solve the system A*X = B, overwriting B with X.
141 *
142          CALL DSPTRS( UPLO, N, NRHS, AP, IPIV, B, LDB, INFO )
143 *
144       END IF
145       RETURN
146 *
147 *     End of DSPSV
148 *
149       END