* tree-loop-distribution.c (struct partition): New field recording
[official-gcc.git] / gcc / testsuite / gfortran.dg / select_type_35.f03
blob92d2f27531311b76abf9dac25745f7c6dfe9bf05
1 ! { dg-do run }
3 ! Contributed by Nathanael Huebbe
4 ! Check fix for PR/70842
6 program foo
8   TYPE, ABSTRACT :: t_Intermediate
9   END TYPE t_Intermediate
11   type, extends(t_Intermediate) :: t_Foo
12     character(:), allocatable :: string
13   end type t_Foo
15   class(t_Foo), allocatable :: obj
17   allocate(obj)
18   obj%string = "blabarfoo"
20   call bar(obj)
22   deallocate(obj)
23 contains
24   subroutine bar(me)
25     class(t_Intermediate), target :: me
27     class(*), pointer :: alias
29     select type(me)
30       type is(t_Foo)
31       if (len(me%string) /= 9) call abort()
32     end select
34     alias => me
35     select type(alias)
36       type is(t_Foo)
37         if (len(alias%string) /= 9) call abort()
38     end select
39   end subroutine bar
40 end program foo