summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/gomp/pr39152.f90
blob: ff088b5ef99ec01ec79863e0657ee660a94c5b29 (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
! { dg-do compile { target { { i?86-*-* x86_64-*-* } && ilp32 } } }
! { dg-options "-march=i486 -fopenmp -mavx -O3 -funroll-all-loops" } 

  call test_workshare

contains
  subroutine test_workshare
    integer :: i, j, k, l, m
    double precision, dimension (64) :: d, e
    integer, dimension (10) :: f, g
    integer, dimension (16, 16) :: a, b, c
    integer, dimension (16) :: n
!$omp parallel num_threads (4) private (j, k)
!$omp barrier
!$omp workshare
    where (g .lt. 0)
      f = 100
    elsewhere
      where (g .gt. 6) f = f + sum (g)
      f = 300 + f
    end where
!$omp end workshare nowait
!$omp workshare
    forall (j = 1:16, k = 1:16) b (k, j) = a (j, k)
    forall (j = 2:16, n (17 - j) / 4 * 4 .ne. n (17 - j))
      n (j) = n (j - 1) * n (j)
    end forall
!$omp endworkshare
!$omp end parallel

  end subroutine test_workshare
end