KTH framework for Nek5000 toolboxes; testing version  0.0.1
dtrmv.f
Go to the documentation of this file.
1  SUBROUTINE dtrmv ( UPLO, TRANS, DIAG, N, A, LDA, X, INCX )
2 * .. Scalar Arguments ..
3  INTEGER INCX, LDA, N
4  CHARACTER*1 DIAG, TRANS, UPLO
5 * .. Array Arguments ..
6  DOUBLE PRECISION A( LDA, * ), X( * )
7 * ..
8 *
9 * Purpose
10 * =======
11 *
12 * DTRMV performs one of the matrix-vector operations
13 *
14 * x := A*x, or x := A'*x,
15 *
16 * where x is an n element vector and A is an n by n unit, or non-unit,
17 * upper or lower triangular matrix.
18 *
19 * Parameters
20 * ==========
21 *
22 * UPLO - CHARACTER*1.
23 * On entry, UPLO specifies whether the matrix is an upper or
24 * lower triangular matrix as follows:
25 *
26 * UPLO = 'U' or 'u' A is an upper triangular matrix.
27 *
28 * UPLO = 'L' or 'l' A is a lower triangular matrix.
29 *
30 * Unchanged on exit.
31 *
32 * TRANS - CHARACTER*1.
33 * On entry, TRANS specifies the operation to be performed as
34 * follows:
35 *
36 * TRANS = 'N' or 'n' x := A*x.
37 *
38 * TRANS = 'T' or 't' x := A'*x.
39 *
40 * TRANS = 'C' or 'c' x := A'*x.
41 *
42 * Unchanged on exit.
43 *
44 * DIAG - CHARACTER*1.
45 * On entry, DIAG specifies whether or not A is unit
46 * triangular as follows:
47 *
48 * DIAG = 'U' or 'u' A is assumed to be unit triangular.
49 *
50 * DIAG = 'N' or 'n' A is not assumed to be unit
51 * triangular.
52 *
53 * Unchanged on exit.
54 *
55 * N - INTEGER.
56 * On entry, N specifies the order of the matrix A.
57 * N must be at least zero.
58 * Unchanged on exit.
59 *
60 * A - DOUBLE PRECISION array of DIMENSION ( LDA, n ).
61 * Before entry with UPLO = 'U' or 'u', the leading n by n
62 * upper triangular part of the array A must contain the upper
63 * triangular matrix and the strictly lower triangular part of
64 * A is not referenced.
65 * Before entry with UPLO = 'L' or 'l', the leading n by n
66 * lower triangular part of the array A must contain the lower
67 * triangular matrix and the strictly upper triangular part of
68 * A is not referenced.
69 * Note that when DIAG = 'U' or 'u', the diagonal elements of
70 * A are not referenced either, but are assumed to be unity.
71 * Unchanged on exit.
72 *
73 * LDA - INTEGER.
74 * On entry, LDA specifies the first dimension of A as declared
75 * in the calling (sub) program. LDA must be at least
76 * max( 1, n ).
77 * Unchanged on exit.
78 *
79 * X - DOUBLE PRECISION array of dimension at least
80 * ( 1 + ( n - 1 )*abs( INCX ) ).
81 * Before entry, the incremented array X must contain the n
82 * element vector x. On exit, X is overwritten with the
83 * tranformed vector x.
84 *
85 * INCX - INTEGER.
86 * On entry, INCX specifies the increment for the elements of
87 * X. INCX must not be zero.
88 * Unchanged on exit.
89 *
90 *
91 * Level 2 Blas routine.
92 *
93 * -- Written on 22-October-1986.
94 * Jack Dongarra, Argonne National Lab.
95 * Jeremy Du Croz, Nag Central Office.
96 * Sven Hammarling, Nag Central Office.
97 * Richard Hanson, Sandia National Labs.
98 *
99 *
100 * .. Parameters ..
101  DOUBLE PRECISION ZERO
102  parameter( zero = 0.0d+0 )
103 * .. Local Scalars ..
104  DOUBLE PRECISION TEMP
105  INTEGER I, INFO, IX, J, JX, KX
106  LOGICAL NOUNIT
107 * .. External Functions ..
108  LOGICAL LSAME
109  EXTERNAL lsame
110 * .. External Subroutines ..
111  EXTERNAL xerbla
112 * .. Intrinsic Functions ..
113  INTRINSIC max
114 * ..
115 * .. Executable Statements ..
116 *
117 * Test the input parameters.
118 *
119  info = 0
120  IF ( .NOT.lsame( uplo , 'U' ).AND.
121  $ .NOT.lsame( uplo , 'L' ) )THEN
122  info = 1
123  ELSE IF( .NOT.lsame( trans, 'N' ).AND.
124  $ .NOT.lsame( trans, 'T' ).AND.
125  $ .NOT.lsame( trans, 'C' ) )THEN
126  info = 2
127  ELSE IF( .NOT.lsame( diag , 'U' ).AND.
128  $ .NOT.lsame( diag , 'N' ) )THEN
129  info = 3
130  ELSE IF( n.LT.0 )THEN
131  info = 4
132  ELSE IF( lda.LT.max( 1, n ) )THEN
133  info = 6
134  ELSE IF( incx.EQ.0 )THEN
135  info = 8
136  END IF
137  IF( info.NE.0 )THEN
138  CALL xerbla( 'DTRMV ', info )
139  RETURN
140  END IF
141 *
142 * Quick return if possible.
143 *
144  IF( n.EQ.0 )
145  $ RETURN
146 *
147  nounit = lsame( diag, 'N' )
148 *
149 * Set up the start point in X if the increment is not unity. This
150 * will be ( N - 1 )*INCX too small for descending loops.
151 *
152  IF( incx.LE.0 )THEN
153  kx = 1 - ( n - 1 )*incx
154  ELSE IF( incx.NE.1 )THEN
155  kx = 1
156  END IF
157 *
158 * Start the operations. In this version the elements of A are
159 * accessed sequentially with one pass through A.
160 *
161  IF( lsame( trans, 'N' ) )THEN
162 *
163 * Form x := A*x.
164 *
165  IF( lsame( uplo, 'U' ) )THEN
166  IF( incx.EQ.1 )THEN
167  DO 20, j = 1, n
168  IF( x( j ).NE.zero )THEN
169  temp = x( j )
170  DO 10, i = 1, j - 1
171  x( i ) = x( i ) + temp*a( i, j )
172  10 CONTINUE
173  IF( nounit )
174  $ x( j ) = x( j )*a( j, j )
175  END IF
176  20 CONTINUE
177  ELSE
178  jx = kx
179  DO 40, j = 1, n
180  IF( x( jx ).NE.zero )THEN
181  temp = x( jx )
182  ix = kx
183  DO 30, i = 1, j - 1
184  x( ix ) = x( ix ) + temp*a( i, j )
185  ix = ix + incx
186  30 CONTINUE
187  IF( nounit )
188  $ x( jx ) = x( jx )*a( j, j )
189  END IF
190  jx = jx + incx
191  40 CONTINUE
192  END IF
193  ELSE
194  IF( incx.EQ.1 )THEN
195  DO 60, j = n, 1, -1
196  IF( x( j ).NE.zero )THEN
197  temp = x( j )
198  DO 50, i = n, j + 1, -1
199  x( i ) = x( i ) + temp*a( i, j )
200  50 CONTINUE
201  IF( nounit )
202  $ x( j ) = x( j )*a( j, j )
203  END IF
204  60 CONTINUE
205  ELSE
206  kx = kx + ( n - 1 )*incx
207  jx = kx
208  DO 80, j = n, 1, -1
209  IF( x( jx ).NE.zero )THEN
210  temp = x( jx )
211  ix = kx
212  DO 70, i = n, j + 1, -1
213  x( ix ) = x( ix ) + temp*a( i, j )
214  ix = ix - incx
215  70 CONTINUE
216  IF( nounit )
217  $ x( jx ) = x( jx )*a( j, j )
218  END IF
219  jx = jx - incx
220  80 CONTINUE
221  END IF
222  END IF
223  ELSE
224 *
225 * Form x := A'*x.
226 *
227  IF( lsame( uplo, 'U' ) )THEN
228  IF( incx.EQ.1 )THEN
229  DO 100, j = n, 1, -1
230  temp = x( j )
231  IF( nounit )
232  $ temp = temp*a( j, j )
233  DO 90, i = j - 1, 1, -1
234  temp = temp + a( i, j )*x( i )
235  90 CONTINUE
236  x( j ) = temp
237  100 CONTINUE
238  ELSE
239  jx = kx + ( n - 1 )*incx
240  DO 120, j = n, 1, -1
241  temp = x( jx )
242  ix = jx
243  IF( nounit )
244  $ temp = temp*a( j, j )
245  DO 110, i = j - 1, 1, -1
246  ix = ix - incx
247  temp = temp + a( i, j )*x( ix )
248  110 CONTINUE
249  x( jx ) = temp
250  jx = jx - incx
251  120 CONTINUE
252  END IF
253  ELSE
254  IF( incx.EQ.1 )THEN
255  DO 140, j = 1, n
256  temp = x( j )
257  IF( nounit )
258  $ temp = temp*a( j, j )
259  DO 130, i = j + 1, n
260  temp = temp + a( i, j )*x( i )
261  130 CONTINUE
262  x( j ) = temp
263  140 CONTINUE
264  ELSE
265  jx = kx
266  DO 160, j = 1, n
267  temp = x( jx )
268  ix = jx
269  IF( nounit )
270  $ temp = temp*a( j, j )
271  DO 150, i = j + 1, n
272  ix = ix + incx
273  temp = temp + a( i, j )*x( ix )
274  150 CONTINUE
275  x( jx ) = temp
276  jx = jx + incx
277  160 CONTINUE
278  END IF
279  END IF
280  END IF
281 *
282  RETURN
283 *
284 * End of DTRMV .
285 *
286  END
subroutine dtrmv(UPLO, TRANS, DIAG, N, A, LDA, X, INCX)
Definition: dtrmv.f:2
subroutine xerbla(SRNAME, INFO)
Definition: xerbla.f:2