Free cookie consent management tool by TermsFeed Policy Generator

source: branches/MathNetNumerics-Exploration-2789/HeuristicLab.Algorithms.DataAnalysis.Experimental/sbart/ssyr.f @ 15457

Last change on this file since 15457 was 15457, checked in by gkronber, 6 years ago

#2789 added Finbarr O'Sullivan smoothing spline code

File size: 5.7 KB
Line 
1      SUBROUTINE SSYR(UPLO,N,ALPHA,X,INCX,A,LDA)
2*     .. Scalar Arguments ..
3      REAL ALPHA
4      INTEGER INCX,LDA,N
5      CHARACTER UPLO
6*     ..
7*     .. Array Arguments ..
8      REAL A(LDA,*),X(*)
9*     ..
10*
11*  Purpose
12*  =======
13*
14*  SSYR   performs the symmetric rank 1 operation
15*
16*     A := alpha*x*x' + A,
17*
18*  where alpha is a real scalar, x is an n element vector and A is an
19*  n 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*  A      - REAL             array of DIMENSION ( LDA, n ).
58*           Before entry with  UPLO = 'U' or 'u', the leading n by n
59*           upper triangular part of the array A must contain the upper
60*           triangular part of the symmetric matrix and the strictly
61*           lower triangular part of A is not referenced. On exit, the
62*           upper triangular part of the array A is overwritten by the
63*           upper triangular part of the updated matrix.
64*           Before entry with UPLO = 'L' or 'l', the leading n by n
65*           lower triangular part of the array A must contain the lower
66*           triangular part of the symmetric matrix and the strictly
67*           upper triangular part of A is not referenced. On exit, the
68*           lower triangular part of the array A is overwritten by the
69*           lower triangular part of the updated matrix.
70*
71*  LDA    - INTEGER.
72*           On entry, LDA specifies the first dimension of A as declared
73*           in the calling (sub) program. LDA must be at least
74*           max( 1, n ).
75*           Unchanged on exit.
76*
77*
78*  Level 2 Blas routine.
79*
80*  -- Written on 22-October-1986.
81*     Jack Dongarra, Argonne National Lab.
82*     Jeremy Du Croz, Nag Central Office.
83*     Sven Hammarling, Nag Central Office.
84*     Richard Hanson, Sandia National Labs.
85*
86*
87*     .. Parameters ..
88      REAL ZERO
89      PARAMETER (ZERO=0.0E+0)
90*     ..
91*     .. Local Scalars ..
92      REAL TEMP
93      INTEGER I,INFO,IX,J,JX,KX
94*     ..
95*     .. External Functions ..
96      LOGICAL LSAME
97      EXTERNAL LSAME
98*     ..
99*     .. External Subroutines ..
100      EXTERNAL XERBLA
101*     ..
102*     .. Intrinsic Functions ..
103      INTRINSIC MAX
104*     ..
105*
106*     Test the input parameters.
107*
108      INFO = 0
109      IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THEN
110          INFO = 1
111      ELSE IF (N.LT.0) THEN
112          INFO = 2
113      ELSE IF (INCX.EQ.0) THEN
114          INFO = 5
115      ELSE IF (LDA.LT.MAX(1,N)) THEN
116          INFO = 7
117      END IF
118      IF (INFO.NE.0) THEN
119          CALL XERBLA('SSYR  ',INFO)
120          RETURN
121      END IF
122*
123*     Quick return if possible.
124*
125      IF ((N.EQ.0) .OR. (ALPHA.EQ.ZERO)) RETURN
126*
127*     Set the start point in X if the increment is not unity.
128*
129      IF (INCX.LE.0) THEN
130          KX = 1 - (N-1)*INCX
131      ELSE IF (INCX.NE.1) THEN
132          KX = 1
133      END IF
134*
135*     Start the operations. In this version the elements of A are
136*     accessed sequentially with one pass through the triangular part
137*     of A.
138*
139      IF (LSAME(UPLO,'U')) THEN
140*
141*        Form  A  when A is stored in upper triangle.
142*
143          IF (INCX.EQ.1) THEN
144              DO 20 J = 1,N
145                  IF (X(J).NE.ZERO) THEN
146                      TEMP = ALPHA*X(J)
147                      DO 10 I = 1,J
148                          A(I,J) = A(I,J) + X(I)*TEMP
149   10                 CONTINUE
150                  END IF
151   20         CONTINUE
152          ELSE
153              JX = KX
154              DO 40 J = 1,N
155                  IF (X(JX).NE.ZERO) THEN
156                      TEMP = ALPHA*X(JX)
157                      IX = KX
158                      DO 30 I = 1,J
159                          A(I,J) = A(I,J) + X(IX)*TEMP
160                          IX = IX + INCX
161   30                 CONTINUE
162                  END IF
163                  JX = JX + INCX
164   40         CONTINUE
165          END IF
166      ELSE
167*
168*        Form  A  when A is stored in lower triangle.
169*
170          IF (INCX.EQ.1) THEN
171              DO 60 J = 1,N
172                  IF (X(J).NE.ZERO) THEN
173                      TEMP = ALPHA*X(J)
174                      DO 50 I = J,N
175                          A(I,J) = A(I,J) + X(I)*TEMP
176   50                 CONTINUE
177                  END IF
178   60         CONTINUE
179          ELSE
180              JX = KX
181              DO 80 J = 1,N
182                  IF (X(JX).NE.ZERO) THEN
183                      TEMP = ALPHA*X(JX)
184                      IX = JX
185                      DO 70 I = J,N
186                          A(I,J) = A(I,J) + X(IX)*TEMP
187                          IX = IX + INCX
188   70                 CONTINUE
189                  END IF
190                  JX = JX + INCX
191   80         CONTINUE
192          END IF
193      END IF
194*
195      RETURN
196*
197*     End of SSYR  .
198*
199      END
Note: See TracBrowser for help on using the repository browser.