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

◆ dtrmv()

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, 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, 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 dtrmv.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 DOUBLE PRECISION A(LDA,*),X(*)
158* ..
159*
160* =====================================================================
161*
162* .. Parameters ..
163 DOUBLE PRECISION ZERO
164 parameter(zero=0.0d+0)
165* ..
166* .. Local Scalars ..
167 DOUBLE PRECISION TEMP
168 INTEGER I,INFO,IX,J,JX,KX
169 LOGICAL NOUNIT
170* ..
171* .. External Functions ..
172 LOGICAL LSAME
173 EXTERNAL lsame
174* ..
175* .. External Subroutines ..
176 EXTERNAL xerbla
177* ..
178* .. Intrinsic Functions ..
179 INTRINSIC 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('DTRMV ',info)
201 RETURN
202 END IF
203*
204* Quick return if possible.
205*
206 IF (n.EQ.0) RETURN
207*
208 nounit = lsame(diag,'N')
209*
210* Set up the start point in X if the increment is not unity. This
211* will be ( N - 1 )*INCX too small for descending loops.
212*
213 IF (incx.LE.0) THEN
214 kx = 1 - (n-1)*incx
215 ELSE IF (incx.NE.1) THEN
216 kx = 1
217 END IF
218*
219* Start the operations. In this version the elements of A are
220* accessed sequentially with one pass through A.
221*
222 IF (lsame(trans,'N')) THEN
223*
224* Form x := A*x.
225*
226 IF (lsame(uplo,'U')) THEN
227 IF (incx.EQ.1) THEN
228 DO 20 j = 1,n
229 IF (x(j).NE.zero) THEN
230 temp = x(j)
231 DO 10 i = 1,j - 1
232 x(i) = x(i) + temp*a(i,j)
233 10 CONTINUE
234 IF (nounit) x(j) = x(j)*a(j,j)
235 END IF
236 20 CONTINUE
237 ELSE
238 jx = kx
239 DO 40 j = 1,n
240 IF (x(jx).NE.zero) THEN
241 temp = x(jx)
242 ix = kx
243 DO 30 i = 1,j - 1
244 x(ix) = x(ix) + temp*a(i,j)
245 ix = ix + incx
246 30 CONTINUE
247 IF (nounit) x(jx) = x(jx)*a(j,j)
248 END IF
249 jx = jx + incx
250 40 CONTINUE
251 END IF
252 ELSE
253 IF (incx.EQ.1) THEN
254 DO 60 j = n,1,-1
255 IF (x(j).NE.zero) THEN
256 temp = x(j)
257 DO 50 i = n,j + 1,-1
258 x(i) = x(i) + temp*a(i,j)
259 50 CONTINUE
260 IF (nounit) x(j) = x(j)*a(j,j)
261 END IF
262 60 CONTINUE
263 ELSE
264 kx = kx + (n-1)*incx
265 jx = kx
266 DO 80 j = n,1,-1
267 IF (x(jx).NE.zero) THEN
268 temp = x(jx)
269 ix = kx
270 DO 70 i = n,j + 1,-1
271 x(ix) = x(ix) + temp*a(i,j)
272 ix = ix - incx
273 70 CONTINUE
274 IF (nounit) x(jx) = x(jx)*a(j,j)
275 END IF
276 jx = jx - incx
277 80 CONTINUE
278 END IF
279 END IF
280 ELSE
281*
282* Form x := A**T*x.
283*
284 IF (lsame(uplo,'U')) THEN
285 IF (incx.EQ.1) THEN
286 DO 100 j = n,1,-1
287 temp = x(j)
288 IF (nounit) temp = temp*a(j,j)
289 DO 90 i = j - 1,1,-1
290 temp = temp + a(i,j)*x(i)
291 90 CONTINUE
292 x(j) = temp
293 100 CONTINUE
294 ELSE
295 jx = kx + (n-1)*incx
296 DO 120 j = n,1,-1
297 temp = x(jx)
298 ix = jx
299 IF (nounit) temp = temp*a(j,j)
300 DO 110 i = j - 1,1,-1
301 ix = ix - incx
302 temp = temp + a(i,j)*x(ix)
303 110 CONTINUE
304 x(jx) = temp
305 jx = jx - incx
306 120 CONTINUE
307 END IF
308 ELSE
309 IF (incx.EQ.1) THEN
310 DO 140 j = 1,n
311 temp = x(j)
312 IF (nounit) temp = temp*a(j,j)
313 DO 130 i = j + 1,n
314 temp = temp + a(i,j)*x(i)
315 130 CONTINUE
316 x(j) = temp
317 140 CONTINUE
318 ELSE
319 jx = kx
320 DO 160 j = 1,n
321 temp = x(jx)
322 ix = jx
323 IF (nounit) temp = temp*a(j,j)
324 DO 150 i = j + 1,n
325 ix = ix + incx
326 temp = temp + a(i,j)*x(ix)
327 150 CONTINUE
328 x(jx) = temp
329 jx = jx + incx
330 160 CONTINUE
331 END IF
332 END IF
333 END IF
334*
335 RETURN
336*
337* End of DTRMV
338*
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:60
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:53
Here is the call graph for this function:
Here is the caller graph for this function: