1! { dg-do run }
2! { dg-options "-ffrontend-optimize -fdump-tree-original" }
3! PR 50564 - this used to ICE with front end optimization.
4! Original test case by Andrew Benson.
5program test
6  implicit none
7  double precision, dimension(2) :: timeSteps, control
8  integer                        :: iTime
9  double precision               :: ratio
10  double precision               :: a
11
12  ratio = 0.7d0
13  control(1) = ratio**(dble(1)-0.5d0)-ratio**(dble(1)-1.5d0)
14  control(2) = ratio**(dble(2)-0.5d0)-ratio**(dble(2)-1.5d0)
15  forall(iTime=1:2)
16     timeSteps(iTime)=ratio**(dble(iTime)-0.5d0)-ratio**(dble(iTime)-1.5d0)
17  end forall
18  if (any(abs(timesteps - control) > 1d-10)) call abort
19
20  ! Make sure we still do the front-end optimization after a forall
21  a = cos(ratio)*cos(ratio) + sin(ratio)*sin(ratio)
22  if (abs(a-1.d0) > 1d-10) call abort
23end program test
24! { dg-final { scan-tree-dump-times "__builtin_cos" 1 "original" } }
25! { dg-final { scan-tree-dump-times "__builtin_sin" 1 "original" } }
26