view gcc/testsuite/gfortran.dg/submodule_29.f08 @ 152:2b5abeee2509

update gcc11
author anatofuz
date Mon, 25 May 2020 07:50:57 +0900
parents 84e7813d76e9
children
line wrap: on
line source

! { dg-do run }
!
! Test the fix for PR80554 in which it was not recognised that the symbol 'i'
! is host associated in the submodule 's' so that the new declaration in the
! submodule was rejected.
!
! Contributed by Tamas Bela Feher  <tamas.bela.feher@ipp.mpg.de>
!
module M
  implicit none
  integer :: i = 0
  character (100) :: buffer
  interface
    module subroutine write_i()
    end subroutine
  end interface
  interface
    module subroutine write_i_2()
    end subroutine
  end interface
contains
  subroutine foo
    integer :: i
  end
end module

submodule (M) S
    integer :: i = 137
  contains
    module subroutine write_i()
       write (buffer,*) i
    end subroutine
end submodule

submodule (M:S) S2
    integer :: i = 1037
  contains
    module subroutine write_i_2()
       write (buffer,*) i
    end subroutine
end submodule

program test_submod_variable
  use M
  implicit none
  integer :: j
  i = 42
  call write_i
  read (buffer, *) j
  if (i .ne. 42) STOP 1
  if (j .ne. 137) STOP 2
  call write_i_2
  read (buffer, *) j
  if (i .ne. 42) STOP 3
  if (j .ne. 1037) STOP 4
end program