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

◆ cpptrf()

subroutine cpptrf ( character  uplo,
integer  n,
complex, dimension( * )  ap,
integer  info 
)

CPPTRF

Download CPPTRF + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 CPPTRF computes the Cholesky factorization of a complex Hermitian
 positive definite matrix A stored in packed format.

 The factorization has the form
    A = U**H * U,  if UPLO = 'U', or
    A = L  * L**H,  if UPLO = 'L',
 where U is an upper triangular matrix and L is lower triangular.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          = 'U':  Upper triangle of A is stored;
          = 'L':  Lower triangle of A is stored.
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in,out]AP
          AP is COMPLEX array, dimension (N*(N+1)/2)
          On entry, the upper or lower triangle of the Hermitian matrix
          A, packed columnwise in a linear array.  The j-th column of A
          is stored in the array AP as follows:
          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
          See below for further details.

          On exit, if INFO = 0, the triangular factor U or L from the
          Cholesky factorization A = U**H*U or A = L*L**H, in the same
          storage format as A.
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -i, the i-th argument had an illegal value
          > 0:  if INFO = i, the leading principal minor of order i
                is not positive definite, and the factorization could
                not be completed.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
  The packed storage scheme is illustrated by the following example
  when N = 4, UPLO = 'U':

  Two-dimensional storage of the Hermitian matrix A:

     a11 a12 a13 a14
         a22 a23 a24
             a33 a34     (aij = conjg(aji))
                 a44

  Packed storage of the upper triangle of A:

  AP = [ a11, a12, a22, a13, a23, a33, a14, a24, a34, a44 ]

Definition at line 118 of file cpptrf.f.

119*
120* -- LAPACK computational routine --
121* -- LAPACK is a software package provided by Univ. of Tennessee, --
122* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
123*
124* .. Scalar Arguments ..
125 CHARACTER UPLO
126 INTEGER INFO, N
127* ..
128* .. Array Arguments ..
129 COMPLEX AP( * )
130* ..
131*
132* =====================================================================
133*
134* .. Parameters ..
135 REAL ZERO, ONE
136 parameter( zero = 0.0e+0, one = 1.0e+0 )
137* ..
138* .. Local Scalars ..
139 LOGICAL UPPER
140 INTEGER J, JC, JJ
141 REAL AJJ
142* ..
143* .. External Functions ..
144 LOGICAL LSAME
145 COMPLEX CDOTC
146 EXTERNAL lsame, cdotc
147* ..
148* .. External Subroutines ..
149 EXTERNAL chpr, csscal, ctpsv, xerbla
150* ..
151* .. Intrinsic Functions ..
152 INTRINSIC real, sqrt
153* ..
154* .. Executable Statements ..
155*
156* Test the input parameters.
157*
158 info = 0
159 upper = lsame( uplo, 'U' )
160 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
161 info = -1
162 ELSE IF( n.LT.0 ) THEN
163 info = -2
164 END IF
165 IF( info.NE.0 ) THEN
166 CALL xerbla( 'CPPTRF', -info )
167 RETURN
168 END IF
169*
170* Quick return if possible
171*
172 IF( n.EQ.0 )
173 $ RETURN
174*
175 IF( upper ) THEN
176*
177* Compute the Cholesky factorization A = U**H * U.
178*
179 jj = 0
180 DO 10 j = 1, n
181 jc = jj + 1
182 jj = jj + j
183*
184* Compute elements 1:J-1 of column J.
185*
186 IF( j.GT.1 )
187 $ CALL ctpsv( 'Upper', 'Conjugate transpose', 'Non-unit',
188 $ j-1, ap, ap( jc ), 1 )
189*
190* Compute U(J,J) and test for non-positive-definiteness.
191*
192 ajj = real( real( ap( jj ) ) - cdotc( j-1,
193 $ ap( jc ), 1, ap( jc ), 1 ) )
194 IF( ajj.LE.zero ) THEN
195 ap( jj ) = ajj
196 GO TO 30
197 END IF
198 ap( jj ) = sqrt( ajj )
199 10 CONTINUE
200 ELSE
201*
202* Compute the Cholesky factorization A = L * L**H.
203*
204 jj = 1
205 DO 20 j = 1, n
206*
207* Compute L(J,J) and test for non-positive-definiteness.
208*
209 ajj = real( ap( jj ) )
210 IF( ajj.LE.zero ) THEN
211 ap( jj ) = ajj
212 GO TO 30
213 END IF
214 ajj = sqrt( ajj )
215 ap( jj ) = ajj
216*
217* Compute elements J+1:N of column J and update the trailing
218* submatrix.
219*
220 IF( j.LT.n ) THEN
221 CALL csscal( n-j, one / ajj, ap( jj+1 ), 1 )
222 CALL chpr( 'Lower', n-j, -one, ap( jj+1 ), 1,
223 $ ap( jj+n-j+1 ) )
224 jj = jj + n - j + 1
225 END IF
226 20 CONTINUE
227 END IF
228 GO TO 40
229*
230 30 CONTINUE
231 info = j
232*
233 40 CONTINUE
234 RETURN
235*
236* End of CPPTRF
237*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
complex function cdotc(n, cx, incx, cy, incy)
CDOTC
Definition cdotc.f:83
subroutine chpr(uplo, n, alpha, x, incx, ap)
CHPR
Definition chpr.f:130
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine csscal(n, sa, cx, incx)
CSSCAL
Definition csscal.f:78
subroutine ctpsv(uplo, trans, diag, n, ap, x, incx)
CTPSV
Definition ctpsv.f:144
Here is the call graph for this function:
Here is the caller graph for this function: