001:       SUBROUTINE ZTRTTP( UPLO, N, A, LDA, AP, INFO )
002: *
003: *  -- LAPACK routine (version 3.2) --
004: *
005: *  -- Contributed by Fred Gustavson of the IBM Watson Research Center --
006: *  --            and Julien Langou of the Univ. of Colorado Denver    --
007: *  -- November 2008                                                   --
008: *
009: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
010: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
011: *
012: *     .. Scalar Arguments ..
013:       CHARACTER          UPLO
014:       INTEGER            INFO, N, LDA
015: *     ..
016: *     .. Array Arguments ..
017:       COMPLEX*16         A( LDA, * ), AP( * )
018: *     ..
019: *
020: *  Purpose
021: *  =======
022: *
023: *  ZTRTTP copies a triangular matrix A from full format (TR) to standard
024: *  packed format (TP).
025: *
026: *  Arguments
027: *  =========
028: *
029: *  UPLO    (input) CHARACTER
030: *          = 'U':  A is upper triangular;
031: *          = 'L':  A is lower triangular.
032: *
033: *  N       (input) INTEGER
034: *          The order of the matrices AP and A.  N >= 0.
035: *
036: *  A       (input) COMPLEX*16 array, dimension (LDA,N)
037: *          On entry, the triangular matrix A.  If UPLO = 'U', the leading
038: *          N-by-N upper triangular part of A contains the upper
039: *          triangular part of the matrix A, and the strictly lower
040: *          triangular part of A is not referenced.  If UPLO = 'L', the
041: *          leading N-by-N lower triangular part of A contains the lower
042: *          triangular part of the matrix A, and the strictly upper
043: *          triangular part of A is not referenced.
044: *
045: *  LDA     (input) INTEGER
046: *          The leading dimension of the array A.  LDA >= max(1,N).
047: *
048: *  AP      (output) COMPLEX*16 array, dimension ( N*(N+1)/2 ),
049: *          On exit, the upper or lower triangular matrix A, packed
050: *          columnwise in a linear array. The j-th column of A is stored
051: *          in the array AP as follows:
052: *          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
053: *          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
054: *
055: *  INFO    (output) INTEGER
056: *          = 0:  successful exit
057: *          < 0:  if INFO = -i, the i-th argument had an illegal value
058: *
059: *  =====================================================================
060: *
061: *     .. Parameters ..
062: *     ..
063: *     .. Local Scalars ..
064:       LOGICAL            LOWER
065:       INTEGER            I, J, K
066: *     ..
067: *     .. External Functions ..
068:       LOGICAL            LSAME
069:       EXTERNAL           LSAME
070: *     ..
071: *     .. External Subroutines ..
072:       EXTERNAL           XERBLA
073: *     ..
074: *     .. Executable Statements ..
075: *
076: *     Test the input parameters.
077: *
078:       INFO = 0
079:       LOWER = LSAME( UPLO, 'L' )
080:       IF( .NOT.LOWER .AND. .NOT.LSAME( UPLO, 'U' ) ) THEN
081:          INFO = -1
082:       ELSE IF( N.LT.0 ) THEN
083:          INFO = -2
084:       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
085:          INFO = -4
086:       END IF
087:       IF( INFO.NE.0 ) THEN
088:          CALL XERBLA( 'ZTRTTP', -INFO )
089:          RETURN
090:       END IF
091: *
092:       IF( LOWER ) THEN
093:          K = 0
094:          DO J = 1, N
095:             DO I = J, N
096:                K = K + 1
097:                AP( K ) = A( I, J )
098:             END DO
099:          END DO
100:       ELSE
101:          K = 0
102:          DO J = 1, N
103:             DO I = 1, J
104:                K = K + 1
105:                AP( K ) = A( I, J )
106:             END DO
107:          END DO
108:       END IF
109: *
110: *
111:       RETURN
112: *
113: *     End of ZTRTTP
114: *
115:       END
116: