File:  [local] / rpl / lapack / lapack / dtpttr.f
Revision 1.3: download - view: text, annotated - select for diffs - revision graph
Fri Aug 13 21:04:00 2010 UTC (13 years, 9 months ago) by bertrand
Branches: MAIN
CVS tags: rpl-4_0_19, rpl-4_0_18, HEAD
Patches pour OS/2

    1:       SUBROUTINE DTPTTR( UPLO, N, AP, A, LDA, INFO )
    2: *
    3: *  -- LAPACK routine (version 3.2)                                    --
    4: *
    5: *  -- Contributed by Julien Langou of the Univ. of Colorado Denver    --
    6: *  -- November 2008                                                   --
    7: *
    8: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
    9: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
   10: *
   11: *     .. Scalar Arguments ..
   12:       CHARACTER          UPLO
   13:       INTEGER            INFO, N, LDA
   14: *     ..
   15: *     .. Array Arguments ..
   16:       DOUBLE PRECISION   A( LDA, * ), AP( * )
   17: *     ..
   18: *
   19: *  Purpose
   20: *  =======
   21: *
   22: *  DTPTTR copies a triangular matrix A from standard packed format (TP)
   23: *  to standard full format (TR).
   24: *
   25: *  Arguments
   26: *  =========
   27: *
   28: *  UPLO    (input) CHARACTER
   29: *          = 'U':  A is upper triangular.
   30: *          = 'L':  A is lower triangular.
   31: *
   32: *  N       (input) INTEGER
   33: *          The order of the matrix A. N >= 0.
   34: *
   35: *  AP      (input) DOUBLE PRECISION array, dimension ( N*(N+1)/2 ),
   36: *          On entry, the upper or lower triangular matrix A, packed
   37: *          columnwise in a linear array. The j-th column of A is stored
   38: *          in the array AP as follows:
   39: *          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
   40: *          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
   41: *
   42: *  A       (output) DOUBLE PRECISION array, dimension ( LDA, N )
   43: *          On exit, the triangular matrix A.  If UPLO = 'U', the leading
   44: *          N-by-N upper triangular part of A contains the upper
   45: *          triangular part of the matrix A, and the strictly lower
   46: *          triangular part of A is not referenced.  If UPLO = 'L', the
   47: *          leading N-by-N lower triangular part of A contains the lower
   48: *          triangular part of the matrix A, and the strictly upper
   49: *          triangular part of A is not referenced.
   50: *
   51: *  LDA     (input) INTEGER
   52: *          The leading dimension of the array A.  LDA >= max(1,N).
   53: *
   54: *  INFO    (output) INTEGER
   55: *          = 0:  successful exit
   56: *          < 0:  if INFO = -i, the i-th argument had an illegal value
   57: *
   58: *  =====================================================================
   59: *
   60: *     .. Parameters ..
   61: *     ..
   62: *     .. Local Scalars ..
   63:       LOGICAL            LOWER
   64:       INTEGER            I, J, K
   65: *     ..
   66: *     .. External Functions ..
   67:       LOGICAL            LSAME
   68:       EXTERNAL           LSAME
   69: *     ..
   70: *     .. External Subroutines ..
   71:       EXTERNAL           XERBLA
   72: *     ..
   73: *     .. Executable Statements ..
   74: *
   75: *     Test the input parameters.
   76: *
   77:       INFO = 0
   78:       LOWER = LSAME( UPLO, 'L' )
   79:       IF( .NOT.LOWER .AND. .NOT.LSAME( UPLO, 'U' ) ) THEN
   80:          INFO = -1
   81:       ELSE IF( N.LT.0 ) THEN
   82:          INFO = -2
   83:       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
   84:          INFO = -5
   85:       END IF
   86:       IF( INFO.NE.0 ) THEN
   87:          CALL XERBLA( 'DTPTTR', -INFO )
   88:          RETURN
   89:       END IF
   90: *
   91:       IF( LOWER ) THEN
   92:          K = 0
   93:          DO J = 1, N
   94:             DO I = J, N
   95:                K = K + 1
   96:                A( I, J ) = AP( K )
   97:             END DO
   98:          END DO
   99:       ELSE
  100:          K = 0
  101:          DO J = 1, N
  102:             DO I = 1, J
  103:                K = K + 1
  104:                A( I, J ) = AP( K )
  105:             END DO
  106:          END DO
  107:       END IF
  108: *
  109: *
  110:       RETURN
  111: *
  112: *     End of DTPTTR
  113: *
  114:       END

CVSweb interface <joel.bertrand@systella.fr>