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

DTRMV

Purpose:
 DTRMV  performs one of the matrix-vector operations

    x := A*x,   or   x := A**T*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**T*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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 dtrmv.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  DOUBLE PRECISION a(lda,*),x(*)
161 * ..
162 *
163 * =====================================================================
164 *
165 * .. Parameters ..
166  DOUBLE PRECISION zero
167  parameter(zero=0.0d+0)
168 * ..
169 * .. Local Scalars ..
170  DOUBLE PRECISION temp
171  INTEGER i,info,ix,j,jx,kx
172  LOGICAL nounit
173 * ..
174 * .. External Functions ..
175  LOGICAL lsame
176  EXTERNAL lsame
177 * ..
178 * .. External Subroutines ..
179  EXTERNAL xerbla
180 * ..
181 * .. Intrinsic Functions ..
182  INTRINSIC 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('DTRMV ',info)
204  RETURN
205  END IF
206 *
207 * Quick return if possible.
208 *
209  IF (n.EQ.0) RETURN
210 *
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.
286 *
287  IF (lsame(uplo,'U')) THEN
288  IF (incx.EQ.1) THEN
289  DO 100 j = n,1,-1
290  temp = x(j)
291  IF (nounit) temp = temp*a(j,j)
292  DO 90 i = j - 1,1,-1
293  temp = temp + a(i,j)*x(i)
294  90 CONTINUE
295  x(j) = temp
296  100 CONTINUE
297  ELSE
298  jx = kx + (n-1)*incx
299  DO 120 j = n,1,-1
300  temp = x(jx)
301  ix = jx
302  IF (nounit) temp = temp*a(j,j)
303  DO 110 i = j - 1,1,-1
304  ix = ix - incx
305  temp = temp + a(i,j)*x(ix)
306  110 CONTINUE
307  x(jx) = temp
308  jx = jx - incx
309  120 CONTINUE
310  END IF
311  ELSE
312  IF (incx.EQ.1) THEN
313  DO 140 j = 1,n
314  temp = x(j)
315  IF (nounit) temp = temp*a(j,j)
316  DO 130 i = j + 1,n
317  temp = temp + a(i,j)*x(i)
318  130 CONTINUE
319  x(j) = temp
320  140 CONTINUE
321  ELSE
322  jx = kx
323  DO 160 j = 1,n
324  temp = x(jx)
325  ix = jx
326  IF (nounit) temp = temp*a(j,j)
327  DO 150 i = j + 1,n
328  ix = ix + incx
329  temp = temp + a(i,j)*x(ix)
330  150 CONTINUE
331  x(jx) = temp
332  jx = jx + incx
333  160 CONTINUE
334  END IF
335  END IF
336  END IF
337 *
338  RETURN
339 *
340 * End of DTRMV .
341 *
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: