c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_allocate_4.f08
blobd2e57f56780a1feed1e3d0a75987947003bb7119
1 ! { dg-do run }
2 ! { dg-options "-fcoarray=single" }
4 ! Contributed by Gerhard Steinmetz  <gerhard.steinmetz.fortran@t-online.de>
5 !               Andre Vehreschild <vehre@gcc.gnu.org>
6 ! Check that PR fortran/69451 is fixed.
8 program main
10 implicit none
12 type foo
13 end type
15 class(foo), allocatable :: p[:]
16 class(foo), pointer :: r
17 class(*), allocatable, target :: z
19 allocate(p[*])
21 call s(p, z)
22 select type (z)
23   class is (foo) 
24         r => z
25   class default
26      STOP 1
27 end select
29 if (.not. associated(r)) STOP 2
31 deallocate(r)
32 deallocate(p)
34 contains
36 subroutine s(x, z) 
37    class(*) :: x[*]
38    class(*), allocatable:: z
39    allocate (z, source=x)
40 end
42 end