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