2 ! { dg-options "-fdump-tree-original " }
3 ! Checks the fix for PR46896, in which the optimization that passes
4 ! the argument of TRANSPOSE directly missed the possible aliasing
5 ! through host association.
7 ! Contributed by Jerry DeLisle <jvdelisle@gcc.gnu.org>
10 integer :: b(2,3) = reshape([1,2,3,4,5,6], [2,3])
16 if (any (b(:,1) /= [99, 1]).or
.any (b(:,2) /= [99, 3])) call abort()
18 subroutine pure_msub(x
, y
)
19 integer, intent(in
) :: x(:,:)
20 integer, intent(OUT
) :: y(size (x
, 2), size (x
, 1))
22 end subroutine pure_msub
26 integer :: a(2,3) = reshape([1,2,3,4,5,6], [2,3])
31 ! pure_sub and pure_msub could be PURE, if so declared. They do not
36 call pure_sub(transpose(a
), c
)
37 if (any (c
.ne
. a
)) call abort
38 call pure_msub(transpose(b
), c
)
39 if (any (c
.ne
. b
)) call abort
42 ! sub and msub both need temporaries to avoid aliasing.
45 call sub(transpose(a
))
52 if (any (a(:,1) /= [88, 1]).or
.any (a(:,2) /= [88, 3])) call abort()
54 subroutine pure_sub(x
, y
)
55 integer, intent(in
) :: x(:,:)
56 integer, intent(OUT
) :: y(size (x
, 2), size (x
, 1))
58 end subroutine pure_sub
61 ! The check below for temporaries gave 14 and 33 for "parm" and "atmp".
63 ! { dg-final { scan-tree-dump-times "parm" 66 "original" } }
64 ! { dg-final { scan-tree-dump-times "atmp" 12 "original" } }
65 ! { dg-final { cleanup-tree-dump "original" } }
66 ! { dg-final { cleanup-modules "mod" } }