LAPACK 3.3.1
Linear Algebra PACKage

VARIANTS/cholesky/TOP/zpotrf.f

Go to the documentation of this file.
00001       SUBROUTINE ZPOTRF ( UPLO, N, A, LDA, INFO )
00002 *
00003 *  -- LAPACK routine (version 3.1) --
00004 *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
00005 *     March 2008
00006 *
00007 *     .. Scalar Arguments ..
00008       CHARACTER          UPLO
00009       INTEGER            INFO, LDA, N
00010 *     ..
00011 *     .. Array Arguments ..
00012       COMPLEX*16         A( LDA, * )
00013 *     ..
00014 *
00015 *  Purpose
00016 *  =======
00017 *
00018 *  ZPOTRF computes the Cholesky factorization of a real symmetric
00019 *  positive definite matrix A.
00020 *
00021 *  The factorization has the form
00022 *     A = U**H * U,  if UPLO = 'U', or
00023 *     A = L  * L**H,  if UPLO = 'L',
00024 *  where U is an upper triangular matrix and L is lower triangular.
00025 *
00026 *  This is the top-looking block version of the algorithm, calling Level 3 BLAS.
00027 *
00028 *  Arguments
00029 *  =========
00030 *
00031 *  UPLO    (input) CHARACTER*1
00032 *          = 'U':  Upper triangle of A is stored;
00033 *          = 'L':  Lower triangle of A is stored.
00034 *
00035 *  N       (input) INTEGER
00036 *          The order of the matrix A.  N >= 0.
00037 *
00038 *  A       (input/output) COMPLEX*16 array, dimension (LDA,N)
00039 *          On entry, the symmetric matrix A.  If UPLO = 'U', the leading
00040 *          N-by-N upper triangular part of A contains the upper
00041 *          triangular part of the matrix A, and the strictly lower
00042 *          triangular part of A is not referenced.  If UPLO = 'L', the
00043 *          leading N-by-N lower triangular part of A contains the lower
00044 *          triangular part of the matrix A, and the strictly upper
00045 *          triangular part of A is not referenced.
00046 *
00047 *          On exit, if INFO = 0, the factor U or L from the Cholesky
00048 *          factorization A = U**H*U or A = L*L**H.
00049 *
00050 *  LDA     (input) INTEGER
00051 *          The leading dimension of the array A.  LDA >= max(1,N).
00052 *
00053 *  INFO    (output) INTEGER
00054 *          = 0:  successful exit
00055 *          < 0:  if INFO = -i, the i-th argument had an illegal value
00056 *          > 0:  if INFO = i, the leading minor of order i is not
00057 *                positive definite, and the factorization could not be
00058 *                completed.
00059 *
00060 *  =====================================================================
00061 *
00062 *     .. Parameters ..
00063       DOUBLE PRECISION   ONE
00064       COMPLEX*16         CONE
00065       PARAMETER          ( ONE = 1.0D+0, CONE = ( 1.0D+0, 0.0D+0 ) )
00066 *     ..
00067 *     .. Local Scalars ..
00068       LOGICAL            UPPER
00069       INTEGER            J, JB, NB
00070 *     ..
00071 *     .. External Functions ..
00072       LOGICAL            LSAME
00073       INTEGER            ILAENV
00074       EXTERNAL           LSAME, ILAENV
00075 *     ..
00076 *     .. External Subroutines ..
00077       EXTERNAL           ZGEMM, ZPOTF2, ZHERK, ZTRSM, XERBLA
00078 *     ..
00079 *     .. Intrinsic Functions ..
00080       INTRINSIC          MAX, MIN
00081 *     ..
00082 *     .. Executable Statements ..
00083 *
00084 *     Test the input parameters.
00085 *
00086       INFO = 0
00087       UPPER = LSAME( UPLO, 'U' )
00088       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
00089          INFO = -1
00090       ELSE IF( N.LT.0 ) THEN
00091          INFO = -2
00092       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
00093          INFO = -4
00094       END IF
00095       IF( INFO.NE.0 ) THEN
00096          CALL XERBLA( 'ZPOTRF', -INFO )
00097          RETURN
00098       END IF
00099 *
00100 *     Quick return if possible
00101 *
00102       IF( N.EQ.0 )
00103      $   RETURN
00104 *
00105 *     Determine the block size for this environment.
00106 *
00107       NB = ILAENV( 1, 'ZPOTRF', UPLO, N, -1, -1, -1 )
00108       IF( NB.LE.1 .OR. NB.GE.N ) THEN
00109 *
00110 *        Use unblocked code.
00111 *
00112          CALL ZPOTF2( UPLO, N, A, LDA, INFO )
00113       ELSE
00114 *
00115 *        Use blocked code.
00116 *
00117          IF( UPPER ) THEN
00118 *
00119 *           Compute the Cholesky factorization A = U'*U.
00120 *
00121             DO 10 J = 1, N, NB
00122 
00123                JB = MIN( NB, N-J+1 )
00124 *
00125 *              Compute the current block.
00126 *
00127                CALL ZTRSM( 'Left', 'Upper', 'Conjugate Transpose', 
00128      $                      'Non-unit', J-1, JB, CONE, A( 1, 1 ), LDA,
00129      $                      A( 1, J ), LDA )
00130 
00131                CALL ZHERK( 'Upper', 'Conjugate Transpose', JB, J-1, 
00132      $                      -ONE, A( 1, J ), LDA, ONE, A( J, J ), LDA )
00133 *
00134 *              Update and factorize the current diagonal block and test
00135 *              for non-positive-definiteness.
00136 *
00137                CALL ZPOTF2( 'Upper', JB, A( J, J ), LDA, INFO )
00138                IF( INFO.NE.0 )
00139      $            GO TO 30
00140 
00141    10       CONTINUE
00142 *
00143          ELSE
00144 *
00145 *           Compute the Cholesky factorization A = L*L'.
00146 *
00147             DO 20 J = 1, N, NB
00148 
00149                JB = MIN( NB, N-J+1 )
00150 *
00151 *              Compute the current block.
00152 *
00153                CALL ZTRSM( 'Right', 'Lower', 'Conjugate Transpose', 
00154      $                     'Non-unit', JB, J-1, CONE, A( 1, 1 ), LDA,
00155      $                     A( J, 1 ), LDA )
00156 
00157                CALL ZHERK( 'Lower', 'No Transpose', JB, J-1, 
00158      $                     -ONE, A( J, 1 ), LDA, 
00159      $                     ONE, A( J, J ), LDA )
00160 *
00161 *              Update and factorize the current diagonal block and test
00162 *              for non-positive-definiteness.
00163 *
00164                CALL ZPOTF2( 'Lower', JB, A( J, J ), LDA, INFO )
00165                IF( INFO.NE.0 )
00166      $            GO TO 30
00167 
00168    20       CONTINUE
00169          END IF
00170       END IF
00171       GO TO 40
00172 *
00173    30 CONTINUE
00174       INFO = INFO + J - 1
00175 *
00176    40 CONTINUE
00177       RETURN
00178 *
00179 *     End of ZPOTRF
00180 *
00181       END
 All Files Functions