LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
dtpmv.f
Go to the documentation of this file.
1 *> \brief \b DTPMV
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE DTPMV(UPLO,TRANS,DIAG,N,AP,X,INCX)
12 *
13 * .. Scalar Arguments ..
14 * INTEGER INCX,N
15 * CHARACTER DIAG,TRANS,UPLO
16 * ..
17 * .. Array Arguments ..
18 * DOUBLE PRECISION AP(*),X(*)
19 * ..
20 *
21 *
22 *> \par Purpose:
23 * =============
24 *>
25 *> \verbatim
26 *>
27 *> DTPMV performs one of the matrix-vector operations
28 *>
29 *> x := A*x, or x := A**T*x,
30 *>
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, supplied in packed form.
33 *> \endverbatim
34 *
35 * Arguments:
36 * ==========
37 *
38 *> \param[in] UPLO
39 *> \verbatim
40 *> UPLO is CHARACTER*1
41 *> On entry, UPLO specifies whether the matrix is an upper or
42 *> lower triangular matrix as follows:
43 *>
44 *> UPLO = 'U' or 'u' A is an upper triangular matrix.
45 *>
46 *> UPLO = 'L' or 'l' A is a lower triangular matrix.
47 *> \endverbatim
48 *>
49 *> \param[in] TRANS
50 *> \verbatim
51 *> TRANS is CHARACTER*1
52 *> On entry, TRANS specifies the operation to be performed as
53 *> follows:
54 *>
55 *> TRANS = 'N' or 'n' x := A*x.
56 *>
57 *> TRANS = 'T' or 't' x := A**T*x.
58 *>
59 *> TRANS = 'C' or 'c' x := A**T*x.
60 *> \endverbatim
61 *>
62 *> \param[in] DIAG
63 *> \verbatim
64 *> DIAG is CHARACTER*1
65 *> On entry, DIAG specifies whether or not A is unit
66 *> triangular as follows:
67 *>
68 *> DIAG = 'U' or 'u' A is assumed to be unit triangular.
69 *>
70 *> DIAG = 'N' or 'n' A is not assumed to be unit
71 *> triangular.
72 *> \endverbatim
73 *>
74 *> \param[in] N
75 *> \verbatim
76 *> N is INTEGER
77 *> On entry, N specifies the order of the matrix A.
78 *> N must be at least zero.
79 *> \endverbatim
80 *>
81 *> \param[in] AP
82 *> \verbatim
83 *> AP is DOUBLE PRECISION array of DIMENSION at least
84 *> ( ( n*( n + 1 ) )/2 ).
85 *> Before entry with UPLO = 'U' or 'u', the array AP must
86 *> contain the upper triangular matrix packed sequentially,
87 *> column by column, so that AP( 1 ) contains a( 1, 1 ),
88 *> AP( 2 ) and AP( 3 ) contain a( 1, 2 ) and a( 2, 2 )
89 *> respectively, and so on.
90 *> Before entry with UPLO = 'L' or 'l', the array AP must
91 *> contain the lower triangular matrix packed sequentially,
92 *> column by column, so that AP( 1 ) contains a( 1, 1 ),
93 *> AP( 2 ) and AP( 3 ) contain a( 2, 1 ) and a( 3, 1 )
94 *> respectively, and so on.
95 *> Note that when DIAG = 'U' or 'u', the diagonal elements of
96 *> A are not referenced, but are assumed to be unity.
97 *> \endverbatim
98 *>
99 *> \param[in,out] X
100 *> \verbatim
101 *> X is DOUBLE PRECISION array of dimension at least
102 *> ( 1 + ( n - 1 )*abs( INCX ) ).
103 *> Before entry, the incremented array X must contain the n
104 *> element vector x. On exit, X is overwritten with the
105 *> tranformed vector x.
106 *> \endverbatim
107 *>
108 *> \param[in] INCX
109 *> \verbatim
110 *> INCX is INTEGER
111 *> On entry, INCX specifies the increment for the elements of
112 *> X. INCX must not be zero.
113 *> \endverbatim
114 *
115 * Authors:
116 * ========
117 *
118 *> \author Univ. of Tennessee
119 *> \author Univ. of California Berkeley
120 *> \author Univ. of Colorado Denver
121 *> \author NAG Ltd.
122 *
123 *> \date November 2011
124 *
125 *> \ingroup double_blas_level2
126 *
127 *> \par Further Details:
128 * =====================
129 *>
130 *> \verbatim
131 *>
132 *> Level 2 Blas routine.
133 *> The vector and matrix arguments are not referenced when N = 0, or M = 0
134 *>
135 *> -- Written on 22-October-1986.
136 *> Jack Dongarra, Argonne National Lab.
137 *> Jeremy Du Croz, Nag Central Office.
138 *> Sven Hammarling, Nag Central Office.
139 *> Richard Hanson, Sandia National Labs.
140 *> \endverbatim
141 *>
142 * =====================================================================
143  SUBROUTINE dtpmv(UPLO,TRANS,DIAG,N,AP,X,INCX)
144 *
145 * -- Reference BLAS level2 routine (version 3.4.0) --
146 * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
147 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
148 * November 2011
149 *
150 * .. Scalar Arguments ..
151  INTEGER incx,n
152  CHARACTER diag,trans,uplo
153 * ..
154 * .. Array Arguments ..
155  DOUBLE PRECISION ap(*),x(*)
156 * ..
157 *
158 * =====================================================================
159 *
160 * .. Parameters ..
161  DOUBLE PRECISION zero
162  parameter(zero=0.0d+0)
163 * ..
164 * .. Local Scalars ..
165  DOUBLE PRECISION temp
166  INTEGER i,info,ix,j,jx,k,kk,kx
167  LOGICAL nounit
168 * ..
169 * .. External Functions ..
170  LOGICAL lsame
171  EXTERNAL lsame
172 * ..
173 * .. External Subroutines ..
174  EXTERNAL xerbla
175 * ..
176 *
177 * Test the input parameters.
178 *
179  info = 0
180  IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
181  info = 1
182  ELSE IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.
183  + .NOT.lsame(trans,'C')) THEN
184  info = 2
185  ELSE IF (.NOT.lsame(diag,'U') .AND. .NOT.lsame(diag,'N')) THEN
186  info = 3
187  ELSE IF (n.LT.0) THEN
188  info = 4
189  ELSE IF (incx.EQ.0) THEN
190  info = 7
191  END IF
192  IF (info.NE.0) THEN
193  CALL xerbla('DTPMV ',info)
194  return
195  END IF
196 *
197 * Quick return if possible.
198 *
199  IF (n.EQ.0) return
200 *
201  nounit = lsame(diag,'N')
202 *
203 * Set up the start point in X if the increment is not unity. This
204 * will be ( N - 1 )*INCX too small for descending loops.
205 *
206  IF (incx.LE.0) THEN
207  kx = 1 - (n-1)*incx
208  ELSE IF (incx.NE.1) THEN
209  kx = 1
210  END IF
211 *
212 * Start the operations. In this version the elements of AP are
213 * accessed sequentially with one pass through AP.
214 *
215  IF (lsame(trans,'N')) THEN
216 *
217 * Form x:= A*x.
218 *
219  IF (lsame(uplo,'U')) THEN
220  kk = 1
221  IF (incx.EQ.1) THEN
222  DO 20 j = 1,n
223  IF (x(j).NE.zero) THEN
224  temp = x(j)
225  k = kk
226  DO 10 i = 1,j - 1
227  x(i) = x(i) + temp*ap(k)
228  k = k + 1
229  10 continue
230  IF (nounit) x(j) = x(j)*ap(kk+j-1)
231  END IF
232  kk = kk + j
233  20 continue
234  ELSE
235  jx = kx
236  DO 40 j = 1,n
237  IF (x(jx).NE.zero) THEN
238  temp = x(jx)
239  ix = kx
240  DO 30 k = kk,kk + j - 2
241  x(ix) = x(ix) + temp*ap(k)
242  ix = ix + incx
243  30 continue
244  IF (nounit) x(jx) = x(jx)*ap(kk+j-1)
245  END IF
246  jx = jx + incx
247  kk = kk + j
248  40 continue
249  END IF
250  ELSE
251  kk = (n* (n+1))/2
252  IF (incx.EQ.1) THEN
253  DO 60 j = n,1,-1
254  IF (x(j).NE.zero) THEN
255  temp = x(j)
256  k = kk
257  DO 50 i = n,j + 1,-1
258  x(i) = x(i) + temp*ap(k)
259  k = k - 1
260  50 continue
261  IF (nounit) x(j) = x(j)*ap(kk-n+j)
262  END IF
263  kk = kk - (n-j+1)
264  60 continue
265  ELSE
266  kx = kx + (n-1)*incx
267  jx = kx
268  DO 80 j = n,1,-1
269  IF (x(jx).NE.zero) THEN
270  temp = x(jx)
271  ix = kx
272  DO 70 k = kk,kk - (n- (j+1)),-1
273  x(ix) = x(ix) + temp*ap(k)
274  ix = ix - incx
275  70 continue
276  IF (nounit) x(jx) = x(jx)*ap(kk-n+j)
277  END IF
278  jx = jx - incx
279  kk = kk - (n-j+1)
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  kk = (n* (n+1))/2
289  IF (incx.EQ.1) THEN
290  DO 100 j = n,1,-1
291  temp = x(j)
292  IF (nounit) temp = temp*ap(kk)
293  k = kk - 1
294  DO 90 i = j - 1,1,-1
295  temp = temp + ap(k)*x(i)
296  k = k - 1
297  90 continue
298  x(j) = temp
299  kk = kk - j
300  100 continue
301  ELSE
302  jx = kx + (n-1)*incx
303  DO 120 j = n,1,-1
304  temp = x(jx)
305  ix = jx
306  IF (nounit) temp = temp*ap(kk)
307  DO 110 k = kk - 1,kk - j + 1,-1
308  ix = ix - incx
309  temp = temp + ap(k)*x(ix)
310  110 continue
311  x(jx) = temp
312  jx = jx - incx
313  kk = kk - j
314  120 continue
315  END IF
316  ELSE
317  kk = 1
318  IF (incx.EQ.1) THEN
319  DO 140 j = 1,n
320  temp = x(j)
321  IF (nounit) temp = temp*ap(kk)
322  k = kk + 1
323  DO 130 i = j + 1,n
324  temp = temp + ap(k)*x(i)
325  k = k + 1
326  130 continue
327  x(j) = temp
328  kk = kk + (n-j+1)
329  140 continue
330  ELSE
331  jx = kx
332  DO 160 j = 1,n
333  temp = x(jx)
334  ix = jx
335  IF (nounit) temp = temp*ap(kk)
336  DO 150 k = kk + 1,kk + n - j
337  ix = ix + incx
338  temp = temp + ap(k)*x(ix)
339  150 continue
340  x(jx) = temp
341  jx = jx + incx
342  kk = kk + (n-j+1)
343  160 continue
344  END IF
345  END IF
346  END IF
347 *
348  return
349 *
350 * End of DTPMV .
351 *
352  END