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