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

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

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

Purpose:
 CSPMV  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
           On entry, ALPHA specifies the scalar alpha.
           Unchanged on exit.
[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 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 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
           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 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.
Date
September 2012

Definition at line 153 of file cspmv.f.

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