f90tst_parallel3.f90 (netcdf-fortran-4.4.4) | : | f90tst_parallel3.f90 (netcdf-fortran-4.4.5) | ||
---|---|---|---|---|
skipping to change at line 25 | skipping to change at line 25 | |||
! int int(x, y) ; | ! int int(x, y) ; | |||
! float float(x, y) ; | ! float float(x, y) ; | |||
! double double(x, y) ; | ! double double(x, y) ; | |||
! ubyte ubyte(x, y) ; | ! ubyte ubyte(x, y) ; | |||
! ushort ushort(x, y) ; | ! ushort ushort(x, y) ; | |||
! uint uint(x, y) ; | ! uint uint(x, y) ; | |||
! $Id: f90tst_parallel3.f90,v 1.5 2010/05/25 13:53:04 ed Exp $ | ! $Id: f90tst_parallel3.f90,v 1.5 2010/05/25 13:53:04 ed Exp $ | |||
program f90tst_parallel3 | program f90tst_parallel3 | |||
use netcdf | ||||
implicit none | ||||
include 'mpif.h' | ||||
integer :: mode_flag | ||||
integer :: p, my_rank, ierr | ||||
call MPI_Init(ierr) | ||||
call MPI_Comm_rank(MPI_COMM_WORLD, my_rank, ierr) | ||||
call MPI_Comm_size(MPI_COMM_WORLD, p, ierr) | ||||
if (my_rank .eq. 0) then | ||||
print *, ' ' | ||||
print *, '*** Testing netCDF-4 parallel I/O with fill values.' | ||||
endif | ||||
! There must be 4 procs for this test. | ||||
if (p .ne. 4) then | ||||
print *, 'Sorry, this test program must be run on four processors.' | ||||
stop 1 | ||||
endif | ||||
#ifdef NF_HAS_PNETCDF | ||||
mode_flag = IOR(nf90_clobber, nf90_mpiio) | ||||
#ifdef ENABLE_CDF5 | ||||
mode_flag = IOR(mode_flag, nf90_64bit_data) | ||||
#else | ||||
mode_flag = IOR(mode_flag, nf90_64bit_offset) | ||||
#endif | ||||
call parallel_io(mode_flag) | ||||
#endif | ||||
#ifdef NF_HAS_PARALLEL4 | ||||
mode_flag = IOR(nf90_netcdf4, nf90_mpiposix) | ||||
mode_flag = IOR(mode_flag, nf90_clobber) | ||||
call parallel_io(mode_flag) | ||||
#endif | ||||
call MPI_Finalize(ierr) | ||||
if (my_rank .eq. 0) print *,'*** SUCCESS!' | ||||
contains | ||||
! This subroutine handles errors by printing an error message and | ||||
! exiting with a non-zero status. | ||||
subroutine check(errcode) | ||||
use netcdf | ||||
implicit none | ||||
integer, intent(in) :: errcode | ||||
if(errcode /= nf90_noerr) then | ||||
print *, 'Error: ', trim(nf90_strerror(errcode)) | ||||
stop 99 | ||||
endif | ||||
end subroutine check | ||||
subroutine parallel_io(mode_flag) | ||||
use typeSizes | use typeSizes | |||
use netcdf | use netcdf | |||
implicit none | implicit none | |||
include 'mpif.h' | include 'mpif.h' | |||
integer :: mode_flag | ||||
! This is the name of the data file we will create. | ! This is the name of the data file we will create. | |||
character (len = *), parameter :: FILE_NAME = "f90tst_parallel3.nc" | character (len = *), parameter :: FILE_NAME = "f90tst_parallel3.nc" | |||
integer, parameter :: MAX_DIMS = 2 | integer, parameter :: MAX_DIMS = 2 | |||
integer, parameter :: NX = 16, NY = 16 | integer, parameter :: NX = 16, NY = 16 | |||
integer, parameter :: HALF_NX = NX/2, HALF_NY = NY/2 | integer, parameter :: HALF_NX = NX/2, HALF_NY = NY/2 | |||
integer, parameter :: NUM_PROC = 4 | integer, parameter :: NUM_PROC = 4 | |||
integer, parameter :: NUM_VARS = 8 | ||||
integer, parameter :: CACHE_SIZE = 4194304, CACHE_NELEMS = 1013 | integer, parameter :: CACHE_SIZE = 4194304, CACHE_NELEMS = 1013 | |||
integer, parameter :: CACHE_PREEMPTION = 79 | integer, parameter :: CACHE_PREEMPTION = 79 | |||
#if defined(NF_HAS_PARALLEL4) || defined(ENABLE_CDF5) | ||||
integer, parameter :: NUM_VARS = 8 | ||||
character (len = *), parameter :: var_name(NUM_VARS) = & | character (len = *), parameter :: var_name(NUM_VARS) = & | |||
(/ 'byte__', 'short_', 'int___', 'float_', 'double', 'ubyte_', 'ushort', 'uint__' /) | (/ 'byte__', 'short_', 'int___', 'float_', 'double', 'ubyte_', 'ushort', 'uint__' /) | |||
integer :: ncid, varid(NUM_VARS), dimids(MAX_DIMS) | ||||
integer :: var_type(NUM_VARS) = (/ nf90_byte, nf90_short, nf90_int, & | integer :: var_type(NUM_VARS) = (/ nf90_byte, nf90_short, nf90_int, & | |||
nf90_float, nf90_double, nf90_ubyte, nf90_ushort, nf90_uint /) | nf90_float, nf90_double, nf90_ubyte, nf90_ushort, nf90_uint /) | |||
#else | ||||
integer, parameter :: NUM_VARS = 5 | ||||
character (len = *), parameter :: var_name(NUM_VARS) = & | ||||
(/ 'byte__', 'short_', 'int___', 'float_', 'double' /) | ||||
integer :: var_type(NUM_VARS) = (/ nf90_byte, nf90_short, nf90_int, & | ||||
nf90_float, nf90_double /) | ||||
#endif | ||||
integer :: ncid, varid(NUM_VARS), dimids(MAX_DIMS) | ||||
integer :: x_dimid, y_dimid | integer :: x_dimid, y_dimid | |||
integer :: byte_out(HALF_NY, HALF_NX), byte_in(HALF_NY, HALF_NX) | integer :: byte_out(HALF_NY, HALF_NX), byte_in(HALF_NY, HALF_NX) | |||
integer :: short_out(HALF_NY, HALF_NX), short_in(HALF_NY, HALF_NX) | integer :: short_out(HALF_NY, HALF_NX), short_in(HALF_NY, HALF_NX) | |||
integer :: int_out(HALF_NY, HALF_NX), int_in(HALF_NY, HALF_NX) | integer :: int_out(HALF_NY, HALF_NX), int_in(HALF_NY, HALF_NX) | |||
real :: areal_out(HALF_NY, HALF_NX), areal_in(HALF_NY, HALF_NX) | real :: areal_out(HALF_NY, HALF_NX), areal_in(HALF_NY, HALF_NX) | |||
real :: double_out(HALF_NY, HALF_NX), double_in(HALF_NY, HALF_NX) | real :: double_out(HALF_NY, HALF_NX), double_in(HALF_NY, HALF_NX) | |||
#if defined(NF_HAS_PARALLEL4) || defined(ENABLE_CDF5) | ||||
integer :: ubyte_out(HALF_NY, HALF_NX), ubyte_in(HALF_NY, HALF_NX) | integer :: ubyte_out(HALF_NY, HALF_NX), ubyte_in(HALF_NY, HALF_NX) | |||
integer :: ushort_out(HALF_NY, HALF_NX), ushort_in(HALF_NY, HALF_NX) | integer :: ushort_out(HALF_NY, HALF_NX), ushort_in(HALF_NY, HALF_NX) | |||
integer (kind = EightByteInt) :: uint_out(HALF_NY, HALF_NX), uint_in(HALF_NY, HALF_NX) | integer (kind = EightByteInt) :: uint_out(HALF_NY, HALF_NX), uint_in(HALF_NY, HALF_NX) | |||
#endif | ||||
integer :: nvars, ngatts, ndims, unlimdimid, file_format | integer :: nvars, ngatts, ndims, unlimdimid, file_format | |||
integer :: x, y, v | integer :: x, y, v | |||
integer :: p, my_rank, ierr | integer :: my_rank, ierr, old_mode | |||
integer :: start(MAX_DIMS), count(MAX_DIMS) | integer :: start(MAX_DIMS), count(MAX_DIMS) | |||
integer :: ret | integer :: ret | |||
call MPI_Init(ierr) | ||||
call MPI_Comm_rank(MPI_COMM_WORLD, my_rank, ierr) | call MPI_Comm_rank(MPI_COMM_WORLD, my_rank, ierr) | |||
call MPI_Comm_size(MPI_COMM_WORLD, p, ierr) | ||||
if (my_rank .eq. 0) then | ||||
print *, ' ' | ||||
print *, '*** Testing netCDF-4 parallel I/O with fill values.' | ||||
endif | ||||
! There must be 4 procs for this test. | ||||
if (p .ne. 4) then | ||||
print *, 'Sorry, this test program must be run on four processors.' | ||||
stop 1 | ||||
endif | ||||
! Create some pretend data. | ! Create some pretend data. | |||
do x = 1, HALF_NX | do x = 1, HALF_NX | |||
do y = 1, HALF_NY | do y = 1, HALF_NY | |||
byte_out(y, x) = my_rank * (-1) | byte_out(y, x) = my_rank * (-1) | |||
short_out(y, x) = my_rank * (-2) | short_out(y, x) = my_rank * (-2) | |||
int_out(y, x) = my_rank * (-4) | int_out(y, x) = my_rank * (-4) | |||
areal_out(y, x) = my_rank * 2.5 | areal_out(y, x) = my_rank * 2.5 | |||
double_out(y, x) = my_rank * (-4.5) | double_out(y, x) = my_rank * (-4.5) | |||
#if defined(NF_HAS_PARALLEL4) || defined(ENABLE_CDF5) | ||||
ubyte_out(y, x) = my_rank | ubyte_out(y, x) = my_rank | |||
ushort_out(y, x) = my_rank * 2 | ushort_out(y, x) = my_rank * 2 | |||
uint_out(y, x) = my_rank * 4 | uint_out(y, x) = my_rank * 4 | |||
#endif | ||||
end do | end do | |||
end do | end do | |||
! THis should fail, because I have not set either mpiposix or mpiio. | ! THis should fail, because I have not set either mpiposix or mpiio. | |||
ret = nf90_create(FILE_NAME, nf90_netcdf4, ncid, & | ret = nf90_create(FILE_NAME, nf90_netcdf4, ncid, & | |||
comm = MPI_COMM_WORLD, info = MPI_INFO_NULL, cache_size = CACHE_SIZE, & | comm = MPI_COMM_WORLD, info = MPI_INFO_NULL, cache_size = CACHE_SIZE, & | |||
cache_nelems = CACHE_NELEMS, cache_preemption = CACHE_PREEMPTION) | cache_nelems = CACHE_NELEMS, cache_preemption = CACHE_PREEMPTION) | |||
if (ret /= nf90_einval) stop 8 | if (ret /= nf90_einval) stop 8 | |||
! Create the netCDF file. | ! Create the netCDF file. | |||
call check(nf90_create(FILE_NAME, IOR(nf90_netcdf4, nf90_mpiposix), ncid, & | call check(nf90_create(FILE_NAME, mode_flag, ncid, & | |||
comm = MPI_COMM_WORLD, info = MPI_INFO_NULL, cache_size = CACHE_SIZE, & | comm = MPI_COMM_WORLD, info = MPI_INFO_NULL, cache_size = CACHE_SIZE, & | |||
cache_nelems = CACHE_NELEMS, cache_preemption = CACHE_PREEMPTION)) | cache_nelems = CACHE_NELEMS, cache_preemption = CACHE_PREEMPTION)) | |||
! Define the dimensions. | ! Define the dimensions. | |||
call check(nf90_def_dim(ncid, "x", NX, x_dimid)) | call check(nf90_def_dim(ncid, "x", NX, x_dimid)) | |||
call check(nf90_def_dim(ncid, "y", NY, y_dimid)) | call check(nf90_def_dim(ncid, "y", NY, y_dimid)) | |||
dimids = (/ y_dimid, x_dimid /) | dimids = (/ y_dimid, x_dimid /) | |||
! Define the variables. | ! Define the variables. | |||
do v = 1, NUM_VARS | do v = 1, NUM_VARS | |||
call check(nf90_def_var(ncid, var_name(v), var_type(v), dimids, varid(v))) | call check(nf90_def_var(ncid, var_name(v), var_type(v), dimids, varid(v))) | |||
end do | end do | |||
! enable fill mode | ||||
call check(nf90_set_fill(ncid, NF90_FILL, old_mode)) | ||||
! This will be the last collective operation. | ! This will be the last collective operation. | |||
call check(nf90_enddef(ncid)) | call check(nf90_enddef(ncid)) | |||
! Determine what part of the variable will be written/read for this | ! Determine what part of the variable will be written/read for this | |||
! processor. It's a checkerboard decomposition. | ! processor. It's a checkerboard decomposition. | |||
count = (/ HALF_NX, HALF_NY /) | count = (/ HALF_NX, HALF_NY /) | |||
if (my_rank .eq. 0) then | if (my_rank .eq. 0) then | |||
start = (/ 1, 1 /) | start = (/ 1, 1 /) | |||
else if (my_rank .eq. 1) then | else if (my_rank .eq. 1) then | |||
start = (/ HALF_NX + 1, 1 /) | start = (/ HALF_NX + 1, 1 /) | |||
skipping to change at line 132 | skipping to change at line 193 | |||
start = (/ HALF_NX + 1, HALF_NY + 1 /) | start = (/ HALF_NX + 1, HALF_NY + 1 /) | |||
endif | endif | |||
! Write this processor's data, except for processor zero. | ! Write this processor's data, except for processor zero. | |||
if (my_rank .ne. 0) then | if (my_rank .ne. 0) then | |||
call check(nf90_put_var(ncid, varid(1), byte_out, start = start, count = co unt)) | call check(nf90_put_var(ncid, varid(1), byte_out, start = start, count = co unt)) | |||
call check(nf90_put_var(ncid, varid(2), short_out, start = start, count = c ount)) | call check(nf90_put_var(ncid, varid(2), short_out, start = start, count = c ount)) | |||
call check(nf90_put_var(ncid, varid(3), int_out, start = start, count = cou nt)) | call check(nf90_put_var(ncid, varid(3), int_out, start = start, count = cou nt)) | |||
call check(nf90_put_var(ncid, varid(4), areal_out, start = start, count = c ount)) | call check(nf90_put_var(ncid, varid(4), areal_out, start = start, count = c ount)) | |||
call check(nf90_put_var(ncid, varid(5), double_out, start = start, count = count)) | call check(nf90_put_var(ncid, varid(5), double_out, start = start, count = count)) | |||
#if defined(NF_HAS_PARALLEL4) || defined(ENABLE_CDF5) | ||||
call check(nf90_put_var(ncid, varid(6), ubyte_out, start = start, count = c ount)) | call check(nf90_put_var(ncid, varid(6), ubyte_out, start = start, count = c ount)) | |||
call check(nf90_put_var(ncid, varid(7), ushort_out, start = start, count = count)) | call check(nf90_put_var(ncid, varid(7), ushort_out, start = start, count = count)) | |||
call check(nf90_put_var(ncid, varid(8), uint_out, start = start, count = co unt)) | call check(nf90_put_var(ncid, varid(8), uint_out, start = start, count = co unt)) | |||
#endif | ||||
endif | endif | |||
! Close the file. | ! Close the file. | |||
call check(nf90_close(ncid)) | call check(nf90_close(ncid)) | |||
! Reopen the file. | ! Reopen the file. | |||
call check(nf90_open(FILE_NAME, IOR(nf90_nowrite, nf90_mpiio), ncid, & | call check(nf90_open(FILE_NAME, IOR(nf90_nowrite, nf90_mpiio), ncid, & | |||
comm = MPI_COMM_WORLD, info = MPI_INFO_NULL)) | comm = MPI_COMM_WORLD, info = MPI_INFO_NULL)) | |||
! Check some stuff out. | ! Check some stuff out. | |||
call check(nf90_inquire(ncid, ndims, nvars, ngatts, unlimdimid, file_format)) | call check(nf90_inquire(ncid, ndims, nvars, ngatts, unlimdimid, file_format)) | |||
if (ndims /= 2 .or. nvars /= NUM_VARS .or. ngatts /= 0 .or. unlimdimid /= -1 . | if (ndims /= 2 .or. nvars /= NUM_VARS .or. ngatts /= 0 .or. unlimdimid /= -1) | |||
or. & | stop 2 | |||
file_format /= nf90_format_netcdf4) stop 2 | ||||
if (IAND(mode_flag, nf90_netcdf4) .GT. 0) then | ||||
if (file_format /= nf90_format_netcdf4) stop 3 | ||||
else | ||||
#ifdef ENABLE_CDF5 | ||||
if (file_format /= nf90_format_cdf5) stop 4 | ||||
#else | ||||
if (file_format /= nf90_format_64bit_offset) stop 4 | ||||
#endif | ||||
endif | ||||
! Read this processor's data. | ! Read this processor's data. | |||
call check(nf90_get_var(ncid, varid(1), byte_in, start = start, count = count) ) | call check(nf90_get_var(ncid, varid(1), byte_in, start = start, count = count) ) | |||
call check(nf90_get_var(ncid, varid(2), short_in, start = start, count = count )) | call check(nf90_get_var(ncid, varid(2), short_in, start = start, count = count )) | |||
call check(nf90_get_var(ncid, varid(3), int_in, start = start, count = count)) | call check(nf90_get_var(ncid, varid(3), int_in, start = start, count = count)) | |||
call check(nf90_get_var(ncid, varid(4), areal_in, start = start, count = count )) | call check(nf90_get_var(ncid, varid(4), areal_in, start = start, count = count )) | |||
call check(nf90_get_var(ncid, varid(5), double_in, start = start, count = coun t)) | call check(nf90_get_var(ncid, varid(5), double_in, start = start, count = coun t)) | |||
#if defined(NF_HAS_PARALLEL4) || defined(ENABLE_CDF5) | ||||
call check(nf90_get_var(ncid, varid(6), ubyte_in, start = start, count = count )) | call check(nf90_get_var(ncid, varid(6), ubyte_in, start = start, count = count )) | |||
call check(nf90_get_var(ncid, varid(7), ushort_in, start = start, count = coun t)) | call check(nf90_get_var(ncid, varid(7), ushort_in, start = start, count = coun t)) | |||
call check(nf90_get_var(ncid, varid(8), uint_in, start = start, count = count) ) | call check(nf90_get_var(ncid, varid(8), uint_in, start = start, count = count) ) | |||
#endif | ||||
! Check the data. All the data from the processor zero are fill | ! Check the data. All the data from the processor zero are fill | |||
! value. | ! value. | |||
do x = 1, HALF_NX | do x = 1, HALF_NX | |||
do y = 1, HALF_NY | do y = 1, HALF_NY | |||
if (my_rank .eq. 0) then | if (my_rank .eq. 0) then | |||
if (byte_in(y, x) .ne. nf90_fill_byte) stop 3 | if (byte_in(y, x) .ne. nf90_fill_byte) stop 5 | |||
if (short_in(y, x) .ne. nf90_fill_short) stop 4 | if (short_in(y, x) .ne. nf90_fill_short) stop 6 | |||
if (int_in(y, x) .ne. nf90_fill_int) stop 5 | if (int_in(y, x) .ne. nf90_fill_int) stop 7 | |||
if (areal_in(y, x) .ne. nf90_fill_real) stop 6 | if (areal_in(y, x) .ne. nf90_fill_real) stop 8 | |||
if (double_in(y, x) .ne. nf90_fill_double) stop 7 | if (double_in(y, x) .ne. nf90_fill_double) stop 9 | |||
if (ubyte_in(y, x) .ne. nf90_fill_ubyte) stop 8 | #if defined(NF_HAS_PARALLEL4) || defined(ENABLE_CDF5) | |||
if (ushort_in(y, x) .ne. nf90_fill_ushort) stop 9 | if (ubyte_in(y, x) .ne. nf90_fill_ubyte) stop 10 | |||
if (uint_in(y, x) .ne. nf90_fill_uint) stop 10 | if (ushort_in(y, x) .ne. nf90_fill_ushort) stop 11 | |||
if (uint_in(y, x) .ne. nf90_fill_uint) stop 12 | ||||
#endif | ||||
else | else | |||
if (byte_in(y, x) .ne. (my_rank * (-1))) stop 13 | if (byte_in(y, x) .ne. (my_rank * (-1))) stop 13 | |||
if (short_in(y, x) .ne. (my_rank * (-2))) stop 14 | if (short_in(y, x) .ne. (my_rank * (-2))) stop 14 | |||
if (int_in(y, x) .ne. (my_rank * (-4))) stop 15 | if (int_in(y, x) .ne. (my_rank * (-4))) stop 15 | |||
if (areal_in(y, x) .ne. (my_rank * (2.5))) stop 16 | if (areal_in(y, x) .ne. (my_rank * (2.5))) stop 16 | |||
if (double_in(y, x) .ne. (my_rank * (-4.5))) stop 17 | if (double_in(y, x) .ne. (my_rank * (-4.5))) stop 17 | |||
#if defined(NF_HAS_PARALLEL4) || defined(ENABLE_CDF5) | ||||
if (ubyte_in(y, x) .ne. (my_rank * (1))) stop 18 | if (ubyte_in(y, x) .ne. (my_rank * (1))) stop 18 | |||
if (ushort_in(y, x) .ne. (my_rank * (2))) stop 19 | if (ushort_in(y, x) .ne. (my_rank * (2))) stop 19 | |||
if (uint_in(y, x) .ne. (my_rank * (4))) stop 20 | if (uint_in(y, x) .ne. (my_rank * (4))) stop 20 | |||
#endif | ||||
endif | endif | |||
end do | end do | |||
end do | end do | |||
! Close the file. | ! Close the file. | |||
call check(nf90_close(ncid)) | call check(nf90_close(ncid)) | |||
end subroutine parallel_io | ||||
call MPI_Finalize(ierr) | ||||
if (my_rank .eq. 0) print *,'*** SUCCESS!' | ||||
contains | ||||
! This subroutine handles errors by printing an error message and | ||||
! exiting with a non-zero status. | ||||
subroutine check(errcode) | ||||
use netcdf | ||||
implicit none | ||||
integer, intent(in) :: errcode | ||||
if(errcode /= nf90_noerr) then | ||||
print *, 'Error: ', trim(nf90_strerror(errcode)) | ||||
stop 99 | ||||
endif | ||||
end subroutine check | ||||
end program f90tst_parallel3 | end program f90tst_parallel3 | |||
End of changes. 25 change blocks. | ||||
45 lines changed or deleted | 107 lines changed or added |