1       SUBROUTINE ZPTTRS( UPLO, N, NRHS, D, E, B, LDB, INFO )
  2 *
  3 *  -- LAPACK 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       DOUBLE PRECISION   D( * )
 14       COMPLEX*16         B( LDB, * ), E( * )
 15 *     ..
 16 *
 17 *  Purpose
 18 *  =======
 19 *
 20 *  ZPTTRS solves a tridiagonal system of the form
 21 *     A * X = B
 22 *  using the factorization A = U**H *D* U or A = L*D*L**H computed by ZPTTRF.
 23 *  D is a diagonal matrix specified in the vector D, U (or L) is a unit
 24 *  bidiagonal matrix whose superdiagonal (subdiagonal) is specified in
 25 *  the vector E, and X and B are N by NRHS matrices.
 26 *
 27 *  Arguments
 28 *  =========
 29 *
 30 *  UPLO    (input) CHARACTER*1
 31 *          Specifies the form of the factorization and whether the
 32 *          vector E is the superdiagonal of the upper bidiagonal factor
 33 *          U or the subdiagonal of the lower bidiagonal factor L.
 34 *          = 'U':  A = U**H *D*U, E is the superdiagonal of U
 35 *          = 'L':  A = L*D*L**H, E is the subdiagonal of L
 36 *
 37 *  N       (input) INTEGER
 38 *          The order of the tridiagonal 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 *  D       (input) DOUBLE PRECISION array, dimension (N)
 45 *          The n diagonal elements of the diagonal matrix D from the
 46 *          factorization A = U**H *D*U or A = L*D*L**H.
 47 *
 48 *  E       (input) COMPLEX*16 array, dimension (N-1)
 49 *          If UPLO = 'U', the (n-1) superdiagonal elements of the unit
 50 *          bidiagonal factor U from the factorization A = U**H*D*U.
 51 *          If UPLO = 'L', the (n-1) subdiagonal elements of the unit
 52 *          bidiagonal factor L from the factorization A = L*D*L**H.
 53 *
 54 *  B       (input/output) DOUBLE PRECISION array, dimension (LDB,NRHS)
 55 *          On entry, the right hand side vectors B for the system of
 56 *          linear equations.
 57 *          On exit, the solution vectors, X.
 58 *
 59 *  LDB     (input) INTEGER
 60 *          The leading dimension of the array B.  LDB >= max(1,N).
 61 *
 62 *  INFO    (output) INTEGER
 63 *          = 0: successful exit
 64 *          < 0: if INFO = -k, the k-th argument had an illegal value
 65 *
 66 *  =====================================================================
 67 *
 68 *     .. Local Scalars ..
 69       LOGICAL            UPPER
 70       INTEGER            IUPLO, J, JB, NB
 71 *     ..
 72 *     .. External Functions ..
 73       INTEGER            ILAENV
 74       EXTERNAL           ILAENV
 75 *     ..
 76 *     .. External Subroutines ..
 77       EXTERNAL           XERBLA, ZPTTS2
 78 *     ..
 79 *     .. Intrinsic Functions ..
 80       INTRINSIC          MAXMIN
 81 *     ..
 82 *     .. Executable Statements ..
 83 *
 84 *     Test the input arguments.
 85 *
 86       INFO = 0
 87       UPPER = ( UPLO.EQ.'U' .OR. UPLO.EQ.'u' )
 88       IF.NOT.UPPER .AND. .NOT.( UPLO.EQ.'L' .OR. UPLO.EQ.'l' ) ) THEN
 89          INFO = -1
 90       ELSE IF( N.LT.0 ) THEN
 91          INFO = -2
 92       ELSE IF( NRHS.LT.0 ) THEN
 93          INFO = -3
 94       ELSE IF( LDB.LT.MAX1, N ) ) THEN
 95          INFO = -7
 96       END IF
 97       IF( INFO.NE.0 ) THEN
 98          CALL XERBLA( 'ZPTTRS'-INFO )
 99          RETURN
100       END IF
101 *
102 *     Quick return if possible
103 *
104       IF( N.EQ.0 .OR. NRHS.EQ.0 )
105      $   RETURN
106 *
107 *     Determine the number of right-hand sides to solve at a time.
108 *
109       IF( NRHS.EQ.1 ) THEN
110          NB = 1
111       ELSE
112          NB = MAX1, ILAENV( 1'ZPTTRS', UPLO, N, NRHS, -1-1 ) )
113       END IF
114 *
115 *     Decode UPLO
116 *
117       IF( UPPER ) THEN
118          IUPLO = 1
119       ELSE
120          IUPLO = 0
121       END IF
122 *
123       IF( NB.GE.NRHS ) THEN
124          CALL ZPTTS2( IUPLO, N, NRHS, D, E, B, LDB )
125       ELSE
126          DO 10 J = 1, NRHS, NB
127             JB = MIN( NRHS-J+1, NB )
128             CALL ZPTTS2( IUPLO, N, JB, D, E, B( 1, J ), LDB )
129    10    CONTINUE
130       END IF
131 *
132       RETURN
133 *
134 *     End of ZPTTRS
135 *
136       END