lto: Remove random_seed from section name.
[official-gcc.git] / gcc / testsuite / gfortran.dg / used_types_10.f90
blob4fbdc8e68e7399af47385f753309acd77ae0c747
1 ! { dg-do compile }
2 ! Tests the fix for PR28959 in which interface derived types were
3 ! not always being associated.
5 ! Contributed by Salvatore Filippone <sfilippone@uniroma2.it>
7 module derived_type_mod
9 type foo_dtype
10 integer, pointer :: v1(:)=>null()
11 end type foo_dtype
14 end module derived_type_mod
17 Module tools
19 interface foo_d_sub
20 subroutine cdalv(m, v, i, desc_a, info, flag)
21 use derived_type_mod
22 Integer, intent(in) :: m,i, v(:)
23 integer, intent(in), optional :: flag
24 integer, intent(out) :: info
25 Type(foo_dtype), intent(out) :: desc_a
26 end subroutine cdalv
27 end interface
29 end module tools
33 subroutine foo_bar(a,p,info)
34 use derived_type_mod
35 implicit none
37 type(foo_dtype), intent(in) :: a
38 type(foo_dtype), intent(inout) :: p
39 integer, intent(out) :: info
41 info=0
43 call inner_sub(info)
46 return
49 contains
51 subroutine inner_sub(info)
52 use tools
53 implicit none
55 integer, intent(out) :: info
57 integer :: i, nt,iv(10)
59 i = 0
60 nt = 1
62 call foo_d_sub(nt,iv,i,p,info,flag=1)
64 return
67 end subroutine inner_sub
71 end subroutine foo_bar