LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zget10.f
Go to the documentation of this file.
1*> \brief \b ZGET10
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* SUBROUTINE ZGET10( M, N, A, LDA, B, LDB, WORK, RWORK, RESULT )
12*
13* .. Scalar Arguments ..
14* INTEGER LDA, LDB, M, N
15* DOUBLE PRECISION RESULT
16* ..
17* .. Array Arguments ..
18* DOUBLE PRECISION RWORK( * )
19* COMPLEX*16 A( LDA, * ), B( LDB, * ), WORK( * )
20* ..
21*
22*
23*> \par Purpose:
24* =============
25*>
26*> \verbatim
27*>
28*> ZGET10 compares two matrices A and B and computes the ratio
29*> RESULT = norm( A - B ) / ( norm(A) * M * EPS )
30*> \endverbatim
31*
32* Arguments:
33* ==========
34*
35*> \param[in] M
36*> \verbatim
37*> M is INTEGER
38*> The number of rows of the matrices A and B.
39*> \endverbatim
40*>
41*> \param[in] N
42*> \verbatim
43*> N is INTEGER
44*> The number of columns of the matrices A and B.
45*> \endverbatim
46*>
47*> \param[in] A
48*> \verbatim
49*> A is COMPLEX*16 array, dimension (LDA,N)
50*> The m by n matrix A.
51*> \endverbatim
52*>
53*> \param[in] LDA
54*> \verbatim
55*> LDA is INTEGER
56*> The leading dimension of the array A. LDA >= max(1,M).
57*> \endverbatim
58*>
59*> \param[in] B
60*> \verbatim
61*> B is COMPLEX*16 array, dimension (LDB,N)
62*> The m by n matrix B.
63*> \endverbatim
64*>
65*> \param[in] LDB
66*> \verbatim
67*> LDB is INTEGER
68*> The leading dimension of the array B. LDB >= max(1,M).
69*> \endverbatim
70*>
71*> \param[out] WORK
72*> \verbatim
73*> WORK is COMPLEX*16 array, dimension (M)
74*> \endverbatim
75*>
76*> \param[out] RWORK
77*> \verbatim
78*> RWORK is COMPLEX*16 array, dimension (M)
79*> \endverbatim
80*>
81*> \param[out] RESULT
82*> \verbatim
83*> RESULT is DOUBLE PRECISION
84*> RESULT = norm( A - B ) / ( norm(A) * M * EPS )
85*> \endverbatim
86*
87* Authors:
88* ========
89*
90*> \author Univ. of Tennessee
91*> \author Univ. of California Berkeley
92*> \author Univ. of Colorado Denver
93*> \author NAG Ltd.
94*
95*> \ingroup complex16_eig
96*
97* =====================================================================
98 SUBROUTINE zget10( M, N, A, LDA, B, LDB, WORK, RWORK, RESULT )
99*
100* -- LAPACK test routine --
101* -- LAPACK is a software package provided by Univ. of Tennessee, --
102* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
103*
104* .. Scalar Arguments ..
105 INTEGER LDA, LDB, M, N
106 DOUBLE PRECISION RESULT
107* ..
108* .. Array Arguments ..
109 DOUBLE PRECISION RWORK( * )
110 COMPLEX*16 A( LDA, * ), B( LDB, * ), WORK( * )
111* ..
112*
113* =====================================================================
114*
115* .. Parameters ..
116 DOUBLE PRECISION ONE, ZERO
117 parameter( one = 1.0d+0, zero = 0.0d+0 )
118* ..
119* .. Local Scalars ..
120 INTEGER J
121 DOUBLE PRECISION ANORM, EPS, UNFL, WNORM
122* ..
123* .. External Functions ..
124 DOUBLE PRECISION DLAMCH, DZASUM, ZLANGE
125 EXTERNAL dlamch, dzasum, zlange
126* ..
127* .. External Subroutines ..
128 EXTERNAL zaxpy, zcopy
129* ..
130* .. Intrinsic Functions ..
131 INTRINSIC dble, dcmplx, max, min
132* ..
133* .. Executable Statements ..
134*
135* Quick return if possible
136*
137 IF( m.LE.0 .OR. n.LE.0 ) THEN
138 result = zero
139 RETURN
140 END IF
141*
142 unfl = dlamch( 'Safe minimum' )
143 eps = dlamch( 'Precision' )
144*
145 wnorm = zero
146 DO 10 j = 1, n
147 CALL zcopy( m, a( 1, j ), 1, work, 1 )
148 CALL zaxpy( m, dcmplx( -one ), b( 1, j ), 1, work, 1 )
149 wnorm = max( wnorm, dzasum( n, work, 1 ) )
150 10 CONTINUE
151*
152 anorm = max( zlange( '1', m, n, a, lda, rwork ), unfl )
153*
154 IF( anorm.GT.wnorm ) THEN
155 result = ( wnorm / anorm ) / ( m*eps )
156 ELSE
157 IF( anorm.LT.one ) THEN
158 result = ( min( wnorm, m*anorm ) / anorm ) / ( m*eps )
159 ELSE
160 result = min( wnorm / anorm, dble( m ) ) / ( m*eps )
161 END IF
162 END IF
163*
164 RETURN
165*
166* End of ZGET10
167*
168 END
subroutine zaxpy(n, za, zx, incx, zy, incy)
ZAXPY
Definition zaxpy.f:88
subroutine zcopy(n, zx, incx, zy, incy)
ZCOPY
Definition zcopy.f:81
subroutine zget10(m, n, a, lda, b, ldb, work, rwork, result)
ZGET10
Definition zget10.f:99