You can not select more than 25 topics Topics must start with a chinese character,a letter or number, can include dashes ('-') and can be up to 35 characters long.

cpotrff.f 5.8 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187
  1. SUBROUTINE CPOTRFF( UPLO, N, A, LDA, INFO )
  2. *
  3. * -- LAPACK routine (version 3.0) --
  4. * Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
  5. * Courant Institute, Argonne National Lab, and Rice University
  6. * September 30, 1994
  7. *
  8. * .. Scalar Arguments ..
  9. CHARACTER UPLO
  10. INTEGER INFO, LDA, N
  11. * ..
  12. * .. Array Arguments ..
  13. COMPLEX A( LDA, * )
  14. * ..
  15. *
  16. * Purpose
  17. * =======
  18. *
  19. * CPOTRF computes the Cholesky factorization of a complex Hermitian
  20. * positive definite matrix A.
  21. *
  22. * The factorization has the form
  23. * A = U**H * U, if UPLO = 'U', or
  24. * A = L * L**H, if UPLO = 'L',
  25. * where U is an upper triangular matrix and L is lower triangular.
  26. *
  27. * This is the block version of the algorithm, calling Level 3 BLAS.
  28. *
  29. * Arguments
  30. * =========
  31. *
  32. * UPLO (input) CHARACTER*1
  33. * = 'U': Upper triangle of A is stored;
  34. * = 'L': Lower triangle of A is stored.
  35. *
  36. * N (input) INTEGER
  37. * The order of the matrix A. N >= 0.
  38. *
  39. * A (input/output) COMPLEX array, dimension (LDA,N)
  40. * On entry, the Hermitian matrix A. If UPLO = 'U', the leading
  41. * N-by-N upper triangular part of A contains the upper
  42. * triangular part of the matrix A, and the strictly lower
  43. * triangular part of A is not referenced. If UPLO = 'L', the
  44. * leading N-by-N lower triangular part of A contains the lower
  45. * triangular part of the matrix A, and the strictly upper
  46. * triangular part of A is not referenced.
  47. *
  48. * On exit, if INFO = 0, the factor U or L from the Cholesky
  49. * factorization A = U**H*U or A = L*L**H.
  50. *
  51. * LDA (input) INTEGER
  52. * The leading dimension of the array A. LDA >= max(1,N).
  53. *
  54. * INFO (output) INTEGER
  55. * = 0: successful exit
  56. * < 0: if INFO = -i, the i-th argument had an illegal value
  57. * > 0: if INFO = i, the leading minor of order i is not
  58. * positive definite, and the factorization could not be
  59. * completed.
  60. *
  61. * =====================================================================
  62. *
  63. * .. Parameters ..
  64. REAL ONE
  65. COMPLEX CONE
  66. PARAMETER ( ONE = 1.0E+0, CONE = ( 1.0E+0, 0.0E+0 ) )
  67. * ..
  68. * .. Local Scalars ..
  69. LOGICAL UPPER
  70. INTEGER J, JB, NB
  71. * ..
  72. * .. External Functions ..
  73. LOGICAL LSAME
  74. EXTERNAL LSAME
  75. * ..
  76. * .. External Subroutines ..
  77. EXTERNAL CGEMM, CHERK, CPOTF2, CTRSM, XERBLA
  78. * ..
  79. * .. Intrinsic Functions ..
  80. INTRINSIC MAX, MIN
  81. * ..
  82. * .. Executable Statements ..
  83. *
  84. * Test the input parameters.
  85. *
  86. INFO = 0
  87. UPPER = LSAME( UPLO, 'U' )
  88. IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
  89. INFO = -1
  90. ELSE IF( N.LT.0 ) THEN
  91. INFO = -2
  92. ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
  93. INFO = -4
  94. END IF
  95. IF( INFO.NE.0 ) THEN
  96. CALL XERBLA( 'CPOTRF', -INFO )
  97. RETURN
  98. END IF
  99. *
  100. * Quick return if possible
  101. *
  102. IF( N.EQ.0 )
  103. $ RETURN
  104. *
  105. * Determine the block size for this environment.
  106. *
  107. NB = 56
  108. IF( NB.LE.1 .OR. NB.GE.N ) THEN
  109. *
  110. * Use unblocked code.
  111. *
  112. CALL CPOTF2( UPLO, N, A, LDA, INFO )
  113. ELSE
  114. *
  115. * Use blocked code.
  116. *
  117. IF( UPPER ) THEN
  118. *
  119. * Compute the Cholesky factorization A = U'*U.
  120. *
  121. DO 10 J = 1, N, NB
  122. *
  123. * Update and factorize the current diagonal block and test
  124. * for non-positive-definiteness.
  125. *
  126. JB = MIN( NB, N-J+1 )
  127. CALL CHERK( 'Upper', 'Conjugate transpose', JB, J-1,
  128. $ -ONE, A( 1, J ), LDA, ONE, A( J, J ), LDA )
  129. CALL CPOTF2( 'Upper', JB, A( J, J ), LDA, INFO )
  130. IF( INFO.NE.0 )
  131. $ GO TO 30
  132. IF( J+JB.LE.N ) THEN
  133. *
  134. * Compute the current block row.
  135. *
  136. CALL CGEMM( 'Conjugate transpose', 'No transpose', JB,
  137. $ N-J-JB+1, J-1, -CONE, A( 1, J ), LDA,
  138. $ A( 1, J+JB ), LDA, CONE, A( J, J+JB ),
  139. $ LDA )
  140. CALL CTRSM( 'Left', 'Upper', 'Conjugate transpose',
  141. $ 'Non-unit', JB, N-J-JB+1, CONE, A( J, J ),
  142. $ LDA, A( J, J+JB ), LDA )
  143. END IF
  144. 10 CONTINUE
  145. *
  146. ELSE
  147. *
  148. * Compute the Cholesky factorization A = L*L'.
  149. *
  150. DO 20 J = 1, N, NB
  151. *
  152. * Update and factorize the current diagonal block and test
  153. * for non-positive-definiteness.
  154. *
  155. JB = MIN( NB, N-J+1 )
  156. CALL CHERK( 'Lower', 'No transpose', JB, J-1, -ONE,
  157. $ A( J, 1 ), LDA, ONE, A( J, J ), LDA )
  158. CALL CPOTF2( 'Lower', JB, A( J, J ), LDA, INFO )
  159. IF( INFO.NE.0 )
  160. $ GO TO 30
  161. IF( J+JB.LE.N ) THEN
  162. *
  163. * Compute the current block column.
  164. *
  165. CALL CGEMM( 'No transpose', 'Conjugate transpose',
  166. $ N-J-JB+1, JB, J-1, -CONE, A( J+JB, 1 ),
  167. $ LDA, A( J, 1 ), LDA, CONE, A( J+JB, J ),
  168. $ LDA )
  169. CALL CTRSM( 'Right', 'Lower', 'Conjugate transpose',
  170. $ 'Non-unit', N-J-JB+1, JB, CONE, A( J, J ),
  171. $ LDA, A( J+JB, J ), LDA )
  172. END IF
  173. 20 CONTINUE
  174. END IF
  175. END IF
  176. GO TO 40
  177. *
  178. 30 CONTINUE
  179. INFO = INFO + J - 1
  180. *
  181. 40 CONTINUE
  182. RETURN
  183. *
  184. * End of CPOTRF
  185. *
  186. END