001:       SUBROUTINE CPTTS2( IUPLO, N, NRHS, D, E, B, LDB )
002: *
003: *  -- LAPACK routine (version 3.2) --
004: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
005: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
006: *     November 2006
007: *
008: *     .. Scalar Arguments ..
009:       INTEGER            IUPLO, LDB, N, NRHS
010: *     ..
011: *     .. Array Arguments ..
012:       REAL               D( * )
013:       COMPLEX            B( LDB, * ), E( * )
014: *     ..
015: *
016: *  Purpose
017: *  =======
018: *
019: *  CPTTS2 solves a tridiagonal system of the form
020: *     A * X = B
021: *  using the factorization A = U'*D*U or A = L*D*L' computed by CPTTRF.
022: *  D is a diagonal matrix specified in the vector D, U (or L) is a unit
023: *  bidiagonal matrix whose superdiagonal (subdiagonal) is specified in
024: *  the vector E, and X and B are N by NRHS matrices.
025: *
026: *  Arguments
027: *  =========
028: *
029: *  IUPLO   (input) INTEGER
030: *          Specifies the form of the factorization and whether the
031: *          vector E is the superdiagonal of the upper bidiagonal factor
032: *          U or the subdiagonal of the lower bidiagonal factor L.
033: *          = 1:  A = U'*D*U, E is the superdiagonal of U
034: *          = 0:  A = L*D*L', E is the subdiagonal of L
035: *
036: *  N       (input) INTEGER
037: *          The order of the tridiagonal matrix A.  N >= 0.
038: *
039: *  NRHS    (input) INTEGER
040: *          The number of right hand sides, i.e., the number of columns
041: *          of the matrix B.  NRHS >= 0.
042: *
043: *  D       (input) REAL array, dimension (N)
044: *          The n diagonal elements of the diagonal matrix D from the
045: *          factorization A = U'*D*U or A = L*D*L'.
046: *
047: *  E       (input) COMPLEX array, dimension (N-1)
048: *          If IUPLO = 1, the (n-1) superdiagonal elements of the unit
049: *          bidiagonal factor U from the factorization A = U'*D*U.
050: *          If IUPLO = 0, the (n-1) subdiagonal elements of the unit
051: *          bidiagonal factor L from the factorization A = L*D*L'.
052: *
053: *  B       (input/output) REAL array, dimension (LDB,NRHS)
054: *          On entry, the right hand side vectors B for the system of
055: *          linear equations.
056: *          On exit, the solution vectors, X.
057: *
058: *  LDB     (input) INTEGER
059: *          The leading dimension of the array B.  LDB >= max(1,N).
060: *
061: *  =====================================================================
062: *
063: *     .. Local Scalars ..
064:       INTEGER            I, J
065: *     ..
066: *     .. External Subroutines ..
067:       EXTERNAL           CSSCAL
068: *     ..
069: *     .. Intrinsic Functions ..
070:       INTRINSIC          CONJG
071: *     ..
072: *     .. Executable Statements ..
073: *
074: *     Quick return if possible
075: *
076:       IF( N.LE.1 ) THEN
077:          IF( N.EQ.1 )
078:      $      CALL CSSCAL( NRHS, 1. / D( 1 ), B, LDB )
079:          RETURN
080:       END IF
081: *
082:       IF( IUPLO.EQ.1 ) THEN
083: *
084: *        Solve A * X = B using the factorization A = U'*D*U,
085: *        overwriting each right hand side vector with its solution.
086: *
087:          IF( NRHS.LE.2 ) THEN
088:             J = 1
089:     5       CONTINUE
090: *
091: *           Solve U' * x = b.
092: *
093:             DO 10 I = 2, N
094:                B( I, J ) = B( I, J ) - B( I-1, J )*CONJG( E( I-1 ) )
095:    10       CONTINUE
096: *
097: *           Solve D * U * x = b.
098: *
099:             DO 20 I = 1, N
100:                B( I, J ) = B( I, J ) / D( I )
101:    20       CONTINUE
102:             DO 30 I = N - 1, 1, -1
103:                B( I, J ) = B( I, J ) - B( I+1, J )*E( I )
104:    30       CONTINUE
105:             IF( J.LT.NRHS ) THEN
106:                J = J + 1
107:                GO TO 5
108:             END IF
109:          ELSE
110:             DO 60 J = 1, NRHS
111: *
112: *              Solve U' * x = b.
113: *
114:                DO 40 I = 2, N
115:                   B( I, J ) = B( I, J ) - B( I-1, J )*CONJG( E( I-1 ) )
116:    40          CONTINUE
117: *
118: *              Solve D * U * x = b.
119: *
120:                B( N, J ) = B( N, J ) / D( N )
121:                DO 50 I = N - 1, 1, -1
122:                   B( I, J ) = B( I, J ) / D( I ) - B( I+1, J )*E( I )
123:    50          CONTINUE
124:    60       CONTINUE
125:          END IF
126:       ELSE
127: *
128: *        Solve A * X = B using the factorization A = L*D*L',
129: *        overwriting each right hand side vector with its solution.
130: *
131:          IF( NRHS.LE.2 ) THEN
132:             J = 1
133:    65       CONTINUE
134: *
135: *           Solve L * x = b.
136: *
137:             DO 70 I = 2, N
138:                B( I, J ) = B( I, J ) - B( I-1, J )*E( I-1 )
139:    70       CONTINUE
140: *
141: *           Solve D * L' * x = b.
142: *
143:             DO 80 I = 1, N
144:                B( I, J ) = B( I, J ) / D( I )
145:    80       CONTINUE
146:             DO 90 I = N - 1, 1, -1
147:                B( I, J ) = B( I, J ) - B( I+1, J )*CONJG( E( I ) )
148:    90       CONTINUE
149:             IF( J.LT.NRHS ) THEN
150:                J = J + 1
151:                GO TO 65
152:             END IF
153:          ELSE
154:             DO 120 J = 1, NRHS
155: *
156: *              Solve L * x = b.
157: *
158:                DO 100 I = 2, N
159:                   B( I, J ) = B( I, J ) - B( I-1, J )*E( I-1 )
160:   100          CONTINUE
161: *
162: *              Solve D * L' * x = b.
163: *
164:                B( N, J ) = B( N, J ) / D( N )
165:                DO 110 I = N - 1, 1, -1
166:                   B( I, J ) = B( I, J ) / D( I ) -
167:      $                        B( I+1, J )*CONJG( E( I ) )
168:   110          CONTINUE
169:   120       CONTINUE
170:          END IF
171:       END IF
172: *
173:       RETURN
174: *
175: *     End of CPTTS2
176: *
177:       END
178: