ScaLAPACK 2.1  2.1
ScaLAPACK: Scalable Linear Algebra PACKage
csymv.f
Go to the documentation of this file.
1  SUBROUTINE csymv( UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY )
2 *
3 * -- PBLAS auxiliary routine (version 2.0) --
4 * University of Tennessee, Knoxville, Oak Ridge National Laboratory,
5 * and University of California, Berkeley.
6 * April 1, 1998
7 *
8 * .. Scalar Arguments ..
9  CHARACTER*1 UPLO
10  INTEGER INCX, INCY, LDA, N
11  COMPLEX ALPHA, BETA
12 * ..
13 * .. Array Arguments ..
14  COMPLEX A( LDA, * ), X( * ), Y( * )
15 * ..
16 *
17 * Purpose
18 * =======
19 *
20 * CSYMV performs the following 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.
26 *
27 * Arguments
28 * =========
29 *
30 * UPLO (input) CHARACTER*1
31 * On entry, UPLO specifies whether the upper or lower triangu-
32 * lar part of the array A is to be referenced as follows:
33 *
34 * UPLO = 'U' or 'u' Only the upper triangular part of A is
35 * to be referenced.
36 * UPLO = 'L' or 'l' Only the lower triangular part of A is
37 * to be referenced.
38 *
39 * N (input) INTEGER
40 * On entry, N specifies the order of the matrix A. N must be at
41 * least zero.
42 *
43 * ALPHA (input) COMPLEX
44 * On entry, ALPHA specifies the real scalar alpha.
45 *
46 * A (input) COMPLEX array
47 * On entry, A is an array of dimension (LDA,N). Before entry
48 * with UPLO = 'U' or 'u', the leading n by n part of the array
49 * A must contain the upper triangular part of the symmetric ma-
50 * trix and the strictly lower triangular part of A is not refe-
51 * renced. When UPLO = 'L' or 'l', the leading n by n part of
52 * the array A must contain the lower triangular part of the
53 * symmetric matrix and the strictly upper trapezoidal part of A
54 * is not referenced.
55 *
56 * LDA (input) INTEGER
57 * On entry, LDA specifies the leading dimension of the array A.
58 * LDA must be at least max( 1, N ).
59 *
60 * X (input) COMPLEX array of dimension at least
61 * ( 1 + ( n - 1 )*abs( INCX ) ). Before entry, the incremented
62 * array X must contain the vector x.
63 *
64 * INCX (input) INTEGER
65 * On entry, INCX specifies the increment for the elements of X.
66 * INCX must not be zero.
67 *
68 * BETA (input) COMPLEX
69 * On entry, BETA specifies the real scalar beta. When BETA is
70 * supplied as zero then Y need not be set on input.
71 *
72 * Y (input/output) COMPLEX array of dimension at least
73 * ( 1 + ( n - 1 )*abs( INCY ) ). Before entry with BETA non-
74 * zero, the incremented array Y must contain the vector y. On
75 * exit, the incremented array Y is overwritten by the updated
76 * vector y.
77 *
78 * INCY (input) INTEGER
79 * On entry, INCY specifies the increment for the elements of Y.
80 * INCY must not be zero.
81 *
82 * =====================================================================
83 *
84 * .. Parameters ..
85  COMPLEX ONE, ZERO
86  parameter( one = ( 1.0e+0, 0.0e+0 ),
87  $ zero = ( 0.0e+0, 0.0e+0 ) )
88 * ..
89 * .. Local Scalars ..
90  INTEGER I, INFO, IX, IY, J, JX, JY, KX, KY
91  COMPLEX TEMP1, TEMP2
92 * ..
93 * .. External Functions ..
94  LOGICAL LSAME
95  EXTERNAL lsame
96 * ..
97 * .. External Subroutines ..
98  EXTERNAL xerbla
99 * ..
100 * .. Intrinsic Functions ..
101  INTRINSIC max
102 * ..
103 * .. Executable Statements ..
104 *
105 * Test the input parameters.
106 *
107  info = 0
108  IF ( .NOT.lsame( uplo, 'U' ).AND.
109  $ .NOT.lsame( uplo, 'L' ) )THEN
110  info = 1
111  ELSE IF( n.LT.0 )THEN
112  info = 2
113  ELSE IF( lda.LT.max( 1, n ) )THEN
114  info = 5
115  ELSE IF( incx.EQ.0 )THEN
116  info = 7
117  ELSE IF( incy.EQ.0 )THEN
118  info = 10
119  END IF
120  IF( info.NE.0 )THEN
121  CALL xerbla( 'CSYMV ', info )
122  RETURN
123  END IF
124 *
125 * Quick return if possible.
126 *
127  IF( ( n.EQ.0 ).OR.( ( alpha.EQ.zero ).AND.( beta.EQ.one ) ) )
128  $ RETURN
129 *
130 * Set up the start points in X and Y.
131 *
132  IF( incx.GT.0 )THEN
133  kx = 1
134  ELSE
135  kx = 1 - ( n - 1 )*incx
136  END IF
137  IF( incy.GT.0 )THEN
138  ky = 1
139  ELSE
140  ky = 1 - ( n - 1 )*incy
141  END IF
142 *
143 * Start the operations. In this version the elements of A are
144 * accessed sequentially with one pass through the triangular part
145 * of A.
146 *
147 * First form y := beta*y.
148 *
149  IF( beta.NE.one )THEN
150  IF( incy.EQ.1 )THEN
151  IF( beta.EQ.zero )THEN
152  DO 10, i = 1, n
153  y( i ) = zero
154  10 CONTINUE
155  ELSE
156  DO 20, i = 1, n
157  y( i ) = beta*y( i )
158  20 CONTINUE
159  END IF
160  ELSE
161  iy = ky
162  IF( beta.EQ.zero )THEN
163  DO 30, i = 1, n
164  y( iy ) = zero
165  iy = iy + incy
166  30 CONTINUE
167  ELSE
168  DO 40, i = 1, n
169  y( iy ) = beta*y( iy )
170  iy = iy + incy
171  40 CONTINUE
172  END IF
173  END IF
174  END IF
175 *
176  IF( alpha.EQ.zero )
177  $ RETURN
178 *
179  IF( lsame( uplo, 'U' ) )THEN
180 *
181 * Form y when A is stored in upper triangle.
182 *
183  IF( ( incx.EQ.1 ).AND.( incy.EQ.1 ) )THEN
184  DO 60, j = 1, n
185  temp1 = alpha*x( j )
186  temp2 = zero
187  DO 50, i = 1, j - 1
188  y( i ) = y( i ) + temp1*a( i, j )
189  temp2 = temp2 + a( i, j )*x( i )
190  50 CONTINUE
191  y( j ) = y( j ) + temp1*a( j, j ) + alpha*temp2
192  60 CONTINUE
193  ELSE
194  jx = kx
195  jy = ky
196  DO 80, j = 1, n
197  temp1 = alpha*x( jx )
198  temp2 = zero
199  ix = kx
200  iy = ky
201  DO 70, i = 1, j - 1
202  y( iy ) = y( iy ) + temp1*a( i, j )
203  temp2 = temp2 + a( i, j )*x( ix )
204  ix = ix + incx
205  iy = iy + incy
206  70 CONTINUE
207  y( jy ) = y( jy ) + temp1*a( j, j ) + alpha*temp2
208  jx = jx + incx
209  jy = jy + incy
210  80 CONTINUE
211  END IF
212  ELSE
213 *
214 * Form y when A is stored in lower triangle.
215 *
216  IF( ( incx.EQ.1 ).AND.( incy.EQ.1 ) )THEN
217  DO 100, j = 1, n
218  temp1 = alpha*x( j )
219  temp2 = zero
220  y( j ) = y( j ) + temp1*a( j, j )
221  DO 90, i = j + 1, n
222  y( i ) = y( i ) + temp1*a( i, j )
223  temp2 = temp2 + a( i, j )*x( i )
224  90 CONTINUE
225  y( j ) = y( j ) + alpha*temp2
226  100 CONTINUE
227  ELSE
228  jx = kx
229  jy = ky
230  DO 120, j = 1, n
231  temp1 = alpha*x( jx )
232  temp2 = zero
233  y( jy ) = y( jy ) + temp1*a( j, j )
234  ix = jx
235  iy = jy
236  DO 110, i = j + 1, n
237  ix = ix + incx
238  iy = iy + incy
239  y( iy ) = y( iy ) + temp1*a( i, j )
240  temp2 = temp2 + a( i, j )*x( ix )
241  110 CONTINUE
242  y( jy ) = y( jy ) + alpha*temp2
243  jx = jx + incx
244  jy = jy + incy
245  120 CONTINUE
246  END IF
247  END IF
248 *
249  RETURN
250 *
251 * End of CSYMV
252 *
253  END
max
#define max(A, B)
Definition: pcgemr.c:180
csymv
subroutine csymv(UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
Definition: csymv.f:2