AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr62125.f90
blobb72fdf6fe6a1e2e41c40dde64fa9b43112a508cd
1 ! { dg-do run }
2 ! PR62125 Nested select type not accepted (rejects valid)
3 module m
4 implicit none
5 type, abstract :: t1
6 logical :: l
7 end type t1
8 type, extends(t1), abstract :: t2
9 integer :: i
10 end type t2
11 type, extends(t2) :: t3
12 real :: x
13 end type t3
14 contains
15 subroutine s(u)
16 class(t1), intent(in) :: u
17 if(.not.u%l) STOP 1
18 select type(u); class is(t2)
19 if(u%i.ne.2) STOP 2
20 select type(u); class is(t3)
21 if(u%x.ne.3.5) STOP 3
22 end select
23 end select
24 end subroutine s
25 end module m
27 program p
28 use m
29 implicit none
30 type(t3) :: var = t3( l=.true. , i=2 , x=3.5 )
31 call s(var)
32 end program p