1! { dg-do run }
2! PR 45777 - component ref aliases when both are pointers
3module m1
4  type t1
5     integer, dimension(:), allocatable :: data
6  end type t1
7contains
8  subroutine s1(t,d)
9    integer, dimension(:), pointer :: d
10    type(t1), pointer :: t
11    d(1:5)=t%data(3:7)
12  end subroutine s1
13  subroutine s2(d,t)
14    integer, dimension(:), pointer :: d
15    type(t1), pointer :: t
16    t%data(3:7) = d(1:5)
17  end subroutine s2
18end module m1
19
20program main
21  use m1
22  type(t1), pointer :: t
23  integer, dimension(:), pointer :: d
24  allocate(t)
25  allocate(t%data(10))
26  t%data=(/(i,i=1,10)/)
27  d=>t%data(5:9)
28  call s1(t,d)
29  if (any(d.ne.(/3,4,5,6,7/))) call abort()
30  t%data=(/(i,i=1,10)/)
31  d=>t%data(1:5)
32  call s2(d,t)
33  if (any(t%data.ne.(/1,2,1,2,3,4,5,8,9,10/))) call abort
34  deallocate(t%data)
35  deallocate(t)
36end program main
37