LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine chpmv ( character  UPLO,
integer  N,
complex  ALPHA,
complex, dimension(*)  AP,
complex, dimension(*)  X,
integer  INCX,
complex  BETA,
complex, dimension(*)  Y,
integer  INCY 
)

CHPMV

Purpose:
 CHPMV  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, supplied in packed form.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
           On entry, UPLO specifies whether the upper or lower
           triangular part of the matrix A is supplied in the packed
           array AP as follows:

              UPLO = 'U' or 'u'   The upper triangular part of A is
                                  supplied in AP.

              UPLO = 'L' or 'l'   The lower triangular part of A is
                                  supplied in AP.
[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]AP
          AP is COMPLEX array of DIMENSION at least
           ( ( n*( n + 1 ) )/2 ).
           Before entry with UPLO = 'U' or 'u', the array AP must
           contain the upper triangular part of the hermitian matrix
           packed sequentially, column by column, so that AP( 1 )
           contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 1, 2 )
           and a( 2, 2 ) respectively, and so on.
           Before entry with UPLO = 'L' or 'l', the array AP must
           contain the lower triangular part of the hermitian matrix
           packed sequentially, column by column, so that AP( 1 )
           contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 2, 1 )
           and a( 3, 1 ) respectively, and so on.
           Note that the imaginary parts of the diagonal elements need
           not be set and are assumed to be zero.
[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 151 of file chpmv.f.

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 alpha,beta
159  INTEGER incx,incy,n
160  CHARACTER uplo
161 * ..
162 * .. Array Arguments ..
163  COMPLEX ap(*),x(*),y(*)
164 * ..
165 *
166 * =====================================================================
167 *
168 * .. Parameters ..
169  COMPLEX one
170  parameter(one= (1.0e+0,0.0e+0))
171  COMPLEX zero
172  parameter(zero= (0.0e+0,0.0e+0))
173 * ..
174 * .. Local Scalars ..
175  COMPLEX 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 conjg,real
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('CHPMV ',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 + conjg(ap(k))*x(i)
268  k = k + 1
269  50 CONTINUE
270  y(j) = y(j) + temp1*REAL(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 + conjg(ap(k))*x(ix)
284  ix = ix + incx
285  iy = iy + incy
286  70 CONTINUE
287  y(jy) = y(jy) + temp1*REAL(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*REAL(ap(kk))
302  k = kk + 1
303  DO 90 i = j + 1,n
304  y(i) = y(i) + temp1*ap(k)
305  temp2 = temp2 + conjg(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*REAL(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 + conjg(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 CHPMV .
337 *
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: