LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine ssyr2 ( character  UPLO,
integer  N,
real  ALPHA,
real, dimension(*)  X,
integer  INCX,
real, dimension(*)  Y,
integer  INCY,
real, dimension(lda,*)  A,
integer  LDA 
)

SSYR2

Purpose:
 SSYR2  performs the symmetric rank 2 operation

    A := alpha*x*y**T + alpha*y*x**T + A,

 where alpha is a scalar, x and y are n element vectors and A is an n
 by n symmetric matrix.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
           On entry, UPLO specifies whether the upper or lower
           triangular part of the array A is to be referenced as
           follows:

              UPLO = 'U' or 'u'   Only the upper triangular part of A
                                  is to be referenced.

              UPLO = 'L' or 'l'   Only the lower triangular part of A
                                  is to be referenced.
[in]N
          N is INTEGER
           On entry, N specifies the order of the matrix A.
           N must be at least zero.
[in]ALPHA
          ALPHA is REAL
           On entry, ALPHA specifies the scalar alpha.
[in]X
          X is REAL array of dimension at least
           ( 1 + ( n - 1 )*abs( INCX ) ).
           Before entry, the incremented array X must contain the n
           element vector x.
[in]INCX
          INCX is INTEGER
           On entry, INCX specifies the increment for the elements of
           X. INCX must not be zero.
[in]Y
          Y is REAL array of dimension at least
           ( 1 + ( n - 1 )*abs( INCY ) ).
           Before entry, the incremented array Y must contain the n
           element vector y.
[in]INCY
          INCY is INTEGER
           On entry, INCY specifies the increment for the elements of
           Y. INCY must not be zero.
[in,out]A
          A is REAL array of DIMENSION ( LDA, n ).
           Before entry with  UPLO = 'U' or 'u', the leading n by n
           upper triangular part of the array A must contain the upper
           triangular part of the symmetric matrix and the strictly
           lower triangular part of A is not referenced. On exit, the
           upper triangular part of the array A is overwritten by the
           upper triangular part of the updated matrix.
           Before entry with UPLO = 'L' or 'l', the leading n by n
           lower triangular part of the array A must contain the lower
           triangular part of the symmetric matrix and the strictly
           upper triangular part of A is not referenced. On exit, the
           lower triangular part of the array A is overwritten by the
           lower triangular part of the updated matrix.
[in]LDA
          LDA is INTEGER
           On entry, LDA specifies the first dimension of A as declared
           in the calling (sub) program. LDA must be at least
           max( 1, n ).
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011
Further Details:
  Level 2 Blas routine.

  -- Written on 22-October-1986.
     Jack Dongarra, Argonne National Lab.
     Jeremy Du Croz, Nag Central Office.
     Sven Hammarling, Nag Central Office.
     Richard Hanson, Sandia National Labs.

Definition at line 149 of file ssyr2.f.

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 *
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: