! 网络最大流算法,基于Ford & Fulkerson算法
  ! 修改自 杨洪,图论常用算法选编,北京:中国铁道出版社,1988
  ! 陆新征,北京清华大学土木工程系
  ! 2007.1.14.
  subroutine MaxC(NNode,Capacity,Distribution,NStart,NEnd,Inf,TotalFlow)
  implicit none
  integer NNode, NStart, NEnd ! 总节点数,起点编号,终点编号
  real*8 Capacity(NNode,NNode), Distribution(NNode,NNode), Inf, TotalFlow
  ! 道路的同行能力 最大分配交通流量 无穷大 总流量
  ! 以下为工作变量
  integer P(NNode), Q(NNode), R(NNode),D1(NNode), D2(NNode)
  real*8 D3(NNode)
  integer K, K0, K1, K2, I, I1, N1
  TotalFlow=0
  Distribution=0
  
  do 
  D1=0; D2=0; D3=0; Q=0; R=0
  Q(NStart)=1; D1(NStart)=-1; D2(NStart)=NStart; D3(NStart)=Inf
  
  do while (D1(NEnd)==0) 
  K0=0
  do K=1, NNode
  if(Q(K)/=1) cycle
  do I=1, NNode
  if(R(I)+Q(I)/=0) cycle
  if(Capacity(K,I)/=0.and.Distribution(K,I)<Capacity(K,I)) then
  K0=1; R(I)=1; D1(I)=1; D2(I)=K
  D3(I)=min(Capacity(K,I)-Distribution(K,I),D3(K))
  else
  if(Distribution(I,K)<=0.or.Capacity(I,K)==0) cycle
  K0=1; R(I)=1; D1(I)=-1; D2(I)=K
  D3(I)=min(Distribution(I,K),D3(K))
  end if
  end do ! for I !21
  end do ! for K !9
  if (K0==0) return
  do K=1,NNode
  if(R(K)==1) Q(K)=1
  end do
  end do
  P=0; Q=0; P(NNode)=D2(NEnd); K=P(NNode); N1=NNode-1
  do I1=1,N1
  I=NNode-I1; Q(I)=D1(K); K=D2(K); P(I)=K
  if(K==NStart) exit
  end do
  K1=P(I)
  do K=1,N1
  K2=P(K+1)
  if(Q(K)>0) Distribution(K1,K2)=Distribution(K1,K2)+D3(NEnd)
  if(Q(K)<0) Distribution(K2,K1)=Distribution(K2,K1)+Q(K)*D3(NEnd)
  K1=K2
  end do
  Distribution(K1,NEnd)=Distribution(K1,NEnd)+D3(NEnd)
  TotalFlow=0
  TotalFlow=TotalFlow+sum(Distribution(1:NNode,NEnd)) 
  end do
  return
  end subroutine
subroutine MXC(N, M0, C, L)
  real*8 C(N,N), L(N,N), MC, M0
  integer S, T
  S=1; T=N
  call MAXC(N,C,L,S,T,M0,MC)
  do I=1, N
  write(*,'(10F8.0)') L(I,1:N)
  end do
  write(*,'(2I5, F8.0)') S,T,MC
  return
  end subroutine
program Main
  real*8,pointer :: C(:,:), L(:,:)
  real*8 M0
  open(55,file="input.txt")
  read(55,*) N, M0
  allocate(C(N,N))
  allocate(L(N,N))
 do I=1,N
  read(55,*) C(I,1:N)
  end do
  close(55)
  call MXC(N,M0,C,L)
  deallocate(C)
  deallocate(L)
  stop
  end program
input.txt
9 90
  0 14 0 23 0 0 0 0 0
  0 0 10 9 0 0 0 0 0
  0 0 0 0 12 0 0 18 0
  0 0 0 0 26 0 0 0 0
  0 0 0 0 0 25 4 0 0
  0 0 0 0 0 0 7 8 0
  0 0 0 0 0 0 0 0 15
  0 0 0 0 0 0 0 0 20
  0 0 0 0 0 0 0 0 0