在MatLab中,命令lu(A)给出两个矩阵L和U的输出,即A的LU分解。我想知道Fortran中是否有一些命令完全相同。我无法在任何地方找到它。我找到了很多LAPACK子程序,通过首先执行LU分解来解决线性系统,但对于我的purpouses,我需要专门执行LU分解并存储L和U矩阵。
是否有一个命令或子程序,它具有方形矩阵A作为输入,并输出LU分解的矩阵L和U?
答案 0 :(得分:4)
在Matlab中没有与lu
对应的内置命令,但我们可以在LAPACK中向dgetrf
编写一个简单的包装器,使得接口类似于lu
,例如,
module linalg
implicit none
integer, parameter :: dp = kind(0.0d0)
contains
subroutine lufact( A, L, U, P )
!... P * A = L * U
!... http://www.netlib.org/lapack/explore-3.1.1-html/dgetrf.f.html
!... (note that the definition of P is opposite to that of the above page)
real(dp), intent(in) :: A(:,:)
real(dp), allocatable, dimension(:,:) :: L, U, P
integer, allocatable :: ipiv(:)
real(dp), allocatable :: row(:)
integer :: i, n, info
n = size( A, 1 )
allocate( L( n, n ), U( n, n ), P( n, n ), ipiv( n ), row( n ) )
L = A
call DGETRF( n, n, L, n, ipiv, info )
if ( info /= 0 ) stop "lufact: info /= 0"
U = 0.0d0
P = 0.0d0
do i = 1, n
U( i, i:n ) = L( i, i:n )
L( i, i:n ) = 0.0d0
L( i, i ) = 1.0d0
P( i, i ) = 1.0d0
enddo
!... Assuming that P = P[ipiv(n),n] * ... * P[ipiv(1),1]
!... where P[i,j] is a permutation matrix for i- and j-th rows.
do i = 1, n
row = P( i, : )
P( i, : ) = P( ipiv(i), : )
P( ipiv(i), : ) = row
enddo
endsubroutine
end module
然后,我们可以使用Matlab页面中显示的3x3矩阵测试例程lu():
program test_lu
use linalg
implicit none
real(dp), allocatable, dimension(:,:) :: A, L, U, P
allocate( A( 3, 3 ) )
A( 1, : ) = [ 1, 2, 3 ]
A( 2, : ) = [ 4, 5, 6 ]
A( 3, : ) = [ 7, 8, 0 ]
call lufact( A, L, U, P ) !<--> [L,U,P] = lu( A ) in Matlab
call show( "A =", A )
call show( "L =", L )
call show( "U =", U )
call show( "P =", P )
call show( "P * A =", matmul( P, A ) )
call show( "L * U =", matmul( L, U ) )
call show( "P' * L * U =", matmul( transpose(P), matmul( L, U ) ) )
contains
subroutine show( msg, X )
character(*) :: msg
real(dp) :: X(:,:)
integer i
print "(/,a)", trim( msg )
do i = 1, size(X,1)
print "(*(f8.4))", X( i, : )
enddo
endsubroutine
end program
给出了预期的结果:
A =
1.0000 2.0000 3.0000
4.0000 5.0000 6.0000
7.0000 8.0000 0.0000
L =
1.0000 0.0000 0.0000
0.1429 1.0000 0.0000
0.5714 0.5000 1.0000
U =
7.0000 8.0000 0.0000
0.0000 0.8571 3.0000
0.0000 0.0000 4.5000
P =
0.0000 0.0000 1.0000
1.0000 0.0000 0.0000
0.0000 1.0000 0.0000
P * A =
7.0000 8.0000 0.0000
1.0000 2.0000 3.0000
4.0000 5.0000 6.0000
L * U =
7.0000 8.0000 0.0000
1.0000 2.0000 3.0000
4.0000 5.0000 6.0000
P' * L * U =
1.0000 2.0000 3.0000
4.0000 5.0000 6.0000
7.0000 8.0000 0.0000
请注意,P
的倒数由其转置(即inv(P) = P' = transpose(P)
)给出,因为P
是(基本)置换矩阵的乘积。
答案 1 :(得分:2)
我添加了一个使用DOLITTLE方法计算LU的方法。 MATLAB使用它来计算LU,以便更快地计算涉及更大的矩阵。算法如下。要执行算法,您必须以下面给出的格式提供输入文件。由于算法是子程序,您可以将其添加到代码中并在需要时调用它。算法,输入文件,输出文件如下。
PROGRAM DOLITTLE
IMPLICIT NONE
INTEGER :: n
!**********************************************************
! READS THE NUMBER OF EQUATIONS TO BE SOLVED.
OPEN(UNIT=1,FILE='input.dat',ACTION='READ',STATUS='OLD')
READ(1,*) n
CLOSE(1)
!**********************************************************
CALL LU(n)
END PROGRAM
!==========================================================
! SUBROUTINES TO MAIN PROGRAM
SUBROUTINE LU(n)
IMPLICIT NONE
INTEGER :: i,j,k,p,n,z,ii,itr = 500000
REAL(KIND=8) :: temporary,s1,s2
REAL(KIND=8),DIMENSION(1:n) :: x,b,y
REAL(KIND=8),DIMENSION(1:n,1:n) :: A,U,L,TEMP
REAL(KIND=8),DIMENSION(1:n,1:n+1) :: AB
! READING THE SYSTEM OF EQUATIONS
OPEN(UNIT=2,FILE='input.dat',ACTION='READ',STATUS='OLD')
READ(2,*)
DO I=1,N
READ(2,*) A(I,:)
END DO
DO I=1,N
READ(2,*) B(I)
END DO
CLOSE(2)
DO z=1,itr
U(:,:) = 0
L(:,:) = 0
DO j = 1,n
L(j,j) = 1.0d0
END DO
DO j = 1,n
U(1,j) = A(1,j)
END DO
DO i=2,n
DO j=1,n
DO k=1,i1
s1=0
if (k==1)then
s1=0
else
DO p=1,k1
s1=s1+L(i,p)*U(p,k)
end DO
endif
L(i,k)=(A(i,k)-s1)/U(k,k)
END DO
DO k=i,n
s2=0
DO p=1,i-1
s2=s2+l(i,p)*u(p,k)
END DO
U(i,k)=A(i,k)*s2
END DO
END DO
END DO
IF(z.eq.1)THEN
OPEN(UNIT=3,FILE='output.dat',ACTION='write')
WRITE(3,*) ''
WRITE(3,*) '********** SOLUTIONS *********************'
WRITE(3,*) ''
WRITE(3,*) ''
WRITE(3,*) 'UPPER TRIANGULAR MATRIX'
DO I=1,N
WRITE(3,*) U(I,:)
END DO
WRITE(3,*) ''
WRITE(3,*) ''
WRITE(3,*) 'LOWER TRIANGULAR MATRIX'
DO I=1,N
WRITE(3,*) L(I,:)
END DO
END SUBROUTINE
这是系统Ax = B的输入文件格式。第一行是方程的数量,接下来的三行是A矩阵元素,接下来的三行是B向量,
3
10 8 3
3 20 1
4 5 15
18
23
9
输出生成为,
********** SOLUTIONS *********************
UPPER TRIANGULAR MATRIX
10.000000000000000 8.0000000000000000 3.0000000000000000
0.0000000000000000 17.600000000000001 0.1000000000000009
0.0000000000000000 0.0000000000000000 13.789772727272727
LOWER TRIANGULAR MATRIX
1.0000000000000000 0.0000000000000000 0.0000000000000000
0.2999999999999999 1.0000000000000000 0.0000000000000000
0.4000000000000002 0.1022727272727273 1.0000000000000000
答案 2 :(得分:0)
你可以试试“fortran 77中的数字食谱”, 有LU分解子程序。
有许多有用的子程序,linalg,stasistics等。