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.

sget01.f 5.6 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212
  1. *> \brief \b SGET01
  2. *
  3. * =========== DOCUMENTATION ===========
  4. *
  5. * Online html documentation available at
  6. * http://www.netlib.org/lapack/explore-html/
  7. *
  8. * Definition:
  9. * ===========
  10. *
  11. * SUBROUTINE SGET01( M, N, A, LDA, AFAC, LDAFAC, IPIV, RWORK,
  12. * RESID )
  13. *
  14. * .. Scalar Arguments ..
  15. * INTEGER LDA, LDAFAC, M, N
  16. * REAL RESID
  17. * ..
  18. * .. Array Arguments ..
  19. * INTEGER IPIV( * )
  20. * REAL A( LDA, * ), AFAC( LDAFAC, * ), RWORK( * )
  21. * ..
  22. *
  23. *
  24. *> \par Purpose:
  25. * =============
  26. *>
  27. *> \verbatim
  28. *>
  29. *> SGET01 reconstructs a matrix A from its L*U factorization and
  30. *> computes the residual
  31. *> norm(L*U - A) / ( N * norm(A) * EPS ),
  32. *> where EPS is the machine epsilon.
  33. *> \endverbatim
  34. *
  35. * Arguments:
  36. * ==========
  37. *
  38. *> \param[in] M
  39. *> \verbatim
  40. *> M is INTEGER
  41. *> The number of rows of the matrix A. M >= 0.
  42. *> \endverbatim
  43. *>
  44. *> \param[in] N
  45. *> \verbatim
  46. *> N is INTEGER
  47. *> The number of columns of the matrix A. N >= 0.
  48. *> \endverbatim
  49. *>
  50. *> \param[in] A
  51. *> \verbatim
  52. *> A is REAL array, dimension (LDA,N)
  53. *> The original M x N matrix A.
  54. *> \endverbatim
  55. *>
  56. *> \param[in] LDA
  57. *> \verbatim
  58. *> LDA is INTEGER
  59. *> The leading dimension of the array A. LDA >= max(1,M).
  60. *> \endverbatim
  61. *>
  62. *> \param[in,out] AFAC
  63. *> \verbatim
  64. *> AFAC is REAL array, dimension (LDAFAC,N)
  65. *> The factored form of the matrix A. AFAC contains the factors
  66. *> L and U from the L*U factorization as computed by SGETRF.
  67. *> Overwritten with the reconstructed matrix, and then with the
  68. *> difference L*U - A.
  69. *> \endverbatim
  70. *>
  71. *> \param[in] LDAFAC
  72. *> \verbatim
  73. *> LDAFAC is INTEGER
  74. *> The leading dimension of the array AFAC. LDAFAC >= max(1,M).
  75. *> \endverbatim
  76. *>
  77. *> \param[in] IPIV
  78. *> \verbatim
  79. *> IPIV is INTEGER array, dimension (N)
  80. *> The pivot indices from SGETRF.
  81. *> \endverbatim
  82. *>
  83. *> \param[out] RWORK
  84. *> \verbatim
  85. *> RWORK is REAL array, dimension (M)
  86. *> \endverbatim
  87. *>
  88. *> \param[out] RESID
  89. *> \verbatim
  90. *> RESID is REAL
  91. *> norm(L*U - A) / ( N * norm(A) * EPS )
  92. *> \endverbatim
  93. *
  94. * Authors:
  95. * ========
  96. *
  97. *> \author Univ. of Tennessee
  98. *> \author Univ. of California Berkeley
  99. *> \author Univ. of Colorado Denver
  100. *> \author NAG Ltd.
  101. *
  102. *> \ingroup single_lin
  103. *
  104. * =====================================================================
  105. SUBROUTINE SGET01( M, N, A, LDA, AFAC, LDAFAC, IPIV, RWORK,
  106. $ RESID )
  107. *
  108. * -- LAPACK test routine --
  109. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  110. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  111. *
  112. * .. Scalar Arguments ..
  113. INTEGER LDA, LDAFAC, M, N
  114. REAL RESID
  115. * ..
  116. * .. Array Arguments ..
  117. INTEGER IPIV( * )
  118. REAL A( LDA, * ), AFAC( LDAFAC, * ), RWORK( * )
  119. * ..
  120. *
  121. * =====================================================================
  122. *
  123. *
  124. * .. Parameters ..
  125. REAL ZERO, ONE
  126. PARAMETER ( ZERO = 0.0E+0, ONE = 1.0E+0 )
  127. * ..
  128. * .. Local Scalars ..
  129. INTEGER I, J, K
  130. REAL ANORM, EPS, T
  131. * ..
  132. * .. External Functions ..
  133. REAL SDOT, SLAMCH, SLANGE
  134. EXTERNAL SDOT, SLAMCH, SLANGE
  135. * ..
  136. * .. External Subroutines ..
  137. EXTERNAL SGEMV, SLASWP, SSCAL, STRMV
  138. * ..
  139. * .. Intrinsic Functions ..
  140. INTRINSIC MIN, REAL
  141. * ..
  142. * .. Executable Statements ..
  143. *
  144. * Quick exit if M = 0 or N = 0.
  145. *
  146. IF( M.LE.0 .OR. N.LE.0 ) THEN
  147. RESID = ZERO
  148. RETURN
  149. END IF
  150. *
  151. * Determine EPS and the norm of A.
  152. *
  153. EPS = SLAMCH( 'Epsilon' )
  154. ANORM = SLANGE( '1', M, N, A, LDA, RWORK )
  155. *
  156. * Compute the product L*U and overwrite AFAC with the result.
  157. * A column at a time of the product is obtained, starting with
  158. * column N.
  159. *
  160. DO 10 K = N, 1, -1
  161. IF( K.GT.M ) THEN
  162. CALL STRMV( 'Lower', 'No transpose', 'Unit', M, AFAC,
  163. $ LDAFAC, AFAC( 1, K ), 1 )
  164. ELSE
  165. *
  166. * Compute elements (K+1:M,K)
  167. *
  168. T = AFAC( K, K )
  169. IF( K+1.LE.M ) THEN
  170. CALL SSCAL( M-K, T, AFAC( K+1, K ), 1 )
  171. CALL SGEMV( 'No transpose', M-K, K-1, ONE,
  172. $ AFAC( K+1, 1 ), LDAFAC, AFAC( 1, K ), 1, ONE,
  173. $ AFAC( K+1, K ), 1 )
  174. END IF
  175. *
  176. * Compute the (K,K) element
  177. *
  178. AFAC( K, K ) = T + SDOT( K-1, AFAC( K, 1 ), LDAFAC,
  179. $ AFAC( 1, K ), 1 )
  180. *
  181. * Compute elements (1:K-1,K)
  182. *
  183. CALL STRMV( 'Lower', 'No transpose', 'Unit', K-1, AFAC,
  184. $ LDAFAC, AFAC( 1, K ), 1 )
  185. END IF
  186. 10 CONTINUE
  187. CALL SLASWP( N, AFAC, LDAFAC, 1, MIN( M, N ), IPIV, -1 )
  188. *
  189. * Compute the difference L*U - A and store in AFAC.
  190. *
  191. DO 30 J = 1, N
  192. DO 20 I = 1, M
  193. AFAC( I, J ) = AFAC( I, J ) - A( I, J )
  194. 20 CONTINUE
  195. 30 CONTINUE
  196. *
  197. * Compute norm( L*U - A ) / ( N * norm(A) * EPS )
  198. *
  199. RESID = SLANGE( '1', M, N, AFAC, LDAFAC, RWORK )
  200. *
  201. IF( ANORM.LE.ZERO ) THEN
  202. IF( RESID.NE.ZERO )
  203. $ RESID = ONE / EPS
  204. ELSE
  205. RESID = ( ( RESID / REAL( N ) ) / ANORM ) / EPS
  206. END IF
  207. *
  208. RETURN
  209. *
  210. * End of SGET01
  211. *
  212. END