3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
11 * SUBROUTINE DTRMV(UPLO,TRANS,DIAG,N,A,LDA,X,INCX)
13 * .. Scalar Arguments ..
15 * CHARACTER DIAG,TRANS,UPLO
17 * .. Array Arguments ..
18 * DOUBLE PRECISION A(LDA,*),X(*)
27 *> DTRMV performs one of the matrix-vector operations
29 *> x := A*x, or x := A**T*x,
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.
40 *> UPLO is CHARACTER*1
41 *> On entry, UPLO specifies whether the matrix is an upper or
42 *> lower triangular matrix as follows:
44 *> UPLO = 'U' or 'u' A is an upper triangular matrix.
46 *> UPLO = 'L' or 'l' A is a lower triangular matrix.
51 *> TRANS is CHARACTER*1
52 *> On entry, TRANS specifies the operation to be performed as
55 *> TRANS = 'N' or 'n' x := A*x.
57 *> TRANS = 'T' or 't' x := A**T*x.
59 *> TRANS = 'C' or 'c' x := A**T*x.
64 *> DIAG is CHARACTER*1
65 *> On entry, DIAG specifies whether or not A is unit
66 *> triangular as follows:
68 *> DIAG = 'U' or 'u' A is assumed to be unit triangular.
70 *> DIAG = 'N' or 'n' A is not assumed to be unit
77 *> On entry, N specifies the order of the matrix A.
78 *> N must be at least zero.
83 *> A is DOUBLE PRECISION array of 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.
99 *> On entry, LDA specifies the first dimension of A as declared
100 *> in the calling (sub) program. LDA must be at least
106 *> X is DOUBLE PRECISION array of 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.
116 *> On entry, INCX specifies the increment for the elements of
117 *> X. INCX must not be zero.
123 *> \author Univ. of Tennessee
124 *> \author Univ. of California Berkeley
125 *> \author Univ. of Colorado Denver
128 *> \date November 2011
130 *> \ingroup double_blas_level2
132 *> \par Further Details:
133 * =====================
137 *> Level 2 Blas routine.
138 *> The vector and matrix arguments are not referenced when N = 0, or M = 0
140 *> -- Written on 22-October-1986.
141 *> Jack Dongarra, Argonne National Lab.
142 *> Jeremy Du Croz, Nag Central Office.
143 *> Sven Hammarling, Nag Central Office.
144 *> Richard Hanson, Sandia National Labs.
147 * =====================================================================
148 SUBROUTINE DTRMV(UPLO,TRANS,DIAG,N,A,LDA,X,INCX)
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..--
155 * .. Scalar Arguments ..
157 CHARACTER DIAG,TRANS,UPLO
159 * .. Array Arguments ..
160 DOUBLE PRECISION A(LDA,*),X(*)
163 * =====================================================================
166 DOUBLE PRECISION ZERO
167 PARAMETER (ZERO=0.0D+0)
169 * .. Local Scalars ..
170 DOUBLE PRECISION TEMP
171 INTEGER I,INFO,IX,J,JX,KX
174 * .. External Functions ..
178 * .. External Subroutines ..
181 * .. Intrinsic Functions ..
185 * Test the input parameters.
188 IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THEN
190 ELSE IF (.NOT.LSAME(TRANS,'N') .AND. .NOT.LSAME(TRANS,'T') .AND.
191 + .NOT.LSAME(TRANS,'C')) THEN
193 ELSE IF (.NOT.LSAME(DIAG,'U') .AND. .NOT.LSAME(DIAG,'N')) THEN
195 ELSE IF (N.LT.0) THEN
197 ELSE IF (LDA.LT.MAX(1,N)) THEN
199 ELSE IF (INCX.EQ.0) THEN
203 CALL XERBLA('DTRMV ',INFO)
207 * Quick return if possible.
211 NOUNIT = LSAME(DIAG,'N')
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.
218 ELSE IF (INCX.NE.1) THEN
222 * Start the operations. In this version the elements of A are
223 * accessed sequentially with one pass through A.
225 IF (LSAME(TRANS,'N')) THEN
229 IF (LSAME(UPLO,'U')) THEN
232 IF (X(J).NE.ZERO) THEN
235 X(I) = X(I) + TEMP*A(I,J)
237 IF (NOUNIT) X(J) = X(J)*A(J,J)
243 IF (X(JX).NE.ZERO) THEN
247 X(IX) = X(IX) + TEMP*A(I,J)
250 IF (NOUNIT) X(JX) = X(JX)*A(J,J)
258 IF (X(J).NE.ZERO) THEN
261 X(I) = X(I) + TEMP*A(I,J)
263 IF (NOUNIT) X(J) = X(J)*A(J,J)
270 IF (X(JX).NE.ZERO) THEN
274 X(IX) = X(IX) + TEMP*A(I,J)
277 IF (NOUNIT) X(JX) = X(JX)*A(J,J)
287 IF (LSAME(UPLO,'U')) THEN
291 IF (NOUNIT) TEMP = TEMP*A(J,J)
293 TEMP = TEMP + A(I,J)*X(I)
302 IF (NOUNIT) TEMP = TEMP*A(J,J)
303 DO 110 I = J - 1,1,-1
305 TEMP = TEMP + A(I,J)*X(IX)
315 IF (NOUNIT) TEMP = TEMP*A(J,J)
317 TEMP = TEMP + A(I,J)*X(I)
326 IF (NOUNIT) TEMP = TEMP*A(J,J)
329 TEMP = TEMP + A(I,J)*X(IX)