LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
slatzm.f
Go to the documentation of this file.
1 *> \brief \b SLATZM
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SLATZM + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slatzm.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slatzm.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slatzm.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE SLATZM( SIDE, M, N, V, INCV, TAU, C1, C2, LDC, WORK )
22 *
23 * .. Scalar Arguments ..
24 * CHARACTER SIDE
25 * INTEGER INCV, LDC, M, N
26 * REAL TAU
27 * ..
28 * .. Array Arguments ..
29 * REAL C1( LDC, * ), C2( LDC, * ), V( * ), WORK( * )
30 * ..
31 *
32 *
33 *> \par Purpose:
34 * =============
35 *>
36 *> \verbatim
37 *>
38 *> This routine is deprecated and has been replaced by routine SORMRZ.
39 *>
40 *> SLATZM applies a Householder matrix generated by STZRQF to a matrix.
41 *>
42 *> Let P = I - tau*u*u**T, u = ( 1 ),
43 *> ( v )
44 *> where v is an (m-1) vector if SIDE = 'L', or a (n-1) vector if
45 *> SIDE = 'R'.
46 *>
47 *> If SIDE equals 'L', let
48 *> C = [ C1 ] 1
49 *> [ C2 ] m-1
50 *> n
51 *> Then C is overwritten by P*C.
52 *>
53 *> If SIDE equals 'R', let
54 *> C = [ C1, C2 ] m
55 *> 1 n-1
56 *> Then C is overwritten by C*P.
57 *> \endverbatim
58 *
59 * Arguments:
60 * ==========
61 *
62 *> \param[in] SIDE
63 *> \verbatim
64 *> SIDE is CHARACTER*1
65 *> = 'L': form P * C
66 *> = 'R': form C * P
67 *> \endverbatim
68 *>
69 *> \param[in] M
70 *> \verbatim
71 *> M is INTEGER
72 *> The number of rows of the matrix C.
73 *> \endverbatim
74 *>
75 *> \param[in] N
76 *> \verbatim
77 *> N is INTEGER
78 *> The number of columns of the matrix C.
79 *> \endverbatim
80 *>
81 *> \param[in] V
82 *> \verbatim
83 *> V is REAL array, dimension
84 *> (1 + (M-1)*abs(INCV)) if SIDE = 'L'
85 *> (1 + (N-1)*abs(INCV)) if SIDE = 'R'
86 *> The vector v in the representation of P. V is not used
87 *> if TAU = 0.
88 *> \endverbatim
89 *>
90 *> \param[in] INCV
91 *> \verbatim
92 *> INCV is INTEGER
93 *> The increment between elements of v. INCV <> 0
94 *> \endverbatim
95 *>
96 *> \param[in] TAU
97 *> \verbatim
98 *> TAU is REAL
99 *> The value tau in the representation of P.
100 *> \endverbatim
101 *>
102 *> \param[in,out] C1
103 *> \verbatim
104 *> C1 is REAL array, dimension
105 *> (LDC,N) if SIDE = 'L'
106 *> (M,1) if SIDE = 'R'
107 *> On entry, the n-vector C1 if SIDE = 'L', or the m-vector C1
108 *> if SIDE = 'R'.
109 *>
110 *> On exit, the first row of P*C if SIDE = 'L', or the first
111 *> column of C*P if SIDE = 'R'.
112 *> \endverbatim
113 *>
114 *> \param[in,out] C2
115 *> \verbatim
116 *> C2 is REAL array, dimension
117 *> (LDC, N) if SIDE = 'L'
118 *> (LDC, N-1) if SIDE = 'R'
119 *> On entry, the (m - 1) x n matrix C2 if SIDE = 'L', or the
120 *> m x (n - 1) matrix C2 if SIDE = 'R'.
121 *>
122 *> On exit, rows 2:m of P*C if SIDE = 'L', or columns 2:m of C*P
123 *> if SIDE = 'R'.
124 *> \endverbatim
125 *>
126 *> \param[in] LDC
127 *> \verbatim
128 *> LDC is INTEGER
129 *> The leading dimension of the arrays C1 and C2. LDC >= (1,M).
130 *> \endverbatim
131 *>
132 *> \param[out] WORK
133 *> \verbatim
134 *> WORK is REAL array, dimension
135 *> (N) if SIDE = 'L'
136 *> (M) if SIDE = 'R'
137 *> \endverbatim
138 *
139 * Authors:
140 * ========
141 *
142 *> \author Univ. of Tennessee
143 *> \author Univ. of California Berkeley
144 *> \author Univ. of Colorado Denver
145 *> \author NAG Ltd.
146 *
147 *> \date November 2011
148 *
149 *> \ingroup realOTHERcomputational
150 *
151 * =====================================================================
152  SUBROUTINE slatzm( SIDE, M, N, V, INCV, TAU, C1, C2, LDC, WORK )
153 *
154 * -- LAPACK computational routine (version 3.4.0) --
155 * -- LAPACK is a software package provided by Univ. of Tennessee, --
156 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
157 * November 2011
158 *
159 * .. Scalar Arguments ..
160  CHARACTER SIDE
161  INTEGER INCV, LDC, M, N
162  REAL TAU
163 * ..
164 * .. Array Arguments ..
165  REAL C1( ldc, * ), C2( ldc, * ), V( * ), WORK( * )
166 * ..
167 *
168 * =====================================================================
169 *
170 * .. Parameters ..
171  REAL ONE, ZERO
172  parameter ( one = 1.0e+0, zero = 0.0e+0 )
173 * ..
174 * .. External Subroutines ..
175  EXTERNAL saxpy, scopy, sgemv, sger
176 * ..
177 * .. External Functions ..
178  LOGICAL LSAME
179  EXTERNAL lsame
180 * ..
181 * .. Intrinsic Functions ..
182  INTRINSIC min
183 * ..
184 * .. Executable Statements ..
185 *
186  IF( ( min( m, n ).EQ.0 ) .OR. ( tau.EQ.zero ) )
187  $ RETURN
188 *
189  IF( lsame( side, 'L' ) ) THEN
190 *
191 * w := (C1 + v**T * C2)**T
192 *
193  CALL scopy( n, c1, ldc, work, 1 )
194  CALL sgemv( 'Transpose', m-1, n, one, c2, ldc, v, incv, one,
195  $ work, 1 )
196 *
197 * [ C1 ] := [ C1 ] - tau* [ 1 ] * w**T
198 * [ C2 ] [ C2 ] [ v ]
199 *
200  CALL saxpy( n, -tau, work, 1, c1, ldc )
201  CALL sger( m-1, n, -tau, v, incv, work, 1, c2, ldc )
202 *
203  ELSE IF( lsame( side, 'R' ) ) THEN
204 *
205 * w := C1 + C2 * v
206 *
207  CALL scopy( m, c1, 1, work, 1 )
208  CALL sgemv( 'No transpose', m, n-1, one, c2, ldc, v, incv, one,
209  $ work, 1 )
210 *
211 * [ C1, C2 ] := [ C1, C2 ] - tau* w * [ 1 , v**T]
212 *
213  CALL saxpy( m, -tau, work, 1, c1, 1 )
214  CALL sger( m, n-1, -tau, work, 1, v, incv, c2, ldc )
215  END IF
216 *
217  RETURN
218 *
219 * End of SLATZM
220 *
221  END
subroutine sger(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)
SGER
Definition: sger.f:132
subroutine sgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
SGEMV
Definition: sgemv.f:158
subroutine saxpy(N, SA, SX, INCX, SY, INCY)
SAXPY
Definition: saxpy.f:54
subroutine slatzm(SIDE, M, N, V, INCV, TAU, C1, C2, LDC, WORK)
SLATZM
Definition: slatzm.f:153
subroutine scopy(N, SX, INCX, SY, INCY)
SCOPY
Definition: scopy.f:53