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