LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ cher()

subroutine cher ( character uplo,
integer n,
real alpha,
complex, dimension(*) x,
integer incx,
complex, dimension(lda,*) a,
integer lda )

CHER

Purpose:
!>
!> CHER   performs the hermitian rank 1 operation
!>
!>    A := alpha*x*x**H + A,
!>
!> where alpha is a real scalar, x is an n element vector and A is an
!> n by n hermitian 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 COMPLEX array, 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,out]A
!>          A is COMPLEX array, 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 hermitian 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 hermitian 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.
!>           Note that the imaginary parts of the diagonal elements need
!>           not be set, they are assumed to be zero, and on exit they
!>           are set to zero.
!> 
[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.
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 134 of file cher.f.

135*
136* -- Reference BLAS level2 routine --
137* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
138* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
139*
140* .. Scalar Arguments ..
141 REAL ALPHA
142 INTEGER INCX,LDA,N
143 CHARACTER UPLO
144* ..
145* .. Array Arguments ..
146 COMPLEX A(LDA,*),X(*)
147* ..
148*
149* =====================================================================
150*
151* .. Parameters ..
152 COMPLEX ZERO
153 parameter(zero= (0.0e+0,0.0e+0))
154* ..
155* .. Local Scalars ..
156 COMPLEX TEMP
157 INTEGER I,INFO,IX,J,JX,KX
158* ..
159* .. External Functions ..
160 LOGICAL LSAME
161 EXTERNAL lsame
162* ..
163* .. External Subroutines ..
164 EXTERNAL xerbla
165* ..
166* .. Intrinsic Functions ..
167 INTRINSIC conjg,max,real
168* ..
169*
170* Test the input parameters.
171*
172 info = 0
173 IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
174 info = 1
175 ELSE IF (n.LT.0) THEN
176 info = 2
177 ELSE IF (incx.EQ.0) THEN
178 info = 5
179 ELSE IF (lda.LT.max(1,n)) THEN
180 info = 7
181 END IF
182 IF (info.NE.0) THEN
183 CALL xerbla('CHER ',info)
184 RETURN
185 END IF
186*
187* Quick return if possible.
188*
189 IF ((n.EQ.0) .OR. (alpha.EQ.real(zero))) RETURN
190*
191* Set the start point in X if the increment is not unity.
192*
193 IF (incx.LE.0) THEN
194 kx = 1 - (n-1)*incx
195 ELSE IF (incx.NE.1) THEN
196 kx = 1
197 END IF
198*
199* Start the operations. In this version the elements of A are
200* accessed sequentially with one pass through the triangular part
201* of A.
202*
203 IF (lsame(uplo,'U')) THEN
204*
205* Form A when A is stored in upper triangle.
206*
207 IF (incx.EQ.1) THEN
208 DO 20 j = 1,n
209 IF (x(j).NE.zero) THEN
210 temp = alpha*conjg(x(j))
211 DO 10 i = 1,j - 1
212 a(i,j) = a(i,j) + x(i)*temp
213 10 CONTINUE
214 a(j,j) = real(a(j,j)) + real(x(j)*temp)
215 ELSE
216 a(j,j) = real(a(j,j))
217 END IF
218 20 CONTINUE
219 ELSE
220 jx = kx
221 DO 40 j = 1,n
222 IF (x(jx).NE.zero) THEN
223 temp = alpha*conjg(x(jx))
224 ix = kx
225 DO 30 i = 1,j - 1
226 a(i,j) = a(i,j) + x(ix)*temp
227 ix = ix + incx
228 30 CONTINUE
229 a(j,j) = real(a(j,j)) + real(x(jx)*temp)
230 ELSE
231 a(j,j) = real(a(j,j))
232 END IF
233 jx = jx + incx
234 40 CONTINUE
235 END IF
236 ELSE
237*
238* Form A when A is stored in lower triangle.
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 a(j,j) = real(a(j,j)) + real(temp*x(j))
245 DO 50 i = j + 1,n
246 a(i,j) = a(i,j) + x(i)*temp
247 50 CONTINUE
248 ELSE
249 a(j,j) = real(a(j,j))
250 END IF
251 60 CONTINUE
252 ELSE
253 jx = kx
254 DO 80 j = 1,n
255 IF (x(jx).NE.zero) THEN
256 temp = alpha*conjg(x(jx))
257 a(j,j) = real(a(j,j)) + real(temp*x(jx))
258 ix = jx
259 DO 70 i = j + 1,n
260 ix = ix + incx
261 a(i,j) = a(i,j) + x(ix)*temp
262 70 CONTINUE
263 ELSE
264 a(j,j) = real(a(j,j))
265 END IF
266 jx = jx + incx
267 80 CONTINUE
268 END IF
269 END IF
270*
271 RETURN
272*
273* End of CHER
274*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: