| 
  12
 3
 4
 5
 6
 7
 8
 9
 10
 11
 12
 13
 14
 15
 16
 17
 18
 19
 20
 21
 22
 23
 24
 25
 26
 27
 28
 29
 30
 31
 32
 33
 34
 35
 36
 37
 38
 39
 40
 41
 42
 43
 44
 45
 46
 47
 48
 49
 50
 51
 52
 53
 54
 55
 56
 57
 58
 59
 60
 61
 62
 63
 64
 65
 66
 67
 68
 69
 70
 71
 72
 73
 74
 75
 76
 77
 78
 79
 80
 81
 82
 83
 84
 85
 86
 87
 88
 89
 90
 91
 92
 93
 94
 95
 96
 97
 98
 99
 100
 101
 102
 103
 104
 105
 106
 107
 108
 109
 110
 111
 112
 113
 114
 115
 116
 117
 118
 119
 120
 121
 122
 123
 124
 125
 126
 127
 128
 129
 130
 131
 132
 133
 134
 135
 136
 137
 138
 139
 140
 141
 142
 143
 144
 145
 146
 147
 148
 149
 150
 151
 152
 153
 154
 155
 156
 157
 158
 159
 160
 161
 162
 163
 164
 165
 166
 167
 168
 169
 170
 171
 172
 173
 174
 175
 176
 177
 178
 
 | 
      SUBROUTINE SPPTRF( UPLO, N, AP, INFO )*
 *  -- LAPACK routine (version 3.3.1) --
 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
 *  -- April 2011                                                      --
 *
 *     .. Scalar Arguments ..
 CHARACTER          UPLO
 INTEGER            INFO, N
 *     ..
 *     .. Array Arguments ..
 REAL               AP( * )
 *     ..
 *
 *  Purpose
 *  =======
 *
 *  SPPTRF computes the Cholesky factorization of a real symmetric
 *  positive definite matrix A stored in packed format.
 *
 *  The factorization has the form
 *     A = U**T * U,  if UPLO = 'U', or
 *     A = L  * L**T,  if UPLO = 'L',
 *  where U is an upper triangular matrix and L is lower triangular.
 *
 *  Arguments
 *  =========
 *
 *  UPLO    (input) CHARACTER*1
 *          = 'U':  Upper triangle of A is stored;
 *          = 'L':  Lower triangle of A is stored.
 *
 *  N       (input) INTEGER
 *          The order of the matrix A.  N >= 0.
 *
 *  AP      (input/output) REAL array, dimension (N*(N+1)/2)
 *          On entry, the upper or lower triangle of the symmetric 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**T*U or A = L*L**T, in the same
 *          storage format as A.
 *
 *  INFO    (output) INTEGER
 *          = 0:  successful exit
 *          < 0:  if INFO = -i, the i-th argument had an illegal value
 *          > 0:  if INFO = i, the leading minor of order i is not
 *                positive definite, and the factorization could not be
 *                completed.
 *
 *  Further Details
 *  ======= =======
 *
 *  The packed storage scheme is illustrated by the following example
 *  when N = 4, UPLO = 'U':
 *
 *  Two-dimensional storage of the symmetric matrix A:
 *
 *     a11 a12 a13 a14
 *         a22 a23 a24
 *             a33 a34     (aij = aji)
 *                 a44
 *
 *  Packed storage of the upper triangle of A:
 *
 *  AP = [ a11, a12, a22, a13, a23, a33, a14, a24, a34, a44 ]
 *
 *  =====================================================================
 *
 *     .. Parameters ..
 REAL               ONE, ZERO
 PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
 *     ..
 *     .. Local Scalars ..
 LOGICAL            UPPER
 INTEGER            J, JC, JJ
 REAL               AJJ
 *     ..
 *     .. External Functions ..
 LOGICAL            LSAME
 REAL               SDOT
 EXTERNAL           LSAME, SDOT
 *     ..
 *     .. External Subroutines ..
 EXTERNAL           SSCAL, SSPR, STPSV, XERBLA
 *     ..
 *     .. Intrinsic Functions ..
 INTRINSIC          SQRT
 *     ..
 *     .. Executable Statements ..
 *
 *     Test the input parameters.
 *
 INFO = 0
 UPPER = LSAME( UPLO, 'U' )
 IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
 INFO = -1
 ELSE IF( N.LT.0 ) THEN
 INFO = -2
 END IF
 IF( INFO.NE.0 ) THEN
 CALL XERBLA( 'SPPTRF', -INFO )
 RETURN
 END IF
 *
 *     Quick return if possible
 *
 IF( N.EQ.0 )
 $   RETURN
 *
 IF( UPPER ) THEN
 *
 *        Compute the Cholesky factorization A = U**T*U.
 *
 JJ = 0
 DO 10 J = 1, N
 JC = JJ + 1
 JJ = JJ + J
 *
 *           Compute elements 1:J-1 of column J.
 *
 IF( J.GT.1 )
 $         CALL STPSV( 'Upper', 'Transpose', 'Non-unit', J-1, AP,
 $                     AP( JC ), 1 )
 *
 *           Compute U(J,J) and test for non-positive-definiteness.
 *
 AJJ = AP( JJ ) - SDOT( J-1, AP( JC ), 1, AP( JC ), 1 )
 IF( AJJ.LE.ZERO ) THEN
 AP( JJ ) = AJJ
 GO TO 30
 END IF
 AP( JJ ) = SQRT( AJJ )
 10    CONTINUE
 ELSE
 *
 *        Compute the Cholesky factorization A = L*L**T.
 *
 JJ = 1
 DO 20 J = 1, N
 *
 *           Compute L(J,J) and test for non-positive-definiteness.
 *
 AJJ = AP( JJ )
 IF( AJJ.LE.ZERO ) THEN
 AP( JJ ) = AJJ
 GO TO 30
 END IF
 AJJ = SQRT( AJJ )
 AP( JJ ) = AJJ
 *
 *           Compute elements J+1:N of column J and update the trailing
 *           submatrix.
 *
 IF( J.LT.N ) THEN
 CALL SSCAL( N-J, ONE / AJJ, AP( JJ+1 ), 1 )
 CALL SSPR( 'Lower', N-J, -ONE, AP( JJ+1 ), 1,
 $                    AP( JJ+N-J+1 ) )
 JJ = JJ + N - J + 1
 END IF
 20    CONTINUE
 END IF
 GO TO 40
 *
 30 CONTINUE
 INFO = J
 *
 40 CONTINUE
 RETURN
 *
 *     End of SPPTRF
 *
 END
 
 |