Statistiques
| Révision :

root / src / blas / ssyr2.f @ 7

Historique | Voir | Annoter | Télécharger (6,9 ko)

1
      SUBROUTINE SSYR2(UPLO,N,ALPHA,X,INCX,Y,INCY,A,LDA)
2
*     .. Scalar Arguments ..
3
      REAL ALPHA
4
      INTEGER INCX,INCY,LDA,N
5
      CHARACTER UPLO
6
*     ..
7
*     .. Array Arguments ..
8
      REAL A(LDA,*),X(*),Y(*)
9
*     ..
10
*
11
*  Purpose
12
*  =======
13
*
14
*  SSYR2  performs the symmetric rank 2 operation
15
*
16
*     A := alpha*x*y' + alpha*y*x' + A,
17
*
18
*  where alpha is a scalar, x and y are n element vectors and A is an n
19
*  by n symmetric matrix.
20
*
21
*  Arguments
22
*  ==========
23
*
24
*  UPLO   - CHARACTER*1.
25
*           On entry, UPLO specifies whether the upper or lower
26
*           triangular part of the array A is to be referenced as
27
*           follows:
28
*
29
*              UPLO = 'U' or 'u'   Only the upper triangular part of A
30
*                                  is to be referenced.
31
*
32
*              UPLO = 'L' or 'l'   Only the lower triangular part of A
33
*                                  is to be referenced.
34
*
35
*           Unchanged on exit.
36
*
37
*  N      - INTEGER.
38
*           On entry, N specifies the order of the matrix A.
39
*           N must be at least zero.
40
*           Unchanged on exit.
41
*
42
*  ALPHA  - REAL            .
43
*           On entry, ALPHA specifies the scalar alpha.
44
*           Unchanged on exit.
45
*
46
*  X      - REAL             array of dimension at least
47
*           ( 1 + ( n - 1 )*abs( INCX ) ).
48
*           Before entry, the incremented array X must contain the n
49
*           element vector x.
50
*           Unchanged on exit.
51
*
52
*  INCX   - INTEGER.
53
*           On entry, INCX specifies the increment for the elements of
54
*           X. INCX must not be zero.
55
*           Unchanged on exit.
56
*
57
*  Y      - REAL             array of dimension at least
58
*           ( 1 + ( n - 1 )*abs( INCY ) ).
59
*           Before entry, the incremented array Y must contain the n
60
*           element vector y.
61
*           Unchanged on exit.
62
*
63
*  INCY   - INTEGER.
64
*           On entry, INCY specifies the increment for the elements of
65
*           Y. INCY must not be zero.
66
*           Unchanged on exit.
67
*
68
*  A      - REAL             array of DIMENSION ( LDA, n ).
69
*           Before entry with  UPLO = 'U' or 'u', the leading n by n
70
*           upper triangular part of the array A must contain the upper
71
*           triangular part of the symmetric matrix and the strictly
72
*           lower triangular part of A is not referenced. On exit, the
73
*           upper triangular part of the array A is overwritten by the
74
*           upper triangular part of the updated matrix.
75
*           Before entry with UPLO = 'L' or 'l', the leading n by n
76
*           lower triangular part of the array A must contain the lower
77
*           triangular part of the symmetric matrix and the strictly
78
*           upper triangular part of A is not referenced. On exit, the
79
*           lower triangular part of the array A is overwritten by the
80
*           lower triangular part of the updated matrix.
81
*
82
*  LDA    - INTEGER.
83
*           On entry, LDA specifies the first dimension of A as declared
84
*           in the calling (sub) program. LDA must be at least
85
*           max( 1, n ).
86
*           Unchanged on exit.
87
*
88
*
89
*  Level 2 Blas routine.
90
*
91
*  -- Written on 22-October-1986.
92
*     Jack Dongarra, Argonne National Lab.
93
*     Jeremy Du Croz, Nag Central Office.
94
*     Sven Hammarling, Nag Central Office.
95
*     Richard Hanson, Sandia National Labs.
96
*
97
*
98
*     .. Parameters ..
99
      REAL ZERO
100
      PARAMETER (ZERO=0.0E+0)
101
*     ..
102
*     .. Local Scalars ..
103
      REAL TEMP1,TEMP2
104
      INTEGER I,INFO,IX,IY,J,JX,JY,KX,KY
105
*     ..
106
*     .. External Functions ..
107
      LOGICAL LSAME
108
      EXTERNAL LSAME
109
*     ..
110
*     .. External Subroutines ..
111
      EXTERNAL XERBLA
112
*     ..
113
*     .. Intrinsic Functions ..
114
      INTRINSIC MAX
115
*     ..
116
*
117
*     Test the input parameters.
118
*
119
      INFO = 0
120
      IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THEN
121
          INFO = 1
122
      ELSE IF (N.LT.0) THEN
123
          INFO = 2
124
      ELSE IF (INCX.EQ.0) THEN
125
          INFO = 5
126
      ELSE IF (INCY.EQ.0) THEN
127
          INFO = 7
128
      ELSE IF (LDA.LT.MAX(1,N)) THEN
129
          INFO = 9
130
      END IF
131
      IF (INFO.NE.0) THEN
132
          CALL XERBLA('SSYR2 ',INFO)
133
          RETURN
134
      END IF
135
*
136
*     Quick return if possible.
137
*
138
      IF ((N.EQ.0) .OR. (ALPHA.EQ.ZERO)) RETURN
139
*
140
*     Set up the start points in X and Y if the increments are not both
141
*     unity.
142
*
143
      IF ((INCX.NE.1) .OR. (INCY.NE.1)) THEN
144
          IF (INCX.GT.0) THEN
145
              KX = 1
146
          ELSE
147
              KX = 1 - (N-1)*INCX
148
          END IF
149
          IF (INCY.GT.0) THEN
150
              KY = 1
151
          ELSE
152
              KY = 1 - (N-1)*INCY
153
          END IF
154
          JX = KX
155
          JY = KY
156
      END IF
157
*
158
*     Start the operations. In this version the elements of A are
159
*     accessed sequentially with one pass through the triangular part
160
*     of A.
161
*
162
      IF (LSAME(UPLO,'U')) THEN
163
*
164
*        Form  A  when A is stored in the upper triangle.
165
*
166
          IF ((INCX.EQ.1) .AND. (INCY.EQ.1)) THEN
167
              DO 20 J = 1,N
168
                  IF ((X(J).NE.ZERO) .OR. (Y(J).NE.ZERO)) THEN
169
                      TEMP1 = ALPHA*Y(J)
170
                      TEMP2 = ALPHA*X(J)
171
                      DO 10 I = 1,J
172
                          A(I,J) = A(I,J) + X(I)*TEMP1 + Y(I)*TEMP2
173
   10                 CONTINUE
174
                  END IF
175
   20         CONTINUE
176
          ELSE
177
              DO 40 J = 1,N
178
                  IF ((X(JX).NE.ZERO) .OR. (Y(JY).NE.ZERO)) THEN
179
                      TEMP1 = ALPHA*Y(JY)
180
                      TEMP2 = ALPHA*X(JX)
181
                      IX = KX
182
                      IY = KY
183
                      DO 30 I = 1,J
184
                          A(I,J) = A(I,J) + X(IX)*TEMP1 + Y(IY)*TEMP2
185
                          IX = IX + INCX
186
                          IY = IY + INCY
187
   30                 CONTINUE
188
                  END IF
189
                  JX = JX + INCX
190
                  JY = JY + INCY
191
   40         CONTINUE
192
          END IF
193
      ELSE
194
*
195
*        Form  A  when A is stored in the lower triangle.
196
*
197
          IF ((INCX.EQ.1) .AND. (INCY.EQ.1)) THEN
198
              DO 60 J = 1,N
199
                  IF ((X(J).NE.ZERO) .OR. (Y(J).NE.ZERO)) THEN
200
                      TEMP1 = ALPHA*Y(J)
201
                      TEMP2 = ALPHA*X(J)
202
                      DO 50 I = J,N
203
                          A(I,J) = A(I,J) + X(I)*TEMP1 + Y(I)*TEMP2
204
   50                 CONTINUE
205
                  END IF
206
   60         CONTINUE
207
          ELSE
208
              DO 80 J = 1,N
209
                  IF ((X(JX).NE.ZERO) .OR. (Y(JY).NE.ZERO)) THEN
210
                      TEMP1 = ALPHA*Y(JY)
211
                      TEMP2 = ALPHA*X(JX)
212
                      IX = JX
213
                      IY = JY
214
                      DO 70 I = J,N
215
                          A(I,J) = A(I,J) + X(IX)*TEMP1 + Y(IY)*TEMP2
216
                          IX = IX + INCX
217
                          IY = IY + INCY
218
   70                 CONTINUE
219
                  END IF
220
                  JX = JX + INCX
221
                  JY = JY + INCY
222
   80         CONTINUE
223
          END IF
224
      END IF
225
*
226
      RETURN
227
*
228
*     End of SSYR2 .
229
*
230
      END