LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zget03()

subroutine zget03 ( integer n,
complex*16, dimension( lda, * ) a,
integer lda,
complex*16, dimension( ldainv, * ) ainv,
integer ldainv,
complex*16, dimension( ldwork, * ) work,
integer ldwork,
double precision, dimension( * ) rwork,
double precision rcond,
double precision resid )

ZGET03

Purpose:
!>
!> ZGET03 computes the residual for a general matrix times its inverse:
!>    norm( I - AINV*A ) / ( N * norm(A) * norm(AINV) * EPS ),
!> where EPS is the machine epsilon.
!> 
Parameters
[in]N
!>          N is INTEGER
!>          The number of rows and columns of the matrix A.  N >= 0.
!> 
[in]A
!>          A is COMPLEX*16 array, dimension (LDA,N)
!>          The original N x N matrix A.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A.  LDA >= max(1,N).
!> 
[in]AINV
!>          AINV is COMPLEX*16 array, dimension (LDAINV,N)
!>          The inverse of the matrix A.
!> 
[in]LDAINV
!>          LDAINV is INTEGER
!>          The leading dimension of the array AINV.  LDAINV >= max(1,N).
!> 
[out]WORK
!>          WORK is COMPLEX*16 array, dimension (LDWORK,N)
!> 
[in]LDWORK
!>          LDWORK is INTEGER
!>          The leading dimension of the array WORK.  LDWORK >= max(1,N).
!> 
[out]RWORK
!>          RWORK is DOUBLE PRECISION array, dimension (N)
!> 
[out]RCOND
!>          RCOND is DOUBLE PRECISION
!>          The reciprocal of the condition number of A, computed as
!>          ( 1/norm(A) ) / norm(AINV).
!> 
[out]RESID
!>          RESID is DOUBLE PRECISION
!>          norm(I - AINV*A) / ( N * norm(A) * norm(AINV) * EPS )
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 108 of file zget03.f.

110*
111* -- LAPACK test routine --
112* -- LAPACK is a software package provided by Univ. of Tennessee, --
113* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
114*
115* .. Scalar Arguments ..
116 INTEGER LDA, LDAINV, LDWORK, N
117 DOUBLE PRECISION RCOND, RESID
118* ..
119* .. Array Arguments ..
120 DOUBLE PRECISION RWORK( * )
121 COMPLEX*16 A( LDA, * ), AINV( LDAINV, * ),
122 $ WORK( LDWORK, * )
123* ..
124*
125* =====================================================================
126*
127* .. Parameters ..
128 DOUBLE PRECISION ZERO, ONE
129 parameter( zero = 0.0d+0, one = 1.0d+0 )
130 COMPLEX*16 CZERO, CONE
131 parameter( czero = ( 0.0d+0, 0.0d+0 ),
132 $ cone = ( 1.0d+0, 0.0d+0 ) )
133* ..
134* .. Local Scalars ..
135 INTEGER I
136 DOUBLE PRECISION AINVNM, ANORM, EPS
137* ..
138* .. External Functions ..
139 DOUBLE PRECISION DLAMCH, ZLANGE
140 EXTERNAL dlamch, zlange
141* ..
142* .. External Subroutines ..
143 EXTERNAL zgemm
144* ..
145* .. Intrinsic Functions ..
146 INTRINSIC dble
147* ..
148* .. Executable Statements ..
149*
150* Quick exit if N = 0.
151*
152 IF( n.LE.0 ) THEN
153 rcond = one
154 resid = zero
155 RETURN
156 END IF
157*
158* Exit with RESID = 1/EPS if ANORM = 0 or AINVNM = 0.
159*
160 eps = dlamch( 'Epsilon' )
161 anorm = zlange( '1', n, n, a, lda, rwork )
162 ainvnm = zlange( '1', n, n, ainv, ldainv, rwork )
163 IF( anorm.LE.zero .OR. ainvnm.LE.zero ) THEN
164 rcond = zero
165 resid = one / eps
166 RETURN
167 END IF
168 rcond = ( one / anorm ) / ainvnm
169*
170* Compute I - A * AINV
171*
172 CALL zgemm( 'No transpose', 'No transpose', n, n, n, -cone, ainv,
173 $ ldainv, a, lda, czero, work, ldwork )
174 DO 10 i = 1, n
175 work( i, i ) = cone + work( i, i )
176 10 CONTINUE
177*
178* Compute norm(I - AINV*A) / (N * norm(A) * norm(AINV) * EPS)
179*
180 resid = zlange( '1', n, n, work, ldwork, rwork )
181*
182 resid = ( ( resid*rcond ) / eps ) / dble( n )
183*
184 RETURN
185*
186* End of ZGET03
187*
subroutine zgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
ZGEMM
Definition zgemm.f:188
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
double precision function zlange(norm, m, n, a, lda, work)
ZLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition zlange.f:113
Here is the call graph for this function:
Here is the caller graph for this function: