Télécharger dgesv.eso

Retour à la liste

Numérotation des lignes :

dgesv
  1. C DGESV SOURCE BP208322 20/09/18 21:15:52 10718
  2. *> \brief <b> DGESV computes the solution to system of linear equations A * X = B for GE matrices</b> (simple driver)
  3. *
  4. * =========== DOCUMENTATION ===========
  5. *
  6. * Online html documentation available at
  7. * http://www.netlib.org/lapack/explore-html/
  8. *
  9. *> \htmlonly
  10. *> Download SGESV + dependencies
  11. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dgesv.f">
  12. *> [TGZ]</a>
  13. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dgesv.f">
  14. *> [ZIP]</a>
  15. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgesv.f">
  16. *> [TXT]</a>
  17. *> \endhtmlonly
  18. *
  19. * Definition:
  20. * ===========
  21. *
  22. * SUBROUTINE DGESV( N, NRHS, A, LDA, IPIV, B, LDB, INFO )
  23. *
  24. * .. Scalar Arguments ..
  25. * INTEGER INFO, LDA, LDB, N, NRHS
  26. * ..
  27. * .. Array Arguments ..
  28. * INTEGER IPIV( * )
  29. * REAL A( LDA, * ), B( LDB, * )
  30. * ..
  31. *
  32. *
  33. *> \par Purpose:
  34. * =============
  35. *>
  36. *> \verbatim
  37. *>
  38. *> DGESV computes the solution to a real system of linear equations
  39. *> A * X = B,
  40. *> where A is an N-by-N matrix and X and B are N-by-NRHS matrices.
  41. *>
  42. *> The LU decomposition with partial pivoting and row interchanges is
  43. *> used to factor A as
  44. *> A = P * L * U,
  45. *> where P is a permutation matrix, L is unit lower triangular, and U is
  46. *> upper triangular. The factored form of A is then used to solve the
  47. *> system of equations A * X = B.
  48. *> \endverbatim
  49. *
  50. * Arguments:
  51. * ==========
  52. *
  53. *> \param[in] N
  54. *> \verbatim
  55. *> N is INTEGER
  56. *> The number of linear equations, i.e., the order of the
  57. *> matrix A. N >= 0.
  58. *> \endverbatim
  59. *>
  60. *> \param[in] NRHS
  61. *> \verbatim
  62. *> NRHS is INTEGER
  63. *> The number of right hand sides, i.e., the number of columns
  64. *> of the matrix B. NRHS >= 0.
  65. *> \endverbatim
  66. *>
  67. *> \param[in,out] A
  68. *> \verbatim
  69. *> A is REAL array, dimension (LDA,N)
  70. *> On entry, the N-by-N coefficient matrix A.
  71. *> On exit, the factors L and U from the factorization
  72. *> A = P*L*U; the unit diagonal elements of L are not stored.
  73. *> \endverbatim
  74. *>
  75. *> \param[in] LDA
  76. *> \verbatim
  77. *> LDA is INTEGER
  78. *> The leading dimension of the array A. LDA >= max(1,N).
  79. *> \endverbatim
  80. *>
  81. *> \param[out] IPIV
  82. *> \verbatim
  83. *> IPIV is INTEGER array, dimension (N)
  84. *> The pivot indices that define the permutation matrix P;
  85. *> row i of the matrix was interchanged with row IPIV(i).
  86. *> \endverbatim
  87. *>
  88. *> \param[in,out] B
  89. *> \verbatim
  90. *> B is REAL array, dimension (LDB,NRHS)
  91. *> On entry, the N-by-NRHS matrix of right hand side matrix B.
  92. *> On exit, if INFO = 0, the N-by-NRHS solution matrix X.
  93. *> \endverbatim
  94. *>
  95. *> \param[in] LDB
  96. *> \verbatim
  97. *> LDB is INTEGER
  98. *> The leading dimension of the array B. LDB >= max(1,N).
  99. *> \endverbatim
  100. *>
  101. *> \param[out] INFO
  102. *> \verbatim
  103. *> INFO is INTEGER
  104. *> = 0: successful exit
  105. *> < 0: if INFO = -i, the i-th argument had an illegal value
  106. *> > 0: if INFO = i, U(i,i) is exactly zero. The factorization
  107. *> has been completed, but the factor U is exactly
  108. *> singular, so the solution could not be computed.
  109. *> \endverbatim
  110. *
  111. * Authors:
  112. * ========
  113. *
  114. *> \author Univ. of Tennessee
  115. *> \author Univ. of California Berkeley
  116. *> \author Univ. of Colorado Denver
  117. *> \author NAG Ltd.
  118. *
  119. *> \date December 2016
  120. *
  121. *> \ingroup realGEsolve
  122. *
  123. * =====================================================================
  124. SUBROUTINE DGESV(N,NRHS,A,LDA,IPIV,B,LDB,INFO)
  125. *
  126. * -- LAPACK driver routine (version 3.7.0) --
  127. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  128. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  129. * December 2016
  130.  
  131. IMPLICIT INTEGER(I-N)
  132. IMPLICIT REAL*8(A-H,O-Z)
  133. *
  134. * .. Scalar Arguments ..
  135. INTEGER INFO, LDA, LDB, N, NRHS,I
  136. * ..
  137. * .. Array Arguments ..
  138. INTEGER IPIV(*)
  139. REAL*8 A(LDA,*), B(LDB,*)
  140. *
  141. INFO = 0
  142. *
  143. IF ( N.LT.0 ) THEN
  144. INFO = -1
  145. ELSE IF ( NRHS.LT.0 ) THEN
  146. INFO = -2
  147. ELSE IF ( LDA.LT.MAX( 1, N ) ) THEN
  148. INFO = -4
  149. ELSE IF ( LDB.LT.MAX( 1, N ) ) THEN
  150. INFO = -7
  151. END IF
  152. IF ( INFO.NE.0 ) THEN
  153. CALL XERBLA( 'DGESV ', -INFO )
  154. RETURN
  155. END IF
  156. * Compute the LU factorization of A.
  157. CALL DGETRF( N, N, A, LDA, IPIV, INFO )
  158. c write(*,*) 'DGESV: LU factorization ok ?',INFO,'A='
  159. c do iou=1,N
  160. c write(*,111)'A_',iou,(A(iou,jou),jou=1,N)
  161. c enddo
  162. c 111 FORMAT(A,I2,'=',11(1X,E10.4))
  163.  
  164. IF ( INFO.EQ.0 ) THEN
  165. *
  166. * Solve the system A*X = B, overwriting B with X.
  167. *
  168. CALL DGETRS( 'No transpose', N, NRHS, A, LDA, IPIV, B, LDB,
  169. & INFO )
  170. END IF
  171. RETURN
  172. *
  173. * End of SGESV
  174. *
  175. END
  176.  
  177.  
  178.  
  179.  

© Cast3M 2003 - Tous droits réservés.
Mentions légales