LAPACK 3.11.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
ztrmv.f
Go to the documentation of this file.
1*> \brief \b ZTRMV
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 ZTRMV(UPLO,TRANS,DIAG,N,A,LDA,X,INCX)
12*
13* .. Scalar Arguments ..
14* INTEGER INCX,LDA,N
15* CHARACTER DIAG,TRANS,UPLO
16* ..
17* .. Array Arguments ..
18* COMPLEX*16 A(LDA,*),X(*)
19* ..
20*
21*
22*> \par Purpose:
23* =============
24*>
25*> \verbatim
26*>
27*> ZTRMV performs one of the matrix-vector operations
28*>
29*> x := A*x, or x := A**T*x, or x := A**H*x,
30*>
31*> where x is an n element vector and A is an n by n unit, or non-unit,
32*> upper or lower triangular matrix.
33*> \endverbatim
34*
35* Arguments:
36* ==========
37*
38*> \param[in] UPLO
39*> \verbatim
40*> UPLO is CHARACTER*1
41*> On entry, UPLO specifies whether the matrix is an upper or
42*> lower triangular matrix as follows:
43*>
44*> UPLO = 'U' or 'u' A is an upper triangular matrix.
45*>
46*> UPLO = 'L' or 'l' A is a lower triangular matrix.
47*> \endverbatim
48*>
49*> \param[in] TRANS
50*> \verbatim
51*> TRANS is CHARACTER*1
52*> On entry, TRANS specifies the operation to be performed as
53*> follows:
54*>
55*> TRANS = 'N' or 'n' x := A*x.
56*>
57*> TRANS = 'T' or 't' x := A**T*x.
58*>
59*> TRANS = 'C' or 'c' x := A**H*x.
60*> \endverbatim
61*>
62*> \param[in] DIAG
63*> \verbatim
64*> DIAG is CHARACTER*1
65*> On entry, DIAG specifies whether or not A is unit
66*> triangular as follows:
67*>
68*> DIAG = 'U' or 'u' A is assumed to be unit triangular.
69*>
70*> DIAG = 'N' or 'n' A is not assumed to be unit
71*> triangular.
72*> \endverbatim
73*>
74*> \param[in] N
75*> \verbatim
76*> N is INTEGER
77*> On entry, N specifies the order of the matrix A.
78*> N must be at least zero.
79*> \endverbatim
80*>
81*> \param[in] A
82*> \verbatim
83*> A is COMPLEX*16 array, dimension ( LDA, N ).
84*> Before entry with UPLO = 'U' or 'u', the leading n by n
85*> upper triangular part of the array A must contain the upper
86*> triangular matrix and the strictly lower triangular part of
87*> A is not referenced.
88*> Before entry with UPLO = 'L' or 'l', the leading n by n
89*> lower triangular part of the array A must contain the lower
90*> triangular matrix and the strictly upper triangular part of
91*> A is not referenced.
92*> Note that when DIAG = 'U' or 'u', the diagonal elements of
93*> A are not referenced either, but are assumed to be unity.
94*> \endverbatim
95*>
96*> \param[in] LDA
97*> \verbatim
98*> LDA is INTEGER
99*> On entry, LDA specifies the first dimension of A as declared
100*> in the calling (sub) program. LDA must be at least
101*> max( 1, n ).
102*> \endverbatim
103*>
104*> \param[in,out] X
105*> \verbatim
106*> X is COMPLEX*16 array, dimension at least
107*> ( 1 + ( n - 1 )*abs( INCX ) ).
108*> Before entry, the incremented array X must contain the n
109*> element vector x. On exit, X is overwritten with the
110*> transformed vector x.
111*> \endverbatim
112*>
113*> \param[in] INCX
114*> \verbatim
115*> INCX is INTEGER
116*> On entry, INCX specifies the increment for the elements of
117*> X. INCX must not be zero.
118*> \endverbatim
119*
120* Authors:
121* ========
122*
123*> \author Univ. of Tennessee
124*> \author Univ. of California Berkeley
125*> \author Univ. of Colorado Denver
126*> \author NAG Ltd.
127*
128*> \ingroup complex16_blas_level2
129*
130*> \par Further Details:
131* =====================
132*>
133*> \verbatim
134*>
135*> Level 2 Blas routine.
136*> The vector and matrix arguments are not referenced when N = 0, or M = 0
137*>
138*> -- Written on 22-October-1986.
139*> Jack Dongarra, Argonne National Lab.
140*> Jeremy Du Croz, Nag Central Office.
141*> Sven Hammarling, Nag Central Office.
142*> Richard Hanson, Sandia National Labs.
143*> \endverbatim
144*>
145* =====================================================================
146 SUBROUTINE ztrmv(UPLO,TRANS,DIAG,N,A,LDA,X,INCX)
147*
148* -- Reference BLAS level2 routine --
149* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
150* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
151*
152* .. Scalar Arguments ..
153 INTEGER INCX,LDA,N
154 CHARACTER DIAG,TRANS,UPLO
155* ..
156* .. Array Arguments ..
157 COMPLEX*16 A(LDA,*),X(*)
158* ..
159*
160* =====================================================================
161*
162* .. Parameters ..
163 COMPLEX*16 ZERO
164 parameter(zero= (0.0d+0,0.0d+0))
165* ..
166* .. Local Scalars ..
167 COMPLEX*16 TEMP
168 INTEGER I,INFO,IX,J,JX,KX
169 LOGICAL NOCONJ,NOUNIT
170* ..
171* .. External Functions ..
172 LOGICAL LSAME
173 EXTERNAL lsame
174* ..
175* .. External Subroutines ..
176 EXTERNAL xerbla
177* ..
178* .. Intrinsic Functions ..
179 INTRINSIC dconjg,max
180* ..
181*
182* Test the input parameters.
183*
184 info = 0
185 IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
186 info = 1
187 ELSE IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.
188 + .NOT.lsame(trans,'C')) THEN
189 info = 2
190 ELSE IF (.NOT.lsame(diag,'U') .AND. .NOT.lsame(diag,'N')) THEN
191 info = 3
192 ELSE IF (n.LT.0) THEN
193 info = 4
194 ELSE IF (lda.LT.max(1,n)) THEN
195 info = 6
196 ELSE IF (incx.EQ.0) THEN
197 info = 8
198 END IF
199 IF (info.NE.0) THEN
200 CALL xerbla('ZTRMV ',info)
201 RETURN
202 END IF
203*
204* Quick return if possible.
205*
206 IF (n.EQ.0) RETURN
207*
208 noconj = lsame(trans,'T')
209 nounit = lsame(diag,'N')
210*
211* Set up the start point in X if the increment is not unity. This
212* will be ( N - 1 )*INCX too small for descending loops.
213*
214 IF (incx.LE.0) THEN
215 kx = 1 - (n-1)*incx
216 ELSE IF (incx.NE.1) THEN
217 kx = 1
218 END IF
219*
220* Start the operations. In this version the elements of A are
221* accessed sequentially with one pass through A.
222*
223 IF (lsame(trans,'N')) THEN
224*
225* Form x := A*x.
226*
227 IF (lsame(uplo,'U')) THEN
228 IF (incx.EQ.1) THEN
229 DO 20 j = 1,n
230 IF (x(j).NE.zero) THEN
231 temp = x(j)
232 DO 10 i = 1,j - 1
233 x(i) = x(i) + temp*a(i,j)
234 10 CONTINUE
235 IF (nounit) x(j) = x(j)*a(j,j)
236 END IF
237 20 CONTINUE
238 ELSE
239 jx = kx
240 DO 40 j = 1,n
241 IF (x(jx).NE.zero) THEN
242 temp = x(jx)
243 ix = kx
244 DO 30 i = 1,j - 1
245 x(ix) = x(ix) + temp*a(i,j)
246 ix = ix + incx
247 30 CONTINUE
248 IF (nounit) x(jx) = x(jx)*a(j,j)
249 END IF
250 jx = jx + incx
251 40 CONTINUE
252 END IF
253 ELSE
254 IF (incx.EQ.1) THEN
255 DO 60 j = n,1,-1
256 IF (x(j).NE.zero) THEN
257 temp = x(j)
258 DO 50 i = n,j + 1,-1
259 x(i) = x(i) + temp*a(i,j)
260 50 CONTINUE
261 IF (nounit) x(j) = x(j)*a(j,j)
262 END IF
263 60 CONTINUE
264 ELSE
265 kx = kx + (n-1)*incx
266 jx = kx
267 DO 80 j = n,1,-1
268 IF (x(jx).NE.zero) THEN
269 temp = x(jx)
270 ix = kx
271 DO 70 i = n,j + 1,-1
272 x(ix) = x(ix) + temp*a(i,j)
273 ix = ix - incx
274 70 CONTINUE
275 IF (nounit) x(jx) = x(jx)*a(j,j)
276 END IF
277 jx = jx - incx
278 80 CONTINUE
279 END IF
280 END IF
281 ELSE
282*
283* Form x := A**T*x or x := A**H*x.
284*
285 IF (lsame(uplo,'U')) THEN
286 IF (incx.EQ.1) THEN
287 DO 110 j = n,1,-1
288 temp = x(j)
289 IF (noconj) THEN
290 IF (nounit) temp = temp*a(j,j)
291 DO 90 i = j - 1,1,-1
292 temp = temp + a(i,j)*x(i)
293 90 CONTINUE
294 ELSE
295 IF (nounit) temp = temp*dconjg(a(j,j))
296 DO 100 i = j - 1,1,-1
297 temp = temp + dconjg(a(i,j))*x(i)
298 100 CONTINUE
299 END IF
300 x(j) = temp
301 110 CONTINUE
302 ELSE
303 jx = kx + (n-1)*incx
304 DO 140 j = n,1,-1
305 temp = x(jx)
306 ix = jx
307 IF (noconj) THEN
308 IF (nounit) temp = temp*a(j,j)
309 DO 120 i = j - 1,1,-1
310 ix = ix - incx
311 temp = temp + a(i,j)*x(ix)
312 120 CONTINUE
313 ELSE
314 IF (nounit) temp = temp*dconjg(a(j,j))
315 DO 130 i = j - 1,1,-1
316 ix = ix - incx
317 temp = temp + dconjg(a(i,j))*x(ix)
318 130 CONTINUE
319 END IF
320 x(jx) = temp
321 jx = jx - incx
322 140 CONTINUE
323 END IF
324 ELSE
325 IF (incx.EQ.1) THEN
326 DO 170 j = 1,n
327 temp = x(j)
328 IF (noconj) THEN
329 IF (nounit) temp = temp*a(j,j)
330 DO 150 i = j + 1,n
331 temp = temp + a(i,j)*x(i)
332 150 CONTINUE
333 ELSE
334 IF (nounit) temp = temp*dconjg(a(j,j))
335 DO 160 i = j + 1,n
336 temp = temp + dconjg(a(i,j))*x(i)
337 160 CONTINUE
338 END IF
339 x(j) = temp
340 170 CONTINUE
341 ELSE
342 jx = kx
343 DO 200 j = 1,n
344 temp = x(jx)
345 ix = jx
346 IF (noconj) THEN
347 IF (nounit) temp = temp*a(j,j)
348 DO 180 i = j + 1,n
349 ix = ix + incx
350 temp = temp + a(i,j)*x(ix)
351 180 CONTINUE
352 ELSE
353 IF (nounit) temp = temp*dconjg(a(j,j))
354 DO 190 i = j + 1,n
355 ix = ix + incx
356 temp = temp + dconjg(a(i,j))*x(ix)
357 190 CONTINUE
358 END IF
359 x(jx) = temp
360 jx = jx + incx
361 200 CONTINUE
362 END IF
363 END IF
364 END IF
365*
366 RETURN
367*
368* End of ZTRMV
369*
370 END
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:60
subroutine ztrmv(UPLO, TRANS, DIAG, N, A, LDA, X, INCX)
ZTRMV
Definition: ztrmv.f:147