-
Notifications
You must be signed in to change notification settings - Fork 19
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Adding 3 new .F90 tests per issue #81 and fixing .c files
- Loading branch information
Showing
4 changed files
with
257 additions
and
14 deletions.
There are no files selected for viewing
79 changes: 79 additions & 0 deletions
79
...arget_teams_distribute_parallel_for/test_target_teams_distribute_parallel_for_devices.F90
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,79 @@ | ||
!===--- test_target_teams_distribute_parallel_for_devices.F90 ---------------===// | ||
! | ||
! OpenMP API Version 4.5 Nov 2015 | ||
! | ||
! Testing for multiple devices checking if it is possible to send work and data | ||
! to different devices with the device clause used with omp target teams distribute | ||
! parallel for | ||
! | ||
!===-------------------------------------------------------------------------===// | ||
|
||
#include "ompvv.F90" | ||
|
||
#define N 1024 | ||
|
||
PROGRAM test_target_teams_distribute_parallel_for_devices | ||
USE iso_fortran_env | ||
USE ompvv_lib | ||
USE omp_lib | ||
implicit none | ||
|
||
OMPVV_TEST_OFFLOADING | ||
|
||
OMPVV_TEST_VERBOSE(target_teams_distribute_parallel_for_devices() .ne. 0) | ||
|
||
OMPVV_REPORT_AND_RETURN() | ||
|
||
CONTAINS | ||
INTEGER FUNCTION target_teams_distribute_parallel_for_devices() | ||
INTEGER :: num_dev, errors, i, dev | ||
INTEGER, DIMENSION(N) :: a | ||
LOGICAL, DIMENSION(N) :: isHost | ||
CHARACTER(len=400) :: numDeviceMsg, hostOrDevMsg | ||
|
||
errors = 0 | ||
|
||
num_dev = omp_get_num_devices() | ||
OMPVV_WARNING_IF(num_dev .le. 1, "Testing devices clause without& | ||
& multiple devices") | ||
|
||
WRITE(numDeviceMsg, *) "Number of devices =", num_dev | ||
OMPVV_INFOMSG(numDeviceMsg) | ||
|
||
DO i = 1, N | ||
a(i) = 1 | ||
END DO | ||
|
||
DO dev = 1, num_dev | ||
!$omp target enter data map(to: a) device(dev) | ||
END DO | ||
|
||
DO dev = 1, num_dev | ||
!$omp target teams distribute parallel do device(dev) map(tofrom: isHost) | ||
DO i = 1, N | ||
IF ((omp_get_team_num() .eq. 0) .or. (omp_get_thread_num() .eq. 0)) THEN | ||
isHost(dev) = omp_is_initial_device() | ||
END IF | ||
a(i) = a(i) + dev | ||
END DO | ||
END DO | ||
|
||
DO dev = 1, num_dev | ||
!$omp target exit data map(from: a) device(dev) | ||
IF (isHost(dev) .eqv. .true.) THEN | ||
WRITE(hostOrDevMsg, *) "Device", dev, "ran on the host" | ||
END IF | ||
IF (isHost(dev) .eqv. .false.) THEN | ||
WRITE(hostOrDevMsg, *) "Device", dev, "ran on the device" | ||
END IF | ||
OMPVV_INFOMSG(hostOrDevMsg) | ||
DO i = 1, N | ||
OMPVV_TEST_AND_SET(errors, a(i) .ne. (1 + dev)) | ||
END DO | ||
END DO | ||
|
||
|
||
target_teams_distribute_parallel_for_devices = errors | ||
END FUNCTION target_teams_distribute_parallel_for_devices | ||
END PROGRAM test_target_teams_distribute_parallel_for_devices | ||
|
87 changes: 87 additions & 0 deletions
87
..._teams_distribute_parallel_for/test_target_teams_distribute_parallel_for_firstprivate.F90
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,87 @@ | ||
!===--- test_target_teams_distribute_parallel_for_firstprivate.F90 ----------===// | ||
! | ||
! OpenMP API Version 4.5 Nov 2015 | ||
! | ||
! This test check for a private variable within a pragma omp target teams | ||
! distribute parallel for that is initialized from the host through firstprivate | ||
! clause. We use a private variable within a for loop and asign it every iteration | ||
! hoping that we won't get into data races. We do this multiple times to improve | ||
! testing. | ||
! | ||
!===-------------------------------------------------------------------------===// | ||
|
||
#include "ompvv.F90" | ||
|
||
#define N 1024 | ||
|
||
PROGRAM test_target_teams_distribute_parallel_for_firstprivate | ||
USE iso_fortran_env | ||
USE ompvv_lib | ||
USE omp_lib | ||
implicit none | ||
|
||
OMPVV_TEST_VERBOSE(target_teams_distribute_parallel_for_firstprivate() .ne. 0) | ||
|
||
OMPVV_REPORT_AND_RETURN() | ||
|
||
CONTAINS | ||
INTEGER FUNCTION target_teams_distribute_parallel_for_firstprivate() | ||
INTEGER, DIMENSION(N) :: a, b, c, d, num_teams, num_threads, team_num | ||
INTEGER :: firstized, privatized, errors, i, j, warning_threads | ||
|
||
firstized = 10 | ||
errors = 0 | ||
privatized = 0 | ||
j = 0 | ||
DO i = 1, N | ||
a(i) = 1 | ||
b(i) = i | ||
c(i) = 2*i | ||
d(i) = 0 | ||
END DO | ||
|
||
!$omp target data map(to: a, b, c) | ||
!$omp target teams distribute parallel do& | ||
!$omp& firstprivate(privatized, firstized, i)& | ||
!$omp& num_threads(OMPVV_NUM_THREADS_DEVICE) num_teams(OMPVV_NUM_TEAMS_DEVICE) | ||
DO j = 1, N | ||
num_teams(j) = omp_get_num_teams() | ||
num_threads(j) = omp_get_num_threads() | ||
team_num = omp_get_team_num() | ||
privatized = 0 | ||
|
||
DO i = 1, (a(j) + b(j)) | ||
privatized = privatized + 1 | ||
END DO | ||
|
||
privatized = privatized + firstized | ||
d(j) = c(j) * privatized | ||
END DO | ||
!$omp end target data | ||
|
||
OMPVV_WARNING_IF(num_teams(0) .eq. 1, "Number of teams reported was 1, test cannot assert privatization across teams") | ||
warning_threads = 0 | ||
DO i = 1, N | ||
IF (num_threads(i) .eq. 1) THEN | ||
warning_threads = warning_threads + 1 | ||
END IF | ||
IF (i .gt. 1) THEN | ||
OMPVV_ERROR_IF(num_teams(i) .ne. num_teams(i-1), "& | ||
& Discrepancy in the reported number of teams across teams") | ||
IF ((team_num(i) .eq. team_num(i-1)) .and. (num_threads(i) .ne. num_threads(i-1))) THEN | ||
OMPVV_ERROR("Discrepancy in the reported number of threads inside a single team") | ||
END IF | ||
END IF | ||
END DO | ||
|
||
OMPVV_WARNING_IF(warning_threads .eq. N, "Number of threads was 1 for all teams. & | ||
&test cannot assert privatization across teams"); | ||
|
||
DO i = 1, N | ||
OMPVV_TEST_AND_SET(errors, d(i) .ne. (10 + 1+ i) * (2 * i)) | ||
END DO | ||
|
||
target_teams_distribute_parallel_for_firstprivate = errors | ||
END FUNCTION target_teams_distribute_parallel_for_firstprivate | ||
END PROGRAM test_target_teams_distribute_parallel_for_firstprivate | ||
|
77 changes: 77 additions & 0 deletions
77
...arget_teams_distribute_parallel_for/test_target_teams_distribute_parallel_for_private.F90
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,77 @@ | ||
!===--- test_target_teams_distribute_parallel_for_private.F90 ---------------===// | ||
! | ||
! OpenMP API Version 4.5 Nov 2015 | ||
! | ||
! This test check for a private variable within a pragma omp target teams | ||
! distribute parallel for. We use a private variable within a for loop and | ||
! assign it every iteration hoping that we won't get into data races. We do this | ||
! multiple times to improve testing. We assign a large number of threads and | ||
! teams to try to increase parallelism and contention on the privatized variable | ||
! | ||
!===-------------------------------------------------------------------------===// | ||
|
||
#include "ompvv.F90" | ||
|
||
#define N 1024 | ||
|
||
PROGRAM test_target_teams_distribute_parallel_for_private | ||
USE iso_fortran_env | ||
USE ompvv_lib | ||
USE omp_lib | ||
implicit none | ||
|
||
OMPVV_TEST_OFFLOADING | ||
|
||
OMPVV_TEST_VERBOSE(target_teams_distribute_parallel_for_private() .ne. 0) | ||
|
||
OMPVV_REPORT_AND_RETURN() | ||
|
||
CONTAINS | ||
INTEGER FUNCTION target_teams_distribute_parallel_for_private() | ||
INTEGER, DIMENSION(N) :: a, b, c, d, num_teams, num_threads | ||
INTEGER :: privatized, errors, i, j, warning_threads, warning_teams | ||
|
||
errors = 0 | ||
j = 0 | ||
|
||
DO i = 1, N | ||
a(i) = 1 | ||
b(i) = i | ||
c(i) = 2*i | ||
d(i) = 0 | ||
num_teams(i) = -1 | ||
num_threads(i) = -1 | ||
END DO | ||
|
||
!$omp target data map(to: a, b, c) map(from: d) | ||
!$omp target teams distribute parallel do private(privatized, i)& | ||
!$omp& num_threads(OMPVV_NUM_THREADS_DEVICE) num_teams(OMPVV_NUM_TEAMS_DEVICE) | ||
DO j = 1, N | ||
num_teams(j) = omp_get_num_teams() | ||
num_threads(j) = omp_get_num_threads() | ||
|
||
privatized = 0 | ||
|
||
DO i = 1, (a(j) + b(j)) | ||
privatized = privatized + 1 | ||
END DO | ||
|
||
d(j) = c(j) * privatized | ||
END DO | ||
!$omp end target data | ||
|
||
warning_threads = 0 | ||
warning_teams = 0 | ||
|
||
DO i = 1, N | ||
OMPVV_TEST_AND_SET(errors, d(i) .ne. ((1 + i) * 2 * i)) | ||
warning_teams = warning_teams + num_teams(i) | ||
warning_threads = warning_threads + num_threads(i) | ||
END DO | ||
|
||
OMPVV_WARNING_IF(warning_teams .eq. N, "There was a single team across the target region. Privatization cannot be tested at the teams level"); | ||
OMPVV_WARNING_IF(warning_threads .eq. N, "All the parallel regions ran with a single thread. Privatization cannot be tested at the thread level"); | ||
|
||
target_teams_distribute_parallel_for_private = errors | ||
END FUNCTION target_teams_distribute_parallel_for_private | ||
END PROGRAM test_target_teams_distribute_parallel_for_private |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters