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