LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ chpmv()

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, 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, 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, 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.
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 148 of file chpmv.f.

149*
150* -- Reference BLAS level2 routine --
151* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
152* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
153*
154* .. Scalar Arguments ..
155 COMPLEX ALPHA,BETA
156 INTEGER INCX,INCY,N
157 CHARACTER UPLO
158* ..
159* .. Array Arguments ..
160 COMPLEX AP(*),X(*),Y(*)
161* ..
162*
163* =====================================================================
164*
165* .. Parameters ..
166 COMPLEX ONE
167 parameter(one= (1.0e+0,0.0e+0))
168 COMPLEX ZERO
169 parameter(zero= (0.0e+0,0.0e+0))
170* ..
171* .. Local Scalars ..
172 COMPLEX TEMP1,TEMP2
173 INTEGER I,INFO,IX,IY,J,JX,JY,K,KK,KX,KY
174* ..
175* .. External Functions ..
176 LOGICAL LSAME
177 EXTERNAL lsame
178* ..
179* .. External Subroutines ..
180 EXTERNAL xerbla
181* ..
182* .. Intrinsic Functions ..
183 INTRINSIC conjg,real
184* ..
185*
186* Test the input parameters.
187*
188 info = 0
189 IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
190 info = 1
191 ELSE IF (n.LT.0) THEN
192 info = 2
193 ELSE IF (incx.EQ.0) THEN
194 info = 6
195 ELSE IF (incy.EQ.0) THEN
196 info = 9
197 END IF
198 IF (info.NE.0) THEN
199 CALL xerbla('CHPMV ',info)
200 RETURN
201 END IF
202*
203* Quick return if possible.
204*
205 IF ((n.EQ.0) .OR. ((alpha.EQ.zero).AND. (beta.EQ.one))) RETURN
206*
207* Set up the start points in X and Y.
208*
209 IF (incx.GT.0) THEN
210 kx = 1
211 ELSE
212 kx = 1 - (n-1)*incx
213 END IF
214 IF (incy.GT.0) THEN
215 ky = 1
216 ELSE
217 ky = 1 - (n-1)*incy
218 END IF
219*
220* Start the operations. In this version the elements of the array AP
221* are accessed sequentially with one pass through AP.
222*
223* First form y := beta*y.
224*
225 IF (beta.NE.one) THEN
226 IF (incy.EQ.1) THEN
227 IF (beta.EQ.zero) THEN
228 DO 10 i = 1,n
229 y(i) = zero
230 10 CONTINUE
231 ELSE
232 DO 20 i = 1,n
233 y(i) = beta*y(i)
234 20 CONTINUE
235 END IF
236 ELSE
237 iy = ky
238 IF (beta.EQ.zero) THEN
239 DO 30 i = 1,n
240 y(iy) = zero
241 iy = iy + incy
242 30 CONTINUE
243 ELSE
244 DO 40 i = 1,n
245 y(iy) = beta*y(iy)
246 iy = iy + incy
247 40 CONTINUE
248 END IF
249 END IF
250 END IF
251 IF (alpha.EQ.zero) RETURN
252 kk = 1
253 IF (lsame(uplo,'U')) THEN
254*
255* Form y when AP contains the upper triangle.
256*
257 IF ((incx.EQ.1) .AND. (incy.EQ.1)) THEN
258 DO 60 j = 1,n
259 temp1 = alpha*x(j)
260 temp2 = zero
261 k = kk
262 DO 50 i = 1,j - 1
263 y(i) = y(i) + temp1*ap(k)
264 temp2 = temp2 + conjg(ap(k))*x(i)
265 k = k + 1
266 50 CONTINUE
267 y(j) = y(j) + temp1*real(ap(kk+j-1)) + alpha*temp2
268 kk = kk + j
269 60 CONTINUE
270 ELSE
271 jx = kx
272 jy = ky
273 DO 80 j = 1,n
274 temp1 = alpha*x(jx)
275 temp2 = zero
276 ix = kx
277 iy = ky
278 DO 70 k = kk,kk + j - 2
279 y(iy) = y(iy) + temp1*ap(k)
280 temp2 = temp2 + conjg(ap(k))*x(ix)
281 ix = ix + incx
282 iy = iy + incy
283 70 CONTINUE
284 y(jy) = y(jy) + temp1*real(ap(kk+j-1)) + alpha*temp2
285 jx = jx + incx
286 jy = jy + incy
287 kk = kk + j
288 80 CONTINUE
289 END IF
290 ELSE
291*
292* Form y when AP contains the lower triangle.
293*
294 IF ((incx.EQ.1) .AND. (incy.EQ.1)) THEN
295 DO 100 j = 1,n
296 temp1 = alpha*x(j)
297 temp2 = zero
298 y(j) = y(j) + temp1*real(ap(kk))
299 k = kk + 1
300 DO 90 i = j + 1,n
301 y(i) = y(i) + temp1*ap(k)
302 temp2 = temp2 + conjg(ap(k))*x(i)
303 k = k + 1
304 90 CONTINUE
305 y(j) = y(j) + alpha*temp2
306 kk = kk + (n-j+1)
307 100 CONTINUE
308 ELSE
309 jx = kx
310 jy = ky
311 DO 120 j = 1,n
312 temp1 = alpha*x(jx)
313 temp2 = zero
314 y(jy) = y(jy) + temp1*real(ap(kk))
315 ix = jx
316 iy = jy
317 DO 110 k = kk + 1,kk + n - j
318 ix = ix + incx
319 iy = iy + incy
320 y(iy) = y(iy) + temp1*ap(k)
321 temp2 = temp2 + conjg(ap(k))*x(ix)
322 110 CONTINUE
323 y(jy) = y(jy) + alpha*temp2
324 jx = jx + incx
325 jy = jy + incy
326 kk = kk + (n-j+1)
327 120 CONTINUE
328 END IF
329 END IF
330*
331 RETURN
332*
333* End of CHPMV
334*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: