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

◆ sqrt11()

real function sqrt11 ( integer m,
integer k,
real, dimension( lda, * ) a,
integer lda,
real, dimension( * ) tau,
real, dimension( lwork ) work,
integer lwork )

SQRT11

Purpose:
!> !> SQRT11 computes the test ratio !> !> || Q'*Q - I || / (eps * m) !> !> where the orthogonal matrix Q is represented as a product of !> elementary transformations. Each transformation has the form !> !> H(k) = I - tau(k) v(k) v(k)' !> !> where tau(k) is stored in TAU(k) and v(k) is an m-vector of the form !> [ 0 ... 0 1 x(k) ]', where x(k) is a vector of length m-k stored !> in A(k+1:m,k). !>
Parameters
[in]M
!> M is INTEGER !> The number of rows of the matrix A. !>
[in]K
!> K is INTEGER !> The number of columns of A whose subdiagonal entries !> contain information about orthogonal transformations. !>
[in]A
!> A is REAL array, dimension (LDA,K) !> The (possibly partial) output of a QR reduction routine. !>
[in]LDA
!> LDA is INTEGER !> The leading dimension of the array A. !>
[in]TAU
!> TAU is REAL array, dimension (K) !> The scaling factors tau for the elementary transformations as !> computed by the QR factorization routine. !>
[out]WORK
!> WORK is REAL array, dimension (LWORK) !>
[in]LWORK
!> LWORK is INTEGER !> The length of the array WORK. LWORK >= M*M + M. !>
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 97 of file sqrt11.f.

98*
99* -- LAPACK test routine --
100* -- LAPACK is a software package provided by Univ. of Tennessee, --
101* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
102*
103* .. Scalar Arguments ..
104 INTEGER K, LDA, LWORK, M
105* ..
106* .. Array Arguments ..
107 REAL A( LDA, * ), TAU( * ), WORK( LWORK )
108* ..
109*
110* =====================================================================
111*
112* .. Parameters ..
113 REAL ZERO, ONE
114 parameter( zero = 0.0e0, one = 1.0e0 )
115* ..
116* .. Local Scalars ..
117 INTEGER INFO, J
118* ..
119* .. External Functions ..
120 REAL SLAMCH, SLANGE
121 EXTERNAL slamch, slange
122* ..
123* .. External Subroutines ..
124 EXTERNAL slaset, sorm2r, xerbla
125* ..
126* .. Intrinsic Functions ..
127 INTRINSIC real
128* ..
129* .. Local Arrays ..
130 REAL RDUMMY( 1 )
131* ..
132* .. Executable Statements ..
133*
134 sqrt11 = zero
135*
136* Test for sufficient workspace
137*
138 IF( lwork.LT.m*m+m ) THEN
139 CALL xerbla( 'SQRT11', 7 )
140 RETURN
141 END IF
142*
143* Quick return if possible
144*
145 IF( m.LE.0 )
146 $ RETURN
147*
148 CALL slaset( 'Full', m, m, zero, one, work, m )
149*
150* Form Q
151*
152 CALL sorm2r( 'Left', 'No transpose', m, m, k, a, lda, tau, work,
153 $ m, work( m*m+1 ), info )
154*
155* Form Q'*Q
156*
157 CALL sorm2r( 'Left', 'Transpose', m, m, k, a, lda, tau, work, m,
158 $ work( m*m+1 ), info )
159*
160 DO j = 1, m
161 work( ( j-1 )*m+j ) = work( ( j-1 )*m+j ) - one
162 END DO
163*
164 sqrt11 = slange( 'One-norm', m, m, work, m, rdummy ) /
165 $ ( real( m )*slamch( 'Epsilon' ) )
166*
167 RETURN
168*
169* End of SQRT11
170*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
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 slaset(uplo, m, n, alpha, beta, a, lda)
SLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
Definition slaset.f:108
subroutine sorm2r(side, trans, m, n, k, a, lda, tau, c, ldc, work, info)
SORM2R multiplies a general matrix by the orthogonal matrix from a QR factorization determined by sge...
Definition sorm2r.f:157
real function sqrt11(m, k, a, lda, tau, work, lwork)
SQRT11
Definition sqrt11.f:98
Here is the call graph for this function:
Here is the caller graph for this function: