LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
cstt21.f
Go to the documentation of this file.
1 *> \brief \b CSTT21
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 CSTT21( N, KBAND, AD, AE, SD, SE, U, LDU, WORK, RWORK,
12 * RESULT )
13 *
14 * .. Scalar Arguments ..
15 * INTEGER KBAND, LDU, N
16 * ..
17 * .. Array Arguments ..
18 * REAL AD( * ), AE( * ), RESULT( 2 ), RWORK( * ),
19 * $ SD( * ), SE( * )
20 * COMPLEX U( LDU, * ), WORK( * )
21 * ..
22 *
23 *
24 *> \par Purpose:
25 * =============
26 *>
27 *> \verbatim
28 *>
29 *> CSTT21 checks a decomposition of the form
30 *>
31 *> A = U S U**H
32 *>
33 *> where **H means conjugate transpose, A is real symmetric tridiagonal,
34 *> U is unitary, and S is real and diagonal (if KBAND=0) or symmetric
35 *> tridiagonal (if KBAND=1). Two tests are performed:
36 *>
37 *> RESULT(1) = | A - U S U**H | / ( |A| n ulp )
38 *>
39 *> RESULT(2) = | I - U U**H | / ( n ulp )
40 *> \endverbatim
41 *
42 * Arguments:
43 * ==========
44 *
45 *> \param[in] N
46 *> \verbatim
47 *> N is INTEGER
48 *> The size of the matrix. If it is zero, CSTT21 does nothing.
49 *> It must be at least zero.
50 *> \endverbatim
51 *>
52 *> \param[in] KBAND
53 *> \verbatim
54 *> KBAND is INTEGER
55 *> The bandwidth of the matrix S. It may only be zero or one.
56 *> If zero, then S is diagonal, and SE is not referenced. If
57 *> one, then S is symmetric tri-diagonal.
58 *> \endverbatim
59 *>
60 *> \param[in] AD
61 *> \verbatim
62 *> AD is REAL array, dimension (N)
63 *> The diagonal of the original (unfactored) matrix A. A is
64 *> assumed to be real symmetric tridiagonal.
65 *> \endverbatim
66 *>
67 *> \param[in] AE
68 *> \verbatim
69 *> AE is REAL array, dimension (N-1)
70 *> The off-diagonal of the original (unfactored) matrix A. A
71 *> is assumed to be symmetric tridiagonal. AE(1) is the (1,2)
72 *> and (2,1) element, AE(2) is the (2,3) and (3,2) element, etc.
73 *> \endverbatim
74 *>
75 *> \param[in] SD
76 *> \verbatim
77 *> SD is REAL array, dimension (N)
78 *> The diagonal of the real (symmetric tri-) diagonal matrix S.
79 *> \endverbatim
80 *>
81 *> \param[in] SE
82 *> \verbatim
83 *> SE is REAL array, dimension (N-1)
84 *> The off-diagonal of the (symmetric tri-) diagonal matrix S.
85 *> Not referenced if KBSND=0. If KBAND=1, then AE(1) is the
86 *> (1,2) and (2,1) element, SE(2) is the (2,3) and (3,2)
87 *> element, etc.
88 *> \endverbatim
89 *>
90 *> \param[in] U
91 *> \verbatim
92 *> U is COMPLEX array, dimension (LDU, N)
93 *> The unitary matrix in the decomposition.
94 *> \endverbatim
95 *>
96 *> \param[in] LDU
97 *> \verbatim
98 *> LDU is INTEGER
99 *> The leading dimension of U. LDU must be at least N.
100 *> \endverbatim
101 *>
102 *> \param[out] WORK
103 *> \verbatim
104 *> WORK is COMPLEX array, dimension (N**2)
105 *> \endverbatim
106 *>
107 *> \param[out] RWORK
108 *> \verbatim
109 *> RWORK is REAL array, dimension (N)
110 *> \endverbatim
111 *>
112 *> \param[out] RESULT
113 *> \verbatim
114 *> RESULT is REAL array, dimension (2)
115 *> The values computed by the two tests described above. The
116 *> values are currently limited to 1/ulp, to avoid overflow.
117 *> RESULT(1) is always modified.
118 *> \endverbatim
119 *
120 * Authors:
121 * ========
122 *
123 *> \author Univ. of Tennessee
124 *> \author Univ. of California Berkeley
125 *> \author Univ. of Colorado Denver
126 *> \author NAG Ltd.
127 *
128 *> \date December 2016
129 *
130 *> \ingroup complex_eig
131 *
132 * =====================================================================
133  SUBROUTINE cstt21( N, KBAND, AD, AE, SD, SE, U, LDU, WORK, RWORK,
134  $ RESULT )
135 *
136 * -- LAPACK test routine (version 3.7.0) --
137 * -- LAPACK is a software package provided by Univ. of Tennessee, --
138 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
139 * December 2016
140 *
141 * .. Scalar Arguments ..
142  INTEGER KBAND, LDU, N
143 * ..
144 * .. Array Arguments ..
145  REAL AD( * ), AE( * ), RESULT( 2 ), RWORK( * ),
146  $ sd( * ), se( * )
147  COMPLEX U( LDU, * ), WORK( * )
148 * ..
149 *
150 * =====================================================================
151 *
152 * .. Parameters ..
153  REAL ZERO, ONE
154  parameter( zero = 0.0e+0, one = 1.0e+0 )
155  COMPLEX CZERO, CONE
156  parameter( czero = ( 0.0e+0, 0.0e+0 ),
157  $ cone = ( 1.0e+0, 0.0e+0 ) )
158 * ..
159 * .. Local Scalars ..
160  INTEGER J
161  REAL ANORM, TEMP1, TEMP2, ULP, UNFL, WNORM
162 * ..
163 * .. External Functions ..
164  REAL CLANGE, CLANHE, SLAMCH
165  EXTERNAL clange, clanhe, slamch
166 * ..
167 * .. External Subroutines ..
168  EXTERNAL cgemm, cher, cher2, claset
169 * ..
170 * .. Intrinsic Functions ..
171  INTRINSIC abs, cmplx, max, min, real
172 * ..
173 * .. Executable Statements ..
174 *
175 * 1) Constants
176 *
177  result( 1 ) = zero
178  result( 2 ) = zero
179  IF( n.LE.0 )
180  $ RETURN
181 *
182  unfl = slamch( 'Safe minimum' )
183  ulp = slamch( 'Precision' )
184 *
185 * Do Test 1
186 *
187 * Copy A & Compute its 1-Norm:
188 *
189  CALL claset( 'Full', n, n, czero, czero, work, n )
190 *
191  anorm = zero
192  temp1 = zero
193 *
194  DO 10 j = 1, n - 1
195  work( ( n+1 )*( j-1 )+1 ) = ad( j )
196  work( ( n+1 )*( j-1 )+2 ) = ae( j )
197  temp2 = abs( ae( j ) )
198  anorm = max( anorm, abs( ad( j ) )+temp1+temp2 )
199  temp1 = temp2
200  10 CONTINUE
201 *
202  work( n**2 ) = ad( n )
203  anorm = max( anorm, abs( ad( n ) )+temp1, unfl )
204 *
205 * Norm of A - U S U**H
206 *
207  DO 20 j = 1, n
208  CALL cher( 'L', n, -sd( j ), u( 1, j ), 1, work, n )
209  20 CONTINUE
210 *
211  IF( n.GT.1 .AND. kband.EQ.1 ) THEN
212  DO 30 j = 1, n - 1
213  CALL cher2( 'L', n, -cmplx( se( j ) ), u( 1, j ), 1,
214  $ u( 1, j+1 ), 1, work, n )
215  30 CONTINUE
216  END IF
217 *
218  wnorm = clanhe( '1', 'L', n, work, n, rwork )
219 *
220  IF( anorm.GT.wnorm ) THEN
221  result( 1 ) = ( wnorm / anorm ) / ( n*ulp )
222  ELSE
223  IF( anorm.LT.one ) THEN
224  result( 1 ) = ( min( wnorm, n*anorm ) / anorm ) / ( n*ulp )
225  ELSE
226  result( 1 ) = min( wnorm / anorm, real( n ) ) / ( n*ulp )
227  END IF
228  END IF
229 *
230 * Do Test 2
231 *
232 * Compute U U**H - I
233 *
234  CALL cgemm( 'N', 'C', n, n, n, cone, u, ldu, u, ldu, czero, work,
235  $ n )
236 *
237  DO 40 j = 1, n
238  work( ( n+1 )*( j-1 )+1 ) = work( ( n+1 )*( j-1 )+1 ) - cone
239  40 CONTINUE
240 *
241  result( 2 ) = min( real( n ), clange( '1', n, n, work, n,
242  $ rwork ) ) / ( n*ulp )
243 *
244  RETURN
245 *
246 * End of CSTT21
247 *
248  END
cstt21
subroutine cstt21(N, KBAND, AD, AE, SD, SE, U, LDU, WORK, RWORK, RESULT)
CSTT21
Definition: cstt21.f:135
cgemm
subroutine cgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
CGEMM
Definition: cgemm.f:189
cher
subroutine cher(UPLO, N, ALPHA, X, INCX, A, LDA)
CHER
Definition: cher.f:137
cher2
subroutine cher2(UPLO, N, ALPHA, X, INCX, Y, INCY, A, LDA)
CHER2
Definition: cher2.f:152
claset
subroutine claset(UPLO, M, N, ALPHA, BETA, A, LDA)
CLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
Definition: claset.f:108