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

◆ zspmv()

subroutine zspmv ( character  uplo,
integer  n,
complex*16  alpha,
complex*16, dimension( * )  ap,
complex*16, dimension( * )  x,
integer  incx,
complex*16  beta,
complex*16, dimension( * )  y,
integer  incy 
)

ZSPMV computes a matrix-vector product for complex vectors using a complex symmetric packed matrix

Download ZSPMV + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 ZSPMV  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 symmetric 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.

           Unchanged on exit.
[in]N
          N is INTEGER
           On entry, N specifies the order of the matrix A.
           N must be at least zero.
           Unchanged on exit.
[in]ALPHA
          ALPHA is COMPLEX*16
           On entry, ALPHA specifies the scalar alpha.
           Unchanged on exit.
[in]AP
          AP is COMPLEX*16 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 symmetric 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 symmetric 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.
           Unchanged on exit.
[in]X
          X is COMPLEX*16 array, dimension at least
           ( 1 + ( N - 1 )*abs( INCX ) ).
           Before entry, the incremented array X must contain the N-
           element vector x.
           Unchanged on exit.
[in]INCX
          INCX is INTEGER
           On entry, INCX specifies the increment for the elements of
           X. INCX must not be zero.
           Unchanged on exit.
[in]BETA
          BETA is COMPLEX*16
           On entry, BETA specifies the scalar beta. When BETA is
           supplied as zero then Y need not be set on input.
           Unchanged on exit.
[in,out]Y
          Y is COMPLEX*16 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.
           Unchanged on exit.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 150 of file zspmv.f.

151*
152* -- LAPACK auxiliary routine --
153* -- LAPACK is a software package provided by Univ. of Tennessee, --
154* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
155*
156* .. Scalar Arguments ..
157 CHARACTER UPLO
158 INTEGER INCX, INCY, N
159 COMPLEX*16 ALPHA, BETA
160* ..
161* .. Array Arguments ..
162 COMPLEX*16 AP( * ), X( * ), Y( * )
163* ..
164*
165* =====================================================================
166*
167* .. Parameters ..
168 COMPLEX*16 ONE
169 parameter( one = ( 1.0d+0, 0.0d+0 ) )
170 COMPLEX*16 ZERO
171 parameter( zero = ( 0.0d+0, 0.0d+0 ) )
172* ..
173* .. Local Scalars ..
174 INTEGER I, INFO, IX, IY, J, JX, JY, K, KK, KX, KY
175 COMPLEX*16 TEMP1, TEMP2
176* ..
177* .. External Functions ..
178 LOGICAL LSAME
179 EXTERNAL lsame
180* ..
181* .. External Subroutines ..
182 EXTERNAL xerbla
183* ..
184* .. Executable Statements ..
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( 'ZSPMV ', 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 ) ) )
206 $ RETURN
207*
208* Set up the start points in X and Y.
209*
210 IF( incx.GT.0 ) THEN
211 kx = 1
212 ELSE
213 kx = 1 - ( n-1 )*incx
214 END IF
215 IF( incy.GT.0 ) THEN
216 ky = 1
217 ELSE
218 ky = 1 - ( n-1 )*incy
219 END IF
220*
221* Start the operations. In this version the elements of the array AP
222* are accessed sequentially with one pass through AP.
223*
224* First form y := beta*y.
225*
226 IF( beta.NE.one ) THEN
227 IF( incy.EQ.1 ) THEN
228 IF( beta.EQ.zero ) THEN
229 DO 10 i = 1, n
230 y( i ) = zero
231 10 CONTINUE
232 ELSE
233 DO 20 i = 1, n
234 y( i ) = beta*y( i )
235 20 CONTINUE
236 END IF
237 ELSE
238 iy = ky
239 IF( beta.EQ.zero ) THEN
240 DO 30 i = 1, n
241 y( iy ) = zero
242 iy = iy + incy
243 30 CONTINUE
244 ELSE
245 DO 40 i = 1, n
246 y( iy ) = beta*y( iy )
247 iy = iy + incy
248 40 CONTINUE
249 END IF
250 END IF
251 END IF
252 IF( alpha.EQ.zero )
253 $ RETURN
254 kk = 1
255 IF( lsame( uplo, 'U' ) ) THEN
256*
257* Form y when AP contains the upper triangle.
258*
259 IF( ( incx.EQ.1 ) .AND. ( incy.EQ.1 ) ) THEN
260 DO 60 j = 1, n
261 temp1 = alpha*x( j )
262 temp2 = zero
263 k = kk
264 DO 50 i = 1, j - 1
265 y( i ) = y( i ) + temp1*ap( k )
266 temp2 = temp2 + ap( k )*x( i )
267 k = k + 1
268 50 CONTINUE
269 y( j ) = y( j ) + temp1*ap( kk+j-1 ) + alpha*temp2
270 kk = kk + j
271 60 CONTINUE
272 ELSE
273 jx = kx
274 jy = ky
275 DO 80 j = 1, n
276 temp1 = alpha*x( jx )
277 temp2 = zero
278 ix = kx
279 iy = ky
280 DO 70 k = kk, kk + j - 2
281 y( iy ) = y( iy ) + temp1*ap( k )
282 temp2 = temp2 + ap( k )*x( ix )
283 ix = ix + incx
284 iy = iy + incy
285 70 CONTINUE
286 y( jy ) = y( jy ) + temp1*ap( kk+j-1 ) + alpha*temp2
287 jx = jx + incx
288 jy = jy + incy
289 kk = kk + j
290 80 CONTINUE
291 END IF
292 ELSE
293*
294* Form y when AP contains the lower triangle.
295*
296 IF( ( incx.EQ.1 ) .AND. ( incy.EQ.1 ) ) THEN
297 DO 100 j = 1, n
298 temp1 = alpha*x( j )
299 temp2 = zero
300 y( j ) = y( j ) + temp1*ap( kk )
301 k = kk + 1
302 DO 90 i = j + 1, n
303 y( i ) = y( i ) + temp1*ap( k )
304 temp2 = temp2 + ap( k )*x( i )
305 k = k + 1
306 90 CONTINUE
307 y( j ) = y( j ) + alpha*temp2
308 kk = kk + ( n-j+1 )
309 100 CONTINUE
310 ELSE
311 jx = kx
312 jy = ky
313 DO 120 j = 1, n
314 temp1 = alpha*x( jx )
315 temp2 = zero
316 y( jy ) = y( jy ) + temp1*ap( kk )
317 ix = jx
318 iy = jy
319 DO 110 k = kk + 1, kk + n - j
320 ix = ix + incx
321 iy = iy + incy
322 y( iy ) = y( iy ) + temp1*ap( k )
323 temp2 = temp2 + ap( k )*x( ix )
324 110 CONTINUE
325 y( jy ) = y( jy ) + alpha*temp2
326 jx = jx + incx
327 jy = jy + incy
328 kk = kk + ( n-j+1 )
329 120 CONTINUE
330 END IF
331 END IF
332*
333 RETURN
334*
335* End of ZSPMV
336*
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: