1 ! Run the target region asynchronously and check it
3 ! Note that map(alloc: work(:, i)) + nowait should be safe
4 ! given that a nondescriptor array is used. However, it still
5 ! violates a map clause restriction, added in OpenMP 5.1 [354:10-13].
7 PROGRAM test_target_teams_distribute_nowait
8 USE ISO_Fortran_env
, only
: INT64
10 INTEGER, parameter :: N
= 1024, N_TASKS
= 16
11 INTEGER :: i
, j
, k
, my_ticket
12 INTEGER :: order(n_tasks
)
13 INTEGER(INT64
) :: work(n
, n_tasks
)
19 !$omp target enter data map(to: ticket, order)
21 !$omp parallel do num_threads(n_tasks)
23 !$omp target map(alloc: work(:, i), ticket) private(my_ticket) nowait
24 !!$omp target teams distribute map(alloc: work(:, i), ticket) private(my_ticket) nowait
28 ! DO k = 1, n*(n_tasks - i)
29 ! work(j, i) = work(j, i) + i*j*k
39 !$omp end target !teams distribute
43 !$omp target exit data map(from:ticket, order)
45 IF (ticket
.ne
. n_tasks
*n
) stop 1
46 if (maxval(order
) /= n_tasks
*n
) stop 2
47 ! order(i) == n*i if synchronous and between n and n*n_tasks if run concurrently
49 if (order(i
) < n
.or
. order(i
) > n
*n_tasks
) stop 3
53 if (order(i
) /= n
*i
) async
= .true
.
55 if (.not
. async
) stop 4 ! Did not run asynchronously