LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zget01.f
Go to the documentation of this file.
1 *> \brief \b ZGET01
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 ZGET01( M, N, A, LDA, AFAC, LDAFAC, IPIV, RWORK,
12 * RESID )
13 *
14 * .. Scalar Arguments ..
15 * INTEGER LDA, LDAFAC, M, N
16 * DOUBLE PRECISION RESID
17 * ..
18 * .. Array Arguments ..
19 * INTEGER IPIV( * )
20 * DOUBLE PRECISION RWORK( * )
21 * COMPLEX*16 A( LDA, * ), AFAC( LDAFAC, * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> ZGET01 reconstructs a matrix A from its L*U factorization and
31 *> computes the residual
32 *> norm(L*U - A) / ( N * norm(A) * EPS ),
33 *> where EPS is the machine epsilon.
34 *> \endverbatim
35 *
36 * Arguments:
37 * ==========
38 *
39 *> \param[in] M
40 *> \verbatim
41 *> M is INTEGER
42 *> The number of rows of the matrix A. M >= 0.
43 *> \endverbatim
44 *>
45 *> \param[in] N
46 *> \verbatim
47 *> N is INTEGER
48 *> The number of columns of the matrix A. N >= 0.
49 *> \endverbatim
50 *>
51 *> \param[in] A
52 *> \verbatim
53 *> A is COMPLEX*16 array, dimension (LDA,N)
54 *> The original M x N matrix A.
55 *> \endverbatim
56 *>
57 *> \param[in] LDA
58 *> \verbatim
59 *> LDA is INTEGER
60 *> The leading dimension of the array A. LDA >= max(1,M).
61 *> \endverbatim
62 *>
63 *> \param[in,out] AFAC
64 *> \verbatim
65 *> AFAC is COMPLEX*16 array, dimension (LDAFAC,N)
66 *> The factored form of the matrix A. AFAC contains the factors
67 *> L and U from the L*U factorization as computed by ZGETRF.
68 *> Overwritten with the reconstructed matrix, and then with the
69 *> difference L*U - A.
70 *> \endverbatim
71 *>
72 *> \param[in] LDAFAC
73 *> \verbatim
74 *> LDAFAC is INTEGER
75 *> The leading dimension of the array AFAC. LDAFAC >= max(1,M).
76 *> \endverbatim
77 *>
78 *> \param[in] IPIV
79 *> \verbatim
80 *> IPIV is INTEGER array, dimension (N)
81 *> The pivot indices from ZGETRF.
82 *> \endverbatim
83 *>
84 *> \param[out] RWORK
85 *> \verbatim
86 *> RWORK is DOUBLE PRECISION array, dimension (M)
87 *> \endverbatim
88 *>
89 *> \param[out] RESID
90 *> \verbatim
91 *> RESID is DOUBLE PRECISION
92 *> norm(L*U - A) / ( N * norm(A) * EPS )
93 *> \endverbatim
94 *
95 * Authors:
96 * ========
97 *
98 *> \author Univ. of Tennessee
99 *> \author Univ. of California Berkeley
100 *> \author Univ. of Colorado Denver
101 *> \author NAG Ltd.
102 *
103 *> \date November 2011
104 *
105 *> \ingroup complex16_lin
106 *
107 * =====================================================================
108  SUBROUTINE zget01( M, N, A, LDA, AFAC, LDAFAC, IPIV, RWORK,
109  $ resid )
110 *
111 * -- LAPACK test routine (version 3.4.0) --
112 * -- LAPACK is a software package provided by Univ. of Tennessee, --
113 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
114 * November 2011
115 *
116 * .. Scalar Arguments ..
117  INTEGER lda, ldafac, m, n
118  DOUBLE PRECISION resid
119 * ..
120 * .. Array Arguments ..
121  INTEGER ipiv( * )
122  DOUBLE PRECISION rwork( * )
123  COMPLEX*16 a( lda, * ), afac( ldafac, * )
124 * ..
125 *
126 * =====================================================================
127 *
128 * .. Parameters ..
129  DOUBLE PRECISION zero, one
130  parameter( zero = 0.0d+0, one = 1.0d+0 )
131  COMPLEX*16 cone
132  parameter( cone = ( 1.0d+0, 0.0d+0 ) )
133 * ..
134 * .. Local Scalars ..
135  INTEGER i, j, k
136  DOUBLE PRECISION anorm, eps
137  COMPLEX*16 t
138 * ..
139 * .. External Functions ..
140  DOUBLE PRECISION dlamch, zlange
141  COMPLEX*16 zdotu
142  EXTERNAL dlamch, zlange, zdotu
143 * ..
144 * .. External Subroutines ..
145  EXTERNAL zgemv, zlaswp, zscal, ztrmv
146 * ..
147 * .. Intrinsic Functions ..
148  INTRINSIC dble, min
149 * ..
150 * .. Executable Statements ..
151 *
152 * Quick exit if M = 0 or N = 0.
153 *
154  IF( m.LE.0 .OR. n.LE.0 ) THEN
155  resid = zero
156  return
157  END IF
158 *
159 * Determine EPS and the norm of A.
160 *
161  eps = dlamch( 'Epsilon' )
162  anorm = zlange( '1', m, n, a, lda, rwork )
163 *
164 * Compute the product L*U and overwrite AFAC with the result.
165 * A column at a time of the product is obtained, starting with
166 * column N.
167 *
168  DO 10 k = n, 1, -1
169  IF( k.GT.m ) THEN
170  CALL ztrmv( 'Lower', 'No transpose', 'Unit', m, afac,
171  $ ldafac, afac( 1, k ), 1 )
172  ELSE
173 *
174 * Compute elements (K+1:M,K)
175 *
176  t = afac( k, k )
177  IF( k+1.LE.m ) THEN
178  CALL zscal( m-k, t, afac( k+1, k ), 1 )
179  CALL zgemv( 'No transpose', m-k, k-1, cone,
180  $ afac( k+1, 1 ), ldafac, afac( 1, k ), 1,
181  $ cone, afac( k+1, k ), 1 )
182  END IF
183 *
184 * Compute the (K,K) element
185 *
186  afac( k, k ) = t + zdotu( k-1, afac( k, 1 ), ldafac,
187  $ afac( 1, k ), 1 )
188 *
189 * Compute elements (1:K-1,K)
190 *
191  CALL ztrmv( 'Lower', 'No transpose', 'Unit', k-1, afac,
192  $ ldafac, afac( 1, k ), 1 )
193  END IF
194  10 continue
195  CALL zlaswp( n, afac, ldafac, 1, min( m, n ), ipiv, -1 )
196 *
197 * Compute the difference L*U - A and store in AFAC.
198 *
199  DO 30 j = 1, n
200  DO 20 i = 1, m
201  afac( i, j ) = afac( i, j ) - a( i, j )
202  20 continue
203  30 continue
204 *
205 * Compute norm( L*U - A ) / ( N * norm(A) * EPS )
206 *
207  resid = zlange( '1', m, n, afac, ldafac, rwork )
208 *
209  IF( anorm.LE.zero ) THEN
210  IF( resid.NE.zero )
211  $ resid = one / eps
212  ELSE
213  resid = ( ( resid / dble( n ) ) / anorm ) / eps
214  END IF
215 *
216  return
217 *
218 * End of ZGET01
219 *
220  END