Skip to content

Commit

Permalink
Merge branch 'trytosort' into develop
Browse files Browse the repository at this point in the history
  • Loading branch information
jedwards4b committed Dec 18, 2018
2 parents 205567f + 2196994 commit 56dcee4
Show file tree
Hide file tree
Showing 2 changed files with 99 additions and 6 deletions.
2 changes: 1 addition & 1 deletion ctest/CTestEnvironment-nwscla.cmake
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@
# set with existing environment variables: NETCDF, PNETCDF, HDF5, etc.

# Define the extra CMake configure options
set (CTEST_CONFIGURE_OPTIONS "-DCMAKE_VERBOSE_MAKEFILE=TRUE -DPIO_ENABLE_ASYNC=TRUE")
set (CTEST_CONFIGURE_OPTIONS "-DCMAKE_VERBOSE_MAKEFILE=TRUE ")

# If MPISERIAL environment variable is set, then enable MPISERIAL
if (DEFINED ENV{MPISERIAL})
Expand Down
103 changes: 98 additions & 5 deletions tests/general/pio_decomp_tests_1d.F90.in
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,7 @@ END SUBROUTINE

! Test block cyclic interface
! Write with one decomp and read with another
! Test all combs
! Test all combs
! - no rearrage read + no rearrange write
! - rearrage read + no rearrange write
! - no rearrage read + rearrange write
Expand Down Expand Up @@ -185,7 +185,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN nc_wr_rd_1d_bc
filename = "test_pio_decomp_simple_tests.testfile"
do i=1,num_iotypes
PIO_TF_LOG(0,*) "Testing : PIO_TF_DATA_TYPE : ", iotype_descs(i)
ierr = PIO_createfile(pio_tf_iosystem_, pio_file, iotypes(i), filename, PIO_CLOBBER)
ierr = PIO_createfile(pio_tf_iosystem_, pio_file, iotypes(i), filename, PIO_CLOBBER)
PIO_TF_CHECK_ERR(ierr, "Could not create file " // trim(filename))

ierr = PIO_def_dim(pio_file, 'PIO_TF_test_dim', dims(1), pio_dim)
Expand All @@ -210,7 +210,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN nc_wr_rd_1d_bc
PIO_TF_CHECK_VAL((rbuf, exp_val), "Got wrong val")

call PIO_closefile(pio_file)

call PIO_deletefile(pio_tf_iosystem_, filename);
end do

Expand Down Expand Up @@ -266,7 +266,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN nc_wr_1d_bc_with_holes
filename = "test_pio_decomp_simple_tests.testfile"
do i=1,num_iotypes
PIO_TF_LOG(0,*) "Testing : PIO_TF_DATA_TYPE : ", iotype_descs(i)
ierr = PIO_createfile(pio_tf_iosystem_, pio_file, iotypes(i), filename, PIO_CLOBBER)
ierr = PIO_createfile(pio_tf_iosystem_, pio_file, iotypes(i), filename, PIO_CLOBBER)
PIO_TF_CHECK_ERR(ierr, "Could not create file " // trim(filename))

ierr = PIO_def_dim(pio_file, 'PIO_TF_test_dim', dims(1), pio_dim)
Expand All @@ -290,7 +290,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN nc_wr_1d_bc_with_holes
PIO_TF_CHECK_VAL((rbuf, exp_val), "Got wrong val")

call PIO_closefile(pio_file)

call PIO_deletefile(pio_tf_iosystem_, filename);
end do

Expand All @@ -304,3 +304,96 @@ PIO_TF_AUTO_TEST_SUB_BEGIN nc_wr_1d_bc_with_holes
deallocate(rbuf)
deallocate(wbuf)
PIO_TF_AUTO_TEST_SUB_END nc_wr_1d_bc_with_holes

PIO_TF_TEMPLATE<PIO_TF_PREDEF_TYPENAME PIO_TF_DATA_TYPE, PIO_TF_PREDEF_TYPENAME PIO_TF_FC_DATA_TYPE>
PIO_TF_AUTO_TEST_SUB_BEGIN nc_wr_1d_bc_random
use mpi, only : MPI_INT, MPI_SCATTER
implicit none
type(var_desc_t) :: pio_var
type(file_desc_t) :: pio_file
character(len=PIO_TF_MAX_STR_LEN) :: filename
type(io_desc_t) :: wr_iodesc
integer, dimension(:), allocatable :: compdof, gcompdof
integer, dimension(1) :: count
PIO_TF_FC_DATA_TYPE, dimension(:), allocatable :: rbuf, wbuf
integer, dimension(1) :: dims
integer :: pio_dim
integer :: i, j, ierr, lsz
integer :: tmp
real :: u
! iotypes = valid io types
integer, dimension(:), allocatable :: iotypes
character(len=PIO_TF_MAX_STR_LEN), dimension(:), allocatable :: iotype_descs
integer :: num_iotypes

! Set the decomposition for writing data - random order same local size
count(1) = 4
dims(1) = count(1)*pio_tf_world_sz_
if(pio_tf_world_rank_ == 0) then
allocate(gcompdof(dims(1)))
gcompdof = 0
do i=1,dims(1)
gcompdof(i) = i
enddo
do i=dims(1),1,-1
call random_number(u)
j = CEILING(real(i)*u)
tmp = gcompdof(j)
gcompdof(j) = gcompdof(i)
gcompdof(i) = tmp
enddo
endif
allocate(compdof(count(1)))
call mpi_scatter(gcompdof, count(1), MPI_INT, compdof, 4, MPI_INT, 0, pio_tf_comm_, ierr)
if(allocated(gcompdof)) deallocate(gcompdof)
allocate(rbuf(count(1)))
allocate(wbuf(count(1)))
do i=1,count(1)
wbuf(i) = compdof(i)
end do

call PIO_initdecomp(pio_tf_iosystem_, PIO_TF_DATA_TYPE, dims, compdof, wr_iodesc)
deallocate(compdof)

num_iotypes = 0
call PIO_TF_Get_nc_iotypes(iotypes, iotype_descs, num_iotypes)
filename = "test_pio_decomp_simple_tests.testfile"
do i=1,num_iotypes
PIO_TF_LOG(0,*) "Testing : PIO_TF_DATA_TYPE : ", iotype_descs(i)
ierr = PIO_createfile(pio_tf_iosystem_, pio_file, iotypes(i), filename, PIO_CLOBBER)
PIO_TF_CHECK_ERR(ierr, "Could not create file " // trim(filename))

ierr = PIO_def_dim(pio_file, 'PIO_TF_test_dim', dims(1), pio_dim)
PIO_TF_CHECK_ERR(ierr, "Failed to define a dim : " // trim(filename))

ierr = PIO_def_var(pio_file, 'PIO_TF_test_var', PIO_TF_DATA_TYPE, (/pio_dim/), pio_var)
PIO_TF_CHECK_ERR(ierr, "Failed to define a var : " // trim(filename))

ierr = PIO_enddef(pio_file)
PIO_TF_CHECK_ERR(ierr, "Failed to end redef mode : " // trim(filename))

! Write the variable out
call PIO_write_darray(pio_file, pio_var, wr_iodesc, wbuf, ierr)
PIO_TF_CHECK_ERR(ierr, "Failed to write darray : " // trim(filename))

call PIO_syncfile(pio_file)

call PIO_read_darray(pio_file, pio_var, wr_iodesc, rbuf, ierr)
PIO_TF_CHECK_ERR(ierr, "Failed to read darray : " // trim(filename))

PIO_TF_CHECK_VAL((rbuf, wbuf), "Got wrong val")

call PIO_closefile(pio_file)

call PIO_deletefile(pio_tf_iosystem_, filename);
end do

if(allocated(iotypes)) then
deallocate(iotypes)
deallocate(iotype_descs)
end if

call PIO_freedecomp(pio_tf_iosystem_, wr_iodesc)
deallocate(rbuf)
deallocate(wbuf)
PIO_TF_AUTO_TEST_SUB_END nc_wr_1d_bc_random

0 comments on commit 56dcee4

Please sign in to comment.