001:       SUBROUTINE SSYSV( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
002:      $                  LWORK, INFO )
003: *
004: *  -- LAPACK driver routine (version 3.2) --
005: *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
006: *     November 2006
007: *
008: *     .. Scalar Arguments ..
009:       CHARACTER          UPLO
010:       INTEGER            INFO, LDA, LDB, LWORK, N, NRHS
011: *     ..
012: *     .. Array Arguments ..
013:       INTEGER            IPIV( * )
014:       REAL               A( LDA, * ), B( LDB, * ), WORK( * )
015: *     ..
016: *
017: *  Purpose
018: *  =======
019: *
020: *  SSYSV computes the solution to a real system of linear equations
021: *     A * X = B,
022: *  where A is an N-by-N symmetric matrix and X and B are N-by-NRHS
023: *  matrices.
024: *
025: *  The diagonal pivoting method is used to factor A as
026: *     A = U * D * U**T,  if UPLO = 'U', or
027: *     A = L * D * L**T,  if UPLO = 'L',
028: *  where U (or L) is a product of permutation and unit upper (lower)
029: *  triangular matrices, and D is symmetric and block diagonal with 
030: *  1-by-1 and 2-by-2 diagonal blocks.  The factored form of A is then
031: *  used to solve the system of equations A * X = B.
032: *
033: *  Arguments
034: *  =========
035: *
036: *  UPLO    (input) CHARACTER*1
037: *          = 'U':  Upper triangle of A is stored;
038: *          = 'L':  Lower triangle of A is stored.
039: *
040: *  N       (input) INTEGER
041: *          The number of linear equations, i.e., the order of the
042: *          matrix A.  N >= 0.
043: *
044: *  NRHS    (input) INTEGER
045: *          The number of right hand sides, i.e., the number of columns
046: *          of the matrix B.  NRHS >= 0.
047: *
048: *  A       (input/output) REAL array, dimension (LDA,N)
049: *          On entry, the symmetric matrix A.  If UPLO = 'U', the leading
050: *          N-by-N upper triangular part of A contains the upper
051: *          triangular part of the matrix A, and the strictly lower
052: *          triangular part of A is not referenced.  If UPLO = 'L', the
053: *          leading N-by-N lower triangular part of A contains the lower
054: *          triangular part of the matrix A, and the strictly upper
055: *          triangular part of A is not referenced.
056: *
057: *          On exit, if INFO = 0, the block diagonal matrix D and the
058: *          multipliers used to obtain the factor U or L from the
059: *          factorization A = U*D*U**T or A = L*D*L**T as computed by
060: *          SSYTRF.
061: *
062: *  LDA     (input) INTEGER
063: *          The leading dimension of the array A.  LDA >= max(1,N).
064: *
065: *  IPIV    (output) INTEGER array, dimension (N)
066: *          Details of the interchanges and the block structure of D, as
067: *          determined by SSYTRF.  If IPIV(k) > 0, then rows and columns
068: *          k and IPIV(k) were interchanged, and D(k,k) is a 1-by-1
069: *          diagonal block.  If UPLO = 'U' and IPIV(k) = IPIV(k-1) < 0,
070: *          then rows and columns k-1 and -IPIV(k) were interchanged and
071: *          D(k-1:k,k-1:k) is a 2-by-2 diagonal block.  If UPLO = 'L' and
072: *          IPIV(k) = IPIV(k+1) < 0, then rows and columns k+1 and
073: *          -IPIV(k) were interchanged and D(k:k+1,k:k+1) is a 2-by-2
074: *          diagonal block.
075: *
076: *  B       (input/output) REAL array, dimension (LDB,NRHS)
077: *          On entry, the N-by-NRHS right hand side matrix B.
078: *          On exit, if INFO = 0, the N-by-NRHS solution matrix X.
079: *
080: *  LDB     (input) INTEGER
081: *          The leading dimension of the array B.  LDB >= max(1,N).
082: *
083: *  WORK    (workspace/output) REAL array, dimension (MAX(1,LWORK))
084: *          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
085: *
086: *  LWORK   (input) INTEGER
087: *          The length of WORK.  LWORK >= 1, and for best performance
088: *          LWORK >= max(1,N*NB), where NB is the optimal blocksize for
089: *          SSYTRF.
090: *
091: *          If LWORK = -1, then a workspace query is assumed; the routine
092: *          only calculates the optimal size of the WORK array, returns
093: *          this value as the first entry of the WORK array, and no error
094: *          message related to LWORK is issued by XERBLA.
095: *
096: *  INFO    (output) INTEGER
097: *          = 0: successful exit
098: *          < 0: if INFO = -i, the i-th argument had an illegal value
099: *          > 0: if INFO = i, D(i,i) is exactly zero.  The factorization
100: *               has been completed, but the block diagonal matrix D is
101: *               exactly singular, so the solution could not be computed.
102: *
103: *  =====================================================================
104: *
105: *     .. Local Scalars ..
106:       LOGICAL            LQUERY
107:       INTEGER            LWKOPT, NB
108: *     ..
109: *     .. External Functions ..
110:       LOGICAL            LSAME
111:       INTEGER            ILAENV
112:       EXTERNAL           ILAENV, LSAME
113: *     ..
114: *     .. External Subroutines ..
115:       EXTERNAL           SSYTRF, SSYTRS, XERBLA
116: *     ..
117: *     .. Intrinsic Functions ..
118:       INTRINSIC          MAX
119: *     ..
120: *     .. Executable Statements ..
121: *
122: *     Test the input parameters.
123: *
124:       INFO = 0
125:       LQUERY = ( LWORK.EQ.-1 )
126:       IF( .NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
127:          INFO = -1
128:       ELSE IF( N.LT.0 ) THEN
129:          INFO = -2
130:       ELSE IF( NRHS.LT.0 ) THEN
131:          INFO = -3
132:       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
133:          INFO = -5
134:       ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
135:          INFO = -8
136:       ELSE IF( LWORK.LT.1 .AND. .NOT.LQUERY ) THEN
137:          INFO = -10
138:       END IF
139: *
140:       IF( INFO.EQ.0 ) THEN
141:          IF( N.EQ.0 ) THEN
142:             LWKOPT = 1
143:          ELSE
144:             NB = ILAENV( 1, 'SSYTRF', UPLO, N, -1, -1, -1 )
145:             LWKOPT = N*NB
146:          END IF
147:          WORK( 1 ) = LWKOPT
148:       END IF
149: *
150:       IF( INFO.NE.0 ) THEN
151:          CALL XERBLA( 'SSYSV ', -INFO )
152:          RETURN
153:       ELSE IF( LQUERY ) THEN
154:          RETURN
155:       END IF
156: *
157: *     Compute the factorization A = U*D*U' or A = L*D*L'.
158: *
159:       CALL SSYTRF( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO )
160:       IF( INFO.EQ.0 ) THEN
161: *
162: *        Solve the system A*X = B, overwriting B with X.
163: *
164:          CALL SSYTRS( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
165: *
166:       END IF
167: *
168:       WORK( 1 ) = LWKOPT
169: *
170:       RETURN
171: *
172: *     End of SSYSV
173: *
174:       END
175: