1       SUBROUTINE DGET03( N, A, LDA, AINV, LDAINV, WORK, LDWORK, RWORK,
  2      $                   RCOND, RESID )
  3 *
  4 *  -- LAPACK test routine (version 3.1) --
  5 *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
  6 *     November 2006
  7 *
  8 *     .. Scalar Arguments ..
  9       INTEGER            LDA, LDAINV, LDWORK, N
 10       DOUBLE PRECISION   RCOND, RESID
 11 *     ..
 12 *     .. Array Arguments ..
 13       DOUBLE PRECISION   A( LDA, * ), AINV( LDAINV, * ), RWORK( * ),
 14      $                   WORK( LDWORK, * )
 15 *     ..
 16 *
 17 *  Purpose
 18 *  =======
 19 *
 20 *  DGET03 computes the residual for a general matrix times its inverse:
 21 *     norm( I - AINV*A ) / ( N * norm(A) * norm(AINV) * EPS ),
 22 *  where EPS is the machine epsilon.
 23 *
 24 *  Arguments
 25 *  ==========
 26 *
 27 *  N       (input) INTEGER
 28 *          The number of rows and columns of the matrix A.  N >= 0.
 29 *
 30 *  A       (input) DOUBLE PRECISION array, dimension (LDA,N)
 31 *          The original N x N matrix A.
 32 *
 33 *  LDA     (input) INTEGER
 34 *          The leading dimension of the array A.  LDA >= max(1,N).
 35 *
 36 *  AINV    (input) DOUBLE PRECISION array, dimension (LDAINV,N)
 37 *          The inverse of the matrix A.
 38 *
 39 *  LDAINV  (input) INTEGER
 40 *          The leading dimension of the array AINV.  LDAINV >= max(1,N).
 41 *
 42 *  WORK    (workspace) DOUBLE PRECISION array, dimension (LDWORK,N)
 43 *
 44 *  LDWORK  (input) INTEGER
 45 *          The leading dimension of the array WORK.  LDWORK >= max(1,N).
 46 *
 47 *  RWORK   (workspace) DOUBLE PRECISION array, dimension (N)
 48 *
 49 *  RCOND   (output) DOUBLE PRECISION
 50 *          The reciprocal of the condition number of A, computed as
 51 *          ( 1/norm(A) ) / norm(AINV).
 52 *
 53 *  RESID   (output) DOUBLE PRECISION
 54 *          norm(I - AINV*A) / ( N * norm(A) * norm(AINV) * EPS )
 55 *
 56 *  =====================================================================
 57 *
 58 *     .. Parameters ..
 59       DOUBLE PRECISION   ZERO, ONE
 60       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
 61 *     ..
 62 *     .. Local Scalars ..
 63       INTEGER            I
 64       DOUBLE PRECISION   AINVNM, ANORM, EPS
 65 *     ..
 66 *     .. External Functions ..
 67       DOUBLE PRECISION   DLAMCH, DLANGE
 68       EXTERNAL           DLAMCH, DLANGE
 69 *     ..
 70 *     .. External Subroutines ..
 71       EXTERNAL           DGEMM
 72 *     ..
 73 *     .. Intrinsic Functions ..
 74       INTRINSIC          DBLE
 75 *     ..
 76 *     .. Executable Statements ..
 77 *
 78 *     Quick exit if N = 0.
 79 *
 80       IF( N.LE.0 ) THEN
 81          RCOND = ONE
 82          RESID = ZERO
 83          RETURN
 84       END IF
 85 *
 86 *     Exit with RESID = 1/EPS if ANORM = 0 or AINVNM = 0.
 87 *
 88       EPS = DLAMCH( 'Epsilon' )
 89       ANORM = DLANGE( '1', N, N, A, LDA, RWORK )
 90       AINVNM = DLANGE( '1', N, N, AINV, LDAINV, RWORK )
 91       IF( ANORM.LE.ZERO .OR. AINVNM.LE.ZERO ) THEN
 92          RCOND = ZERO
 93          RESID = ONE / EPS
 94          RETURN
 95       END IF
 96       RCOND = ( ONE / ANORM ) / AINVNM
 97 *
 98 *     Compute I - A * AINV
 99 *
100       CALL DGEMM( 'No transpose''No transpose', N, N, N, -ONE, AINV,
101      $            LDAINV, A, LDA, ZERO, WORK, LDWORK )
102       DO 10 I = 1, N
103          WORK( I, I ) = ONE + WORK( I, I )
104    10 CONTINUE
105 *
106 *     Compute norm(I - AINV*A) / (N * norm(A) * norm(AINV) * EPS)
107 *
108       RESID = DLANGE( '1', N, N, WORK, LDWORK, RWORK )
109 *
110       RESID = ( ( RESID*RCOND ) / EPS ) / DBLE( N )
111 *
112       RETURN
113 *
114 *     End of DGET03
115 *
116       END