LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
drzt01.f
Go to the documentation of this file.
1*> \brief \b DRZT01
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* DOUBLE PRECISION FUNCTION DRZT01( M, N, A, AF, LDA, TAU, WORK,
12* LWORK )
13*
14* .. Scalar Arguments ..
15* INTEGER LDA, LWORK, M, N
16* ..
17* .. Array Arguments ..
18* DOUBLE PRECISION A( LDA, * ), AF( LDA, * ), TAU( * ),
19* $ WORK( LWORK )
20* ..
21*
22*
23*> \par Purpose:
24* =============
25*>
26*> \verbatim
27*>
28*> DRZT01 returns
29*> || A - R*Q || / ( M * eps * ||A|| )
30*> for an upper trapezoidal A that was factored with DTZRZF.
31*> \endverbatim
32*
33* Arguments:
34* ==========
35*
36*> \param[in] M
37*> \verbatim
38*> M is INTEGER
39*> The number of rows of the matrices A and AF.
40*> \endverbatim
41*>
42*> \param[in] N
43*> \verbatim
44*> N is INTEGER
45*> The number of columns of the matrices A and AF.
46*> \endverbatim
47*>
48*> \param[in] A
49*> \verbatim
50*> A is DOUBLE PRECISION array, dimension (LDA,N)
51*> The original upper trapezoidal M by N matrix A.
52*> \endverbatim
53*>
54*> \param[in] AF
55*> \verbatim
56*> AF is DOUBLE PRECISION array, dimension (LDA,N)
57*> The output of DTZRZF for input matrix A.
58*> The lower triangle is not referenced.
59*> \endverbatim
60*>
61*> \param[in] LDA
62*> \verbatim
63*> LDA is INTEGER
64*> The leading dimension of the arrays A and AF.
65*> \endverbatim
66*>
67*> \param[in] TAU
68*> \verbatim
69*> TAU is DOUBLE PRECISION array, dimension (M)
70*> Details of the Householder transformations as returned by
71*> DTZRZF.
72*> \endverbatim
73*>
74*> \param[out] WORK
75*> \verbatim
76*> WORK is DOUBLE PRECISION array, dimension (LWORK)
77*> \endverbatim
78*>
79*> \param[in] LWORK
80*> \verbatim
81*> LWORK is INTEGER
82*> The length of the array WORK. LWORK >= m*n + m*nb.
83*> \endverbatim
84*
85* Authors:
86* ========
87*
88*> \author Univ. of Tennessee
89*> \author Univ. of California Berkeley
90*> \author Univ. of Colorado Denver
91*> \author NAG Ltd.
92*
93*> \ingroup double_lin
94*
95* =====================================================================
96 DOUBLE PRECISION FUNCTION drzt01( M, N, A, AF, LDA, TAU, WORK,
97 $ LWORK )
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 DOUBLE PRECISION a( lda, * ), af( lda, * ), tau( * ),
108 $ work( lwork )
109* ..
110*
111* =====================================================================
112*
113* .. Parameters ..
114 DOUBLE PRECISION zero, one
115 parameter( zero = 0.0d+0, one = 1.0d+0 )
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, dlange
126 EXTERNAL dlamch, dlange
127* ..
128* .. External Subroutines ..
129 EXTERNAL daxpy, dlaset, dormrz, xerbla
130* ..
131* .. Intrinsic Functions ..
132 INTRINSIC dble, max
133* ..
134* .. Executable Statements ..
135*
136 drzt01 = zero
137*
138 IF( lwork.LT.m*n+m ) THEN
139 CALL xerbla( 'DRZT01', 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 = dlange( 'One-norm', m, n, a, lda, rwork )
149*
150* Copy upper triangle R
151*
152 CALL dlaset( 'Full', m, n, zero, zero, work, m )
153 DO 20 j = 1, m
154 DO 10 i = 1, j
155 work( ( j-1 )*m+i ) = af( i, j )
156 10 CONTINUE
157 20 CONTINUE
158*
159* R = R * P(1) * ... *P(m)
160*
161 CALL dormrz( 'Right', 'No transpose', m, n, m, n-m, af, lda, tau,
162 $ work, m, work( m*n+1 ), lwork-m*n, info )
163*
164* R = R - A
165*
166 DO 30 i = 1, n
167 CALL daxpy( m, -one, a( 1, i ), 1, work( ( i-1 )*m+1 ), 1 )
168 30 CONTINUE
169*
170 drzt01 = dlange( 'One-norm', m, n, work, m, rwork )
171*
172 drzt01 = drzt01 / ( dlamch( 'Epsilon' )*dble( max( m, n ) ) )
173 IF( norma.NE.zero )
174 $ drzt01 = drzt01 / norma
175*
176 RETURN
177*
178* End of DRZT01
179*
180 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
double precision function drzt01(m, n, a, af, lda, tau, work, lwork)
DRZT01
Definition drzt01.f:98
subroutine daxpy(n, da, dx, incx, dy, incy)
DAXPY
Definition daxpy.f:89
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
double precision function dlange(norm, m, n, a, lda, work)
DLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition dlange.f:114
subroutine dlaset(uplo, m, n, alpha, beta, a, lda)
DLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
Definition dlaset.f:110
subroutine dormrz(side, trans, m, n, k, l, a, lda, tau, c, ldc, work, lwork, info)
DORMRZ
Definition dormrz.f:187