Parallelization of where constructs

TL;DR: Is anyone aware of a compiler which provides an extension for automatic parallelization of where constructs in a similar way as for concurrencies?


The question was if replacing a (parallelizable) concurrency like the one below:

! adjust input for opposing winds
do concurrent (o = 1:om, p = 1:pm, i = istart:iend, ssin(o,p,i) < 0)
  ssin(o,p,i) = ssin(o,p,i) * fieldscale1
end do

with a where clause

associate(ssin_view => ssin(1:om,1:pm,istart:iend))
  where (ssin_view < 0)
    ssin_view = ssin_view * fieldscale1
  end where
end associate

would still be a parallelizable construct in a similar sense as a concurrency.

For comparison, the corresponding OpenMP parallel construct for the concurrency could look like this

!$omp parallel do collapse(3)
do i = istart, iend
  do p = 1, pm
    do o = 1, om
      if (ssin(o,p,i) < 0) &
        & ssin(o,p,i) = ssin(o,p,i) * fieldscale1
    end do
  end do
end do

To parallelize an equivalent array operation we usually have to use a worksharing construct like here

associate(ssin_view => ssin(1:om,1:pm,istart:iend))
  !$omp parallel workshare
  where (ssin_view < 0)
    ssin_view = ssin_view * fieldscale1
  end where
  !$omp end parallel workshare
end associate

If a where construct is parallelizable by some compiler extensions, the above wouldn’t be required or maybe even harmful.


This originates from a discussion on parallel concurrencies on the stdlib issue tracker and come to the question whether the where construct is parallelizable in the same way as a concurrencies (start of the thread).

2 Likes