LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
ssyr2.f
Go to the documentation of this file.
1 *> \brief \b SSYR2
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE SSYR2(UPLO,N,ALPHA,X,INCX,Y,INCY,A,LDA)
12 *
13 * .. Scalar Arguments ..
14 * REAL ALPHA
15 * INTEGER INCX,INCY,LDA,N
16 * CHARACTER UPLO
17 * ..
18 * .. Array Arguments ..
19 * REAL A(LDA,*),X(*),Y(*)
20 * ..
21 *
22 *
23 *> \par Purpose:
24 * =============
25 *>
26 *> \verbatim
27 *>
28 *> SSYR2 performs the symmetric rank 2 operation
29 *>
30 *> A := alpha*x*y**T + alpha*y*x**T + A,
31 *>
32 *> where alpha is a scalar, x and y are n element vectors and A is an n
33 *> by n symmetric matrix.
34 *> \endverbatim
35 *
36 * Arguments:
37 * ==========
38 *
39 *> \param[in] UPLO
40 *> \verbatim
41 *> UPLO is CHARACTER*1
42 *> On entry, UPLO specifies whether the upper or lower
43 *> triangular part of the array A is to be referenced as
44 *> follows:
45 *>
46 *> UPLO = 'U' or 'u' Only the upper triangular part of A
47 *> is to be referenced.
48 *>
49 *> UPLO = 'L' or 'l' Only the lower triangular part of A
50 *> is to be referenced.
51 *> \endverbatim
52 *>
53 *> \param[in] N
54 *> \verbatim
55 *> N is INTEGER
56 *> On entry, N specifies the order of the matrix A.
57 *> N must be at least zero.
58 *> \endverbatim
59 *>
60 *> \param[in] ALPHA
61 *> \verbatim
62 *> ALPHA is REAL
63 *> On entry, ALPHA specifies the scalar alpha.
64 *> \endverbatim
65 *>
66 *> \param[in] X
67 *> \verbatim
68 *> X is REAL array of dimension at least
69 *> ( 1 + ( n - 1 )*abs( INCX ) ).
70 *> Before entry, the incremented array X must contain the n
71 *> element vector x.
72 *> \endverbatim
73 *>
74 *> \param[in] INCX
75 *> \verbatim
76 *> INCX is INTEGER
77 *> On entry, INCX specifies the increment for the elements of
78 *> X. INCX must not be zero.
79 *> \endverbatim
80 *>
81 *> \param[in] Y
82 *> \verbatim
83 *> Y is REAL array of dimension at least
84 *> ( 1 + ( n - 1 )*abs( INCY ) ).
85 *> Before entry, the incremented array Y must contain the n
86 *> element vector y.
87 *> \endverbatim
88 *>
89 *> \param[in] INCY
90 *> \verbatim
91 *> INCY is INTEGER
92 *> On entry, INCY specifies the increment for the elements of
93 *> Y. INCY must not be zero.
94 *> \endverbatim
95 *>
96 *> \param[in,out] A
97 *> \verbatim
98 *> A is REAL array of DIMENSION ( LDA, n ).
99 *> Before entry with UPLO = 'U' or 'u', the leading n by n
100 *> upper triangular part of the array A must contain the upper
101 *> triangular part of the symmetric matrix and the strictly
102 *> lower triangular part of A is not referenced. On exit, the
103 *> upper triangular part of the array A is overwritten by the
104 *> upper triangular part of the updated matrix.
105 *> Before entry with UPLO = 'L' or 'l', the leading n by n
106 *> lower triangular part of the array A must contain the lower
107 *> triangular part of the symmetric matrix and the strictly
108 *> upper triangular part of A is not referenced. On exit, the
109 *> lower triangular part of the array A is overwritten by the
110 *> lower triangular part of the updated matrix.
111 *> \endverbatim
112 *>
113 *> \param[in] LDA
114 *> \verbatim
115 *> LDA is INTEGER
116 *> On entry, LDA specifies the first dimension of A as declared
117 *> in the calling (sub) program. LDA must be at least
118 *> max( 1, n ).
119 *> \endverbatim
120 *
121 * Authors:
122 * ========
123 *
124 *> \author Univ. of Tennessee
125 *> \author Univ. of California Berkeley
126 *> \author Univ. of Colorado Denver
127 *> \author NAG Ltd.
128 *
129 *> \date November 2011
130 *
131 *> \ingroup single_blas_level2
132 *
133 *> \par Further Details:
134 * =====================
135 *>
136 *> \verbatim
137 *>
138 *> Level 2 Blas routine.
139 *>
140 *> -- Written on 22-October-1986.
141 *> Jack Dongarra, Argonne National Lab.
142 *> Jeremy Du Croz, Nag Central Office.
143 *> Sven Hammarling, Nag Central Office.
144 *> Richard Hanson, Sandia National Labs.
145 *> \endverbatim
146 *>
147 * =====================================================================
148  SUBROUTINE ssyr2(UPLO,N,ALPHA,X,INCX,Y,INCY,A,LDA)
149 *
150 * -- Reference BLAS level2 routine (version 3.4.0) --
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 * November 2011
154 *
155 * .. Scalar Arguments ..
156  REAL alpha
157  INTEGER incx,incy,lda,n
158  CHARACTER uplo
159 * ..
160 * .. Array Arguments ..
161  REAL a(lda,*),x(*),y(*)
162 * ..
163 *
164 * =====================================================================
165 *
166 * .. Parameters ..
167  REAL zero
168  parameter(zero=0.0e+0)
169 * ..
170 * .. Local Scalars ..
171  REAL temp1,temp2
172  INTEGER i,info,ix,iy,j,jx,jy,kx,ky
173 * ..
174 * .. External Functions ..
175  LOGICAL lsame
176  EXTERNAL lsame
177 * ..
178 * .. External Subroutines ..
179  EXTERNAL xerbla
180 * ..
181 * .. Intrinsic Functions ..
182  INTRINSIC max
183 * ..
184 *
185 * Test the input parameters.
186 *
187  info = 0
188  IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
189  info = 1
190  ELSE IF (n.LT.0) THEN
191  info = 2
192  ELSE IF (incx.EQ.0) THEN
193  info = 5
194  ELSE IF (incy.EQ.0) THEN
195  info = 7
196  ELSE IF (lda.LT.max(1,n)) THEN
197  info = 9
198  END IF
199  IF (info.NE.0) THEN
200  CALL xerbla('SSYR2 ',info)
201  return
202  END IF
203 *
204 * Quick return if possible.
205 *
206  IF ((n.EQ.0) .OR. (alpha.EQ.zero)) return
207 *
208 * Set up the start points in X and Y if the increments are not both
209 * unity.
210 *
211  IF ((incx.NE.1) .OR. (incy.NE.1)) THEN
212  IF (incx.GT.0) THEN
213  kx = 1
214  ELSE
215  kx = 1 - (n-1)*incx
216  END IF
217  IF (incy.GT.0) THEN
218  ky = 1
219  ELSE
220  ky = 1 - (n-1)*incy
221  END IF
222  jx = kx
223  jy = ky
224  END IF
225 *
226 * Start the operations. In this version the elements of A are
227 * accessed sequentially with one pass through the triangular part
228 * of A.
229 *
230  IF (lsame(uplo,'U')) THEN
231 *
232 * Form A when A is stored in the upper triangle.
233 *
234  IF ((incx.EQ.1) .AND. (incy.EQ.1)) THEN
235  DO 20 j = 1,n
236  IF ((x(j).NE.zero) .OR. (y(j).NE.zero)) THEN
237  temp1 = alpha*y(j)
238  temp2 = alpha*x(j)
239  DO 10 i = 1,j
240  a(i,j) = a(i,j) + x(i)*temp1 + y(i)*temp2
241  10 continue
242  END IF
243  20 continue
244  ELSE
245  DO 40 j = 1,n
246  IF ((x(jx).NE.zero) .OR. (y(jy).NE.zero)) THEN
247  temp1 = alpha*y(jy)
248  temp2 = alpha*x(jx)
249  ix = kx
250  iy = ky
251  DO 30 i = 1,j
252  a(i,j) = a(i,j) + x(ix)*temp1 + y(iy)*temp2
253  ix = ix + incx
254  iy = iy + incy
255  30 continue
256  END IF
257  jx = jx + incx
258  jy = jy + incy
259  40 continue
260  END IF
261  ELSE
262 *
263 * Form A when A is stored in the lower triangle.
264 *
265  IF ((incx.EQ.1) .AND. (incy.EQ.1)) THEN
266  DO 60 j = 1,n
267  IF ((x(j).NE.zero) .OR. (y(j).NE.zero)) THEN
268  temp1 = alpha*y(j)
269  temp2 = alpha*x(j)
270  DO 50 i = j,n
271  a(i,j) = a(i,j) + x(i)*temp1 + y(i)*temp2
272  50 continue
273  END IF
274  60 continue
275  ELSE
276  DO 80 j = 1,n
277  IF ((x(jx).NE.zero) .OR. (y(jy).NE.zero)) THEN
278  temp1 = alpha*y(jy)
279  temp2 = alpha*x(jx)
280  ix = jx
281  iy = jy
282  DO 70 i = j,n
283  a(i,j) = a(i,j) + x(ix)*temp1 + y(iy)*temp2
284  ix = ix + incx
285  iy = iy + incy
286  70 continue
287  END IF
288  jx = jx + incx
289  jy = jy + incy
290  80 continue
291  END IF
292  END IF
293 *
294  return
295 *
296 * End of SSYR2 .
297 *
298  END