arm: Add .type and .size to __gnu_cmse_nonsecure_call [PR115360]
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr87946.f90
blob793d37a7f3999f7a2852e7780c40a70a91e9f384
1 ! { dg-do run }
3 ! Contributed by Gerhard Steinmetz <gscfq@t-online.de>
5 module m
6 type t
7 contains
8 generic :: h => g
9 procedure, private :: g
10 end type
11 contains
12 function g(x, y) result(z)
13 class(t), intent(in) :: x
14 real, intent(in) :: y(:, :)
15 real :: z(size(y, 2))
16 integer :: i
17 do i = 1, size(y, 2)
18 z(i) = i
19 end do
20 end
21 end
22 module m2
23 use m
24 type t2
25 class(t), allocatable :: u(:)
26 end type
27 end
28 use m2
29 type(t2) :: x
30 real :: y(1,5)
31 allocate (x%u(1))
32 if (any (int(f (x, y)) .ne. [1,2,3,4,5])) stop 1
33 deallocate (x%u)
34 contains
35 function f(x, y) result(z)
36 use m2
37 type(t2) :: x
38 real :: y(:, :)
39 real :: z(size(y, 2))
40 z = x%u(1)%h(y) ! Used to segfault here
41 end
42 end