Diff for /rpl/lapack/lapack/zptts2.f between versions 1.7 and 1.8

version 1.7, 2010/12/21 13:53:55 version 1.8, 2011/07/22 07:38:20
Line 1 Line 1
       SUBROUTINE ZPTTS2( IUPLO, N, NRHS, D, E, B, LDB )        SUBROUTINE ZPTTS2( IUPLO, N, NRHS, D, E, B, LDB )
 *  *
 *  -- LAPACK routine (version 3.2) --  *  -- LAPACK routine (version 3.3.1) --
 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --  *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--  *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
 *     November 2006  *  -- April 2011                                                      --
 *  *
 *     .. Scalar Arguments ..  *     .. Scalar Arguments ..
       INTEGER            IUPLO, LDB, N, NRHS        INTEGER            IUPLO, LDB, N, NRHS
Line 18 Line 18
 *  *
 *  ZPTTS2 solves a tridiagonal system of the form  *  ZPTTS2 solves a tridiagonal system of the form
 *     A * X = B  *     A * X = B
 *  using the factorization A = U'*D*U or A = L*D*L' computed by ZPTTRF.  *  using the factorization A = U**H *D*U or A = L*D*L**H computed by ZPTTRF.
 *  D is a diagonal matrix specified in the vector D, U (or L) is a unit  *  D is a diagonal matrix specified in the vector D, U (or L) is a unit
 *  bidiagonal matrix whose superdiagonal (subdiagonal) is specified in  *  bidiagonal matrix whose superdiagonal (subdiagonal) is specified in
 *  the vector E, and X and B are N by NRHS matrices.  *  the vector E, and X and B are N by NRHS matrices.
Line 30 Line 30
 *          Specifies the form of the factorization and whether the  *          Specifies the form of the factorization and whether the
 *          vector E is the superdiagonal of the upper bidiagonal factor  *          vector E is the superdiagonal of the upper bidiagonal factor
 *          U or the subdiagonal of the lower bidiagonal factor L.  *          U or the subdiagonal of the lower bidiagonal factor L.
 *          = 1:  A = U'*D*U, E is the superdiagonal of U  *          = 1:  A = U**H *D*U, E is the superdiagonal of U
 *          = 0:  A = L*D*L', E is the subdiagonal of L  *          = 0:  A = L*D*L**H, E is the subdiagonal of L
 *  *
 *  N       (input) INTEGER  *  N       (input) INTEGER
 *          The order of the tridiagonal matrix A.  N >= 0.  *          The order of the tridiagonal matrix A.  N >= 0.
Line 42 Line 42
 *  *
 *  D       (input) DOUBLE PRECISION array, dimension (N)  *  D       (input) DOUBLE PRECISION array, dimension (N)
 *          The n diagonal elements of the diagonal matrix D from the  *          The n diagonal elements of the diagonal matrix D from the
 *          factorization A = U'*D*U or A = L*D*L'.  *          factorization A = U**H *D*U or A = L*D*L**H.
 *  *
 *  E       (input) COMPLEX*16 array, dimension (N-1)  *  E       (input) COMPLEX*16 array, dimension (N-1)
 *          If IUPLO = 1, the (n-1) superdiagonal elements of the unit  *          If IUPLO = 1, the (n-1) superdiagonal elements of the unit
 *          bidiagonal factor U from the factorization A = U'*D*U.  *          bidiagonal factor U from the factorization A = U**H*D*U.
 *          If IUPLO = 0, the (n-1) subdiagonal elements of the unit  *          If IUPLO = 0, the (n-1) subdiagonal elements of the unit
 *          bidiagonal factor L from the factorization A = L*D*L'.  *          bidiagonal factor L from the factorization A = L*D*L**H.
 *  *
 *  B       (input/output) DOUBLE PRECISION array, dimension (LDB,NRHS)  *  B       (input/output) DOUBLE PRECISION array, dimension (LDB,NRHS)
 *          On entry, the right hand side vectors B for the system of  *          On entry, the right hand side vectors B for the system of
Line 81 Line 81
 *  *
       IF( IUPLO.EQ.1 ) THEN        IF( IUPLO.EQ.1 ) THEN
 *  *
 *        Solve A * X = B using the factorization A = U'*D*U,  *        Solve A * X = B using the factorization A = U**H *D*U,
 *        overwriting each right hand side vector with its solution.  *        overwriting each right hand side vector with its solution.
 *  *
          IF( NRHS.LE.2 ) THEN           IF( NRHS.LE.2 ) THEN
             J = 1              J = 1
    10       CONTINUE     10       CONTINUE
 *  *
 *           Solve U' * x = b.  *           Solve U**H * x = b.
 *  *
             DO 20 I = 2, N              DO 20 I = 2, N
                B( I, J ) = B( I, J ) - B( I-1, J )*DCONJG( E( I-1 ) )                 B( I, J ) = B( I, J ) - B( I-1, J )*DCONJG( E( I-1 ) )
Line 109 Line 109
          ELSE           ELSE
             DO 70 J = 1, NRHS              DO 70 J = 1, NRHS
 *  *
 *              Solve U' * x = b.  *              Solve U**H * x = b.
 *  *
                DO 50 I = 2, N                 DO 50 I = 2, N
                   B( I, J ) = B( I, J ) - B( I-1, J )*DCONJG( E( I-1 ) )                    B( I, J ) = B( I, J ) - B( I-1, J )*DCONJG( E( I-1 ) )
Line 125 Line 125
          END IF           END IF
       ELSE        ELSE
 *  *
 *        Solve A * X = B using the factorization A = L*D*L',  *        Solve A * X = B using the factorization A = L*D*L**H,
 *        overwriting each right hand side vector with its solution.  *        overwriting each right hand side vector with its solution.
 *  *
          IF( NRHS.LE.2 ) THEN           IF( NRHS.LE.2 ) THEN
Line 138 Line 138
                B( I, J ) = B( I, J ) - B( I-1, J )*E( I-1 )                 B( I, J ) = B( I, J ) - B( I-1, J )*E( I-1 )
    90       CONTINUE     90       CONTINUE
 *  *
 *           Solve D * L' * x = b.  *           Solve D * L**H * x = b.
 *  *
             DO 100 I = 1, N              DO 100 I = 1, N
                B( I, J ) = B( I, J ) / D( I )                 B( I, J ) = B( I, J ) / D( I )
Line 159 Line 159
                   B( I, J ) = B( I, J ) - B( I-1, J )*E( I-1 )                    B( I, J ) = B( I, J ) - B( I-1, J )*E( I-1 )
   120          CONTINUE    120          CONTINUE
 *  *
 *              Solve D * L' * x = b.  *              Solve D * L**H * x = b.
 *  *
                B( N, J ) = B( N, J ) / D( N )                 B( N, J ) = B( N, J ) / D( N )
                DO 130 I = N - 1, 1, -1                 DO 130 I = N - 1, 1, -1

Removed from v.1.7  
changed lines
  Added in v.1.8


CVSweb interface <joel.bertrand@systella.fr>