aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/transpose_optimization_2.f90
blob: 54ef8417eb95303e4931d93541ebc241f2ce7fab (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
! { dg-do run }
! { dg-options "-fdump-tree-original " }
! Checks the fix for PR46896, in which the optimization that passes
! the argument of TRANSPOSE directly missed the possible aliasing
! through host association.
!
! Contributed by Jerry DeLisle  <jvdelisle@gcc.gnu.org>
!
module mod
  integer :: b(2,3) = reshape([1,2,3,4,5,6], [2,3])
contains
  subroutine msub(x)
    integer :: x(:,:)
    b(1,:) = 99
    b(2,:) = x(:,1)
    if (any (b(:,1) /= [99, 1]).or.any (b(:,2) /= [99, 3])) call abort()
  end subroutine msub
  subroutine pure_msub(x, y)
    integer, intent(in) :: x(:,:)
    integer, intent(OUT) :: y(size (x, 2), size (x, 1))
    y = transpose (x)
  end subroutine pure_msub
end

  use mod
  integer :: a(2,3) = reshape([1,2,3,4,5,6], [2,3])
  call impure
  call purity
contains
!
! pure_sub and pure_msub could be PURE, if so declared.  They do not
! need a temporary.
!
  subroutine purity
    integer :: c(2,3)
    call pure_sub(transpose(a), c)
    if (any (c .ne. a)) call abort
    call pure_msub(transpose(b), c)
    if (any (c .ne. b)) call abort
  end subroutine purity
!
! sub and msub both need temporaries to avoid aliasing.
!
  subroutine impure
    call sub(transpose(a))
  end subroutine impure

  subroutine sub(x)
    integer :: x(:,:)
    a(1,:) = 88
    a(2,:) = x(:,1)
    if (any (a(:,1) /= [88, 1]).or.any (a(:,2) /= [88, 3])) call abort()
  end subroutine sub
  subroutine pure_sub(x, y)
    integer, intent(in) :: x(:,:)
    integer, intent(OUT) :: y(size (x, 2), size (x, 1))
    y = transpose (x)
  end subroutine pure_sub
end
!
! The check below for temporaries gave 14 and 33 for "parm" and "atmp".
!
! { dg-final { scan-tree-dump-times "parm" 66 "original" } }
! { dg-final { scan-tree-dump-times "atmp" 12 "original" } }
! { dg-final { cleanup-tree-dump "original" } }