summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorScot Breitenfeld <brtnfld@hdfgroup.org>2023-09-14 14:51:39 (GMT)
committerGitHub <noreply@github.com>2023-09-14 14:51:39 (GMT)
commit75ba9ec7a695a334ac390911700b488da5b70fef (patch)
tree78a8f5f77778a3f3c871ea2c8fe73080afd8378e
parentf2a284dc80428bd7736577b83c896c3804de8ede (diff)
downloadhdf5-75ba9ec7a695a334ac390911700b488da5b70fef.zip
hdf5-75ba9ec7a695a334ac390911700b488da5b70fef.tar.gz
hdf5-75ba9ec7a695a334ac390911700b488da5b70fef.tar.bz2
removed C_INT32_T from Fortran APIs (#3537)
-rw-r--r--fortran/src/H5Dff.F9014
-rw-r--r--fortran/src/H5Pff.F9028
-rw-r--r--fortran/src/H5_f.c54
-rw-r--r--fortran/test/tH5D.F9010
-rw-r--r--fortran/testpar/hyper.F9013
-rw-r--r--test/chunk_info.c40
-rw-r--r--test/direct_chunk.c22
7 files changed, 103 insertions, 78 deletions
diff --git a/fortran/src/H5Dff.F90 b/fortran/src/H5Dff.F90
index 2353ca2..c8c1212 100644
--- a/fortran/src/H5Dff.F90
+++ b/fortran/src/H5Dff.F90
@@ -2396,7 +2396,7 @@ CONTAINS
INTEGER(HID_T) , INTENT(IN) :: dset_id
INTEGER(HSIZE_T) , INTENT(IN), DIMENSION(:) :: offset
- INTEGER(C_INT32_T), INTENT(INOUT) :: filters
+ INTEGER , INTENT(INOUT) :: filters
TYPE(C_PTR) :: buf
INTEGER , INTENT(OUT) :: hdferr
INTEGER(HID_T) , INTENT(IN), OPTIONAL :: dxpl_id
@@ -2404,6 +2404,7 @@ CONTAINS
INTEGER(HID_T) :: dxpl_id_default
INTEGER(HSIZE_T), DIMENSION(:), ALLOCATABLE :: offset_c
INTEGER(HSIZE_T) :: i, rank
+ INTEGER(C_INT32_T) :: c_filters
INTERFACE
INTEGER(C_INT) FUNCTION H5Dread_chunk(dset_id, dxpl_id, offset, filters, buf) &
@@ -2422,6 +2423,8 @@ CONTAINS
dxpl_id_default = H5P_DEFAULT_F
IF (PRESENT(dxpl_id)) dxpl_id_default = dxpl_id
+ c_filters = INT(filters, KIND=C_INT32_T)
+
rank = SIZE(offset, KIND=HSIZE_T)
ALLOCATE(offset_c(rank), STAT=hdferr)
@@ -2437,7 +2440,9 @@ CONTAINS
offset_c(i) = offset(rank - i + 1)
ENDDO
- hdferr = INT(H5Dread_chunk(dset_id, dxpl_id_default, offset_c, filters, buf))
+ hdferr = INT(H5Dread_chunk(dset_id, dxpl_id_default, offset_c, c_filters, buf))
+
+ filters = INT(c_filters)
DEALLOCATE(offset_c)
@@ -2462,7 +2467,7 @@ CONTAINS
IMPLICIT NONE
INTEGER(HID_T) , INTENT(IN) :: dset_id
- INTEGER(C_INT32_T), INTENT(IN) :: filters
+ INTEGER , INTENT(IN) :: filters
INTEGER(HSIZE_T) , INTENT(IN), DIMENSION(:) :: offset
INTEGER(SIZE_T) , INTENT(IN) :: data_size
TYPE(C_PTR) :: buf
@@ -2472,6 +2477,7 @@ CONTAINS
INTEGER(HID_T) :: dxpl_id_default
INTEGER(HSIZE_T), DIMENSION(:), ALLOCATABLE :: offset_c
INTEGER(HSIZE_T) :: i, rank
+ INTEGER(C_INT32_T) :: c_filters
INTERFACE
INTEGER(C_INT) FUNCTION H5Dwrite_chunk(dset_id, dxpl_id, filters, offset, data_size, buf) &
@@ -2506,6 +2512,8 @@ CONTAINS
offset_c(i) = offset(rank - i + 1)
ENDDO
+ c_filters = INT(filters, C_INT32_T)
+
hdferr = INT(H5Dwrite_chunk(dset_id, dxpl_id_default, filters, offset_c, data_size, buf))
DEALLOCATE(offset_c)
diff --git a/fortran/src/H5Pff.F90 b/fortran/src/H5Pff.F90
index 1b55fe9..bbc7a9d 100644
--- a/fortran/src/H5Pff.F90
+++ b/fortran/src/H5Pff.F90
@@ -5346,10 +5346,13 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
SUBROUTINE h5pget_mpio_no_collective_cause_f(plist_id, local_no_collective_cause, global_no_collective_cause, hdferr)
IMPLICIT NONE
INTEGER(HID_T) , INTENT(IN) :: plist_id
- INTEGER(C_INT32_T), INTENT(OUT) :: local_no_collective_cause
- INTEGER(C_INT32_T), INTENT(OUT) :: global_no_collective_cause
+ INTEGER, INTENT(OUT) :: local_no_collective_cause
+ INTEGER, INTENT(OUT) :: global_no_collective_cause
INTEGER , INTENT(OUT) :: hdferr
+ INTEGER(C_INT32_T) :: c_local_no_collective_cause
+ INTEGER(C_INT32_T) :: c_global_no_collective_cause
+
INTERFACE
INTEGER(C_INT) FUNCTION H5Pget_mpio_no_collective_cause(plist_id, local_no_collective_cause, global_no_collective_cause) &
BIND(C, NAME='H5Pget_mpio_no_collective_cause')
@@ -5361,7 +5364,10 @@ SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr)
END FUNCTION H5Pget_mpio_no_collective_cause
END INTERFACE
- hdferr = INT(H5Pget_mpio_no_collective_cause(plist_id, local_no_collective_cause, global_no_collective_cause))
+ hdferr = INT(H5Pget_mpio_no_collective_cause(plist_id, c_local_no_collective_cause, c_global_no_collective_cause))
+
+ local_no_collective_cause = INT(c_local_no_collective_cause)
+ global_no_collective_cause = INT(c_global_no_collective_cause)
END SUBROUTINE h5pget_mpio_no_collective_cause_f
@@ -6328,9 +6334,11 @@ END SUBROUTINE h5pget_virtual_dsetname_f
!!
SUBROUTINE h5pget_no_selection_io_cause_f(plist_id, no_selection_io_cause, hdferr)
IMPLICIT NONE
- INTEGER(HID_T) , INTENT(IN) :: plist_id
- INTEGER(C_INT32_T), INTENT(OUT) :: no_selection_io_cause
- INTEGER , INTENT(OUT) :: hdferr
+ INTEGER(HID_T), INTENT(IN) :: plist_id
+ INTEGER , INTENT(OUT) :: no_selection_io_cause
+ INTEGER , INTENT(OUT) :: hdferr
+
+ INTEGER(C_INT32_T) :: c_no_selection_io_cause
INTERFACE
INTEGER(C_INT) FUNCTION H5Pget_no_selection_io_cause(plist_id, no_selection_io_cause) &
@@ -6342,7 +6350,9 @@ END SUBROUTINE h5pget_virtual_dsetname_f
END FUNCTION H5Pget_no_selection_io_cause
END INTERFACE
- hdferr = INT( H5Pget_no_selection_io_cause(plist_id, no_selection_io_cause))
+ hdferr = INT( H5Pget_no_selection_io_cause(plist_id, c_no_selection_io_cause))
+
+ no_selection_io_cause = INT(c_no_selection_io_cause)
END SUBROUTINE h5pget_no_selection_io_cause_f
@@ -6373,7 +6383,7 @@ END SUBROUTINE h5pget_virtual_dsetname_f
INTERFACE
INTEGER(C_INT) FUNCTION H5Pset_file_space_strategy(plist_id, strategy, persist, threshold) &
BIND(C, NAME='H5Pset_file_space_strategy')
- IMPORT :: HID_T, HSIZE_T, C_INT, C_INT32_T, C_BOOL
+ IMPORT :: HID_T, HSIZE_T, C_INT, C_BOOL
IMPLICIT NONE
INTEGER(HID_T) , VALUE :: plist_id
INTEGER(C_INT) , VALUE :: strategy
@@ -6416,7 +6426,7 @@ END SUBROUTINE h5pget_virtual_dsetname_f
INTERFACE
INTEGER(C_INT) FUNCTION H5Pget_file_space_strategy(plist_id, strategy, persist, threshold) &
BIND(C, NAME='H5Pget_file_space_strategy')
- IMPORT :: HID_T, HSIZE_T, C_INT, C_INT32_T, C_BOOL
+ IMPORT :: HID_T, HSIZE_T, C_INT, C_BOOL
IMPLICIT NONE
INTEGER(HID_T), VALUE :: plist_id
INTEGER(C_INT) :: strategy
diff --git a/fortran/src/H5_f.c b/fortran/src/H5_f.c
index 067cd3e..181047b 100644
--- a/fortran/src/H5_f.c
+++ b/fortran/src/H5_f.c
@@ -449,33 +449,33 @@ h5init_flags_c(int_f *h5d_flags, size_t_f *h5d_size_flags, int_f *h5e_flags, hid
h5d_flags[30] = (int_f)H5D_SELECTION_IO_MODE_OFF;
h5d_flags[31] = (int_f)H5D_SELECTION_IO_MODE_ON;
- h5d_flags[32] = H5D_MPIO_COLLECTIVE;
- h5d_flags[33] = H5D_MPIO_SET_INDEPENDENT;
- h5d_flags[34] = H5D_MPIO_DATATYPE_CONVERSION;
- h5d_flags[35] = H5D_MPIO_DATA_TRANSFORMS;
- h5d_flags[36] = H5D_MPIO_MPI_OPT_TYPES_ENV_VAR_DISABLED;
- h5d_flags[37] = H5D_MPIO_NOT_SIMPLE_OR_SCALAR_DATASPACES;
- h5d_flags[38] = H5D_MPIO_NOT_CONTIGUOUS_OR_CHUNKED_DATASET;
- h5d_flags[39] = H5D_MPIO_PARALLEL_FILTERED_WRITES_DISABLED;
- h5d_flags[40] = H5D_MPIO_ERROR_WHILE_CHECKING_COLLECTIVE_POSSIBLE;
- h5d_flags[41] = H5D_MPIO_NO_SELECTION_IO;
- h5d_flags[42] = H5D_MPIO_NO_COLLECTIVE_MAX_CAUSE;
-
- h5d_flags[43] = H5D_SEL_IO_DISABLE_BY_API;
- h5d_flags[44] = H5D_SEL_IO_NOT_CONTIGUOUS_OR_CHUNKED_DATASET;
- h5d_flags[45] = H5D_SEL_IO_CONTIGUOUS_SIEVE_BUFFER;
- h5d_flags[46] = H5D_SEL_IO_NO_VECTOR_OR_SELECTION_IO_CB;
- h5d_flags[47] = H5D_SEL_IO_PAGE_BUFFER;
- h5d_flags[48] = H5D_SEL_IO_DATASET_FILTER;
- h5d_flags[49] = H5D_SEL_IO_CHUNK_CACHE;
- h5d_flags[50] = H5D_SEL_IO_TCONV_BUF_TOO_SMALL;
- h5d_flags[51] = H5D_SEL_IO_BKG_BUF_TOO_SMALL;
- h5d_flags[52] = H5D_SEL_IO_DEFAULT_OFF;
- h5d_flags[53] = H5D_MPIO_NO_SELECTION_IO_CAUSES;
-
- h5d_flags[54] = H5D_MPIO_NO_CHUNK_OPTIMIZATION;
- h5d_flags[55] = H5D_MPIO_LINK_CHUNK;
- h5d_flags[56] = H5D_MPIO_MULTI_CHUNK;
+ h5d_flags[32] = (int_f)H5D_MPIO_COLLECTIVE;
+ h5d_flags[33] = (int_f)H5D_MPIO_SET_INDEPENDENT;
+ h5d_flags[34] = (int_f)H5D_MPIO_DATATYPE_CONVERSION;
+ h5d_flags[35] = (int_f)H5D_MPIO_DATA_TRANSFORMS;
+ h5d_flags[36] = (int_f)H5D_MPIO_MPI_OPT_TYPES_ENV_VAR_DISABLED;
+ h5d_flags[37] = (int_f)H5D_MPIO_NOT_SIMPLE_OR_SCALAR_DATASPACES;
+ h5d_flags[38] = (int_f)H5D_MPIO_NOT_CONTIGUOUS_OR_CHUNKED_DATASET;
+ h5d_flags[39] = (int_f)H5D_MPIO_PARALLEL_FILTERED_WRITES_DISABLED;
+ h5d_flags[40] = (int_f)H5D_MPIO_ERROR_WHILE_CHECKING_COLLECTIVE_POSSIBLE;
+ h5d_flags[41] = (int_f)H5D_MPIO_NO_SELECTION_IO;
+ h5d_flags[42] = (int_f)H5D_MPIO_NO_COLLECTIVE_MAX_CAUSE;
+
+ h5d_flags[43] = (int_f)H5D_SEL_IO_DISABLE_BY_API;
+ h5d_flags[44] = (int_f)H5D_SEL_IO_NOT_CONTIGUOUS_OR_CHUNKED_DATASET;
+ h5d_flags[45] = (int_f)H5D_SEL_IO_CONTIGUOUS_SIEVE_BUFFER;
+ h5d_flags[46] = (int_f)H5D_SEL_IO_NO_VECTOR_OR_SELECTION_IO_CB;
+ h5d_flags[47] = (int_f)H5D_SEL_IO_PAGE_BUFFER;
+ h5d_flags[48] = (int_f)H5D_SEL_IO_DATASET_FILTER;
+ h5d_flags[49] = (int_f)H5D_SEL_IO_CHUNK_CACHE;
+ h5d_flags[50] = (int_f)H5D_SEL_IO_TCONV_BUF_TOO_SMALL;
+ h5d_flags[51] = (int_f)H5D_SEL_IO_BKG_BUF_TOO_SMALL;
+ h5d_flags[52] = (int_f)H5D_SEL_IO_DEFAULT_OFF;
+ h5d_flags[53] = (int_f)H5D_MPIO_NO_SELECTION_IO_CAUSES;
+
+ h5d_flags[54] = (int_f)H5D_MPIO_NO_CHUNK_OPTIMIZATION;
+ h5d_flags[55] = (int_f)H5D_MPIO_LINK_CHUNK;
+ h5d_flags[56] = (int_f)H5D_MPIO_MULTI_CHUNK;
/*
* H5E flags
diff --git a/fortran/test/tH5D.F90 b/fortran/test/tH5D.F90
index 328141d..8c1484f 100644
--- a/fortran/test/tH5D.F90
+++ b/fortran/test/tH5D.F90
@@ -1026,7 +1026,7 @@ CONTAINS
INTEGER :: i, j, n
INTEGER :: error
TYPE(C_PTR) :: f_ptr
- INTEGER(C_int32_t) :: filters
+ INTEGER :: filters
INTEGER(SIZE_T) :: sizeINT
INTEGER(HID_T) :: dxpl
@@ -1081,12 +1081,12 @@ CONTAINS
f_ptr = C_LOC(wdata1)
offset(1:2) = (/0, 0/)
- CALL H5Dwrite_chunk_f(dset_id, 0_C_INT32_T, offset, CHUNK0 * CHUNK1 * sizeINT, f_ptr, error)
+ CALL H5Dwrite_chunk_f(dset_id, 0, offset, CHUNK0 * CHUNK1 * sizeINT, f_ptr, error)
CALL check("h5dwrite_f",error,total_error)
f_ptr = C_LOC(wdata2)
offset(1:2) = (/0, 16/)
- CALL H5Dwrite_chunk_f(dset_id, 0_C_INT32_T, offset, CHUNK0 * CHUNK1 * sizeINT, f_ptr, error, dxpl)
+ CALL H5Dwrite_chunk_f(dset_id, 0, offset, CHUNK0 * CHUNK1 * sizeINT, f_ptr, error, dxpl)
CALL check("h5dwrite_f",error,total_error)
CALL h5dclose_f(dset_id, error)
@@ -1126,7 +1126,7 @@ CONTAINS
ENDDO
ENDDO
- CALL VERIFY("H5Dread_chunk_f",filters, 0_C_INT32_T, total_error)
+ CALL VERIFY("H5Dread_chunk_f",filters, 0, total_error)
f_ptr = C_LOC(rdata2)
offset(1:2) = (/0, 16/)
@@ -1141,7 +1141,7 @@ CONTAINS
ENDDO
ENDDO
- CALL VERIFY("H5Dread_chunk_f",filters, 0_C_INT32_T, total_error)
+ CALL VERIFY("H5Dread_chunk_f",filters, 0, total_error)
CALL h5dclose_f(dset_id, error)
CALL check("h5dclose_f",error,total_error)
diff --git a/fortran/testpar/hyper.F90 b/fortran/testpar/hyper.F90
index 2120f48..edd93cf 100644
--- a/fortran/testpar/hyper.F90
+++ b/fortran/testpar/hyper.F90
@@ -52,9 +52,9 @@ SUBROUTINE hyper(length,do_collective,do_chunk, mpi_size, mpi_rank, nerrors)
LOGICAL :: is_coll
LOGICAL :: is_coll_true = .TRUE.
- INTEGER(C_INT32_T) :: local_no_collective_cause
- INTEGER(C_INT32_T) :: global_no_collective_cause
- INTEGER(C_INT32_T) :: no_selection_io_cause
+ INTEGER :: local_no_collective_cause
+ INTEGER :: global_no_collective_cause
+ INTEGER :: no_selection_io_cause
!
! initialize the array data between the processes (3)
@@ -275,6 +275,13 @@ SUBROUTINE hyper(length,do_collective,do_chunk, mpi_size, mpi_rank, nerrors)
CALL h5dwrite_f(dset_id,H5T_NATIVE_INTEGER,wbuf,dims,hdferror,file_space_id=fspace_id,mem_space_id=mspace_id,xfer_prp=dxpl_id)
CALL check("h5dwrite_f", hdferror, nerrors)
+ ! Verify bitwise operations are correct
+
+ IF( IOR(H5D_MPIO_DATATYPE_CONVERSION_F,H5D_MPIO_DATA_TRANSFORMS_F).NE.6)THEN
+ PRINT*, "Incorrect bitwise operations for Fortran defined constants"
+ nerrors = nerrors + 1
+ ENDIF
+
CALL h5pget_no_selection_io_cause_f(dxpl_id, no_selection_io_cause, hdferror)
CALL check("h5pget_no_selection_io_cause_f", hdferror, nerrors)
diff --git a/test/chunk_info.c b/test/chunk_info.c
index cb79dc1..7ccf5fa 100644
--- a/test/chunk_info.c
+++ b/test/chunk_info.c
@@ -169,7 +169,7 @@ static int
verify_get_chunk_info(hid_t dset, hid_t dspace, hsize_t chk_index, hsize_t exp_chk_size,
const hsize_t *exp_offset, unsigned exp_flt_msk)
{
- unsigned read_flt_msk = 0; /* Read filter mask */
+ uint32_t read_flt_msk = 0; /* Read filter mask */
hsize_t out_offset[2] = {0, 0}; /* Buffer to get offset coordinates */
hsize_t size = 0; /* Size of an allocated/written chunk */
haddr_t addr = 0; /* Address of an allocated/written chunk */
@@ -210,7 +210,7 @@ error:
static int
verify_get_chunk_info_by_coord(hid_t dset, hsize_t *offset, hsize_t exp_chk_size, unsigned exp_flt_msk)
{
- unsigned read_flt_msk = 0; /* Read filter mask */
+ uint32_t read_flt_msk = 0; /* Read filter mask */
hsize_t size = 0; /* Size of an allocated/written chunk */
haddr_t addr = 0; /* Address of an allocated/written chunk */
@@ -247,7 +247,7 @@ error:
static int
verify_empty_chunk_info(hid_t dset, hsize_t *offset)
{
- unsigned read_flt_msk = 0; /* Read filter mask */
+ uint32_t read_flt_msk = 0; /* Read filter mask */
hsize_t size = 0; /* Size of an allocated/written chunk */
haddr_t addr = 0; /* Address of an allocated/written chunk */
@@ -319,7 +319,7 @@ verify_selected_chunks(hid_t dset, hid_t plist, const hsize_t *start, const hsiz
{
int read_buf[CHUNK_NX][CHUNK_NY];
int expected_buf[NUM_CHUNKS][CHUNK_NX][CHUNK_NY]; /* Expected data */
- unsigned read_flt_msk = 0; /* Filter mask read back */
+ uint32_t read_flt_msk = 0; /* Filter mask read back */
hsize_t offset[2] = {0, 0}; /* Offset coordinates of a chunk */
hsize_t chk_index; /* Chunk index */
hsize_t ii, jj; /* Array indices */
@@ -494,8 +494,8 @@ test_get_chunk_info_highest_v18(hid_t fapl)
haddr_t addr = 0; /* Address of an allocated/written chunk */
hsize_t chk_index = 0; /* Index of a chunk */
hsize_t dims[2] = {NX, NY}; /* Dataset dimensions */
- unsigned flt_msk = 0; /* Filter mask */
- unsigned read_flt_msk = 0; /* Filter mask after direct read */
+ uint32_t flt_msk = 0; /* Filter mask */
+ uint32_t read_flt_msk = 0; /* Filter mask after direct read */
int fillvalue = -1; /* Fill value */
hsize_t offset[2] = {0, 0}; /* Offset coordinates of a chunk */
#ifdef H5_HAVE_FILTER_DEFLATE
@@ -825,8 +825,8 @@ test_chunk_info_single_chunk(const char *filename, hid_t fapl)
hsize_t chunk_dims[2] = {NX, NY}; /* Chunk dimensions */
int data_buf[NX][NY]; /* Input buffer */
H5D_chunk_index_t idx_type; /* Dataset chunk index type */
- unsigned flt_msk = 0; /* Filter mask */
- unsigned read_flt_msk = 0; /* Filter mask after direct read */
+ uint32_t flt_msk = 0; /* Filter mask */
+ uint32_t read_flt_msk = 0; /* Filter mask after direct read */
hsize_t offset[2]; /* Offset coordinates of a chunk */
hsize_t out_offset[2] = {0, 0}; /* Buffer to get offset coordinates */
hsize_t size = 0; /* Size of an allocated/written chunk */
@@ -970,7 +970,7 @@ test_chunk_info_implicit(char *filename, hid_t fapl)
hid_t cparms = H5I_INVALID_HID; /* Creation plist */
hsize_t dims[2] = {NX, NY}; /* Dataset dimensions */
hsize_t chunk_dims[2] = {CHUNK_NX, CHUNK_NY}; /* Chunk dimensions */
- unsigned flt_msk = 0; /* Filter mask */
+ uint32_t flt_msk = 0; /* Filter mask */
hsize_t chk_index = 0; /* Index of a chunk */
hsize_t ii, jj; /* Array indices */
hsize_t start[2] = {START_CHK_X, START_CHK_Y}; /* Start position */
@@ -1089,8 +1089,8 @@ test_chunk_info_fixed_array(const char *filename, hid_t fapl)
hid_t cparms = H5I_INVALID_HID; /* Creation plist */
hsize_t dims[2] = {NX, NY}; /* Dataset dimensions */
hsize_t chunk_dims[2] = {CHUNK_NX, CHUNK_NY}; /* Chunk dimensions */
- unsigned flt_msk = 0; /* Filter mask */
- unsigned read_flt_msk = 0; /* Filter mask after direct read */
+ uint32_t flt_msk = 0; /* Filter mask */
+ uint32_t read_flt_msk = 0; /* Filter mask after direct read */
hsize_t offset[2]; /* Offset coordinates of a chunk */
hsize_t start[2] = {START_CHK_X, START_CHK_Y}; /* Start position */
hsize_t end[2] = {END_CHK_X, END_CHK_Y}; /* End position */
@@ -1233,8 +1233,8 @@ test_chunk_info_extensible_array(const char *filename, hid_t fapl)
hsize_t dims[2] = {NX, NY}; /* Dataset dimensions */
hsize_t chunk_dims[2] = {CHUNK_NX, CHUNK_NY}; /* Chunk dimensions */
hsize_t maxdims[2] = {H5S_UNLIMITED, NY}; /* One unlimited dimension */
- unsigned flt_msk = 0; /* Filter mask */
- unsigned read_flt_msk = 0; /* Filter mask after direct read */
+ uint32_t flt_msk = 0; /* Filter mask */
+ uint32_t read_flt_msk = 0; /* Filter mask after direct read */
hsize_t offset[2]; /* Offset coordinates of a chunk */
hsize_t start[2] = {START_CHK_X, START_CHK_Y}; /* Start position */
hsize_t end[2] = {END_CHK_X, END_CHK_Y}; /* End position */
@@ -1382,8 +1382,8 @@ test_chunk_info_version2_btrees(const char *filename, hid_t fapl)
hsize_t dims[2] = {NX, NY}; /* Dataset dimensions */
hsize_t chunk_dims[2] = {CHUNK_NX, CHUNK_NY}; /* Chunk dimensions */
hsize_t maxdims[2] = {H5S_UNLIMITED, H5S_UNLIMITED}; /* Two unlimited dims */
- unsigned flt_msk = 0; /* Filter mask */
- unsigned read_flt_msk = 0; /* Filter mask after direct read */
+ uint32_t flt_msk = 0; /* Filter mask */
+ uint32_t read_flt_msk = 0; /* Filter mask after direct read */
hsize_t offset[2]; /* Offset coordinates of a chunk */
hsize_t start[2] = {START_CHK_X, START_CHK_Y}; /* Start position */
hsize_t end[2] = {END_CHK_X, END_CHK_Y}; /* End position */
@@ -1579,8 +1579,8 @@ test_basic_query(hid_t fapl)
hsize_t dims[2] = {NX, NY}; /* Dataset dimensions */
hsize_t chunk_dims[2] = {CHUNK_NX, CHUNK_NY}; /* Chunk dimensions */
int direct_buf[CHUNK_NX][CHUNK_NY]; /* Data in chunks */
- unsigned flt_msk = 0; /* Filter mask */
- unsigned read_flt_msk = 0; /* Filter mask after direct read */
+ uint32_t flt_msk = 0; /* Filter mask */
+ uint32_t read_flt_msk = 0; /* Filter mask after direct read */
hsize_t offset[2]; /* Offset coordinates of a chunk */
hsize_t out_offset[2] = {0, 0}; /* Buffer to get offset coordinates */
hsize_t size = 0; /* Size of an allocated/written chunk */
@@ -1797,7 +1797,7 @@ test_failed_attempts(const char *filename, hid_t fapl)
hid_t dset = H5I_INVALID_HID; /* Dataset ID */
hsize_t dims[2] = {NX, NY}; /* Dataset dimensions */
int data_buf[NX][NY]; /* Input buffer */
- unsigned read_flt_msk = 0; /* Filter mask after direct read */
+ uint32_t read_flt_msk = 0; /* Filter mask after direct read */
hsize_t offset[2]; /* Offset coordinates of a chunk */
hsize_t out_offset[2] = {0, 0}; /* Buffer to get offset coordinates */
hsize_t size = 0; /* Size of an allocated/written chunk */
@@ -2009,8 +2009,8 @@ test_flt_msk_with_skip_compress(hid_t fapl)
int check_chunk[CHUNK_NX][CHUNK_NY]; /* Buffer to read data in */
int read_direct_buf[CHUNK_NX][CHUNK_NY]; /* Buffer to read a chunk */
hsize_t read_buf_size = 0; /* buf size */
- unsigned flt_msk = 0; /* Filter mask */
- unsigned read_flt_msk = 0; /* Filter mask after direct read */
+ uint32_t flt_msk = 0; /* Filter mask */
+ uint32_t read_flt_msk = 0; /* Filter mask after direct read */
hsize_t offset[2] = {0, 0}; /* Offset coordinates of a chunk */
hsize_t nchunks = 0; /* Number of chunks */
hsize_t chk_index = 0; /* Index of a chunk */
diff --git a/test/direct_chunk.c b/test/direct_chunk.c
index 605eb2c..7c79b26 100644
--- a/test/direct_chunk.c
+++ b/test/direct_chunk.c
@@ -131,7 +131,7 @@ test_direct_chunk_write(hid_t file)
int data[NX][NY];
int i, j, n;
- unsigned filter_mask = 0;
+ uint32_t filter_mask = 0;
int direct_buf[CHUNK_NX][CHUNK_NY];
int check_chunk[CHUNK_NX][CHUNK_NY];
hsize_t offset[2] = {0, 0};
@@ -499,14 +499,14 @@ test_skip_compress_write1(hid_t file)
herr_t status;
int i, j, n;
- unsigned filter_mask = 0;
+ uint32_t filter_mask = 0;
int direct_buf[CHUNK_NX][CHUNK_NY];
int check_chunk[CHUNK_NX][CHUNK_NY];
hsize_t offset[2] = {0, 0};
size_t buf_size = CHUNK_NX * CHUNK_NY * sizeof(int);
int aggression = 9; /* Compression aggression setting */
- unsigned read_filter_mask = 0; /* filter mask after direct read */
+ uint32_t read_filter_mask = 0; /* filter mask after direct read */
int read_direct_buf[CHUNK_NX][CHUNK_NY];
hsize_t read_buf_size = 0; /* buf size */
@@ -747,7 +747,7 @@ test_skip_compress_write2(hid_t file)
herr_t status;
int i, j, n;
- unsigned filter_mask = 0; /* orig filter mask */
+ uint32_t filter_mask = 0; /* orig filter mask */
int origin_direct_buf[CHUNK_NX][CHUNK_NY];
int direct_buf[CHUNK_NX][CHUNK_NY];
int check_chunk[CHUNK_NX][CHUNK_NY];
@@ -755,7 +755,7 @@ test_skip_compress_write2(hid_t file)
size_t buf_size = CHUNK_NX * CHUNK_NY * sizeof(int);
int aggression = 9; /* Compression aggression setting */
- unsigned read_filter_mask = 0; /* filter mask after direct read */
+ uint32_t read_filter_mask = 0; /* filter mask after direct read */
int read_direct_buf[CHUNK_NX][CHUNK_NY];
hsize_t read_buf_size = 0; /* buf size */
@@ -956,7 +956,7 @@ test_data_conv(hid_t file)
hid_t st = H5I_INVALID_HID, dt = H5I_INVALID_HID;
hid_t array_dt;
- unsigned filter_mask = 0;
+ uint32_t filter_mask = 0;
src_type_t direct_buf[CHUNK_NX][CHUNK_NY];
dst_type_t check_chunk[CHUNK_NX][CHUNK_NY];
src_type_t read_chunk[CHUNK_NX][CHUNK_NY]; /* For H5Dread_chunk */
@@ -1178,7 +1178,7 @@ test_invalid_parameters(hid_t file)
herr_t status;
int i, j, n;
- unsigned filter_mask = 0;
+ uint32_t filter_mask = 0;
int direct_buf[CHUNK_NX][CHUNK_NY];
hsize_t offset[2] = {0, 0};
size_t buf_size = CHUNK_NX * CHUNK_NY * sizeof(int);
@@ -1428,7 +1428,7 @@ test_direct_chunk_read_no_cache(hid_t file)
int data[NX][NY];
int i, j, k, l, n; /* local index variables */
- unsigned filter_mask = 0; /* filter mask returned from H5Dread_chunk */
+ uint32_t filter_mask = 0; /* filter mask returned from H5Dread_chunk */
int direct_buf[CHUNK_NX][CHUNK_NY]; /* chunk read with H5Dread and manually decompressed */
int check_chunk[CHUNK_NX][CHUNK_NY]; /* chunk read with H5Dread */
hsize_t offset[2]; /* chunk offset used for H5Dread_chunk */
@@ -1606,7 +1606,7 @@ test_direct_chunk_read_cache(hid_t file, bool flush)
int data[NX][NY];
int i, j, k, l, n; /* local index variables */
- unsigned filter_mask = 0; /* filter mask returned from H5Dread_chunk */
+ uint32_t filter_mask = 0; /* filter mask returned from H5Dread_chunk */
int direct_buf[CHUNK_NX][CHUNK_NY]; /* chunk read with H5Dread and manually decompressed */
int check_chunk[CHUNK_NX][CHUNK_NY]; /* chunk read with H5Dread */
hsize_t offset[2]; /* chunk offset used for H5Dread_chunk */
@@ -1804,7 +1804,7 @@ test_read_unfiltered_dset(hid_t file)
int data[NX][NY];
int i, j, k, l, n;
- unsigned filter_mask = 0;
+ uint32_t filter_mask = 0;
int direct_buf[CHUNK_NX][CHUNK_NY];
int check_chunk[CHUNK_NX][CHUNK_NY]; /* chunk read with H5Dread */
hsize_t offset[2] = {0, 0};
@@ -1958,7 +1958,7 @@ test_read_unallocated_chunk(hid_t file)
herr_t status; /* status from H5 function calls */
hsize_t i, j; /* local index variables */
- unsigned filter_mask = 0; /* filter mask returned from H5Dread_chunk */
+ uint32_t filter_mask = 0; /* filter mask returned from H5Dread_chunk */
int direct_buf[CHUNK_NX][CHUNK_NY]; /* chunk read with H5Dread and manually decompressed */
hsize_t offset[2]; /* chunk offset used for H5Dread_chunk */