1       SUBROUTINE ZTPT01( UPLO, DIAG, N, AP, AINVP, RCOND, RWORK, RESID )
  2 *
  3 *  -- LAPACK test routine (version 3.1) --
  4 *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
  5 *     November 2006
  6 *
  7 *     .. Scalar Arguments ..
  8       CHARACTER          DIAG, UPLO
  9       INTEGER            N
 10       DOUBLE PRECISION   RCOND, RESID
 11 *     ..
 12 *     .. Array Arguments ..
 13       DOUBLE PRECISION   RWORK( * )
 14       COMPLEX*16         AINVP( * ), AP( * )
 15 *     ..
 16 *
 17 *  Purpose
 18 *  =======
 19 *
 20 *  ZTPT01 computes the residual for a triangular matrix A times its
 21 *  inverse when A is stored in packed format:
 22 *     RESID = norm(A*AINV - I) / ( N * norm(A) * norm(AINV) * EPS ),
 23 *  where EPS is the machine epsilon.
 24 *
 25 *  Arguments
 26 *  ==========
 27 *
 28 *  UPLO    (input) CHARACTER*1
 29 *          Specifies whether the matrix A is upper or lower triangular.
 30 *          = 'U':  Upper triangular
 31 *          = 'L':  Lower triangular
 32 *
 33 *  DIAG    (input) CHARACTER*1
 34 *          Specifies whether or not the matrix A is unit triangular.
 35 *          = 'N':  Non-unit triangular
 36 *          = 'U':  Unit triangular
 37 *
 38 *  N       (input) INTEGER
 39 *          The order of the matrix A.  N >= 0.
 40 *
 41 *  AP      (input) COMPLEX*16 array, dimension (N*(N+1)/2)
 42 *          The original upper or lower triangular matrix A, packed
 43 *          columnwise in a linear array.  The j-th column of A is stored
 44 *          in the array AP as follows:
 45 *          if UPLO = 'U', AP((j-1)*j/2 + i) = A(i,j) for 1<=i<=j;
 46 *          if UPLO = 'L',
 47 *             AP((j-1)*(n-j) + j*(j+1)/2 + i-j) = A(i,j) for j<=i<=n.
 48 *
 49 *  AINVP   (input) COMPLEX*16 array, dimension (N*(N+1)/2)
 50 *          On entry, the (triangular) inverse of the matrix A, packed
 51 *          columnwise in a linear array as in AP.
 52 *          On exit, the contents of AINVP are destroyed.
 53 *
 54 *  RCOND   (output) DOUBLE PRECISION
 55 *          The reciprocal condition number of A, computed as
 56 *          1/(norm(A) * norm(AINV)).
 57 *
 58 *  RWORK   (workspace) DOUBLE PRECISION array, dimension (N)
 59 *
 60 *  RESID   (output) DOUBLE PRECISION
 61 *          norm(A*AINV - I) / ( N * norm(A) * norm(AINV) * EPS )
 62 *
 63 *  =====================================================================
 64 *
 65 *     .. Parameters ..
 66       DOUBLE PRECISION   ZERO, ONE
 67       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
 68 *     ..
 69 *     .. Local Scalars ..
 70       LOGICAL            UNITD
 71       INTEGER            J, JC
 72       DOUBLE PRECISION   AINVNM, ANORM, EPS
 73 *     ..
 74 *     .. External Functions ..
 75       LOGICAL            LSAME
 76       DOUBLE PRECISION   DLAMCH, ZLANTP
 77       EXTERNAL           LSAME, DLAMCH, ZLANTP
 78 *     ..
 79 *     .. External Subroutines ..
 80       EXTERNAL           ZTPMV
 81 *     ..
 82 *     .. Intrinsic Functions ..
 83       INTRINSIC          DBLE
 84 *     ..
 85 *     .. Executable Statements ..
 86 *
 87 *     Quick exit if N = 0.
 88 *
 89       IF( N.LE.0 ) THEN
 90          RCOND = ONE
 91          RESID = ZERO
 92          RETURN
 93       END IF
 94 *
 95 *     Exit with RESID = 1/EPS if ANORM = 0 or AINVNM = 0.
 96 *
 97       EPS = DLAMCH( 'Epsilon' )
 98       ANORM = ZLANTP( '1', UPLO, DIAG, N, AP, RWORK )
 99       AINVNM = ZLANTP( '1', UPLO, DIAG, N, AINVP, RWORK )
100       IF( ANORM.LE.ZERO .OR. AINVNM.LE.ZERO ) THEN
101          RCOND = ZERO
102          RESID = ONE / EPS
103          RETURN
104       END IF
105       RCOND = ( ONE / ANORM ) / AINVNM
106 *
107 *     Compute A * AINV, overwriting AINV.
108 *
109       UNITD = LSAME( DIAG, 'U' )
110       IF( LSAME( UPLO, 'U' ) ) THEN
111          JC = 1
112          DO 10 J = 1, N
113             IF( UNITD )
114      $         AINVP( JC+J-1 ) = ONE
115 *
116 *           Form the j-th column of A*AINV.
117 *
118             CALL ZTPMV( 'Upper''No transpose', DIAG, J, AP,
119      $                  AINVP( JC ), 1 )
120 *
121 *           Subtract 1 from the diagonal to form A*AINV - I.
122 *
123             AINVP( JC+J-1 ) = AINVP( JC+J-1 ) - ONE
124             JC = JC + J
125    10    CONTINUE
126       ELSE
127          JC = 1
128          DO 20 J = 1, N
129             IF( UNITD )
130      $         AINVP( JC ) = ONE
131 *
132 *           Form the j-th column of A*AINV.
133 *
134             CALL ZTPMV( 'Lower''No transpose', DIAG, N-J+1, AP( JC ),
135      $                  AINVP( JC ), 1 )
136 *
137 *           Subtract 1 from the diagonal to form A*AINV - I.
138 *
139             AINVP( JC ) = AINVP( JC ) - ONE
140             JC = JC + N - J + 1
141    20    CONTINUE
142       END IF
143 *
144 *     Compute norm(A*AINV - I) / (N * norm(A) * norm(AINV) * EPS)
145 *
146       RESID = ZLANTP( '1', UPLO, 'Non-unit', N, AINVP, RWORK )
147 *
148       RESID = ( ( RESID*RCOND ) / DBLE( N ) ) / EPS
149 *
150       RETURN
151 *
152 *     End of ZTPT01
153 *
154       END