LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cunt03.f
Go to the documentation of this file.
1 *> \brief \b CUNT03
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 CUNT03( RC, MU, MV, N, K, U, LDU, V, LDV, WORK, LWORK,
12 * RWORK, RESULT, INFO )
13 *
14 * .. Scalar Arguments ..
15 * CHARACTER*( * ) RC
16 * INTEGER INFO, K, LDU, LDV, LWORK, MU, MV, N
17 * REAL RESULT
18 * ..
19 * .. Array Arguments ..
20 * REAL RWORK( * )
21 * COMPLEX U( LDU, * ), V( LDV, * ), WORK( * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> CUNT03 compares two unitary matrices U and V to see if their
31 *> corresponding rows or columns span the same spaces. The rows are
32 *> checked if RC = 'R', and the columns are checked if RC = 'C'.
33 *>
34 *> RESULT is the maximum of
35 *>
36 *> | V*V' - I | / ( MV ulp ), if RC = 'R', or
37 *>
38 *> | V'*V - I | / ( MV ulp ), if RC = 'C',
39 *>
40 *> and the maximum over rows (or columns) 1 to K of
41 *>
42 *> | U(i) - S*V(i) |/ ( N ulp )
43 *>
44 *> where abs(S) = 1 (chosen to minimize the expression), U(i) is the
45 *> i-th row (column) of U, and V(i) is the i-th row (column) of V.
46 *> \endverbatim
47 *
48 * Arguments:
49 * ==========
50 *
51 *> \param[in] RC
52 *> \verbatim
53 *> RC is CHARACTER*1
54 *> If RC = 'R' the rows of U and V are to be compared.
55 *> If RC = 'C' the columns of U and V are to be compared.
56 *> \endverbatim
57 *>
58 *> \param[in] MU
59 *> \verbatim
60 *> MU is INTEGER
61 *> The number of rows of U if RC = 'R', and the number of
62 *> columns if RC = 'C'. If MU = 0 CUNT03 does nothing.
63 *> MU must be at least zero.
64 *> \endverbatim
65 *>
66 *> \param[in] MV
67 *> \verbatim
68 *> MV is INTEGER
69 *> The number of rows of V if RC = 'R', and the number of
70 *> columns if RC = 'C'. If MV = 0 CUNT03 does nothing.
71 *> MV must be at least zero.
72 *> \endverbatim
73 *>
74 *> \param[in] N
75 *> \verbatim
76 *> N is INTEGER
77 *> If RC = 'R', the number of columns in the matrices U and V,
78 *> and if RC = 'C', the number of rows in U and V. If N = 0
79 *> CUNT03 does nothing. N must be at least zero.
80 *> \endverbatim
81 *>
82 *> \param[in] K
83 *> \verbatim
84 *> K is INTEGER
85 *> The number of rows or columns of U and V to compare.
86 *> 0 <= K <= max(MU,MV).
87 *> \endverbatim
88 *>
89 *> \param[in] U
90 *> \verbatim
91 *> U is COMPLEX array, dimension (LDU,N)
92 *> The first matrix to compare. If RC = 'R', U is MU by N, and
93 *> if RC = 'C', U is N by MU.
94 *> \endverbatim
95 *>
96 *> \param[in] LDU
97 *> \verbatim
98 *> LDU is INTEGER
99 *> The leading dimension of U. If RC = 'R', LDU >= max(1,MU),
100 *> and if RC = 'C', LDU >= max(1,N).
101 *> \endverbatim
102 *>
103 *> \param[in] V
104 *> \verbatim
105 *> V is COMPLEX array, dimension (LDV,N)
106 *> The second matrix to compare. If RC = 'R', V is MV by N, and
107 *> if RC = 'C', V is N by MV.
108 *> \endverbatim
109 *>
110 *> \param[in] LDV
111 *> \verbatim
112 *> LDV is INTEGER
113 *> The leading dimension of V. If RC = 'R', LDV >= max(1,MV),
114 *> and if RC = 'C', LDV >= max(1,N).
115 *> \endverbatim
116 *>
117 *> \param[out] WORK
118 *> \verbatim
119 *> WORK is COMPLEX array, dimension (LWORK)
120 *> \endverbatim
121 *>
122 *> \param[in] LWORK
123 *> \verbatim
124 *> LWORK is INTEGER
125 *> The length of the array WORK. For best performance, LWORK
126 *> should be at least N*N if RC = 'C' or M*M if RC = 'R', but
127 *> the tests will be done even if LWORK is 0.
128 *> \endverbatim
129 *>
130 *> \param[out] RWORK
131 *> \verbatim
132 *> RWORK is REAL array, dimension (max(MV,N))
133 *> \endverbatim
134 *>
135 *> \param[out] RESULT
136 *> \verbatim
137 *> RESULT is REAL
138 *> The value computed by the test described above. RESULT is
139 *> limited to 1/ulp to avoid overflow.
140 *> \endverbatim
141 *>
142 *> \param[out] INFO
143 *> \verbatim
144 *> INFO is INTEGER
145 *> 0 indicates a successful exit
146 *> -k indicates the k-th parameter had an illegal value
147 *> \endverbatim
148 *
149 * Authors:
150 * ========
151 *
152 *> \author Univ. of Tennessee
153 *> \author Univ. of California Berkeley
154 *> \author Univ. of Colorado Denver
155 *> \author NAG Ltd.
156 *
157 *> \date November 2011
158 *
159 *> \ingroup complex_eig
160 *
161 * =====================================================================
162  SUBROUTINE cunt03( RC, MU, MV, N, K, U, LDU, V, LDV, WORK, LWORK,
163  $ rwork, result, info )
164 *
165 * -- LAPACK test routine (version 3.4.0) --
166 * -- LAPACK is a software package provided by Univ. of Tennessee, --
167 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
168 * November 2011
169 *
170 * .. Scalar Arguments ..
171  CHARACTER*( * ) RC
172  INTEGER INFO, K, LDU, LDV, LWORK, MU, MV, N
173  REAL RESULT
174 * ..
175 * .. Array Arguments ..
176  REAL RWORK( * )
177  COMPLEX U( ldu, * ), V( ldv, * ), WORK( * )
178 * ..
179 *
180 * =====================================================================
181 *
182 *
183 * .. Parameters ..
184  REAL ZERO, ONE
185  parameter ( zero = 0.0e0, one = 1.0e0 )
186 * ..
187 * .. Local Scalars ..
188  INTEGER I, IRC, J, LMX
189  REAL RES1, RES2, ULP
190  COMPLEX S, SU, SV
191 * ..
192 * .. External Functions ..
193  LOGICAL LSAME
194  INTEGER ICAMAX
195  REAL SLAMCH
196  EXTERNAL lsame, icamax, slamch
197 * ..
198 * .. Intrinsic Functions ..
199  INTRINSIC abs, cmplx, max, min, real
200 * ..
201 * .. External Subroutines ..
202  EXTERNAL cunt01, xerbla
203 * ..
204 * .. Executable Statements ..
205 *
206 * Check inputs
207 *
208  info = 0
209  IF( lsame( rc, 'R' ) ) THEN
210  irc = 0
211  ELSE IF( lsame( rc, 'C' ) ) THEN
212  irc = 1
213  ELSE
214  irc = -1
215  END IF
216  IF( irc.EQ.-1 ) THEN
217  info = -1
218  ELSE IF( mu.LT.0 ) THEN
219  info = -2
220  ELSE IF( mv.LT.0 ) THEN
221  info = -3
222  ELSE IF( n.LT.0 ) THEN
223  info = -4
224  ELSE IF( k.LT.0 .OR. k.GT.max( mu, mv ) ) THEN
225  info = -5
226  ELSE IF( ( irc.EQ.0 .AND. ldu.LT.max( 1, mu ) ) .OR.
227  $ ( irc.EQ.1 .AND. ldu.LT.max( 1, n ) ) ) THEN
228  info = -7
229  ELSE IF( ( irc.EQ.0 .AND. ldv.LT.max( 1, mv ) ) .OR.
230  $ ( irc.EQ.1 .AND. ldv.LT.max( 1, n ) ) ) THEN
231  info = -9
232  END IF
233  IF( info.NE.0 ) THEN
234  CALL xerbla( 'CUNT03', -info )
235  RETURN
236  END IF
237 *
238 * Initialize result
239 *
240  result = zero
241  IF( mu.EQ.0 .OR. mv.EQ.0 .OR. n.EQ.0 )
242  $ RETURN
243 *
244 * Machine constants
245 *
246  ulp = slamch( 'Precision' )
247 *
248  IF( irc.EQ.0 ) THEN
249 *
250 * Compare rows
251 *
252  res1 = zero
253  DO 20 i = 1, k
254  lmx = icamax( n, u( i, 1 ), ldu )
255  IF( v( i, lmx ).EQ.cmplx( zero ) ) THEN
256  sv = one
257  ELSE
258  sv = abs( v( i, lmx ) ) / v( i, lmx )
259  END IF
260  IF( u( i, lmx ).EQ.cmplx( zero ) ) THEN
261  su = one
262  ELSE
263  su = abs( u( i, lmx ) ) / u( i, lmx )
264  END IF
265  s = sv / su
266  DO 10 j = 1, n
267  res1 = max( res1, abs( u( i, j )-s*v( i, j ) ) )
268  10 CONTINUE
269  20 CONTINUE
270  res1 = res1 / ( REAL( n )*ULP )
271 *
272 * Compute orthogonality of rows of V.
273 *
274  CALL cunt01( 'Rows', mv, n, v, ldv, work, lwork, rwork, res2 )
275 *
276  ELSE
277 *
278 * Compare columns
279 *
280  res1 = zero
281  DO 40 i = 1, k
282  lmx = icamax( n, u( 1, i ), 1 )
283  IF( v( lmx, i ).EQ.cmplx( zero ) ) THEN
284  sv = one
285  ELSE
286  sv = abs( v( lmx, i ) ) / v( lmx, i )
287  END IF
288  IF( u( lmx, i ).EQ.cmplx( zero ) ) THEN
289  su = one
290  ELSE
291  su = abs( u( lmx, i ) ) / u( lmx, i )
292  END IF
293  s = sv / su
294  DO 30 j = 1, n
295  res1 = max( res1, abs( u( j, i )-s*v( j, i ) ) )
296  30 CONTINUE
297  40 CONTINUE
298  res1 = res1 / ( REAL( n )*ULP )
299 *
300 * Compute orthogonality of columns of V.
301 *
302  CALL cunt01( 'Columns', n, mv, v, ldv, work, lwork, rwork,
303  $ res2 )
304  END IF
305 *
306  result = min( max( res1, res2 ), one / ulp )
307  RETURN
308 *
309 * End of CUNT03
310 *
311  END
subroutine cunt03(RC, MU, MV, N, K, U, LDU, V, LDV, WORK, LWORK, RWORK, RESULT, INFO)
CUNT03
Definition: cunt03.f:164
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine cunt01(ROWCOL, M, N, U, LDU, WORK, LWORK, RWORK, RESID)
CUNT01
Definition: cunt01.f:128