LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zunt01.f
Go to the documentation of this file.
1 *> \brief \b ZUNT01
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 ZUNT01( ROWCOL, M, N, U, LDU, WORK, LWORK, RWORK,
12 * RESID )
13 *
14 * .. Scalar Arguments ..
15 * CHARACTER ROWCOL
16 * INTEGER LDU, LWORK, M, N
17 * DOUBLE PRECISION RESID
18 * ..
19 * .. Array Arguments ..
20 * DOUBLE PRECISION RWORK( * )
21 * COMPLEX*16 U( LDU, * ), WORK( * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> ZUNT01 checks that the matrix U is unitary by computing the ratio
31 *>
32 *> RESID = norm( I - U*U' ) / ( n * EPS ), if ROWCOL = 'R',
33 *> or
34 *> RESID = norm( I - U'*U ) / ( m * EPS ), if ROWCOL = 'C'.
35 *>
36 *> Alternatively, if there isn't sufficient workspace to form
37 *> I - U*U' or I - U'*U, the ratio is computed as
38 *>
39 *> RESID = abs( I - U*U' ) / ( n * EPS ), if ROWCOL = 'R',
40 *> or
41 *> RESID = abs( I - U'*U ) / ( m * EPS ), if ROWCOL = 'C'.
42 *>
43 *> where EPS is the machine precision. ROWCOL is used only if m = n;
44 *> if m > n, ROWCOL is assumed to be 'C', and if m < n, ROWCOL is
45 *> assumed to be 'R'.
46 *> \endverbatim
47 *
48 * Arguments:
49 * ==========
50 *
51 *> \param[in] ROWCOL
52 *> \verbatim
53 *> ROWCOL is CHARACTER
54 *> Specifies whether the rows or columns of U should be checked
55 *> for orthogonality. Used only if M = N.
56 *> = 'R': Check for orthogonal rows of U
57 *> = 'C': Check for orthogonal columns of U
58 *> \endverbatim
59 *>
60 *> \param[in] M
61 *> \verbatim
62 *> M is INTEGER
63 *> The number of rows of the matrix U.
64 *> \endverbatim
65 *>
66 *> \param[in] N
67 *> \verbatim
68 *> N is INTEGER
69 *> The number of columns of the matrix U.
70 *> \endverbatim
71 *>
72 *> \param[in] U
73 *> \verbatim
74 *> U is COMPLEX*16 array, dimension (LDU,N)
75 *> The unitary matrix U. U is checked for orthogonal columns
76 *> if m > n or if m = n and ROWCOL = 'C'. U is checked for
77 *> orthogonal rows if m < n or if m = n and ROWCOL = 'R'.
78 *> \endverbatim
79 *>
80 *> \param[in] LDU
81 *> \verbatim
82 *> LDU is INTEGER
83 *> The leading dimension of the array U. LDU >= max(1,M).
84 *> \endverbatim
85 *>
86 *> \param[out] WORK
87 *> \verbatim
88 *> WORK is COMPLEX*16 array, dimension (LWORK)
89 *> \endverbatim
90 *>
91 *> \param[in] LWORK
92 *> \verbatim
93 *> LWORK is INTEGER
94 *> The length of the array WORK. For best performance, LWORK
95 *> should be at least N*N if ROWCOL = 'C' or M*M if
96 *> ROWCOL = 'R', but the test will be done even if LWORK is 0.
97 *> \endverbatim
98 *>
99 *> \param[out] RWORK
100 *> \verbatim
101 *> RWORK is DOUBLE PRECISION array, dimension (min(M,N))
102 *> Used only if LWORK is large enough to use the Level 3 BLAS
103 *> code.
104 *> \endverbatim
105 *>
106 *> \param[out] RESID
107 *> \verbatim
108 *> RESID is DOUBLE PRECISION
109 *> RESID = norm( I - U * U' ) / ( n * EPS ), if ROWCOL = 'R', or
110 *> RESID = norm( I - U' * U ) / ( m * EPS ), if ROWCOL = 'C'.
111 *> \endverbatim
112 *
113 * Authors:
114 * ========
115 *
116 *> \author Univ. of Tennessee
117 *> \author Univ. of California Berkeley
118 *> \author Univ. of Colorado Denver
119 *> \author NAG Ltd.
120 *
121 *> \date November 2011
122 *
123 *> \ingroup complex16_eig
124 *
125 * =====================================================================
126  SUBROUTINE zunt01( ROWCOL, M, N, U, LDU, WORK, LWORK, RWORK,
127  $ resid )
128 *
129 * -- LAPACK test routine (version 3.4.0) --
130 * -- LAPACK is a software package provided by Univ. of Tennessee, --
131 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
132 * November 2011
133 *
134 * .. Scalar Arguments ..
135  CHARACTER rowcol
136  INTEGER ldu, lwork, m, n
137  DOUBLE PRECISION resid
138 * ..
139 * .. Array Arguments ..
140  DOUBLE PRECISION rwork( * )
141  COMPLEX*16 u( ldu, * ), work( * )
142 * ..
143 *
144 * =====================================================================
145 *
146 * .. Parameters ..
147  DOUBLE PRECISION zero, one
148  parameter( zero = 0.0d+0, one = 1.0d+0 )
149 * ..
150 * .. Local Scalars ..
151  CHARACTER transu
152  INTEGER i, j, k, ldwork, mnmin
153  DOUBLE PRECISION eps
154  COMPLEX*16 tmp, zdum
155 * ..
156 * .. External Functions ..
157  LOGICAL lsame
158  DOUBLE PRECISION dlamch, zlansy
159  COMPLEX*16 zdotc
160  EXTERNAL lsame, dlamch, zlansy, zdotc
161 * ..
162 * .. External Subroutines ..
163  EXTERNAL zherk, zlaset
164 * ..
165 * .. Intrinsic Functions ..
166  INTRINSIC abs, dble, dcmplx, dimag, max, min
167 * ..
168 * .. Statement Functions ..
169  DOUBLE PRECISION cabs1
170 * ..
171 * .. Statement Function definitions ..
172  cabs1( zdum ) = abs( dble( zdum ) ) + abs( dimag( zdum ) )
173 * ..
174 * .. Executable Statements ..
175 *
176  resid = zero
177 *
178 * Quick return if possible
179 *
180  IF( m.LE.0 .OR. n.LE.0 )
181  $ return
182 *
183  eps = dlamch( 'Precision' )
184  IF( m.LT.n .OR. ( m.EQ.n .AND. lsame( rowcol, 'R' ) ) ) THEN
185  transu = 'N'
186  k = n
187  ELSE
188  transu = 'C'
189  k = m
190  END IF
191  mnmin = min( m, n )
192 *
193  IF( ( mnmin+1 )*mnmin.LE.lwork ) THEN
194  ldwork = mnmin
195  ELSE
196  ldwork = 0
197  END IF
198  IF( ldwork.GT.0 ) THEN
199 *
200 * Compute I - U*U' or I - U'*U.
201 *
202  CALL zlaset( 'Upper', mnmin, mnmin, dcmplx( zero ),
203  $ dcmplx( one ), work, ldwork )
204  CALL zherk( 'Upper', transu, mnmin, k, -one, u, ldu, one, work,
205  $ ldwork )
206 *
207 * Compute norm( I - U*U' ) / ( K * EPS ) .
208 *
209  resid = zlansy( '1', 'Upper', mnmin, work, ldwork, rwork )
210  resid = ( resid / dble( k ) ) / eps
211  ELSE IF( transu.EQ.'C' ) THEN
212 *
213 * Find the maximum element in abs( I - U'*U ) / ( m * EPS )
214 *
215  DO 20 j = 1, n
216  DO 10 i = 1, j
217  IF( i.NE.j ) THEN
218  tmp = zero
219  ELSE
220  tmp = one
221  END IF
222  tmp = tmp - zdotc( m, u( 1, i ), 1, u( 1, j ), 1 )
223  resid = max( resid, cabs1( tmp ) )
224  10 continue
225  20 continue
226  resid = ( resid / dble( m ) ) / eps
227  ELSE
228 *
229 * Find the maximum element in abs( I - U*U' ) / ( n * EPS )
230 *
231  DO 40 j = 1, m
232  DO 30 i = 1, j
233  IF( i.NE.j ) THEN
234  tmp = zero
235  ELSE
236  tmp = one
237  END IF
238  tmp = tmp - zdotc( n, u( j, 1 ), ldu, u( i, 1 ), ldu )
239  resid = max( resid, cabs1( tmp ) )
240  30 continue
241  40 continue
242  resid = ( resid / dble( n ) ) / eps
243  END IF
244  return
245 *
246 * End of ZUNT01
247 *
248  END