LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
cget03.f
Go to the documentation of this file.
1 *> \brief \b CGET03
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 CGET03( N, A, LDA, AINV, LDAINV, WORK, LDWORK, RWORK,
12 * RCOND, RESID )
13 *
14 * .. Scalar Arguments ..
15 * INTEGER LDA, LDAINV, LDWORK, N
16 * REAL RCOND, RESID
17 * ..
18 * .. Array Arguments ..
19 * REAL RWORK( * )
20 * COMPLEX A( LDA, * ), AINV( LDAINV, * ),
21 * $ WORK( LDWORK, * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> CGET03 computes the residual for a general matrix times its inverse:
31 *> norm( I - AINV*A ) / ( N * norm(A) * norm(AINV) * EPS ),
32 *> where EPS is the machine epsilon.
33 *> \endverbatim
34 *
35 * Arguments:
36 * ==========
37 *
38 *> \param[in] N
39 *> \verbatim
40 *> N is INTEGER
41 *> The number of rows and columns of the matrix A. N >= 0.
42 *> \endverbatim
43 *>
44 *> \param[in] A
45 *> \verbatim
46 *> A is COMPLEX array, dimension (LDA,N)
47 *> The original N x N matrix A.
48 *> \endverbatim
49 *>
50 *> \param[in] LDA
51 *> \verbatim
52 *> LDA is INTEGER
53 *> The leading dimension of the array A. LDA >= max(1,N).
54 *> \endverbatim
55 *>
56 *> \param[in] AINV
57 *> \verbatim
58 *> AINV is COMPLEX array, dimension (LDAINV,N)
59 *> The inverse of the matrix A.
60 *> \endverbatim
61 *>
62 *> \param[in] LDAINV
63 *> \verbatim
64 *> LDAINV is INTEGER
65 *> The leading dimension of the array AINV. LDAINV >= max(1,N).
66 *> \endverbatim
67 *>
68 *> \param[out] WORK
69 *> \verbatim
70 *> WORK is COMPLEX array, dimension (LDWORK,N)
71 *> \endverbatim
72 *>
73 *> \param[in] LDWORK
74 *> \verbatim
75 *> LDWORK is INTEGER
76 *> The leading dimension of the array WORK. LDWORK >= max(1,N).
77 *> \endverbatim
78 *>
79 *> \param[out] RWORK
80 *> \verbatim
81 *> RWORK is REAL array, dimension (N)
82 *> \endverbatim
83 *>
84 *> \param[out] RCOND
85 *> \verbatim
86 *> RCOND is REAL
87 *> The reciprocal of the condition number of A, computed as
88 *> ( 1/norm(A) ) / norm(AINV).
89 *> \endverbatim
90 *>
91 *> \param[out] RESID
92 *> \verbatim
93 *> RESID is REAL
94 *> norm(I - AINV*A) / ( N * norm(A) * norm(AINV) * EPS )
95 *> \endverbatim
96 *
97 * Authors:
98 * ========
99 *
100 *> \author Univ. of Tennessee
101 *> \author Univ. of California Berkeley
102 *> \author Univ. of Colorado Denver
103 *> \author NAG Ltd.
104 *
105 *> \date November 2011
106 *
107 *> \ingroup complex_lin
108 *
109 * =====================================================================
110  SUBROUTINE cget03( N, A, LDA, AINV, LDAINV, WORK, LDWORK, RWORK,
111  $ rcond, resid )
112 *
113 * -- LAPACK test routine (version 3.4.0) --
114 * -- LAPACK is a software package provided by Univ. of Tennessee, --
115 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
116 * November 2011
117 *
118 * .. Scalar Arguments ..
119  INTEGER lda, ldainv, ldwork, n
120  REAL rcond, resid
121 * ..
122 * .. Array Arguments ..
123  REAL rwork( * )
124  COMPLEX a( lda, * ), ainv( ldainv, * ),
125  $ work( ldwork, * )
126 * ..
127 *
128 * =====================================================================
129 *
130 * .. Parameters ..
131  REAL zero, one
132  parameter( zero = 0.0e+0, one = 1.0e+0 )
133  COMPLEX czero, cone
134  parameter( czero = ( 0.0e+0, 0.0e+0 ),
135  $ cone = ( 1.0e+0, 0.0e+0 ) )
136 * ..
137 * .. Local Scalars ..
138  INTEGER i
139  REAL ainvnm, anorm, eps
140 * ..
141 * .. External Functions ..
142  REAL clange, slamch
143  EXTERNAL clange, slamch
144 * ..
145 * .. External Subroutines ..
146  EXTERNAL cgemm
147 * ..
148 * .. Intrinsic Functions ..
149  INTRINSIC real
150 * ..
151 * .. Executable Statements ..
152 *
153 * Quick exit if N = 0.
154 *
155  IF( n.LE.0 ) THEN
156  rcond = one
157  resid = zero
158  return
159  END IF
160 *
161 * Exit with RESID = 1/EPS if ANORM = 0 or AINVNM = 0.
162 *
163  eps = slamch( 'Epsilon' )
164  anorm = clange( '1', n, n, a, lda, rwork )
165  ainvnm = clange( '1', n, n, ainv, ldainv, rwork )
166  IF( anorm.LE.zero .OR. ainvnm.LE.zero ) THEN
167  rcond = zero
168  resid = one / eps
169  return
170  END IF
171  rcond = ( one/anorm ) / ainvnm
172 *
173 * Compute I - A * AINV
174 *
175  CALL cgemm( 'No transpose', 'No transpose', n, n, n, -cone,
176  $ ainv, ldainv, a, lda, czero, work, ldwork )
177  DO 10 i = 1, n
178  work( i, i ) = cone + work( i, i )
179  10 continue
180 *
181 * Compute norm(I - AINV*A) / (N * norm(A) * norm(AINV) * EPS)
182 *
183  resid = clange( '1', n, n, work, ldwork, rwork )
184 *
185  resid = ( ( resid*rcond )/eps ) / REAL( n )
186 *
187  return
188 *
189 * End of CGET03
190 *
191  END