PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / gomp / workshare3.f90
bloba10c48277db114c01ced717d81f3104fc27c0b24
1 ! { dg-do compile }
2 ! { dg-options "-ffrontend-optimize -fdump-tree-original -fopenmp" }
3 ! Test that common function elimination is done within the OMP parallel
4 ! blocks even if there is a workshare around it.
5 program foo
6 implicit none
7 integer, parameter :: n = 10000000
8 real, parameter :: eps = 3e-7
9 integer :: i,j
10 real :: A(n), B(5), C(n)
11 real :: tmp
12 B(1) = 3.344
13 tmp = B(1)
14 do i=1,10
15 call random_number(a)
16 c = a
17 !$omp parallel workshare
18 !$omp parallel default(shared)
19 !$omp do
20 do j=1,n
21 A(j) = A(j)*cos(B(1))+A(j)*cos(B(1))
22 end do
23 !$omp end do
24 !$omp end parallel
25 !$omp end parallel workshare
26 end do
28 c = c*cos(b(1))+ c*cos(b(1))
30 do j=1,n
31 if (abs(a(j)-c(j)) > eps) then
32 print *,1,j,a(j), c(j)
33 STOP 1
34 end if
35 end do
37 end program foo
38 ! { dg-final { scan-tree-dump-times "__builtin_cosf" 2 "original" } }