aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/array_constructor_40.f90
blob: 424f6f4fe75684ffb4d28618a6a33e75c782994c (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
! { dg-do run }
! { dg-options "-ffrontend-optimize -fdump-tree-original" }
! PR 55806 - replace ANY intrinsic for array
! constructor with .or.

module mymod
  implicit none
contains
  subroutine bar(a,b,c, lo)
    real, dimension(3,3), intent(in) :: a,b
    logical, dimension(3,3), intent(in) :: lo
    integer, intent(out) :: c
    real, parameter :: acc = 1e-4
    integer :: i,j
    
    c = 0
    do i=1,3
       if (any([abs(a(i,1) - b(i,1)) > acc,  &
            (j==i+1,j=3,8)])) cycle
       if (any([abs(a(i,2) - b(i,2)) > acc, &
            abs(a(i,3) - b(i,3)) > acc, lo(i,:)])) cycle
       c = c + i
    end do
  end subroutine bar

  subroutine baz(a, b, c)
    real, dimension(3,3), intent(in) :: a,b
    real, intent(out) :: c
    c = sum([a(1,1),a(2,2),a(3,3),b(:,1)])
  end subroutine baz
end module mymod

program main
  use mymod
  implicit none
  real, dimension(3,3) :: a,b
  real :: res
  integer :: c
  logical lo(3,3)
  data a/1.1, 1.2, 1.3, 1.4, 1.5, 1.6, 1.7, 1.8, 1.9/

  b = a
  b(2,2) = a(2,2) + 0.2
  lo = .false.
  lo(3,3) = .true.
  call bar(a,b,c,lo)
  if (c /= 1) call abort
  call baz(a,b,res);
  if (abs(res - 8.1) > 1e-5) call abort
end program main
! { dg-final { scan-tree-dump-times "while" 5 "original" } }
! { dg-final { cleanup-tree-dump "original" } }