LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
chpt21.f
Go to the documentation of this file.
1 *> \brief \b CHPT21
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 CHPT21( ITYPE, UPLO, N, KBAND, AP, D, E, U, LDU, VP,
12 * TAU, WORK, RWORK, RESULT )
13 *
14 * .. Scalar Arguments ..
15 * CHARACTER UPLO
16 * INTEGER ITYPE, KBAND, LDU, N
17 * ..
18 * .. Array Arguments ..
19 * REAL D( * ), E( * ), RESULT( 2 ), RWORK( * )
20 * COMPLEX AP( * ), TAU( * ), U( LDU, * ), VP( * ),
21 * $ WORK( * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> CHPT21 generally checks a decomposition of the form
31 *>
32 *> A = U S UC>
33 *> where * means conjugate transpose, A is hermitian, U is
34 *> unitary, and S is diagonal (if KBAND=0) or (real) symmetric
35 *> tridiagonal (if KBAND=1). If ITYPE=1, then U is represented as
36 *> a dense matrix, otherwise the U is expressed as a product of
37 *> Householder transformations, whose vectors are stored in the
38 *> array "V" and whose scaling constants are in "TAU"; we shall
39 *> use the letter "V" to refer to the product of Householder
40 *> transformations (which should be equal to U).
41 *>
42 *> Specifically, if ITYPE=1, then:
43 *>
44 *> RESULT(1) = | A - U S U* | / ( |A| n ulp ) *andC> RESULT(2) = | I - UU* | / ( n ulp )
45 *>
46 *> If ITYPE=2, then:
47 *>
48 *> RESULT(1) = | A - V S V* | / ( |A| n ulp )
49 *>
50 *> If ITYPE=3, then:
51 *>
52 *> RESULT(1) = | I - UV* | / ( n ulp )
53 *>
54 *> Packed storage means that, for example, if UPLO='U', then the columns
55 *> of the upper triangle of A are stored one after another, so that
56 *> A(1,j+1) immediately follows A(j,j) in the array AP. Similarly, if
57 *> UPLO='L', then the columns of the lower triangle of A are stored one
58 *> after another in AP, so that A(j+1,j+1) immediately follows A(n,j)
59 *> in the array AP. This means that A(i,j) is stored in:
60 *>
61 *> AP( i + j*(j-1)/2 ) if UPLO='U'
62 *>
63 *> AP( i + (2*n-j)*(j-1)/2 ) if UPLO='L'
64 *>
65 *> The array VP bears the same relation to the matrix V that A does to
66 *> AP.
67 *>
68 *> For ITYPE > 1, the transformation U is expressed as a product
69 *> of Householder transformations:
70 *>
71 *> If UPLO='U', then V = H(n-1)...H(1), where
72 *>
73 *> H(j) = I - tau(j) v(j) v(j)C>
74 *> and the first j-1 elements of v(j) are stored in V(1:j-1,j+1),
75 *> (i.e., VP( j*(j+1)/2 + 1 : j*(j+1)/2 + j-1 ) ),
76 *> the j-th element is 1, and the last n-j elements are 0.
77 *>
78 *> If UPLO='L', then V = H(1)...H(n-1), where
79 *>
80 *> H(j) = I - tau(j) v(j) v(j)C>
81 *> and the first j elements of v(j) are 0, the (j+1)-st is 1, and the
82 *> (j+2)-nd through n-th elements are stored in V(j+2:n,j) (i.e.,
83 *> in VP( (2*n-j)*(j-1)/2 + j+2 : (2*n-j)*(j-1)/2 + n ) .)
84 *> \endverbatim
85 *
86 * Arguments:
87 * ==========
88 *
89 *> \param[in] ITYPE
90 *> \verbatim
91 *> ITYPE is INTEGER
92 *> Specifies the type of tests to be performed.
93 *> 1: U expressed as a dense unitary matrix:
94 *> RESULT(1) = | A - U S U* | / ( |A| n ulp ) *andC> RESULT(2) = | I - UU* | / ( n ulp )
95 *>
96 *> 2: U expressed as a product V of Housholder transformations:
97 *> RESULT(1) = | A - V S V* | / ( |A| n ulp )
98 *>
99 *> 3: U expressed both as a dense unitary matrix and
100 *> as a product of Housholder transformations:
101 *> RESULT(1) = | I - UV* | / ( n ulp )
102 *> \endverbatim
103 *>
104 *> \param[in] UPLO
105 *> \verbatim
106 *> UPLO is CHARACTER
107 *> If UPLO='U', the upper triangle of A and V will be used and
108 *> the (strictly) lower triangle will not be referenced.
109 *> If UPLO='L', the lower triangle of A and V will be used and
110 *> the (strictly) upper triangle will not be referenced.
111 *> \endverbatim
112 *>
113 *> \param[in] N
114 *> \verbatim
115 *> N is INTEGER
116 *> The size of the matrix. If it is zero, CHPT21 does nothing.
117 *> It must be at least zero.
118 *> \endverbatim
119 *>
120 *> \param[in] KBAND
121 *> \verbatim
122 *> KBAND is INTEGER
123 *> The bandwidth of the matrix. It may only be zero or one.
124 *> If zero, then S is diagonal, and E is not referenced. If
125 *> one, then S is symmetric tri-diagonal.
126 *> \endverbatim
127 *>
128 *> \param[in] AP
129 *> \verbatim
130 *> AP is COMPLEX array, dimension (N*(N+1)/2)
131 *> The original (unfactored) matrix. It is assumed to be
132 *> hermitian, and contains the columns of just the upper
133 *> triangle (UPLO='U') or only the lower triangle (UPLO='L'),
134 *> packed one after another.
135 *> \endverbatim
136 *>
137 *> \param[in] D
138 *> \verbatim
139 *> D is REAL array, dimension (N)
140 *> The diagonal of the (symmetric tri-) diagonal matrix.
141 *> \endverbatim
142 *>
143 *> \param[in] E
144 *> \verbatim
145 *> E is REAL array, dimension (N)
146 *> The off-diagonal of the (symmetric tri-) diagonal matrix.
147 *> E(1) is the (1,2) and (2,1) element, E(2) is the (2,3) and
148 *> (3,2) element, etc.
149 *> Not referenced if KBAND=0.
150 *> \endverbatim
151 *>
152 *> \param[in] U
153 *> \verbatim
154 *> U is COMPLEX array, dimension (LDU, N)
155 *> If ITYPE=1 or 3, this contains the unitary matrix in
156 *> the decomposition, expressed as a dense matrix. If ITYPE=2,
157 *> then it is not referenced.
158 *> \endverbatim
159 *>
160 *> \param[in] LDU
161 *> \verbatim
162 *> LDU is INTEGER
163 *> The leading dimension of U. LDU must be at least N and
164 *> at least 1.
165 *> \endverbatim
166 *>
167 *> \param[in] VP
168 *> \verbatim
169 *> VP is REAL array, dimension (N*(N+1)/2)
170 *> If ITYPE=2 or 3, the columns of this array contain the
171 *> Householder vectors used to describe the unitary matrix
172 *> in the decomposition, as described in purpose.
173 *> *NOTE* If ITYPE=2 or 3, V is modified and restored. The
174 *> subdiagonal (if UPLO='L') or the superdiagonal (if UPLO='U')
175 *> is set to one, and later reset to its original value, during
176 *> the course of the calculation.
177 *> If ITYPE=1, then it is neither referenced nor modified.
178 *> \endverbatim
179 *>
180 *> \param[in] TAU
181 *> \verbatim
182 *> TAU is COMPLEX array, dimension (N)
183 *> If ITYPE >= 2, then TAU(j) is the scalar factor of
184 *> v(j) v(j)* in the Householder transformation H(j) of
185 *> the product U = H(1)...H(n-2)
186 *> If ITYPE < 2, then TAU is not referenced.
187 *> \endverbatim
188 *>
189 *> \param[out] WORK
190 *> \verbatim
191 *> WORK is COMPLEX array, dimension (N**2)
192 *> Workspace.
193 *> \endverbatim
194 *>
195 *> \param[out] RWORK
196 *> \verbatim
197 *> RWORK is REAL array, dimension (N)
198 *> Workspace.
199 *> \endverbatim
200 *>
201 *> \param[out] RESULT
202 *> \verbatim
203 *> RESULT is REAL array, dimension (2)
204 *> The values computed by the two tests described above. The
205 *> values are currently limited to 1/ulp, to avoid overflow.
206 *> RESULT(1) is always modified. RESULT(2) is modified only
207 *> if ITYPE=1.
208 *> \endverbatim
209 *
210 * Authors:
211 * ========
212 *
213 *> \author Univ. of Tennessee
214 *> \author Univ. of California Berkeley
215 *> \author Univ. of Colorado Denver
216 *> \author NAG Ltd.
217 *
218 *> \date November 2011
219 *
220 *> \ingroup complex_eig
221 *
222 * =====================================================================
223  SUBROUTINE chpt21( ITYPE, UPLO, N, KBAND, AP, D, E, U, LDU, VP,
224  $ tau, work, rwork, result )
225 *
226 * -- LAPACK test routine (version 3.4.0) --
227 * -- LAPACK is a software package provided by Univ. of Tennessee, --
228 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
229 * November 2011
230 *
231 * .. Scalar Arguments ..
232  CHARACTER uplo
233  INTEGER itype, kband, ldu, n
234 * ..
235 * .. Array Arguments ..
236  REAL d( * ), e( * ), result( 2 ), rwork( * )
237  COMPLEX ap( * ), tau( * ), u( ldu, * ), vp( * ),
238  $ work( * )
239 * ..
240 *
241 * =====================================================================
242 *
243 * .. Parameters ..
244  REAL zero, one, ten
245  parameter( zero = 0.0e+0, one = 1.0e+0, ten = 10.0e+0 )
246  REAL half
247  parameter( half = 1.0e+0 / 2.0e+0 )
248  COMPLEX czero, cone
249  parameter( czero = ( 0.0e+0, 0.0e+0 ),
250  $ cone = ( 1.0e+0, 0.0e+0 ) )
251 * ..
252 * .. Local Scalars ..
253  LOGICAL lower
254  CHARACTER cuplo
255  INTEGER iinfo, j, jp, jp1, jr, lap
256  REAL anorm, ulp, unfl, wnorm
257  COMPLEX temp, vsave
258 * ..
259 * .. External Functions ..
260  LOGICAL lsame
261  REAL clange, clanhp, slamch
262  COMPLEX cdotc
263  EXTERNAL lsame, clange, clanhp, slamch, cdotc
264 * ..
265 * .. External Subroutines ..
266  EXTERNAL caxpy, ccopy, cgemm, chpmv, chpr, chpr2,
267  $ clacpy, claset, cupmtr
268 * ..
269 * .. Intrinsic Functions ..
270  INTRINSIC cmplx, max, min, real
271 * ..
272 * .. Executable Statements ..
273 *
274 * Constants
275 *
276  result( 1 ) = zero
277  IF( itype.EQ.1 )
278  $ result( 2 ) = zero
279  IF( n.LE.0 )
280  $ return
281 *
282  lap = ( n*( n+1 ) ) / 2
283 *
284  IF( lsame( uplo, 'U' ) ) THEN
285  lower = .false.
286  cuplo = 'U'
287  ELSE
288  lower = .true.
289  cuplo = 'L'
290  END IF
291 *
292  unfl = slamch( 'Safe minimum' )
293  ulp = slamch( 'Epsilon' )*slamch( 'Base' )
294 *
295 * Some Error Checks
296 *
297  IF( itype.LT.1 .OR. itype.GT.3 ) THEN
298  result( 1 ) = ten / ulp
299  return
300  END IF
301 *
302 * Do Test 1
303 *
304 * Norm of A:
305 *
306  IF( itype.EQ.3 ) THEN
307  anorm = one
308  ELSE
309  anorm = max( clanhp( '1', cuplo, n, ap, rwork ), unfl )
310  END IF
311 *
312 * Compute error matrix:
313 *
314  IF( itype.EQ.1 ) THEN
315 *
316 * ITYPE=1: error = A - U S U*
317 *
318  CALL claset( 'Full', n, n, czero, czero, work, n )
319  CALL ccopy( lap, ap, 1, work, 1 )
320 *
321  DO 10 j = 1, n
322  CALL chpr( cuplo, n, -d( j ), u( 1, j ), 1, work )
323  10 continue
324 *
325  IF( n.GT.1 .AND. kband.EQ.1 ) THEN
326  DO 20 j = 1, n - 1
327  CALL chpr2( cuplo, n, -cmplx( e( j ) ), u( 1, j ), 1,
328  $ u( 1, j-1 ), 1, work )
329  20 continue
330  END IF
331  wnorm = clanhp( '1', cuplo, n, work, rwork )
332 *
333  ELSE IF( itype.EQ.2 ) THEN
334 *
335 * ITYPE=2: error = V S V* - A
336 *
337  CALL claset( 'Full', n, n, czero, czero, work, n )
338 *
339  IF( lower ) THEN
340  work( lap ) = d( n )
341  DO 40 j = n - 1, 1, -1
342  jp = ( ( 2*n-j )*( j-1 ) ) / 2
343  jp1 = jp + n - j
344  IF( kband.EQ.1 ) THEN
345  work( jp+j+1 ) = ( cone-tau( j ) )*e( j )
346  DO 30 jr = j + 2, n
347  work( jp+jr ) = -tau( j )*e( j )*vp( jp+jr )
348  30 continue
349  END IF
350 *
351  IF( tau( j ).NE.czero ) THEN
352  vsave = vp( jp+j+1 )
353  vp( jp+j+1 ) = cone
354  CALL chpmv( 'L', n-j, cone, work( jp1+j+1 ),
355  $ vp( jp+j+1 ), 1, czero, work( lap+1 ), 1 )
356  temp = -half*tau( j )*cdotc( n-j, work( lap+1 ), 1,
357  $ vp( jp+j+1 ), 1 )
358  CALL caxpy( n-j, temp, vp( jp+j+1 ), 1, work( lap+1 ),
359  $ 1 )
360  CALL chpr2( 'L', n-j, -tau( j ), vp( jp+j+1 ), 1,
361  $ work( lap+1 ), 1, work( jp1+j+1 ) )
362 *
363  vp( jp+j+1 ) = vsave
364  END IF
365  work( jp+j ) = d( j )
366  40 continue
367  ELSE
368  work( 1 ) = d( 1 )
369  DO 60 j = 1, n - 1
370  jp = ( j*( j-1 ) ) / 2
371  jp1 = jp + j
372  IF( kband.EQ.1 ) THEN
373  work( jp1+j ) = ( cone-tau( j ) )*e( j )
374  DO 50 jr = 1, j - 1
375  work( jp1+jr ) = -tau( j )*e( j )*vp( jp1+jr )
376  50 continue
377  END IF
378 *
379  IF( tau( j ).NE.czero ) THEN
380  vsave = vp( jp1+j )
381  vp( jp1+j ) = cone
382  CALL chpmv( 'U', j, cone, work, vp( jp1+1 ), 1, czero,
383  $ work( lap+1 ), 1 )
384  temp = -half*tau( j )*cdotc( j, work( lap+1 ), 1,
385  $ vp( jp1+1 ), 1 )
386  CALL caxpy( j, temp, vp( jp1+1 ), 1, work( lap+1 ),
387  $ 1 )
388  CALL chpr2( 'U', j, -tau( j ), vp( jp1+1 ), 1,
389  $ work( lap+1 ), 1, work )
390  vp( jp1+j ) = vsave
391  END IF
392  work( jp1+j+1 ) = d( j+1 )
393  60 continue
394  END IF
395 *
396  DO 70 j = 1, lap
397  work( j ) = work( j ) - ap( j )
398  70 continue
399  wnorm = clanhp( '1', cuplo, n, work, rwork )
400 *
401  ELSE IF( itype.EQ.3 ) THEN
402 *
403 * ITYPE=3: error = U V* - I
404 *
405  IF( n.LT.2 )
406  $ return
407  CALL clacpy( ' ', n, n, u, ldu, work, n )
408  CALL cupmtr( 'R', cuplo, 'C', n, n, vp, tau, work, n,
409  $ work( n**2+1 ), iinfo )
410  IF( iinfo.NE.0 ) THEN
411  result( 1 ) = ten / ulp
412  return
413  END IF
414 *
415  DO 80 j = 1, n
416  work( ( n+1 )*( j-1 )+1 ) = work( ( n+1 )*( j-1 )+1 ) - cone
417  80 continue
418 *
419  wnorm = clange( '1', n, n, work, n, rwork )
420  END IF
421 *
422  IF( anorm.GT.wnorm ) THEN
423  result( 1 ) = ( wnorm / anorm ) / ( n*ulp )
424  ELSE
425  IF( anorm.LT.one ) THEN
426  result( 1 ) = ( min( wnorm, n*anorm ) / anorm ) / ( n*ulp )
427  ELSE
428  result( 1 ) = min( wnorm / anorm, REAL( N ) ) / ( n*ulp )
429  END IF
430  END IF
431 *
432 * Do Test 2
433 *
434 * Compute UU* - I
435 *
436  IF( itype.EQ.1 ) THEN
437  CALL cgemm( 'N', 'C', n, n, n, cone, u, ldu, u, ldu, czero,
438  $ work, n )
439 *
440  DO 90 j = 1, n
441  work( ( n+1 )*( j-1 )+1 ) = work( ( n+1 )*( j-1 )+1 ) - cone
442  90 continue
443 *
444  result( 2 ) = min( clange( '1', n, n, work, n, rwork ),
445  $ REAL( N ) ) / ( n*ulp )
446  END IF
447 *
448  return
449 *
450 * End of CHPT21
451 *
452  END