LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zget54.f
Go to the documentation of this file.
1 *> \brief \b ZGET54
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 ZGET54( N, A, LDA, B, LDB, S, LDS, T, LDT, U, LDU, V,
12 * LDV, WORK, RESULT )
13 *
14 * .. Scalar Arguments ..
15 * INTEGER LDA, LDB, LDS, LDT, LDU, LDV, N
16 * DOUBLE PRECISION RESULT
17 * ..
18 * .. Array Arguments ..
19 * COMPLEX*16 A( LDA, * ), B( LDB, * ), S( LDS, * ),
20 * $ T( LDT, * ), U( LDU, * ), V( LDV, * ),
21 * $ WORK( * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> ZGET54 checks a generalized decomposition of the form
31 *>
32 *> A = U*S*V' and B = U*T* V'
33 *>
34 *> where ' means conjugate transpose and U and V are unitary.
35 *>
36 *> Specifically,
37 *>
38 *> RESULT = ||( A - U*S*V', B - U*T*V' )|| / (||( A, B )||*n*ulp )
39 *> \endverbatim
40 *
41 * Arguments:
42 * ==========
43 *
44 *> \param[in] N
45 *> \verbatim
46 *> N is INTEGER
47 *> The size of the matrix. If it is zero, DGET54 does nothing.
48 *> It must be at least zero.
49 *> \endverbatim
50 *>
51 *> \param[in] A
52 *> \verbatim
53 *> A is COMPLEX*16 array, dimension (LDA, N)
54 *> The original (unfactored) matrix A.
55 *> \endverbatim
56 *>
57 *> \param[in] LDA
58 *> \verbatim
59 *> LDA is INTEGER
60 *> The leading dimension of A. It must be at least 1
61 *> and at least N.
62 *> \endverbatim
63 *>
64 *> \param[in] B
65 *> \verbatim
66 *> B is COMPLEX*16 array, dimension (LDB, N)
67 *> The original (unfactored) matrix B.
68 *> \endverbatim
69 *>
70 *> \param[in] LDB
71 *> \verbatim
72 *> LDB is INTEGER
73 *> The leading dimension of B. It must be at least 1
74 *> and at least N.
75 *> \endverbatim
76 *>
77 *> \param[in] S
78 *> \verbatim
79 *> S is COMPLEX*16 array, dimension (LDS, N)
80 *> The factored matrix S.
81 *> \endverbatim
82 *>
83 *> \param[in] LDS
84 *> \verbatim
85 *> LDS is INTEGER
86 *> The leading dimension of S. It must be at least 1
87 *> and at least N.
88 *> \endverbatim
89 *>
90 *> \param[in] T
91 *> \verbatim
92 *> T is COMPLEX*16 array, dimension (LDT, N)
93 *> The factored matrix T.
94 *> \endverbatim
95 *>
96 *> \param[in] LDT
97 *> \verbatim
98 *> LDT is INTEGER
99 *> The leading dimension of T. It must be at least 1
100 *> and at least N.
101 *> \endverbatim
102 *>
103 *> \param[in] U
104 *> \verbatim
105 *> U is COMPLEX*16 array, dimension (LDU, N)
106 *> The orthogonal matrix on the left-hand side in the
107 *> decomposition.
108 *> \endverbatim
109 *>
110 *> \param[in] LDU
111 *> \verbatim
112 *> LDU is INTEGER
113 *> The leading dimension of U. LDU must be at least N and
114 *> at least 1.
115 *> \endverbatim
116 *>
117 *> \param[in] V
118 *> \verbatim
119 *> V is COMPLEX*16 array, dimension (LDV, N)
120 *> The orthogonal matrix on the left-hand side in the
121 *> decomposition.
122 *> \endverbatim
123 *>
124 *> \param[in] LDV
125 *> \verbatim
126 *> LDV is INTEGER
127 *> The leading dimension of V. LDV must be at least N and
128 *> at least 1.
129 *> \endverbatim
130 *>
131 *> \param[out] WORK
132 *> \verbatim
133 *> WORK is COMPLEX*16 array, dimension (3*N**2)
134 *> \endverbatim
135 *>
136 *> \param[out] RESULT
137 *> \verbatim
138 *> RESULT is DOUBLE PRECISION
139 *> The value RESULT, It is currently limited to 1/ulp, to
140 *> avoid overflow. Errors are flagged by RESULT=10/ulp.
141 *> \endverbatim
142 *
143 * Authors:
144 * ========
145 *
146 *> \author Univ. of Tennessee
147 *> \author Univ. of California Berkeley
148 *> \author Univ. of Colorado Denver
149 *> \author NAG Ltd.
150 *
151 *> \date November 2011
152 *
153 *> \ingroup complex16_eig
154 *
155 * =====================================================================
156  SUBROUTINE zget54( N, A, LDA, B, LDB, S, LDS, T, LDT, U, LDU, V,
157  $ ldv, work, result )
158 *
159 * -- LAPACK test routine (version 3.4.0) --
160 * -- LAPACK is a software package provided by Univ. of Tennessee, --
161 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
162 * November 2011
163 *
164 * .. Scalar Arguments ..
165  INTEGER LDA, LDB, LDS, LDT, LDU, LDV, N
166  DOUBLE PRECISION RESULT
167 * ..
168 * .. Array Arguments ..
169  COMPLEX*16 A( lda, * ), B( ldb, * ), S( lds, * ),
170  $ t( ldt, * ), u( ldu, * ), v( ldv, * ),
171  $ work( * )
172 * ..
173 *
174 * =====================================================================
175 *
176 * .. Parameters ..
177  DOUBLE PRECISION ZERO, ONE
178  parameter ( zero = 0.0d+0, one = 1.0d+0 )
179  COMPLEX*16 CZERO, CONE
180  parameter ( czero = ( 0.0d+0, 0.0d+0 ),
181  $ cone = ( 1.0d+0, 0.0d+0 ) )
182 * ..
183 * .. Local Scalars ..
184  DOUBLE PRECISION ABNORM, ULP, UNFL, WNORM
185 * ..
186 * .. Local Arrays ..
187  DOUBLE PRECISION DUM( 1 )
188 * ..
189 * .. External Functions ..
190  DOUBLE PRECISION DLAMCH, ZLANGE
191  EXTERNAL dlamch, zlange
192 * ..
193 * .. External Subroutines ..
194  EXTERNAL zgemm, zlacpy
195 * ..
196 * .. Intrinsic Functions ..
197  INTRINSIC dble, max, min
198 * ..
199 * .. Executable Statements ..
200 *
201  result = zero
202  IF( n.LE.0 )
203  $ RETURN
204 *
205 * Constants
206 *
207  unfl = dlamch( 'Safe minimum' )
208  ulp = dlamch( 'Epsilon' )*dlamch( 'Base' )
209 *
210 * compute the norm of (A,B)
211 *
212  CALL zlacpy( 'Full', n, n, a, lda, work, n )
213  CALL zlacpy( 'Full', n, n, b, ldb, work( n*n+1 ), n )
214  abnorm = max( zlange( '1', n, 2*n, work, n, dum ), unfl )
215 *
216 * Compute W1 = A - U*S*V', and put in the array WORK(1:N*N)
217 *
218  CALL zlacpy( ' ', n, n, a, lda, work, n )
219  CALL zgemm( 'N', 'N', n, n, n, cone, u, ldu, s, lds, czero,
220  $ work( n*n+1 ), n )
221 *
222  CALL zgemm( 'N', 'C', n, n, n, -cone, work( n*n+1 ), n, v, ldv,
223  $ cone, work, n )
224 *
225 * Compute W2 = B - U*T*V', and put in the workarray W(N*N+1:2*N*N)
226 *
227  CALL zlacpy( ' ', n, n, b, ldb, work( n*n+1 ), n )
228  CALL zgemm( 'N', 'N', n, n, n, cone, u, ldu, t, ldt, czero,
229  $ work( 2*n*n+1 ), n )
230 *
231  CALL zgemm( 'N', 'C', n, n, n, -cone, work( 2*n*n+1 ), n, v, ldv,
232  $ cone, work( n*n+1 ), n )
233 *
234 * Compute norm(W)/ ( ulp*norm((A,B)) )
235 *
236  wnorm = zlange( '1', n, 2*n, work, n, dum )
237 *
238  IF( abnorm.GT.wnorm ) THEN
239  result = ( wnorm / abnorm ) / ( 2*n*ulp )
240  ELSE
241  IF( abnorm.LT.one ) THEN
242  result = ( min( wnorm, 2*n*abnorm ) / abnorm ) / ( 2*n*ulp )
243  ELSE
244  result = min( wnorm / abnorm, dble( 2*n ) ) / ( 2*n*ulp )
245  END IF
246  END IF
247 *
248  RETURN
249 *
250 * End of ZGET54
251 *
252  END
subroutine zlacpy(UPLO, M, N, A, LDA, B, LDB)
ZLACPY copies all or part of one two-dimensional array to another.
Definition: zlacpy.f:105
subroutine zget54(N, A, LDA, B, LDB, S, LDS, T, LDT, U, LDU, V, LDV, WORK, RESULT)
ZGET54
Definition: zget54.f:158
subroutine zgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
ZGEMM
Definition: zgemm.f:189