OSDN Git Service

2011-01-08 Paul Thomas <pault@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / transpose_optimization_2.f90
1 ! { dg-do run }
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.
6 !
7 ! Contributed by Jerry DeLisle  <jvdelisle@gcc.gnu.org>
8 !
9 module mod
10   integer :: b(2,3) = reshape([1,2,3,4,5,6], [2,3])
11 contains
12   subroutine msub(x)
13     integer :: x(:,:)
14     b(1,:) = 99
15     b(2,:) = x(:,1)
16     if (any (b(:,1) /= [99, 1]).or.any (b(:,2) /= [99, 3])) call abort()
17   end subroutine msub
18   subroutine pure_msub(x, y)
19     integer, intent(in) :: x(:,:)
20     integer, intent(OUT) :: y(size (x, 2), size (x, 1))
21     y = transpose (x)
22   end subroutine pure_msub
23 end
24
25   use mod
26   integer :: a(2,3) = reshape([1,2,3,4,5,6], [2,3])
27   call impure
28   call purity
29 contains
30 !
31 ! pure_sub and pure_msub could be PURE, if so declared.  They do not
32 ! need a temporary.
33 !
34   subroutine purity
35     integer :: c(2,3)
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
40   end subroutine purity
41 !
42 ! sub and msub both need temporaries to avoid aliasing.
43 !
44   subroutine impure
45     call sub(transpose(a))
46   end subroutine impure
47
48   subroutine sub(x)
49     integer :: x(:,:)
50     a(1,:) = 88
51     a(2,:) = x(:,1)
52     if (any (a(:,1) /= [88, 1]).or.any (a(:,2) /= [88, 3])) call abort()
53   end subroutine sub
54   subroutine pure_sub(x, y)
55     integer, intent(in) :: x(:,:)
56     integer, intent(OUT) :: y(size (x, 2), size (x, 1))
57     y = transpose (x)
58   end subroutine pure_sub
59 end
60 !
61 ! The check below for temporaries gave 14 and 33 for "parm" and "atmp".
62 !
63 ! { dg-final { scan-tree-dump-times "parm" 66 "original" } }
64 ! { dg-final { scan-tree-dump-times "atmp" 12 "original" } }
65 ! { dg-final { cleanup-modules "mod" } }