LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
sspr.f
Go to the documentation of this file.
1 *> \brief \b SSPR
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 SSPR(UPLO,N,ALPHA,X,INCX,AP)
12 *
13 * .. Scalar Arguments ..
14 * REAL ALPHA
15 * INTEGER INCX,N
16 * CHARACTER UPLO
17 * ..
18 * .. Array Arguments ..
19 * REAL AP(*),X(*)
20 * ..
21 *
22 *
23 *> \par Purpose:
24 * =============
25 *>
26 *> \verbatim
27 *>
28 *> SSPR performs the symmetric rank 1 operation
29 *>
30 *> A := alpha*x*x**T + A,
31 *>
32 *> where alpha is a real scalar, x is an n element vector and A is an
33 *> n by n symmetric matrix, supplied in packed form.
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 matrix A is supplied in the packed
44 *> array AP as follows:
45 *>
46 *> UPLO = 'U' or 'u' The upper triangular part of A is
47 *> supplied in AP.
48 *>
49 *> UPLO = 'L' or 'l' The lower triangular part of A is
50 *> supplied in AP.
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,out] AP
82 *> \verbatim
83 *> AP is REAL array of DIMENSION at least
84 *> ( ( n*( n + 1 ) )/2 ).
85 *> Before entry with UPLO = 'U' or 'u', the array AP must
86 *> contain the upper triangular part of the symmetric matrix
87 *> packed sequentially, column by column, so that AP( 1 )
88 *> contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 1, 2 )
89 *> and a( 2, 2 ) respectively, and so on. On exit, the array
90 *> AP is overwritten by the upper triangular part of the
91 *> updated matrix.
92 *> Before entry with UPLO = 'L' or 'l', the array AP must
93 *> contain the lower triangular part of the symmetric matrix
94 *> packed sequentially, column by column, so that AP( 1 )
95 *> contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 2, 1 )
96 *> and a( 3, 1 ) respectively, and so on. On exit, the array
97 *> AP is overwritten by the lower triangular part of the
98 *> updated matrix.
99 *> \endverbatim
100 *
101 * Authors:
102 * ========
103 *
104 *> \author Univ. of Tennessee
105 *> \author Univ. of California Berkeley
106 *> \author Univ. of Colorado Denver
107 *> \author NAG Ltd.
108 *
109 *> \date November 2011
110 *
111 *> \ingroup single_blas_level2
112 *
113 *> \par Further Details:
114 * =====================
115 *>
116 *> \verbatim
117 *>
118 *> Level 2 Blas routine.
119 *>
120 *> -- Written on 22-October-1986.
121 *> Jack Dongarra, Argonne National Lab.
122 *> Jeremy Du Croz, Nag Central Office.
123 *> Sven Hammarling, Nag Central Office.
124 *> Richard Hanson, Sandia National Labs.
125 *> \endverbatim
126 *>
127 * =====================================================================
128  SUBROUTINE sspr(UPLO,N,ALPHA,X,INCX,AP)
129 *
130 * -- Reference BLAS level2 routine (version 3.4.0) --
131 * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
132 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
133 * November 2011
134 *
135 * .. Scalar Arguments ..
136  REAL ALPHA
137  INTEGER INCX,N
138  CHARACTER UPLO
139 * ..
140 * .. Array Arguments ..
141  REAL AP(*),X(*)
142 * ..
143 *
144 * =====================================================================
145 *
146 * .. Parameters ..
147  REAL ZERO
148  parameter(zero=0.0e+0)
149 * ..
150 * .. Local Scalars ..
151  REAL TEMP
152  INTEGER I,INFO,IX,J,JX,K,KK,KX
153 * ..
154 * .. External Functions ..
155  LOGICAL LSAME
156  EXTERNAL lsame
157 * ..
158 * .. External Subroutines ..
159  EXTERNAL xerbla
160 * ..
161 *
162 * Test the input parameters.
163 *
164  info = 0
165  IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
166  info = 1
167  ELSE IF (n.LT.0) THEN
168  info = 2
169  ELSE IF (incx.EQ.0) THEN
170  info = 5
171  END IF
172  IF (info.NE.0) THEN
173  CALL xerbla('SSPR ',info)
174  RETURN
175  END IF
176 *
177 * Quick return if possible.
178 *
179  IF ((n.EQ.0) .OR. (alpha.EQ.zero)) RETURN
180 *
181 * Set the start point in X if the increment is not unity.
182 *
183  IF (incx.LE.0) THEN
184  kx = 1 - (n-1)*incx
185  ELSE IF (incx.NE.1) THEN
186  kx = 1
187  END IF
188 *
189 * Start the operations. In this version the elements of the array AP
190 * are accessed sequentially with one pass through AP.
191 *
192  kk = 1
193  IF (lsame(uplo,'U')) THEN
194 *
195 * Form A when upper triangle is stored in AP.
196 *
197  IF (incx.EQ.1) THEN
198  DO 20 j = 1,n
199  IF (x(j).NE.zero) THEN
200  temp = alpha*x(j)
201  k = kk
202  DO 10 i = 1,j
203  ap(k) = ap(k) + x(i)*temp
204  k = k + 1
205  10 CONTINUE
206  END IF
207  kk = kk + j
208  20 CONTINUE
209  ELSE
210  jx = kx
211  DO 40 j = 1,n
212  IF (x(jx).NE.zero) THEN
213  temp = alpha*x(jx)
214  ix = kx
215  DO 30 k = kk,kk + j - 1
216  ap(k) = ap(k) + x(ix)*temp
217  ix = ix + incx
218  30 CONTINUE
219  END IF
220  jx = jx + incx
221  kk = kk + j
222  40 CONTINUE
223  END IF
224  ELSE
225 *
226 * Form A when lower triangle is stored in AP.
227 *
228  IF (incx.EQ.1) THEN
229  DO 60 j = 1,n
230  IF (x(j).NE.zero) THEN
231  temp = alpha*x(j)
232  k = kk
233  DO 50 i = j,n
234  ap(k) = ap(k) + x(i)*temp
235  k = k + 1
236  50 CONTINUE
237  END IF
238  kk = kk + n - j + 1
239  60 CONTINUE
240  ELSE
241  jx = kx
242  DO 80 j = 1,n
243  IF (x(jx).NE.zero) THEN
244  temp = alpha*x(jx)
245  ix = jx
246  DO 70 k = kk,kk + n - j
247  ap(k) = ap(k) + x(ix)*temp
248  ix = ix + incx
249  70 CONTINUE
250  END IF
251  jx = jx + incx
252  kk = kk + n - j + 1
253  80 CONTINUE
254  END IF
255  END IF
256 *
257  RETURN
258 *
259 * End of SSPR .
260 *
261  END
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine sspr(UPLO, N, ALPHA, X, INCX, AP)
SSPR
Definition: sspr.f:129