Skip to content

Commit

Permalink
new test for get_device_data with non-contig. data
Browse files Browse the repository at this point in the history
  • Loading branch information
wertysas committed Dec 11, 2024
1 parent 3bcbaa6 commit a8353a3
Show file tree
Hide file tree
Showing 2 changed files with 47 additions and 0 deletions.
1 change: 1 addition & 0 deletions tests/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -80,6 +80,7 @@ list(APPEND TEST_FILES
test_field_array.F90
test_field_delete_on_null.F90
test_get_device_data_wronly.F90
test_get_device_data_non_contiguous.F90
test_host_mem_pool.F90
test_lastdim.F90
test_legacy.F90
Expand Down
46 changes: 46 additions & 0 deletions tests/test_get_device_data_non_contiguous.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,46 @@
! (C) Copyright 2022- ECMWF.
! (C) Copyright 2022- Meteo-France.
!
! This software is licensed under the terms of the Apache Licence Version 2.0
! which can be obtained at http://www.apache.org/licenses/LICENSE-2.0.
! In applying this licence, ECMWF does not waive the privileges and immunities
! granted to it by virtue of its status as an intergovernmental organisation
! nor does it submit to any jurisdiction.

PROGRAM TEST_GET_DEVICE_DATA_NON_CONTIGUOUS
USE FIELD_MODULE
USE FIELD_FACTORY_MODULE
USE PARKIND1
USE FIELD_ABORT_MODULE
IMPLICIT NONE
CLASS(FIELD_2RB), POINTER :: W => NULL()
REAL(KIND=JPRB), ALLOCATABLE :: D(:,:,:)
REAL(KIND=JPRB), POINTER :: PTR_CPU(:,:)
REAL(KIND=JPRB), POINTER :: PTR_GPU(:,:)
LOGICAL :: OKAY
INTEGER :: I,J

ALLOCATE(D(-4:3, 1:5, -4:3))
D= 11
CALL FIELD_NEW(W, DATA=D(:,2,:), LBOUNDS=[-4,-4])
CALL W%GET_HOST_DATA_RDWR(PTR_CPU)
PTR_CPU=42

CALL W%GET_DEVICE_DATA_RDWR(PTR_GPU)
OKAY=.TRUE.
!$ACC SERIAL PRESENT (PTR_GPU) COPY(OKAY)
DO I=-4,3
DO J=-4,3
IF(PTR_GPU(I,J) /= 42) THEN
OKAY = .FALSE.
END IF
END DO
END DO
!$ACC END SERIAL

IF (.NOT. OKAY) THEN
CALL FIELD_ABORT ("PTR_GPU differ from 42")
END IF
CALL FIELD_DELETE(W)
END PROGRAM TEST_GET_DEVICE_DATA_NON_CONTIGUOUS

0 comments on commit a8353a3

Please sign in to comment.