view gcc/testsuite/gfortran.dg/dependency_21.f90 @ 131:84e7813d76e9

gcc-8.2
author mir3636
date Thu, 25 Oct 2018 07:37:49 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do run }
! Test the fix for PR31711 in which the dependency in the assignment
! at line 18 was detected and then ignored.
!
! Contributed by Tobias Ivarsson <thobes@gmail.com>
!
program laplsolv
  IMPLICIT NONE
  integer, parameter                  :: n = 2
  double precision,dimension(0:n+1, 0:n+1) :: T
  integer                             :: i

  T=0.0
  T(0:n+1 , 0)     = 1.0
  T(0:n+1 , n+1)   = 1.0
  T(n+1   , 0:n+1) = 2.0

  T(1:n,1)=(T(0:n-1,1)+T(1:n,1+1)+1d0)

  if (any (T(1:n,1) .ne. 1d0 )) STOP 1
end program laplsolv