AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr102332.f90
blobf95570940834fd787cbb2a7f2838c15452b8886f
1 ! { dg-do compile }
2 ! PR fortran/102332 - ICE in select_type_set_tmp
3 ! Contributed by G.Steinmetz
5 program p
6 type t
7 real :: a, b
8 end type
9 class(t), allocatable :: x ! Valid
10 select type (y => x)
11 type is (t)
12 y%a = 0
13 end select
14 end
16 subroutine s0 (x)
17 type t
18 real :: a, b
19 end type
20 class(t) :: x ! Valid
21 select type (y => x)
22 type is (t)
23 y%a = 0
24 end select
25 end
27 subroutine s1
28 type t
29 real :: a, b
30 end type
31 class(t) :: x ! { dg-error "must be dummy, allocatable or pointer" }
32 select type (y => x)
33 type is (t)
34 y%a = 0
35 end select
36 end
38 subroutine s3
39 type t
40 real :: a, b
41 end type
42 class(t) :: x ! { dg-error "must be dummy, allocatable or pointer" }
43 select type (y => x)
44 class is (t)
45 y%a = 0
46 end select
47 end
49 subroutine s2
50 type t
51 real :: a, b
52 end type
53 class(t) :: x ! { dg-error "must be dummy, allocatable or pointer" }
54 select type (y => x)
55 type default ! { dg-error "Expected" }
56 y%a = 0
57 end select
58 end
60 subroutine s4
61 type t
62 real :: a, b
63 end type
64 class(t) :: x ! { dg-error "must be dummy, allocatable or pointer" }
65 select type (y => x)
66 class default
67 y%a = 0
68 end select
69 end