LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Modules Pages

◆ shst01()

subroutine shst01 ( integer n,
integer ilo,
integer ihi,
real, dimension( lda, * ) a,
integer lda,
real, dimension( ldh, * ) h,
integer ldh,
real, dimension( ldq, * ) q,
integer ldq,
real, dimension( lwork ) work,
integer lwork,
real, dimension( 2 ) result )

SHST01

Purpose:
!> !> SHST01 tests the reduction of a general matrix A to upper Hessenberg !> form: A = Q*H*Q'. Two test ratios are computed; !> !> RESULT(1) = norm( A - Q*H*Q' ) / ( norm(A) * N * EPS ) !> RESULT(2) = norm( I - Q'*Q ) / ( N * EPS ) !> !> The matrix Q is assumed to be given explicitly as it would be !> following SGEHRD + SORGHR. !> !> In this version, ILO and IHI are not used and are assumed to be 1 and !> N, respectively. !>
Parameters
[in]N
!> N is INTEGER !> The order of the matrix A. N >= 0. !>
[in]ILO
!> ILO is INTEGER !>
[in]IHI
!> IHI is INTEGER !> !> A is assumed to be upper triangular in rows and columns !> 1:ILO-1 and IHI+1:N, so Q differs from the identity only in !> rows and columns ILO+1:IHI. !>
[in]A
!> A is REAL array, dimension (LDA,N) !> The original n by n matrix A. !>
[in]LDA
!> LDA is INTEGER !> The leading dimension of the array A. LDA >= max(1,N). !>
[in]H
!> H is REAL array, dimension (LDH,N) !> The upper Hessenberg matrix H from the reduction A = Q*H*Q' !> as computed by SGEHRD. H is assumed to be zero below the !> first subdiagonal. !>
[in]LDH
!> LDH is INTEGER !> The leading dimension of the array H. LDH >= max(1,N). !>
[in]Q
!> Q is REAL array, dimension (LDQ,N) !> The orthogonal matrix Q from the reduction A = Q*H*Q' as !> computed by SGEHRD + SORGHR. !>
[in]LDQ
!> LDQ is INTEGER !> The leading dimension of the array Q. LDQ >= max(1,N). !>
[out]WORK
!> WORK is REAL array, dimension (LWORK) !>
[in]LWORK
!> LWORK is INTEGER !> The length of the array WORK. LWORK >= 2*N*N. !>
[out]RESULT
!> RESULT is REAL array, dimension (2) !> RESULT(1) = norm( A - Q*H*Q' ) / ( norm(A) * N * EPS ) !> RESULT(2) = norm( I - Q'*Q ) / ( N * EPS ) !>
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 132 of file shst01.f.

134*
135* -- LAPACK test routine --
136* -- LAPACK is a software package provided by Univ. of Tennessee, --
137* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
138*
139* .. Scalar Arguments ..
140 INTEGER IHI, ILO, LDA, LDH, LDQ, LWORK, N
141* ..
142* .. Array Arguments ..
143 REAL A( LDA, * ), H( LDH, * ), Q( LDQ, * ),
144 $ RESULT( 2 ), WORK( LWORK )
145* ..
146*
147* =====================================================================
148*
149* .. Parameters ..
150 REAL ONE, ZERO
151 parameter( one = 1.0e+0, zero = 0.0e+0 )
152* ..
153* .. Local Scalars ..
154 INTEGER LDWORK
155 REAL ANORM, EPS, OVFL, SMLNUM, UNFL, WNORM
156* ..
157* .. External Functions ..
158 REAL SLAMCH, SLANGE
159 EXTERNAL slamch, slange
160* ..
161* .. External Subroutines ..
162 EXTERNAL sgemm, slacpy, sort01
163* ..
164* .. Intrinsic Functions ..
165 INTRINSIC max, min
166* ..
167* .. Executable Statements ..
168*
169* Quick return if possible
170*
171 IF( n.LE.0 ) THEN
172 result( 1 ) = zero
173 result( 2 ) = zero
174 RETURN
175 END IF
176*
177 unfl = slamch( 'Safe minimum' )
178 eps = slamch( 'Precision' )
179 ovfl = one / unfl
180 smlnum = unfl*n / eps
181*
182* Test 1: Compute norm( A - Q*H*Q' ) / ( norm(A) * N * EPS )
183*
184* Copy A to WORK
185*
186 ldwork = max( 1, n )
187 CALL slacpy( ' ', n, n, a, lda, work, ldwork )
188*
189* Compute Q*H
190*
191 CALL sgemm( 'No transpose', 'No transpose', n, n, n, one, q, ldq,
192 $ h, ldh, zero, work( ldwork*n+1 ), ldwork )
193*
194* Compute A - Q*H*Q'
195*
196 CALL sgemm( 'No transpose', 'Transpose', n, n, n, -one,
197 $ work( ldwork*n+1 ), ldwork, q, ldq, one, work,
198 $ ldwork )
199*
200 anorm = max( slange( '1', n, n, a, lda, work( ldwork*n+1 ) ),
201 $ unfl )
202 wnorm = slange( '1', n, n, work, ldwork, work( ldwork*n+1 ) )
203*
204* Note that RESULT(1) cannot overflow and is bounded by 1/(N*EPS)
205*
206 result( 1 ) = min( wnorm, anorm ) / max( smlnum, anorm*eps ) / n
207*
208* Test 2: Compute norm( I - Q'*Q ) / ( N * EPS )
209*
210 CALL sort01( 'Columns', n, n, q, ldq, work, lwork, result( 2 ) )
211*
212 RETURN
213*
214* End of SHST01
215*
subroutine sgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
SGEMM
Definition sgemm.f:188
subroutine slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
Definition slacpy.f:101
real function slamch(cmach)
SLAMCH
Definition slamch.f:68
real function slange(norm, m, n, a, lda, work)
SLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition slange.f:112
subroutine sort01(rowcol, m, n, u, ldu, work, lwork, resid)
SORT01
Definition sort01.f:116
Here is the call graph for this function:
Here is the caller graph for this function: