LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zqrt11()

double precision function zqrt11 ( integer  m,
integer  k,
complex*16, dimension( lda, * )  a,
integer  lda,
complex*16, dimension( * )  tau,
complex*16, dimension( lwork )  work,
integer  lwork 
)

ZQRT11

Purpose:
 ZQRT11 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 COMPLEX*16 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 COMPLEX*16 array, dimension (K)
          The scaling factors tau for the elementary transformations as
          computed by the QR factorization routine.
[out]WORK
          WORK is COMPLEX*16 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 zqrt11.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 COMPLEX*16 A( LDA, * ), TAU( * ), WORK( LWORK )
108* ..
109*
110* =====================================================================
111*
112* .. Parameters ..
113 DOUBLE PRECISION ZERO, ONE
114 parameter( zero = 0.0d0, one = 1.0d0 )
115* ..
116* .. Local Scalars ..
117 INTEGER INFO, J
118* ..
119* .. External Functions ..
120 DOUBLE PRECISION DLAMCH, ZLANGE
121 EXTERNAL dlamch, zlange
122* ..
123* .. External Subroutines ..
124 EXTERNAL xerbla, zlaset, zunm2r
125* ..
126* .. Intrinsic Functions ..
127 INTRINSIC dble, dcmplx
128* ..
129* .. Local Arrays ..
130 DOUBLE PRECISION RDUMMY( 1 )
131* ..
132* .. Executable Statements ..
133*
134 zqrt11 = zero
135*
136* Test for sufficient workspace
137*
138 IF( lwork.LT.m*m+m ) THEN
139 CALL xerbla( 'ZQRT11', 7 )
140 RETURN
141 END IF
142*
143* Quick return if possible
144*
145 IF( m.LE.0 )
146 $ RETURN
147*
148 CALL zlaset( 'Full', m, m, dcmplx( zero ), dcmplx( one ), work,
149 $ m )
150*
151* Form Q
152*
153 CALL zunm2r( 'Left', 'No transpose', m, m, k, a, lda, tau, work,
154 $ m, work( m*m+1 ), info )
155*
156* Form Q'*Q
157*
158 CALL zunm2r( 'Left', 'Conjugate transpose', m, m, k, a, lda, tau,
159 $ work, m, work( m*m+1 ), info )
160*
161 DO j = 1, m
162 work( ( j-1 )*m+j ) = work( ( j-1 )*m+j ) - one
163 END DO
164*
165 zqrt11 = zlange( 'One-norm', m, m, work, m, rdummy ) /
166 $ ( dble( m )*dlamch( 'Epsilon' ) )
167*
168 RETURN
169*
170* End of ZQRT11
171*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
double precision function zlange(norm, m, n, a, lda, work)
ZLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition zlange.f:115
subroutine zlaset(uplo, m, n, alpha, beta, a, lda)
ZLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
Definition zlaset.f:106
subroutine zunm2r(side, trans, m, n, k, a, lda, tau, c, ldc, work, info)
ZUNM2R multiplies a general matrix by the unitary matrix from a QR factorization determined by cgeqrf...
Definition zunm2r.f:159
double precision function zqrt11(m, k, a, lda, tau, work, lwork)
ZQRT11
Definition zqrt11.f:98
Here is the call graph for this function:
Here is the caller graph for this function: