PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / host_assoc_function_2.f90
blobf2a37b6869709664490d39eb96fdfff5ae85a476
1 ! { dg-do compile }
2 ! Tests the fix for PR32464, where the use associated procedure would
3 ! mess up the check for "grandparent" host association.
5 ! Contributed by Harald Anlauf <anlauf@gmx.de>
8 module gfcbug64_mod1
9 implicit none
11 public :: inverse
13 interface inverse
14 module procedure copy
15 end interface
17 contains
19 function copy (d) result (y)
20 real, intent(in) :: d(:)
21 real :: y(size (d)) ! <- this version kills gfortran
22 ! real, intent(in) :: d
23 ! real :: y
24 y = d
25 end function copy
27 end module gfcbug64_mod1
29 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
31 module gfcbug64_mod2
32 implicit none
33 contains
35 subroutine foo (x_o)
36 real, intent(in) :: x_o(:)
38 integer :: s(size (x_o)) ! <- this line kills gfortran
40 contains
42 subroutine bar ()
43 use gfcbug64_mod1, only: inverse ! <- this line kills gfortran
44 end subroutine bar
46 end subroutine foo
47 end module gfcbug64_mod2