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

◆ ztrmv()

subroutine ztrmv ( character  uplo,
character  trans,
character  diag,
integer  n,
complex*16, dimension(lda,*)  a,
integer  lda,
complex*16, dimension(*)  x,
integer  incx 
)

ZTRMV

Purpose:
 ZTRMV  performs one of the matrix-vector operations

    x := A*x,   or   x := A**T*x,   or   x := A**H*x,

 where x is an n element vector and  A is an n by n unit, or non-unit,
 upper or lower triangular matrix.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
           On entry, UPLO specifies whether the matrix is an upper or
           lower triangular matrix as follows:

              UPLO = 'U' or 'u'   A is an upper triangular matrix.

              UPLO = 'L' or 'l'   A is a lower triangular matrix.
[in]TRANS
          TRANS is CHARACTER*1
           On entry, TRANS specifies the operation to be performed as
           follows:

              TRANS = 'N' or 'n'   x := A*x.

              TRANS = 'T' or 't'   x := A**T*x.

              TRANS = 'C' or 'c'   x := A**H*x.
[in]DIAG
          DIAG is CHARACTER*1
           On entry, DIAG specifies whether or not A is unit
           triangular as follows:

              DIAG = 'U' or 'u'   A is assumed to be unit triangular.

              DIAG = 'N' or 'n'   A is not assumed to be unit
                                  triangular.
[in]N
          N is INTEGER
           On entry, N specifies the order of the matrix A.
           N must be at least zero.
[in]A
          A is COMPLEX*16 array, dimension ( LDA, N ).
           Before entry with  UPLO = 'U' or 'u', the leading n by n
           upper triangular part of the array A must contain the upper
           triangular matrix and the strictly lower triangular part of
           A is not referenced.
           Before entry with UPLO = 'L' or 'l', the leading n by n
           lower triangular part of the array A must contain the lower
           triangular matrix and the strictly upper triangular part of
           A is not referenced.
           Note that when  DIAG = 'U' or 'u', the diagonal elements of
           A are not referenced either, but are assumed to be unity.
[in]LDA
          LDA is INTEGER
           On entry, LDA specifies the first dimension of A as declared
           in the calling (sub) program. LDA must be at least
           max( 1, n ).
[in,out]X
          X is COMPLEX*16 array, dimension at least
           ( 1 + ( n - 1 )*abs( INCX ) ).
           Before entry, the incremented array X must contain the n
           element vector x. On exit, X is overwritten with the
           transformed vector x.
[in]INCX
          INCX is INTEGER
           On entry, INCX specifies the increment for the elements of
           X. INCX must not be zero.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
  Level 2 Blas routine.
  The vector and matrix arguments are not referenced when N = 0, or M = 0

  -- Written on 22-October-1986.
     Jack Dongarra, Argonne National Lab.
     Jeremy Du Croz, Nag Central Office.
     Sven Hammarling, Nag Central Office.
     Richard Hanson, Sandia National Labs.

Definition at line 146 of file ztrmv.f.

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.
188 + .NOT.lsame(trans,'T') .AND.
189 + .NOT.lsame(trans,'C')) THEN
190 info = 2
191 ELSE IF (.NOT.lsame(diag,'U') .AND.
192 + .NOT.lsame(diag,'N')) THEN
193 info = 3
194 ELSE IF (n.LT.0) THEN
195 info = 4
196 ELSE IF (lda.LT.max(1,n)) THEN
197 info = 6
198 ELSE IF (incx.EQ.0) THEN
199 info = 8
200 END IF
201 IF (info.NE.0) THEN
202 CALL xerbla('ZTRMV ',info)
203 RETURN
204 END IF
205*
206* Quick return if possible.
207*
208 IF (n.EQ.0) RETURN
209*
210 noconj = lsame(trans,'T')
211 nounit = lsame(diag,'N')
212*
213* Set up the start point in X if the increment is not unity. This
214* will be ( N - 1 )*INCX too small for descending loops.
215*
216 IF (incx.LE.0) THEN
217 kx = 1 - (n-1)*incx
218 ELSE IF (incx.NE.1) THEN
219 kx = 1
220 END IF
221*
222* Start the operations. In this version the elements of A are
223* accessed sequentially with one pass through A.
224*
225 IF (lsame(trans,'N')) THEN
226*
227* Form x := A*x.
228*
229 IF (lsame(uplo,'U')) THEN
230 IF (incx.EQ.1) THEN
231 DO 20 j = 1,n
232 IF (x(j).NE.zero) THEN
233 temp = x(j)
234 DO 10 i = 1,j - 1
235 x(i) = x(i) + temp*a(i,j)
236 10 CONTINUE
237 IF (nounit) x(j) = x(j)*a(j,j)
238 END IF
239 20 CONTINUE
240 ELSE
241 jx = kx
242 DO 40 j = 1,n
243 IF (x(jx).NE.zero) THEN
244 temp = x(jx)
245 ix = kx
246 DO 30 i = 1,j - 1
247 x(ix) = x(ix) + temp*a(i,j)
248 ix = ix + incx
249 30 CONTINUE
250 IF (nounit) x(jx) = x(jx)*a(j,j)
251 END IF
252 jx = jx + incx
253 40 CONTINUE
254 END IF
255 ELSE
256 IF (incx.EQ.1) THEN
257 DO 60 j = n,1,-1
258 IF (x(j).NE.zero) THEN
259 temp = x(j)
260 DO 50 i = n,j + 1,-1
261 x(i) = x(i) + temp*a(i,j)
262 50 CONTINUE
263 IF (nounit) x(j) = x(j)*a(j,j)
264 END IF
265 60 CONTINUE
266 ELSE
267 kx = kx + (n-1)*incx
268 jx = kx
269 DO 80 j = n,1,-1
270 IF (x(jx).NE.zero) THEN
271 temp = x(jx)
272 ix = kx
273 DO 70 i = n,j + 1,-1
274 x(ix) = x(ix) + temp*a(i,j)
275 ix = ix - incx
276 70 CONTINUE
277 IF (nounit) x(jx) = x(jx)*a(j,j)
278 END IF
279 jx = jx - incx
280 80 CONTINUE
281 END IF
282 END IF
283 ELSE
284*
285* Form x := A**T*x or x := A**H*x.
286*
287 IF (lsame(uplo,'U')) THEN
288 IF (incx.EQ.1) THEN
289 DO 110 j = n,1,-1
290 temp = x(j)
291 IF (noconj) THEN
292 IF (nounit) temp = temp*a(j,j)
293 DO 90 i = j - 1,1,-1
294 temp = temp + a(i,j)*x(i)
295 90 CONTINUE
296 ELSE
297 IF (nounit) temp = temp*dconjg(a(j,j))
298 DO 100 i = j - 1,1,-1
299 temp = temp + dconjg(a(i,j))*x(i)
300 100 CONTINUE
301 END IF
302 x(j) = temp
303 110 CONTINUE
304 ELSE
305 jx = kx + (n-1)*incx
306 DO 140 j = n,1,-1
307 temp = x(jx)
308 ix = jx
309 IF (noconj) THEN
310 IF (nounit) temp = temp*a(j,j)
311 DO 120 i = j - 1,1,-1
312 ix = ix - incx
313 temp = temp + a(i,j)*x(ix)
314 120 CONTINUE
315 ELSE
316 IF (nounit) temp = temp*dconjg(a(j,j))
317 DO 130 i = j - 1,1,-1
318 ix = ix - incx
319 temp = temp + dconjg(a(i,j))*x(ix)
320 130 CONTINUE
321 END IF
322 x(jx) = temp
323 jx = jx - incx
324 140 CONTINUE
325 END IF
326 ELSE
327 IF (incx.EQ.1) THEN
328 DO 170 j = 1,n
329 temp = x(j)
330 IF (noconj) THEN
331 IF (nounit) temp = temp*a(j,j)
332 DO 150 i = j + 1,n
333 temp = temp + a(i,j)*x(i)
334 150 CONTINUE
335 ELSE
336 IF (nounit) temp = temp*dconjg(a(j,j))
337 DO 160 i = j + 1,n
338 temp = temp + dconjg(a(i,j))*x(i)
339 160 CONTINUE
340 END IF
341 x(j) = temp
342 170 CONTINUE
343 ELSE
344 jx = kx
345 DO 200 j = 1,n
346 temp = x(jx)
347 ix = jx
348 IF (noconj) THEN
349 IF (nounit) temp = temp*a(j,j)
350 DO 180 i = j + 1,n
351 ix = ix + incx
352 temp = temp + a(i,j)*x(ix)
353 180 CONTINUE
354 ELSE
355 IF (nounit) temp = temp*dconjg(a(j,j))
356 DO 190 i = j + 1,n
357 ix = ix + incx
358 temp = temp + dconjg(a(i,j))*x(ix)
359 190 CONTINUE
360 END IF
361 x(jx) = temp
362 jx = jx + incx
363 200 CONTINUE
364 END IF
365 END IF
366 END IF
367*
368 RETURN
369*
370* End of ZTRMV
371*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: