Diff for /rpl/lapack/lapack/zhetrs2.f between versions 1.2 and 1.3

version 1.2, 2010/12/21 13:53:47 version 1.3, 2011/07/22 07:38:15
Line 1 Line 1
       SUBROUTINE ZHETRS2( UPLO, N, NRHS, A, LDA, IPIV, B, LDB,         SUBROUTINE ZHETRS2( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, 
      $                    WORK, INFO )       $                    WORK, INFO )
 *  *
 *  -- LAPACK PROTOTYPE routine (version 3.3.0) --  *  -- LAPACK PROTOTYPE routine (version 3.3.1) --
 *  *
 *  -- Written by Julie Langou of the Univ. of TN    --  *  -- Written by Julie Langou of the Univ. of TN    --
 *     November 2010  *  -- April 2011                                                      --
 *  *
 *  -- 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..--
Line 21 Line 21
 *  Purpose  *  Purpose
 *  =======  *  =======
 *  *
 *  ZHETRS2 solves a system of linear equations A*X = B with a real  *  ZHETRS2 solves a system of linear equations A*X = B with a complex
 *  Hermitian matrix A using the factorization A = U*D*U**T or  *  Hermitian matrix A using the factorization A = U*D*U**H or
 *  A = L*D*L**T computed by ZSYTRF and converted by ZSYCONV.  *  A = L*D*L**H computed by ZHETRF and converted by ZSYCONV.
 *  *
 *  Arguments  *  Arguments
 *  =========  *  =========
Line 118 Line 118
 *  *
       IF( UPPER ) THEN        IF( UPPER ) THEN
 *  *
 *        Solve A*X = B, where A = U*D*U'.  *        Solve A*X = B, where A = U*D*U**H.
 *  *
 *       P' * B    *       P**T * B  
         K=N          K=N
         DO WHILE ( K .GE. 1 )          DO WHILE ( K .GE. 1 )
          IF( IPIV( K ).GT.0 ) THEN           IF( IPIV( K ).GT.0 ) THEN
Line 140 Line 140
          END IF           END IF
         END DO          END DO
 *  *
 *  Compute (U \P' * B) -> B    [ (U \P' * B) ]  *  Compute (U \P**T * B) -> B    [ (U \P**T * B) ]
 *  *
         CALL ZTRSM('L','U','N','U',N,NRHS,ONE,A,N,B,N)          CALL ZTRSM('L','U','N','U',N,NRHS,ONE,A,LDA,B,LDB)
 *  *
 *  Compute D \ B -> B   [ D \ (U \P' * B) ]  *  Compute D \ B -> B   [ D \ (U \P**T * B) ]
 *         *       
          I=N           I=N
          DO WHILE ( I .GE. 1 )           DO WHILE ( I .GE. 1 )
Line 169 Line 169
             I = I - 1              I = I - 1
          END DO           END DO
 *  *
 *      Compute (U' \ B) -> B   [ U' \ (D \ (U \P' * B) ) ]  *      Compute (U**H \ B) -> B   [ U**H \ (D \ (U \P**T * B) ) ]
 *  *
          CALL ZTRSM('L','U','C','U',N,NRHS,ONE,A,N,B,N)           CALL ZTRSM('L','U','C','U',N,NRHS,ONE,A,LDA,B,LDB)
 *  *
 *       P * B  [ P * (U' \ (D \ (U \P' * B) )) ]  *       P * B  [ P * (U**H \ (D \ (U \P**T * B) )) ]
 *  *
         K=1          K=1
         DO WHILE ( K .LE. N )          DO WHILE ( K .LE. N )
Line 196 Line 196
 *  *
       ELSE        ELSE
 *  *
 *        Solve A*X = B, where A = L*D*L'.  *        Solve A*X = B, where A = L*D*L**H.
 *  *
 *       P' * B    *       P**T * B  
         K=1          K=1
         DO WHILE ( K .LE. N )          DO WHILE ( K .LE. N )
          IF( IPIV( K ).GT.0 ) THEN           IF( IPIV( K ).GT.0 ) THEN
Line 218 Line 218
          ENDIF           ENDIF
         END DO          END DO
 *  *
 *  Compute (L \P' * B) -> B    [ (L \P' * B) ]  *  Compute (L \P**T * B) -> B    [ (L \P**T * B) ]
 *  *
         CALL ZTRSM('L','L','N','U',N,NRHS,ONE,A,N,B,N)          CALL ZTRSM('L','L','N','U',N,NRHS,ONE,A,LDA,B,LDB)
 *  *
 *  Compute D \ B -> B   [ D \ (L \P' * B) ]  *  Compute D \ B -> B   [ D \ (L \P**T * B) ]
 *         *       
          I=1           I=1
          DO WHILE ( I .LE. N )           DO WHILE ( I .LE. N )
Line 245 Line 245
             I = I + 1              I = I + 1
          END DO           END DO
 *  *
 *  Compute (L' \ B) -> B   [ L' \ (D \ (L \P' * B) ) ]  *  Compute (L**H \ B) -> B   [ L**H \ (D \ (L \P**T * B) ) ]
 *   * 
         CALL ZTRSM('L','L','C','U',N,NRHS,ONE,A,N,B,N)          CALL ZTRSM('L','L','C','U',N,NRHS,ONE,A,LDA,B,LDB)
 *  *
 *       P * B  [ P * (L' \ (D \ (L \P' * B) )) ]  *       P * B  [ P * (L**H \ (D \ (L \P**T * B) )) ]
 *  *
         K=N          K=N
         DO WHILE ( K .GE. 1 )          DO WHILE ( K .GE. 1 )

Removed from v.1.2  
changed lines
  Added in v.1.3


CVSweb interface <joel.bertrand@systella.fr>