1 SUBROUTINE ZHST01( N, ILO, IHI, A, LDA, H, LDH, Q, LDQ, WORK,
2 $ LWORK, RWORK, RESULT )
3 *
4 * -- LAPACK test routine (version 3.1) --
5 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
6 * November 2006
7 *
8 * .. Scalar Arguments ..
9 INTEGER IHI, ILO, LDA, LDH, LDQ, LWORK, N
10 * ..
11 * .. Array Arguments ..
12 DOUBLE PRECISION RESULT( 2 ), RWORK( * )
13 COMPLEX*16 A( LDA, * ), H( LDH, * ), Q( LDQ, * ),
14 $ WORK( LWORK )
15 * ..
16 *
17 * Purpose
18 * =======
19 *
20 * ZHST01 tests the reduction of a general matrix A to upper Hessenberg
21 * form: A = Q*H*Q'. Two test ratios are computed;
22 *
23 * RESULT(1) = norm( A - Q*H*Q' ) / ( norm(A) * N * EPS )
24 * RESULT(2) = norm( I - Q'*Q ) / ( N * EPS )
25 *
26 * The matrix Q is assumed to be given explicitly as it would be
27 * following ZGEHRD + ZUNGHR.
28 *
29 * In this version, ILO and IHI are not used, but they could be used
30 * to save some work if this is desired.
31 *
32 * Arguments
33 * =========
34 *
35 * N (input) INTEGER
36 * The order of the matrix A. N >= 0.
37 *
38 * ILO (input) INTEGER
39 * IHI (input) INTEGER
40 * A is assumed to be upper triangular in rows and columns
41 * 1:ILO-1 and IHI+1:N, so Q differs from the identity only in
42 * rows and columns ILO+1:IHI.
43 *
44 * A (input) COMPLEX*16 array, dimension (LDA,N)
45 * The original n by n matrix A.
46 *
47 * LDA (input) INTEGER
48 * The leading dimension of the array A. LDA >= max(1,N).
49 *
50 * H (input) COMPLEX*16 array, dimension (LDH,N)
51 * The upper Hessenberg matrix H from the reduction A = Q*H*Q'
52 * as computed by ZGEHRD. H is assumed to be zero below the
53 * first subdiagonal.
54 *
55 * LDH (input) INTEGER
56 * The leading dimension of the array H. LDH >= max(1,N).
57 *
58 * Q (input) COMPLEX*16 array, dimension (LDQ,N)
59 * The orthogonal matrix Q from the reduction A = Q*H*Q' as
60 * computed by ZGEHRD + ZUNGHR.
61 *
62 * LDQ (input) INTEGER
63 * The leading dimension of the array Q. LDQ >= max(1,N).
64 *
65 * WORK (workspace) COMPLEX*16 array, dimension (LWORK)
66 *
67 * LWORK (input) INTEGER
68 * The length of the array WORK. LWORK >= 2*N*N.
69 *
70 * RWORK (workspace) DOUBLE PRECISION array, dimension (N)
71 *
72 * RESULT (output) DOUBLE PRECISION array, dimension (2)
73 * RESULT(1) = norm( A - Q*H*Q' ) / ( norm(A) * N * EPS )
74 * RESULT(2) = norm( I - Q'*Q ) / ( N * EPS )
75 *
76 * =====================================================================
77 *
78 * .. Parameters ..
79 DOUBLE PRECISION ONE, ZERO
80 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
81 * ..
82 * .. Local Scalars ..
83 INTEGER LDWORK
84 DOUBLE PRECISION ANORM, EPS, OVFL, SMLNUM, UNFL, WNORM
85 * ..
86 * .. External Functions ..
87 DOUBLE PRECISION DLAMCH, ZLANGE
88 EXTERNAL DLAMCH, ZLANGE
89 * ..
90 * .. External Subroutines ..
91 EXTERNAL DLABAD, ZGEMM, ZLACPY, ZUNT01
92 * ..
93 * .. Intrinsic Functions ..
94 INTRINSIC DCMPLX, MAX, MIN
95 * ..
96 * .. Executable Statements ..
97 *
98 * Quick return if possible
99 *
100 IF( N.LE.0 ) THEN
101 RESULT( 1 ) = ZERO
102 RESULT( 2 ) = ZERO
103 RETURN
104 END IF
105 *
106 UNFL = DLAMCH( 'Safe minimum' )
107 EPS = DLAMCH( 'Precision' )
108 OVFL = ONE / UNFL
109 CALL DLABAD( UNFL, OVFL )
110 SMLNUM = UNFL*N / EPS
111 *
112 * Test 1: Compute norm( A - Q*H*Q' ) / ( norm(A) * N * EPS )
113 *
114 * Copy A to WORK
115 *
116 LDWORK = MAX( 1, N )
117 CALL ZLACPY( ' ', N, N, A, LDA, WORK, LDWORK )
118 *
119 * Compute Q*H
120 *
121 CALL ZGEMM( 'No transpose', 'No transpose', N, N, N,
122 $ DCMPLX( ONE ), Q, LDQ, H, LDH, DCMPLX( ZERO ),
123 $ WORK( LDWORK*N+1 ), LDWORK )
124 *
125 * Compute A - Q*H*Q'
126 *
127 CALL ZGEMM( 'No transpose', 'Conjugate transpose', N, N, N,
128 $ DCMPLX( -ONE ), WORK( LDWORK*N+1 ), LDWORK, Q, LDQ,
129 $ DCMPLX( ONE ), WORK, LDWORK )
130 *
131 ANORM = MAX( ZLANGE( '1', N, N, A, LDA, RWORK ), UNFL )
132 WNORM = ZLANGE( '1', N, N, WORK, LDWORK, RWORK )
133 *
134 * Note that RESULT(1) cannot overflow and is bounded by 1/(N*EPS)
135 *
136 RESULT( 1 ) = MIN( WNORM, ANORM ) / MAX( SMLNUM, ANORM*EPS ) / N
137 *
138 * Test 2: Compute norm( I - Q'*Q ) / ( N * EPS )
139 *
140 CALL ZUNT01( 'Columns', N, N, Q, LDQ, WORK, LWORK, RWORK,
141 $ RESULT( 2 ) )
142 *
143 RETURN
144 *
145 * End of ZHST01
146 *
147 END
2 $ LWORK, RWORK, RESULT )
3 *
4 * -- LAPACK test routine (version 3.1) --
5 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
6 * November 2006
7 *
8 * .. Scalar Arguments ..
9 INTEGER IHI, ILO, LDA, LDH, LDQ, LWORK, N
10 * ..
11 * .. Array Arguments ..
12 DOUBLE PRECISION RESULT( 2 ), RWORK( * )
13 COMPLEX*16 A( LDA, * ), H( LDH, * ), Q( LDQ, * ),
14 $ WORK( LWORK )
15 * ..
16 *
17 * Purpose
18 * =======
19 *
20 * ZHST01 tests the reduction of a general matrix A to upper Hessenberg
21 * form: A = Q*H*Q'. Two test ratios are computed;
22 *
23 * RESULT(1) = norm( A - Q*H*Q' ) / ( norm(A) * N * EPS )
24 * RESULT(2) = norm( I - Q'*Q ) / ( N * EPS )
25 *
26 * The matrix Q is assumed to be given explicitly as it would be
27 * following ZGEHRD + ZUNGHR.
28 *
29 * In this version, ILO and IHI are not used, but they could be used
30 * to save some work if this is desired.
31 *
32 * Arguments
33 * =========
34 *
35 * N (input) INTEGER
36 * The order of the matrix A. N >= 0.
37 *
38 * ILO (input) INTEGER
39 * IHI (input) INTEGER
40 * A is assumed to be upper triangular in rows and columns
41 * 1:ILO-1 and IHI+1:N, so Q differs from the identity only in
42 * rows and columns ILO+1:IHI.
43 *
44 * A (input) COMPLEX*16 array, dimension (LDA,N)
45 * The original n by n matrix A.
46 *
47 * LDA (input) INTEGER
48 * The leading dimension of the array A. LDA >= max(1,N).
49 *
50 * H (input) COMPLEX*16 array, dimension (LDH,N)
51 * The upper Hessenberg matrix H from the reduction A = Q*H*Q'
52 * as computed by ZGEHRD. H is assumed to be zero below the
53 * first subdiagonal.
54 *
55 * LDH (input) INTEGER
56 * The leading dimension of the array H. LDH >= max(1,N).
57 *
58 * Q (input) COMPLEX*16 array, dimension (LDQ,N)
59 * The orthogonal matrix Q from the reduction A = Q*H*Q' as
60 * computed by ZGEHRD + ZUNGHR.
61 *
62 * LDQ (input) INTEGER
63 * The leading dimension of the array Q. LDQ >= max(1,N).
64 *
65 * WORK (workspace) COMPLEX*16 array, dimension (LWORK)
66 *
67 * LWORK (input) INTEGER
68 * The length of the array WORK. LWORK >= 2*N*N.
69 *
70 * RWORK (workspace) DOUBLE PRECISION array, dimension (N)
71 *
72 * RESULT (output) DOUBLE PRECISION array, dimension (2)
73 * RESULT(1) = norm( A - Q*H*Q' ) / ( norm(A) * N * EPS )
74 * RESULT(2) = norm( I - Q'*Q ) / ( N * EPS )
75 *
76 * =====================================================================
77 *
78 * .. Parameters ..
79 DOUBLE PRECISION ONE, ZERO
80 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
81 * ..
82 * .. Local Scalars ..
83 INTEGER LDWORK
84 DOUBLE PRECISION ANORM, EPS, OVFL, SMLNUM, UNFL, WNORM
85 * ..
86 * .. External Functions ..
87 DOUBLE PRECISION DLAMCH, ZLANGE
88 EXTERNAL DLAMCH, ZLANGE
89 * ..
90 * .. External Subroutines ..
91 EXTERNAL DLABAD, ZGEMM, ZLACPY, ZUNT01
92 * ..
93 * .. Intrinsic Functions ..
94 INTRINSIC DCMPLX, MAX, MIN
95 * ..
96 * .. Executable Statements ..
97 *
98 * Quick return if possible
99 *
100 IF( N.LE.0 ) THEN
101 RESULT( 1 ) = ZERO
102 RESULT( 2 ) = ZERO
103 RETURN
104 END IF
105 *
106 UNFL = DLAMCH( 'Safe minimum' )
107 EPS = DLAMCH( 'Precision' )
108 OVFL = ONE / UNFL
109 CALL DLABAD( UNFL, OVFL )
110 SMLNUM = UNFL*N / EPS
111 *
112 * Test 1: Compute norm( A - Q*H*Q' ) / ( norm(A) * N * EPS )
113 *
114 * Copy A to WORK
115 *
116 LDWORK = MAX( 1, N )
117 CALL ZLACPY( ' ', N, N, A, LDA, WORK, LDWORK )
118 *
119 * Compute Q*H
120 *
121 CALL ZGEMM( 'No transpose', 'No transpose', N, N, N,
122 $ DCMPLX( ONE ), Q, LDQ, H, LDH, DCMPLX( ZERO ),
123 $ WORK( LDWORK*N+1 ), LDWORK )
124 *
125 * Compute A - Q*H*Q'
126 *
127 CALL ZGEMM( 'No transpose', 'Conjugate transpose', N, N, N,
128 $ DCMPLX( -ONE ), WORK( LDWORK*N+1 ), LDWORK, Q, LDQ,
129 $ DCMPLX( ONE ), WORK, LDWORK )
130 *
131 ANORM = MAX( ZLANGE( '1', N, N, A, LDA, RWORK ), UNFL )
132 WNORM = ZLANGE( '1', N, N, WORK, LDWORK, RWORK )
133 *
134 * Note that RESULT(1) cannot overflow and is bounded by 1/(N*EPS)
135 *
136 RESULT( 1 ) = MIN( WNORM, ANORM ) / MAX( SMLNUM, ANORM*EPS ) / N
137 *
138 * Test 2: Compute norm( I - Q'*Q ) / ( N * EPS )
139 *
140 CALL ZUNT01( 'Columns', N, N, Q, LDQ, WORK, LWORK, RWORK,
141 $ RESULT( 2 ) )
142 *
143 RETURN
144 *
145 * End of ZHST01
146 *
147 END