PLASMA  2.4.5
PLASMA - Parallel Linear Algebra for Scalable Multi-core Architectures
 All Data Structures Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Groups
cspmv.f
Go to the documentation of this file.
1  SUBROUTINE cspmv( UPLO, N, ALPHA, AP, X, INCX, BETA, Y, INCY )
2 *
3 * -- LAPACK auxiliary routine (version 3.2) --
4 * -- LAPACK is a software package provided by Univ. of Tennessee, --
5 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
6 * November 2006
7 *
8 * .. Scalar Arguments ..
9  CHARACTER uplo
10  INTEGER incx, incy, n
11  COMPLEX alpha, beta
12 * ..
13 * .. Array Arguments ..
14  COMPLEX ap( * ), x( * ), y( * )
15 * ..
16 *
17 * Purpose
18 * =======
19 *
20 * CSPMV performs the matrix-vector operation
21 *
22 * y := alpha*A*x + beta*y,
23 *
24 * where alpha and beta are scalars, x and y are n element vectors and
25 * A is an n by n symmetric matrix, supplied in packed form.
26 *
27 * Arguments
28 * ==========
29 *
30 * UPLO (input) CHARACTER*1
31 * On entry, UPLO specifies whether the upper or lower
32 * triangular part of the matrix A is supplied in the packed
33 * array AP as follows:
34 *
35 * UPLO = 'U' or 'u' The upper triangular part of A is
36 * supplied in AP.
37 *
38 * UPLO = 'L' or 'l' The lower triangular part of A is
39 * supplied in AP.
40 *
41 * Unchanged on exit.
42 *
43 * N (input) INTEGER
44 * On entry, N specifies the order of the matrix A.
45 * N must be at least zero.
46 * Unchanged on exit.
47 *
48 * ALPHA (input) COMPLEX
49 * On entry, ALPHA specifies the scalar alpha.
50 * Unchanged on exit.
51 *
52 * AP (input) COMPLEX array, dimension at least
53 * ( ( N*( N + 1 ) )/2 ).
54 * Before entry, with UPLO = 'U' or 'u', the array AP must
55 * contain the upper triangular part of the symmetric matrix
56 * packed sequentially, column by column, so that AP( 1 )
57 * contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 1, 2 )
58 * and a( 2, 2 ) respectively, and so on.
59 * Before entry, with UPLO = 'L' or 'l', the array AP must
60 * contain the lower triangular part of the symmetric matrix
61 * packed sequentially, column by column, so that AP( 1 )
62 * contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 2, 1 )
63 * and a( 3, 1 ) respectively, and so on.
64 * Unchanged on exit.
65 *
66 * X (input) COMPLEX array, dimension at least
67 * ( 1 + ( N - 1 )*abs( INCX ) ).
68 * Before entry, the incremented array X must contain the N-
69 * element vector x.
70 * Unchanged on exit.
71 *
72 * INCX (input) INTEGER
73 * On entry, INCX specifies the increment for the elements of
74 * X. INCX must not be zero.
75 * Unchanged on exit.
76 *
77 * BETA (input) COMPLEX
78 * On entry, BETA specifies the scalar beta. When BETA is
79 * supplied as zero then Y need not be set on input.
80 * Unchanged on exit.
81 *
82 * Y (input/output) COMPLEX array, dimension at least
83 * ( 1 + ( N - 1 )*abs( INCY ) ).
84 * Before entry, the incremented array Y must contain the n
85 * element vector y. On exit, Y is overwritten by the updated
86 * vector y.
87 *
88 * INCY (input) INTEGER
89 * On entry, INCY specifies the increment for the elements of
90 * Y. INCY must not be zero.
91 * Unchanged on exit.
92 *
93 * =====================================================================
94 *
95 * .. Parameters ..
96  COMPLEX one
97  parameter( one = ( 1.0e+0, 0.0e+0 ) )
98  COMPLEX zero
99  parameter( zero = ( 0.0e+0, 0.0e+0 ) )
100 * ..
101 * .. Local Scalars ..
102  INTEGER i, info, ix, iy, j, jx, jy, k, kk, kx, ky
103  COMPLEX temp1, temp2
104 * ..
105 * .. External Functions ..
106  LOGICAL lsame
107  EXTERNAL lsame
108 * ..
109 * .. External Subroutines ..
110  EXTERNAL xerbla
111 * ..
112 * .. Executable Statements ..
113 *
114 * Test the input parameters.
115 *
116  info = 0
117  IF( .NOT.lsame( uplo, 'U' ) .AND. .NOT.lsame( uplo, 'L' ) ) THEN
118  info = 1
119  ELSE IF( n.LT.0 ) THEN
120  info = 2
121  ELSE IF( incx.EQ.0 ) THEN
122  info = 6
123  ELSE IF( incy.EQ.0 ) THEN
124  info = 9
125  END IF
126  IF( info.NE.0 ) THEN
127  CALL xerbla( 'CSPMV ', info )
128  return
129  END IF
130 *
131 * Quick return if possible.
132 *
133  IF( ( n.EQ.0 ) .OR. ( ( alpha.EQ.zero ) .AND. ( beta.EQ.one ) ) )
134  $ return
135 *
136 * Set up the start points in X and Y.
137 *
138  IF( incx.GT.0 ) THEN
139  kx = 1
140  ELSE
141  kx = 1 - ( n-1 )*incx
142  END IF
143  IF( incy.GT.0 ) THEN
144  ky = 1
145  ELSE
146  ky = 1 - ( n-1 )*incy
147  END IF
148 *
149 * Start the operations. In this version the elements of the array AP
150 * are accessed sequentially with one pass through AP.
151 *
152 * First form y := beta*y.
153 *
154  IF( beta.NE.one ) THEN
155  IF( incy.EQ.1 ) THEN
156  IF( beta.EQ.zero ) THEN
157  DO 10 i = 1, n
158  y( i ) = zero
159  10 continue
160  ELSE
161  DO 20 i = 1, n
162  y( i ) = beta*y( i )
163  20 continue
164  END IF
165  ELSE
166  iy = ky
167  IF( beta.EQ.zero ) THEN
168  DO 30 i = 1, n
169  y( iy ) = zero
170  iy = iy + incy
171  30 continue
172  ELSE
173  DO 40 i = 1, n
174  y( iy ) = beta*y( iy )
175  iy = iy + incy
176  40 continue
177  END IF
178  END IF
179  END IF
180  IF( alpha.EQ.zero )
181  $ return
182  kk = 1
183  IF( lsame( uplo, 'U' ) ) THEN
184 *
185 * Form y when AP contains the upper triangle.
186 *
187  IF( ( incx.EQ.1 ) .AND. ( incy.EQ.1 ) ) THEN
188  DO 60 j = 1, n
189  temp1 = alpha*x( j )
190  temp2 = zero
191  k = kk
192  DO 50 i = 1, j - 1
193  y( i ) = y( i ) + temp1*ap( k )
194  temp2 = temp2 + ap( k )*x( i )
195  k = k + 1
196  50 continue
197  y( j ) = y( j ) + temp1*ap( kk+j-1 ) + alpha*temp2
198  kk = kk + j
199  60 continue
200  ELSE
201  jx = kx
202  jy = ky
203  DO 80 j = 1, n
204  temp1 = alpha*x( jx )
205  temp2 = zero
206  ix = kx
207  iy = ky
208  DO 70 k = kk, kk + j - 2
209  y( iy ) = y( iy ) + temp1*ap( k )
210  temp2 = temp2 + ap( k )*x( ix )
211  ix = ix + incx
212  iy = iy + incy
213  70 continue
214  y( jy ) = y( jy ) + temp1*ap( kk+j-1 ) + alpha*temp2
215  jx = jx + incx
216  jy = jy + incy
217  kk = kk + j
218  80 continue
219  END IF
220  ELSE
221 *
222 * Form y when AP contains the lower triangle.
223 *
224  IF( ( incx.EQ.1 ) .AND. ( incy.EQ.1 ) ) THEN
225  DO 100 j = 1, n
226  temp1 = alpha*x( j )
227  temp2 = zero
228  y( j ) = y( j ) + temp1*ap( kk )
229  k = kk + 1
230  DO 90 i = j + 1, n
231  y( i ) = y( i ) + temp1*ap( k )
232  temp2 = temp2 + ap( k )*x( i )
233  k = k + 1
234  90 continue
235  y( j ) = y( j ) + alpha*temp2
236  kk = kk + ( n-j+1 )
237  100 continue
238  ELSE
239  jx = kx
240  jy = ky
241  DO 120 j = 1, n
242  temp1 = alpha*x( jx )
243  temp2 = zero
244  y( jy ) = y( jy ) + temp1*ap( kk )
245  ix = jx
246  iy = jy
247  DO 110 k = kk + 1, kk + n - j
248  ix = ix + incx
249  iy = iy + incy
250  y( iy ) = y( iy ) + temp1*ap( k )
251  temp2 = temp2 + ap( k )*x( ix )
252  110 continue
253  y( jy ) = y( jy ) + alpha*temp2
254  jx = jx + incx
255  jy = jy + incy
256  kk = kk + ( n-j+1 )
257  120 continue
258  END IF
259  END IF
260 *
261  return
262 *
263 * End of CSPMV
264 *
265  END