c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / pointer_check_14.f90
blob8ef6b3611fa65d8d7fa2ea81769cc932f6f82243
1 ! { dg-do run }
2 ! { dg-options "-fcheck=pointer -fdump-tree-original" }
3 ! PR100602 - Erroneous "pointer argument is not associated" runtime error
5 module m
6 type :: T
7 end type
8 contains
9 subroutine f(this)
10 class(T), intent(in) :: this(:)
11 class(T), allocatable :: ca(:)
12 class(T), pointer :: cp(:)
13 if (size (this) == 0) return
14 write(*,*) size (this)
15 stop 1
16 write(*,*) size (ca) ! Check #1
17 write(*,*) size (cp) ! Check #2
18 end subroutine f
19 end module
21 program main
22 use m
23 call f([T::])
24 end program
26 ! { dg-final { scan-tree-dump-times "_gfortran_runtime_error_at" 2 "original" } }
27 ! { dg-final { scan-tree-dump-times "Allocatable argument .*ca" 1 "original" } }
28 ! { dg-final { scan-tree-dump-times "Pointer argument .*cp" 1 "original" } }