LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine ctrmv ( character  UPLO,
character  TRANS,
character  DIAG,
integer  N,
complex, dimension(lda,*)  A,
integer  LDA,
complex, dimension(*)  X,
integer  INCX 
)

CTRMV

Purpose:
 CTRMV  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 array of 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 array of 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
           tranformed 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.
Date
November 2011
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 149 of file ctrmv.f.

149 *
150 * -- Reference BLAS level2 routine (version 3.4.0) --
151 * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
152 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
153 * November 2011
154 *
155 * .. Scalar Arguments ..
156  INTEGER incx,lda,n
157  CHARACTER diag,trans,uplo
158 * ..
159 * .. Array Arguments ..
160  COMPLEX a(lda,*),x(*)
161 * ..
162 *
163 * =====================================================================
164 *
165 * .. Parameters ..
166  COMPLEX zero
167  parameter(zero= (0.0e+0,0.0e+0))
168 * ..
169 * .. Local Scalars ..
170  COMPLEX temp
171  INTEGER i,info,ix,j,jx,kx
172  LOGICAL noconj,nounit
173 * ..
174 * .. External Functions ..
175  LOGICAL lsame
176  EXTERNAL lsame
177 * ..
178 * .. External Subroutines ..
179  EXTERNAL xerbla
180 * ..
181 * .. Intrinsic Functions ..
182  INTRINSIC conjg,max
183 * ..
184 *
185 * Test the input parameters.
186 *
187  info = 0
188  IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
189  info = 1
190  ELSE IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.
191  + .NOT.lsame(trans,'C')) THEN
192  info = 2
193  ELSE IF (.NOT.lsame(diag,'U') .AND. .NOT.lsame(diag,'N')) THEN
194  info = 3
195  ELSE IF (n.LT.0) THEN
196  info = 4
197  ELSE IF (lda.LT.max(1,n)) THEN
198  info = 6
199  ELSE IF (incx.EQ.0) THEN
200  info = 8
201  END IF
202  IF (info.NE.0) THEN
203  CALL xerbla('CTRMV ',info)
204  RETURN
205  END IF
206 *
207 * Quick return if possible.
208 *
209  IF (n.EQ.0) RETURN
210 *
211  noconj = lsame(trans,'T')
212  nounit = lsame(diag,'N')
213 *
214 * Set up the start point in X if the increment is not unity. This
215 * will be ( N - 1 )*INCX too small for descending loops.
216 *
217  IF (incx.LE.0) THEN
218  kx = 1 - (n-1)*incx
219  ELSE IF (incx.NE.1) THEN
220  kx = 1
221  END IF
222 *
223 * Start the operations. In this version the elements of A are
224 * accessed sequentially with one pass through A.
225 *
226  IF (lsame(trans,'N')) THEN
227 *
228 * Form x := A*x.
229 *
230  IF (lsame(uplo,'U')) THEN
231  IF (incx.EQ.1) THEN
232  DO 20 j = 1,n
233  IF (x(j).NE.zero) THEN
234  temp = x(j)
235  DO 10 i = 1,j - 1
236  x(i) = x(i) + temp*a(i,j)
237  10 CONTINUE
238  IF (nounit) x(j) = x(j)*a(j,j)
239  END IF
240  20 CONTINUE
241  ELSE
242  jx = kx
243  DO 40 j = 1,n
244  IF (x(jx).NE.zero) THEN
245  temp = x(jx)
246  ix = kx
247  DO 30 i = 1,j - 1
248  x(ix) = x(ix) + temp*a(i,j)
249  ix = ix + incx
250  30 CONTINUE
251  IF (nounit) x(jx) = x(jx)*a(j,j)
252  END IF
253  jx = jx + incx
254  40 CONTINUE
255  END IF
256  ELSE
257  IF (incx.EQ.1) THEN
258  DO 60 j = n,1,-1
259  IF (x(j).NE.zero) THEN
260  temp = x(j)
261  DO 50 i = n,j + 1,-1
262  x(i) = x(i) + temp*a(i,j)
263  50 CONTINUE
264  IF (nounit) x(j) = x(j)*a(j,j)
265  END IF
266  60 CONTINUE
267  ELSE
268  kx = kx + (n-1)*incx
269  jx = kx
270  DO 80 j = n,1,-1
271  IF (x(jx).NE.zero) THEN
272  temp = x(jx)
273  ix = kx
274  DO 70 i = n,j + 1,-1
275  x(ix) = x(ix) + temp*a(i,j)
276  ix = ix - incx
277  70 CONTINUE
278  IF (nounit) x(jx) = x(jx)*a(j,j)
279  END IF
280  jx = jx - incx
281  80 CONTINUE
282  END IF
283  END IF
284  ELSE
285 *
286 * Form x := A**T*x or x := A**H*x.
287 *
288  IF (lsame(uplo,'U')) THEN
289  IF (incx.EQ.1) THEN
290  DO 110 j = n,1,-1
291  temp = x(j)
292  IF (noconj) THEN
293  IF (nounit) temp = temp*a(j,j)
294  DO 90 i = j - 1,1,-1
295  temp = temp + a(i,j)*x(i)
296  90 CONTINUE
297  ELSE
298  IF (nounit) temp = temp*conjg(a(j,j))
299  DO 100 i = j - 1,1,-1
300  temp = temp + conjg(a(i,j))*x(i)
301  100 CONTINUE
302  END IF
303  x(j) = temp
304  110 CONTINUE
305  ELSE
306  jx = kx + (n-1)*incx
307  DO 140 j = n,1,-1
308  temp = x(jx)
309  ix = jx
310  IF (noconj) THEN
311  IF (nounit) temp = temp*a(j,j)
312  DO 120 i = j - 1,1,-1
313  ix = ix - incx
314  temp = temp + a(i,j)*x(ix)
315  120 CONTINUE
316  ELSE
317  IF (nounit) temp = temp*conjg(a(j,j))
318  DO 130 i = j - 1,1,-1
319  ix = ix - incx
320  temp = temp + conjg(a(i,j))*x(ix)
321  130 CONTINUE
322  END IF
323  x(jx) = temp
324  jx = jx - incx
325  140 CONTINUE
326  END IF
327  ELSE
328  IF (incx.EQ.1) THEN
329  DO 170 j = 1,n
330  temp = x(j)
331  IF (noconj) THEN
332  IF (nounit) temp = temp*a(j,j)
333  DO 150 i = j + 1,n
334  temp = temp + a(i,j)*x(i)
335  150 CONTINUE
336  ELSE
337  IF (nounit) temp = temp*conjg(a(j,j))
338  DO 160 i = j + 1,n
339  temp = temp + conjg(a(i,j))*x(i)
340  160 CONTINUE
341  END IF
342  x(j) = temp
343  170 CONTINUE
344  ELSE
345  jx = kx
346  DO 200 j = 1,n
347  temp = x(jx)
348  ix = jx
349  IF (noconj) THEN
350  IF (nounit) temp = temp*a(j,j)
351  DO 180 i = j + 1,n
352  ix = ix + incx
353  temp = temp + a(i,j)*x(ix)
354  180 CONTINUE
355  ELSE
356  IF (nounit) temp = temp*conjg(a(j,j))
357  DO 190 i = j + 1,n
358  ix = ix + incx
359  temp = temp + conjg(a(i,j))*x(ix)
360  190 CONTINUE
361  END IF
362  x(jx) = temp
363  jx = jx + incx
364  200 CONTINUE
365  END IF
366  END IF
367  END IF
368 *
369  RETURN
370 *
371 * End of CTRMV .
372 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: