aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/forall_15.f90
blob: c875e033312c5eacd95efd26c4f0e6722ac19bd7 (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
! { dg-do run }
! { dg-options "-ffrontend-optimize -fdump-tree-original" }
! PR 50564 - this used to ICE with front end optimization.
! Original test case by Andrew Benson.
program test
  implicit none
  double precision, dimension(2) :: timeSteps, control
  integer                        :: iTime
  double precision               :: ratio
  double precision               :: a

  ratio = 0.7d0
  control(1) = ratio**(dble(1)-0.5d0)-ratio**(dble(1)-1.5d0)
  control(2) = ratio**(dble(2)-0.5d0)-ratio**(dble(2)-1.5d0)
  forall(iTime=1:2)
     timeSteps(iTime)=ratio**(dble(iTime)-0.5d0)-ratio**(dble(iTime)-1.5d0)
  end forall
  if (any(abs(timesteps - control) > 1d-10)) call abort

  ! Make sure we still do the front-end optimization after a forall
  a = cos(ratio)*cos(ratio) + sin(ratio)*sin(ratio)
  if (abs(a-1.d0) > 1d-10) call abort
end program test
! { dg-final { scan-tree-dump-times "__builtin_cos" 1 "original" } }
! { dg-final { scan-tree-dump-times "__builtin_sin" 1 "original" } }
! { dg-final { cleanup-tree-dump "original" } }