File:  [local] / rpl / lapack / lapack / ztrti2.f
Revision 1.4: download - view: text, annotated - select for diffs - revision graph
Fri Aug 6 15:32:51 2010 UTC (13 years, 9 months ago) by bertrand
Branches: MAIN
CVS tags: HEAD
Cohérence

    1:       SUBROUTINE ZTRTI2( UPLO, DIAG, N, A, LDA, INFO )
    2: *
    3: *  -- LAPACK routine (version 3.2) --
    4: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
    5: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
    6: *     November 2006
    7: *
    8: *     .. Scalar Arguments ..
    9:       CHARACTER          DIAG, UPLO
   10:       INTEGER            INFO, LDA, N
   11: *     ..
   12: *     .. Array Arguments ..
   13:       COMPLEX*16         A( LDA, * )
   14: *     ..
   15: *
   16: *  Purpose
   17: *  =======
   18: *
   19: *  ZTRTI2 computes the inverse of a complex upper or lower triangular
   20: *  matrix.
   21: *
   22: *  This is the Level 2 BLAS version of the algorithm.
   23: *
   24: *  Arguments
   25: *  =========
   26: *
   27: *  UPLO    (input) CHARACTER*1
   28: *          Specifies whether the matrix A is upper or lower triangular.
   29: *          = 'U':  Upper triangular
   30: *          = 'L':  Lower triangular
   31: *
   32: *  DIAG    (input) CHARACTER*1
   33: *          Specifies whether or not the matrix A is unit triangular.
   34: *          = 'N':  Non-unit triangular
   35: *          = 'U':  Unit triangular
   36: *
   37: *  N       (input) INTEGER
   38: *          The order of the matrix A.  N >= 0.
   39: *
   40: *  A       (input/output) COMPLEX*16 array, dimension (LDA,N)
   41: *          On entry, the triangular matrix A.  If UPLO = 'U', the
   42: *          leading n by n upper triangular part of the array A contains
   43: *          the upper triangular matrix, and the strictly lower
   44: *          triangular part of A is not referenced.  If UPLO = 'L', the
   45: *          leading n by n lower triangular part of the array A contains
   46: *          the lower triangular matrix, and the strictly upper
   47: *          triangular part of A is not referenced.  If DIAG = 'U', the
   48: *          diagonal elements of A are also not referenced and are
   49: *          assumed to be 1.
   50: *
   51: *          On exit, the (triangular) inverse of the original matrix, in
   52: *          the same storage format.
   53: *
   54: *  LDA     (input) INTEGER
   55: *          The leading dimension of the array A.  LDA >= max(1,N).
   56: *
   57: *  INFO    (output) INTEGER
   58: *          = 0: successful exit
   59: *          < 0: if INFO = -k, the k-th argument had an illegal value
   60: *
   61: *  =====================================================================
   62: *
   63: *     .. Parameters ..
   64:       COMPLEX*16         ONE
   65:       PARAMETER          ( ONE = ( 1.0D+0, 0.0D+0 ) )
   66: *     ..
   67: *     .. Local Scalars ..
   68:       LOGICAL            NOUNIT, UPPER
   69:       INTEGER            J
   70:       COMPLEX*16         AJJ
   71: *     ..
   72: *     .. External Functions ..
   73:       LOGICAL            LSAME
   74:       EXTERNAL           LSAME
   75: *     ..
   76: *     .. External Subroutines ..
   77:       EXTERNAL           XERBLA, ZSCAL, ZTRMV
   78: *     ..
   79: *     .. Intrinsic Functions ..
   80:       INTRINSIC          MAX
   81: *     ..
   82: *     .. Executable Statements ..
   83: *
   84: *     Test the input parameters.
   85: *
   86:       INFO = 0
   87:       UPPER = LSAME( UPLO, 'U' )
   88:       NOUNIT = LSAME( DIAG, 'N' )
   89:       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
   90:          INFO = -1
   91:       ELSE IF( .NOT.NOUNIT .AND. .NOT.LSAME( DIAG, 'U' ) ) THEN
   92:          INFO = -2
   93:       ELSE IF( N.LT.0 ) THEN
   94:          INFO = -3
   95:       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
   96:          INFO = -5
   97:       END IF
   98:       IF( INFO.NE.0 ) THEN
   99:          CALL XERBLA( 'ZTRTI2', -INFO )
  100:          RETURN
  101:       END IF
  102: *
  103:       IF( UPPER ) THEN
  104: *
  105: *        Compute inverse of upper triangular matrix.
  106: *
  107:          DO 10 J = 1, N
  108:             IF( NOUNIT ) THEN
  109:                A( J, J ) = ONE / A( J, J )
  110:                AJJ = -A( J, J )
  111:             ELSE
  112:                AJJ = -ONE
  113:             END IF
  114: *
  115: *           Compute elements 1:j-1 of j-th column.
  116: *
  117:             CALL ZTRMV( 'Upper', 'No transpose', DIAG, J-1, A, LDA,
  118:      $                  A( 1, J ), 1 )
  119:             CALL ZSCAL( J-1, AJJ, A( 1, J ), 1 )
  120:    10    CONTINUE
  121:       ELSE
  122: *
  123: *        Compute inverse of lower triangular matrix.
  124: *
  125:          DO 20 J = N, 1, -1
  126:             IF( NOUNIT ) THEN
  127:                A( J, J ) = ONE / A( J, J )
  128:                AJJ = -A( J, J )
  129:             ELSE
  130:                AJJ = -ONE
  131:             END IF
  132:             IF( J.LT.N ) THEN
  133: *
  134: *              Compute elements j+1:n of j-th column.
  135: *
  136:                CALL ZTRMV( 'Lower', 'No transpose', DIAG, N-J,
  137:      $                     A( J+1, J+1 ), LDA, A( J+1, J ), 1 )
  138:                CALL ZSCAL( N-J, AJJ, A( J+1, J ), 1 )
  139:             END IF
  140:    20    CONTINUE
  141:       END IF
  142: *
  143:       RETURN
  144: *
  145: *     End of ZTRTI2
  146: *
  147:       END

CVSweb interface <joel.bertrand@systella.fr>