lto: Remove random_seed from section name.
[official-gcc.git] / gcc / testsuite / gfortran.dg / assumed_type_11.f90
blob391fa0de8f22284cba80a5d4e6467a9d16058e1a
1 ! { dg-do compile }
2 ! { dg-options "-O3 -fdump-tree-original" }
3 ! PR 61968 - this used to generate invalid assembler containing
4 ! TYPE(*).
6 module testmod
7 use iso_c_binding, only: c_size_t, c_int32_t, c_int64_t
8 implicit none
10 interface test
11 procedure :: test_32
12 procedure :: test_array
13 end interface test
15 interface
16 subroutine test_lib (a, len) bind(C, name="xxx")
17 use iso_c_binding, only: c_size_t
18 type(*), dimension(*) :: a
19 integer(c_size_t), value :: len
20 end subroutine
21 end interface
23 contains
25 subroutine test_32 (a, len)
26 type(*), dimension(*) :: a
27 integer(c_int32_t), value :: len
28 call test_lib (a, int (len, kind=c_size_t))
29 end subroutine
31 subroutine test_array (a)
32 use iso_c_binding, only: c_size_t
33 class(*), dimension(..), target :: a
34 select rank (a)
35 rank (1)
36 call test_lib (a, int (sizeof (a), kind=c_size_t))
37 end select
38 end subroutine
40 end module
42 subroutine test_32_ (a, len)
43 use iso_c_binding, only: c_int32_t
44 use testmod
45 type(*), dimension(*) :: a
46 integer(c_int32_t), value :: len
47 call test (a, len)
48 end subroutine
49 ! { dg-final { scan-tree-dump-not "! __vtype_TYPE\\(*\\)" "original" } }