LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
chpr.f
Go to the documentation of this file.
1 *> \brief \b CHPR
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 CHPR(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 * COMPLEX AP(*),X(*)
20 * ..
21 *
22 *
23 *> \par Purpose:
24 * =============
25 *>
26 *> \verbatim
27 *>
28 *> CHPR performs the hermitian rank 1 operation
29 *>
30 *> A := alpha*x*x**H + A,
31 *>
32 *> where alpha is a real scalar, x is an n element vector and A is an
33 *> n by n hermitian 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 COMPLEX 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 COMPLEX 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 hermitian 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 hermitian 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 *> Note that the imaginary parts of the diagonal elements need
100 *> not be set, they are assumed to be zero, and on exit they
101 *> are set to zero.
102 *> \endverbatim
103 *
104 * Authors:
105 * ========
106 *
107 *> \author Univ. of Tennessee
108 *> \author Univ. of California Berkeley
109 *> \author Univ. of Colorado Denver
110 *> \author NAG Ltd.
111 *
112 *> \date November 2011
113 *
114 *> \ingroup complex_blas_level2
115 *
116 *> \par Further Details:
117 * =====================
118 *>
119 *> \verbatim
120 *>
121 *> Level 2 Blas routine.
122 *>
123 *> -- Written on 22-October-1986.
124 *> Jack Dongarra, Argonne National Lab.
125 *> Jeremy Du Croz, Nag Central Office.
126 *> Sven Hammarling, Nag Central Office.
127 *> Richard Hanson, Sandia National Labs.
128 *> \endverbatim
129 *>
130 * =====================================================================
131  SUBROUTINE chpr(UPLO,N,ALPHA,X,INCX,AP)
132 *
133 * -- Reference BLAS level2 routine (version 3.4.0) --
134 * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
135 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
136 * November 2011
137 *
138 * .. Scalar Arguments ..
139  REAL ALPHA
140  INTEGER INCX,N
141  CHARACTER UPLO
142 * ..
143 * .. Array Arguments ..
144  COMPLEX AP(*),X(*)
145 * ..
146 *
147 * =====================================================================
148 *
149 * .. Parameters ..
150  COMPLEX ZERO
151  parameter(zero= (0.0e+0,0.0e+0))
152 * ..
153 * .. Local Scalars ..
154  COMPLEX TEMP
155  INTEGER I,INFO,IX,J,JX,K,KK,KX
156 * ..
157 * .. External Functions ..
158  LOGICAL LSAME
159  EXTERNAL lsame
160 * ..
161 * .. External Subroutines ..
162  EXTERNAL xerbla
163 * ..
164 * .. Intrinsic Functions ..
165  INTRINSIC conjg,real
166 * ..
167 *
168 * Test the input parameters.
169 *
170  info = 0
171  IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
172  info = 1
173  ELSE IF (n.LT.0) THEN
174  info = 2
175  ELSE IF (incx.EQ.0) THEN
176  info = 5
177  END IF
178  IF (info.NE.0) THEN
179  CALL xerbla('CHPR ',info)
180  RETURN
181  END IF
182 *
183 * Quick return if possible.
184 *
185  IF ((n.EQ.0) .OR. (alpha.EQ.REAL(zero))) return
186 *
187 * Set the start point in X if the increment is not unity.
188 *
189  IF (incx.LE.0) THEN
190  kx = 1 - (n-1)*incx
191  ELSE IF (incx.NE.1) THEN
192  kx = 1
193  END IF
194 *
195 * Start the operations. In this version the elements of the array AP
196 * are accessed sequentially with one pass through AP.
197 *
198  kk = 1
199  IF (lsame(uplo,'U')) THEN
200 *
201 * Form A when upper triangle is stored in AP.
202 *
203  IF (incx.EQ.1) THEN
204  DO 20 j = 1,n
205  IF (x(j).NE.zero) THEN
206  temp = alpha*conjg(x(j))
207  k = kk
208  DO 10 i = 1,j - 1
209  ap(k) = ap(k) + x(i)*temp
210  k = k + 1
211  10 CONTINUE
212  ap(kk+j-1) = REAL(AP(KK+J-1)) + REAL(x(j)*temp)
213  ELSE
214  ap(kk+j-1) = REAL(ap(kk+j-1))
215  END IF
216  kk = kk + j
217  20 CONTINUE
218  ELSE
219  jx = kx
220  DO 40 j = 1,n
221  IF (x(jx).NE.zero) THEN
222  temp = alpha*conjg(x(jx))
223  ix = kx
224  DO 30 k = kk,kk + j - 2
225  ap(k) = ap(k) + x(ix)*temp
226  ix = ix + incx
227  30 CONTINUE
228  ap(kk+j-1) = REAL(AP(KK+J-1)) + REAL(x(jx)*temp)
229  ELSE
230  ap(kk+j-1) = REAL(ap(kk+j-1))
231  END IF
232  jx = jx + incx
233  kk = kk + j
234  40 CONTINUE
235  END IF
236  ELSE
237 *
238 * Form A when lower triangle is stored in AP.
239 *
240  IF (incx.EQ.1) THEN
241  DO 60 j = 1,n
242  IF (x(j).NE.zero) THEN
243  temp = alpha*conjg(x(j))
244  ap(kk) = REAL(AP(KK)) + REAL(temp*x(j))
245  k = kk + 1
246  DO 50 i = j + 1,n
247  ap(k) = ap(k) + x(i)*temp
248  k = k + 1
249  50 CONTINUE
250  ELSE
251  ap(kk) = REAL(ap(kk))
252  END IF
253  kk = kk + n - j + 1
254  60 CONTINUE
255  ELSE
256  jx = kx
257  DO 80 j = 1,n
258  IF (x(jx).NE.zero) THEN
259  temp = alpha*conjg(x(jx))
260  ap(kk) = REAL(AP(KK)) + REAL(temp*x(jx))
261  ix = jx
262  DO 70 k = kk + 1,kk + n - j
263  ix = ix + incx
264  ap(k) = ap(k) + x(ix)*temp
265  70 CONTINUE
266  ELSE
267  ap(kk) = REAL(ap(kk))
268  END IF
269  jx = jx + incx
270  kk = kk + n - j + 1
271  80 CONTINUE
272  END IF
273  END IF
274 *
275  RETURN
276 *
277 * End of CHPR .
278 *
279  END
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine chpr(UPLO, N, ALPHA, X, INCX, AP)
CHPR
Definition: chpr.f:132