c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / select_type_48.f90
blobd9ad01ce4f605a1a77fda7e799c8d08f1d6f2caf
1 ! { dg-do run }
3 ! Test the fix for PR92976, in which the TYPE IS statement caused an ICE
4 ! because of the explicit bounds of 'x'.
6 ! Contributed by Gerhard Steinmetz <gscfq@t-online.de>
8 program p
9 type t
10 integer :: i
11 end type
12 class(t), allocatable :: c(:)
13 allocate (c, source = [t(1111),t(2222),t(3333)])
14 call s(c)
15 if (sum (c%i) .ne. 3333) stop 1
16 contains
17 subroutine s(x)
18 class(t) :: x(2)
19 select type (x)
20 ! ICE as compiler attempted to assign descriptor to an array
21 type is (t)
22 x%i = 0
23 ! Make sure that bounds are correctly translated.
24 call counter (x)
25 end select
26 end
27 subroutine counter (arg)
28 type(t) :: arg(:)
29 if (size (arg, 1) .ne. 2) stop 2
30 end
31 end