LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dlarfy.f
Go to the documentation of this file.
1*> \brief \b DLARFY
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* SUBROUTINE DLARFY( UPLO, N, V, INCV, TAU, C, LDC, WORK )
12*
13* .. Scalar Arguments ..
14* CHARACTER UPLO
15* INTEGER INCV, LDC, N
16* DOUBLE PRECISION TAU
17* ..
18* .. Array Arguments ..
19* DOUBLE PRECISION C( LDC, * ), V( * ), WORK( * )
20* ..
21*
22*
23*> \par Purpose:
24* =============
25*>
26*> \verbatim
27*>
28*> DLARFY applies an elementary reflector, or Householder matrix, H,
29*> to an n x n symmetric matrix C, from both the left and the right.
30*>
31*> H is represented in the form
32*>
33*> H = I - tau * v * v'
34*>
35*> where tau is a scalar and v is a vector.
36*>
37*> If tau is zero, then H is taken to be the unit matrix.
38*> \endverbatim
39*
40* Arguments:
41* ==========
42*
43*> \param[in] UPLO
44*> \verbatim
45*> UPLO is CHARACTER*1
46*> Specifies whether the upper or lower triangular part of the
47*> symmetric matrix C is stored.
48*> = 'U': Upper triangle
49*> = 'L': Lower triangle
50*> \endverbatim
51*>
52*> \param[in] N
53*> \verbatim
54*> N is INTEGER
55*> The number of rows and columns of the matrix C. N >= 0.
56*> \endverbatim
57*>
58*> \param[in] V
59*> \verbatim
60*> V is DOUBLE PRECISION array, dimension
61*> (1 + (N-1)*abs(INCV))
62*> The vector v as described above.
63*> \endverbatim
64*>
65*> \param[in] INCV
66*> \verbatim
67*> INCV is INTEGER
68*> The increment between successive elements of v. INCV must
69*> not be zero.
70*> \endverbatim
71*>
72*> \param[in] TAU
73*> \verbatim
74*> TAU is DOUBLE PRECISION
75*> The value tau as described above.
76*> \endverbatim
77*>
78*> \param[in,out] C
79*> \verbatim
80*> C is DOUBLE PRECISION array, dimension (LDC, N)
81*> On entry, the matrix C.
82*> On exit, C is overwritten by H * C * H'.
83*> \endverbatim
84*>
85*> \param[in] LDC
86*> \verbatim
87*> LDC is INTEGER
88*> The leading dimension of the array C. LDC >= max( 1, N ).
89*> \endverbatim
90*>
91*> \param[out] WORK
92*> \verbatim
93*> WORK is DOUBLE PRECISION array, dimension (N)
94*> \endverbatim
95*
96* Authors:
97* ========
98*
99*> \author Univ. of Tennessee
100*> \author Univ. of California Berkeley
101*> \author Univ. of Colorado Denver
102*> \author NAG Ltd.
103*
104*> \ingroup larfy
105*
106* =====================================================================
107 SUBROUTINE dlarfy( UPLO, N, V, INCV, TAU, C, LDC, WORK )
108*
109* -- LAPACK test routine --
110* -- LAPACK is a software package provided by Univ. of Tennessee, --
111* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
112*
113* .. Scalar Arguments ..
114 CHARACTER UPLO
115 INTEGER INCV, LDC, N
116 DOUBLE PRECISION TAU
117* ..
118* .. Array Arguments ..
119 DOUBLE PRECISION C( LDC, * ), V( * ), WORK( * )
120* ..
121*
122* =====================================================================
123*
124* .. Parameters ..
125 DOUBLE PRECISION ONE, ZERO, HALF
126 parameter( one = 1.0d+0, zero = 0.0d+0, half = 0.5d+0 )
127* ..
128* .. Local Scalars ..
129 DOUBLE PRECISION ALPHA
130* ..
131* .. External Subroutines ..
132 EXTERNAL daxpy, dsymv, dsyr2
133* ..
134* .. External Functions ..
135 DOUBLE PRECISION DDOT
136 EXTERNAL ddot
137* ..
138* .. Executable Statements ..
139*
140 IF( tau.EQ.zero )
141 $ RETURN
142*
143* Form w:= C * v
144*
145 CALL dsymv( uplo, n, one, c, ldc, v, incv, zero, work, 1 )
146*
147 alpha = -half*tau*ddot( n, work, 1, v, incv )
148 CALL daxpy( n, alpha, v, incv, work, 1 )
149*
150* C := C - v * w' - w * v'
151*
152 CALL dsyr2( uplo, n, -tau, v, incv, work, 1, c, ldc )
153*
154 RETURN
155*
156* End of DLARFY
157*
158 END
subroutine daxpy(n, da, dx, incx, dy, incy)
DAXPY
Definition daxpy.f:89
subroutine dsymv(uplo, n, alpha, a, lda, x, incx, beta, y, incy)
DSYMV
Definition dsymv.f:152
subroutine dsyr2(uplo, n, alpha, x, incx, y, incy, a, lda)
DSYR2
Definition dsyr2.f:147
subroutine dlarfy(uplo, n, v, incv, tau, c, ldc, work)
DLARFY
Definition dlarfy.f:108