OSDN Git Service

* config/i386/i386.md (UNSPEC_VSIBADDR): New.
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / interface_derived_type_1.f90
1 ! { dg-do compile }
2 ! Test the fix for PR20903, in which derived types could be host associated within
3 ! interface bodies.
4 !
5 ! Contributed by Joost VandeVondele <jv244@cam.ac.uk>
6
7 module test
8   implicit none
9   type fcnparms
10     integer :: i
11   end type fcnparms
12 contains
13   subroutine sim_1(func1,params)
14     interface
15       function func1(fparams)
16         type(fcnparms) :: fparams ! { dg-error "not been declared within the interface" }
17         real :: func1
18       end function func1
19     end interface
20     type(fcnparms)     :: params
21    end subroutine sim_1
22
23   subroutine sim_2(func2,params)
24     interface
25       function func2(fparams)     ! This is OK because of the derived type decl.
26         type fcnparms
27           integer :: i
28         end type fcnparms
29         type(fcnparms)  :: fparams
30         real :: func2
31       end function func2
32     end interface
33     type(fcnparms)      :: params ! This is OK, of course
34    end subroutine sim_2
35 end module  test
36
37 module type_decl
38   implicit none
39   type fcnparms
40     integer :: i
41   end type fcnparms
42 end module type_decl
43
44 subroutine sim_3(func3,params)
45   use type_decl
46   interface
47     function func3(fparams)
48       use type_decl
49       type(fcnparms)   :: fparams ! This is OK - use associated
50       real :: func3
51     end function func3
52   end interface
53   type(fcnparms)       :: params  !         -ditto-
54 end subroutine sim_3
55
56 ! { dg-final { cleanup-modules "test type_decl" } }