OSDN Git Service

2006-09-05 Paul Thomas <pault@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / used_types_9.f90
1 ! { dg-do compile }\r
2 ! Tests the fix for a further regression caused by the\r
3 ! fix for PR28788 and posted as PR28908. The problem was\r
4 ! caused by the patch preventing interface derived types\r
5 ! from associating with identical derived types in the\r
6 ! containing namespaces.\r
7 !\r
8 ! Contributed by HJ Lu  <hjl@lucon.org>\r
9 !\r
10 module bar\r
11   implicit none\r
12   public\r
13   type domain_ptr\r
14     type(domain), POINTER  :: ptr\r
15   end type domain_ptr\r
16   type domain\r
17     TYPE(domain_ptr) , DIMENSION( : ) , POINTER         :: parents\r
18     TYPE(domain_ptr) , DIMENSION( : ) , POINTER         :: nests\r
19   end type domain\r
20 end module bar\r
21 \r
22 module foo\r
23 contains\r
24   recursive subroutine integrate (grid)\r
25     use bar\r
26     implicit none\r
27     type(domain), POINTER  :: grid\r
28     interface\r
29       subroutine solve_interface (grid)\r
30         use bar\r
31         TYPE (domain) grid\r
32       end subroutine solve_interface\r
33     end interface\r
34   end subroutine integrate\r
35 end module foo\r
36 ! { dg-final { cleanup-modules "foo bar" } }\r