LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine chemv ( character  UPLO,
integer  N,
complex  ALPHA,
complex, dimension(lda,*)  A,
integer  LDA,
complex, dimension(*)  X,
integer  INCX,
complex  BETA,
complex, dimension(*)  Y,
integer  INCY 
)

CHEMV

Purpose:
 CHEMV  performs the matrix-vector  operation

    y := alpha*A*x + beta*y,

 where alpha and beta are scalars, x and y are n element vectors and
 A is an n by n hermitian matrix.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
           On entry, UPLO specifies whether the upper or lower
           triangular part of the array A is to be referenced as
           follows:

              UPLO = 'U' or 'u'   Only the upper triangular part of A
                                  is to be referenced.

              UPLO = 'L' or 'l'   Only the lower triangular part of A
                                  is to be referenced.
[in]N
          N is INTEGER
           On entry, N specifies the order of the matrix A.
           N must be at least zero.
[in]ALPHA
          ALPHA is COMPLEX
           On entry, ALPHA specifies the scalar alpha.
[in]A
          A is COMPLEX array of 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 part of the hermitian 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 part of the hermitian matrix and the strictly
           upper triangular part of A is not referenced.
           Note that the imaginary parts of the diagonal elements need
           not be set and are assumed to be zero.
[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]X
          X is COMPLEX array of dimension at least
           ( 1 + ( n - 1 )*abs( INCX ) ).
           Before entry, the incremented array X must contain the n
           element vector x.
[in]INCX
          INCX is INTEGER
           On entry, INCX specifies the increment for the elements of
           X. INCX must not be zero.
[in]BETA
          BETA is COMPLEX
           On entry, BETA specifies the scalar beta. When BETA is
           supplied as zero then Y need not be set on input.
[in,out]Y
          Y is COMPLEX array of dimension at least
           ( 1 + ( n - 1 )*abs( INCY ) ).
           Before entry, the incremented array Y must contain the n
           element vector y. On exit, Y is overwritten by the updated
           vector y.
[in]INCY
          INCY is INTEGER
           On entry, INCY specifies the increment for the elements of
           Y. INCY must not be zero.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011
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 156 of file chemv.f.

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 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: