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

◆ zrzt01()

double precision function zrzt01 ( integer m,
integer n,
complex*16, dimension( lda, * ) a,
complex*16, dimension( lda, * ) af,
integer lda,
complex*16, dimension( * ) tau,
complex*16, dimension( lwork ) work,
integer lwork )

ZRZT01

Purpose:
!>
!> ZRZT01 returns
!>      || A - R*Q || / ( M * eps * ||A|| )
!> for an upper trapezoidal A that was factored with ZTZRZF.
!> 
Parameters
[in]M
!>          M is INTEGER
!>          The number of rows of the matrices A and AF.
!> 
[in]N
!>          N is INTEGER
!>          The number of columns of the matrices A and AF.
!> 
[in]A
!>          A is COMPLEX*16 array, dimension (LDA,N)
!>          The original upper trapezoidal M by N matrix A.
!> 
[in]AF
!>          AF is COMPLEX*16 array, dimension (LDA,N)
!>          The output of ZTZRZF for input matrix A.
!>          The lower triangle is not referenced.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the arrays A and AF.
!> 
[in]TAU
!>          TAU is COMPLEX*16 array, dimension (M)
!>          Details of the  Householder transformations as returned by
!>          ZTZRZF.
!> 
[out]WORK
!>          WORK is COMPLEX*16 array, dimension (LWORK)
!> 
[in]LWORK
!>          LWORK is INTEGER
!>          The length of the array WORK.  LWORK >= m*n + m.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 96 of file zrzt01.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 LDA, LWORK, M, N
105* ..
106* .. Array Arguments ..
107 COMPLEX*16 A( LDA, * ), AF( LDA, * ), TAU( * ),
108 $ WORK( LWORK )
109* ..
110*
111* =====================================================================
112*
113* .. Parameters ..
114 DOUBLE PRECISION ZERO, ONE
115 parameter( zero = 0.0d0, one = 1.0d0 )
116* ..
117* .. Local Scalars ..
118 INTEGER I, INFO, J
119 DOUBLE PRECISION NORMA
120* ..
121* .. Local Arrays ..
122 DOUBLE PRECISION RWORK( 1 )
123* ..
124* .. External Functions ..
125 DOUBLE PRECISION DLAMCH, ZLANGE
126 EXTERNAL dlamch, zlange
127* ..
128* .. External Subroutines ..
129 EXTERNAL xerbla, zaxpy, zlaset, zunmrz
130* ..
131* .. Intrinsic Functions ..
132 INTRINSIC dble, dcmplx, max
133* ..
134* .. Executable Statements ..
135*
136 zrzt01 = zero
137*
138 IF( lwork.LT.m*n+m ) THEN
139 CALL xerbla( 'ZRZT01', 8 )
140 RETURN
141 END IF
142*
143* Quick return if possible
144*
145 IF( m.LE.0 .OR. n.LE.0 )
146 $ RETURN
147*
148 norma = zlange( 'One-norm', m, n, a, lda, rwork )
149*
150* Copy upper triangle R
151*
152 CALL zlaset( 'Full', m, n, dcmplx( zero ), dcmplx( zero ), work,
153 $ m )
154 DO 20 j = 1, m
155 DO 10 i = 1, j
156 work( ( j-1 )*m+i ) = af( i, j )
157 10 CONTINUE
158 20 CONTINUE
159*
160* R = R * P(1) * ... *P(m)
161*
162 CALL zunmrz( 'Right', 'No transpose', m, n, m, n-m, af, lda, tau,
163 $ work, m, work( m*n+1 ), lwork-m*n, info )
164*
165* R = R - A
166*
167 DO 30 i = 1, n
168 CALL zaxpy( m, dcmplx( -one ), a( 1, i ), 1,
169 $ work( ( i-1 )*m+1 ), 1 )
170 30 CONTINUE
171*
172 zrzt01 = zlange( 'One-norm', m, n, work, m, rwork )
173*
174 zrzt01 = zrzt01 / ( dlamch( 'Epsilon' )*dble( max( m, n ) ) )
175 IF( norma.NE.zero )
176 $ zrzt01 = zrzt01 / norma
177*
178 RETURN
179*
180* End of ZRZT01
181*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zaxpy(n, za, zx, incx, zy, incy)
ZAXPY
Definition zaxpy.f:88
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:113
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:104
subroutine zunmrz(side, trans, m, n, k, l, a, lda, tau, c, ldc, work, lwork, info)
ZUNMRZ
Definition zunmrz.f:186
double precision function zrzt01(m, n, a, af, lda, tau, work, lwork)
ZRZT01
Definition zrzt01.f:98
Here is the call graph for this function:
Here is the caller graph for this function: