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.

spotrff.f 5.6 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184
  1. SUBROUTINE SPOTRFF( 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. * March 31, 1993
  7. *
  8. * .. Scalar Arguments ..
  9. CHARACTER UPLO
  10. INTEGER INFO, LDA, N
  11. * ..
  12. * .. Array Arguments ..
  13. REAL A( LDA, * )
  14. * ..
  15. *
  16. * Purpose
  17. * =======
  18. *
  19. * SPOTRF computes the Cholesky factorization of a real symmetric
  20. * positive definite matrix A.
  21. *
  22. * The factorization has the form
  23. * A = U**T * U, if UPLO = 'U', or
  24. * A = L * L**T, 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) REAL array, dimension (LDA,N)
  40. * On entry, the symmetric 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**T*U or A = L*L**T.
  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. PARAMETER ( ONE = 1.0E+0 )
  66. * ..
  67. * .. Local Scalars ..
  68. LOGICAL UPPER
  69. INTEGER J, JB, NB
  70. * ..
  71. * .. External Functions ..
  72. LOGICAL LSAME
  73. EXTERNAL LSAME
  74. * ..
  75. * .. External Subroutines ..
  76. EXTERNAL SGEMM, SPOTF2, SSYRK, STRSM, XERBLA
  77. * ..
  78. * .. Intrinsic Functions ..
  79. INTRINSIC MAX, MIN
  80. * ..
  81. * .. Executable Statements ..
  82. *
  83. * Test the input parameters.
  84. *
  85. INFO = 0
  86. UPPER = LSAME( UPLO, 'U' )
  87. IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
  88. INFO = -1
  89. ELSE IF( N.LT.0 ) THEN
  90. INFO = -2
  91. ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
  92. INFO = -4
  93. END IF
  94. IF( INFO.NE.0 ) THEN
  95. CALL XERBLA( 'SPOTRF', -INFO )
  96. RETURN
  97. END IF
  98. *
  99. * Quick return if possible
  100. *
  101. IF( N.EQ.0 )
  102. $ RETURN
  103. *
  104. * Determine the block size for this environment.
  105. *
  106. NB = 56
  107. IF( NB.LE.1 .OR. NB.GE.N ) THEN
  108. *
  109. * Use unblocked code.
  110. *
  111. CALL SPOTF2( UPLO, N, A, LDA, INFO )
  112. ELSE
  113. *
  114. * Use blocked code.
  115. *
  116. IF( UPPER ) THEN
  117. *
  118. * Compute the Cholesky factorization A = U'*U.
  119. *
  120. DO 10 J = 1, N, NB
  121. *
  122. * Update and factorize the current diagonal block and test
  123. * for non-positive-definiteness.
  124. *
  125. JB = MIN( NB, N-J+1 )
  126. CALL SSYRK( 'Upper', 'Transpose', JB, J-1, -ONE,
  127. $ A( 1, J ), LDA, ONE, A( J, J ), LDA )
  128. CALL SPOTF2( 'Upper', JB, A( J, J ), LDA, INFO )
  129. IF( INFO.NE.0 )
  130. $ GO TO 30
  131. IF( J+JB.LE.N ) THEN
  132. *
  133. * Compute the current block row.
  134. *
  135. CALL SGEMM( 'Transpose', 'No transpose', JB, N-J-JB+1,
  136. $ J-1, -ONE, A( 1, J ), LDA, A( 1, J+JB ),
  137. $ LDA, ONE, A( J, J+JB ), LDA )
  138. CALL STRSM( 'Left', 'Upper', 'Transpose', 'Non-unit',
  139. $ JB, N-J-JB+1, ONE, A( J, J ), LDA,
  140. $ A( J, J+JB ), LDA )
  141. END IF
  142. 10 CONTINUE
  143. *
  144. ELSE
  145. *
  146. * Compute the Cholesky factorization A = L*L'.
  147. *
  148. DO 20 J = 1, N, NB
  149. *
  150. * Update and factorize the current diagonal block and test
  151. * for non-positive-definiteness.
  152. *
  153. JB = MIN( NB, N-J+1 )
  154. CALL SSYRK( 'Lower', 'No transpose', JB, J-1, -ONE,
  155. $ A( J, 1 ), LDA, ONE, A( J, J ), LDA )
  156. CALL SPOTF2( 'Lower', JB, A( J, J ), LDA, INFO )
  157. IF( INFO.NE.0 )
  158. $ GO TO 30
  159. IF( J+JB.LE.N ) THEN
  160. *
  161. * Compute the current block column.
  162. *
  163. CALL SGEMM( 'No transpose', 'Transpose', N-J-JB+1, JB,
  164. $ J-1, -ONE, A( J+JB, 1 ), LDA, A( J, 1 ),
  165. $ LDA, ONE, A( J+JB, J ), LDA )
  166. CALL STRSM( 'Right', 'Lower', 'Transpose', 'Non-unit',
  167. $ N-J-JB+1, JB, ONE, A( J, J ), LDA,
  168. $ A( J+JB, J ), LDA )
  169. END IF
  170. 20 CONTINUE
  171. END IF
  172. END IF
  173. GO TO 40
  174. *
  175. 30 CONTINUE
  176. INFO = INFO + J - 1
  177. *
  178. 40 CONTINUE
  179. RETURN
  180. *
  181. * End of SPOTRF
  182. *
  183. END