Merge branch 'develop' of https://bitbucket.hdfgroup.org/scm/~songyulu/hdf5_ray into HDFFV-10658-performance-drop-from-1-8

This commit is contained in:
Songyu Lu 2019-04-09 18:11:06 -05:00
commit c0b13e078e
29 changed files with 2703 additions and 777 deletions

View File

@ -847,6 +847,7 @@
./src/H5S.c
./src/H5Sall.c
./src/H5Sdbg.c
./src/H5Sdeprec.c
./src/H5Shyper.c
./src/H5Smodule.h
./src/H5Smpio.c

View File

@ -1149,7 +1149,7 @@ h5sdecode_c ( _fcd buf, hid_t_f *obj_id )
*/
int_f
h5sencode_c (_fcd buf, hid_t_f *obj_id, size_t_f *nalloc )
h5sencode_c (_fcd buf, hid_t_f *obj_id, size_t_f *nalloc, hid_t_f *fapl_id )
/******/
{
int ret_value = -1;
@ -1162,7 +1162,7 @@ h5sencode_c (_fcd buf, hid_t_f *obj_id, size_t_f *nalloc )
if (*nalloc == 0) {
if(H5Sencode((hid_t)*obj_id, c_buf, &c_size) < 0)
if(H5Sencode2((hid_t)*obj_id, c_buf, &c_size, (hid_t)*fapl_id) < 0)
return ret_value;
*nalloc = (size_t_f)c_size;
@ -1180,7 +1180,7 @@ h5sencode_c (_fcd buf, hid_t_f *obj_id, size_t_f *nalloc )
/*
* Call H5Sencode function.
*/
if(H5Sencode((hid_t)*obj_id, c_buf, &c_size) < 0){
if(H5Sencode2((hid_t)*obj_id, c_buf, &c_size, (hid_t)*fapl_id) < 0){
return ret_value;
}

View File

@ -1379,25 +1379,32 @@ CONTAINS
! M. Scot Breitenfeld
! March 26, 2008
! SOURCE
SUBROUTINE h5sencode_f(obj_id, buf, nalloc, hdferr)
SUBROUTINE h5sencode_f(obj_id, buf, nalloc, hdferr, fapl_id)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: obj_id
CHARACTER(LEN=*), INTENT(OUT) :: buf
INTEGER(SIZE_T), INTENT(INOUT) :: nalloc
INTEGER, INTENT(OUT) :: hdferr
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: fapl_id ! File access property list
!*****
INTEGER(HID_T) :: fapl_id_default
INTERFACE
INTEGER FUNCTION h5sencode_c(buf, obj_id, nalloc) BIND(C,NAME='h5sencode_c')
INTEGER FUNCTION h5sencode_c(buf, obj_id, nalloc, fapl_id_default) BIND(C,NAME='h5sencode_c')
IMPORT :: C_CHAR
IMPORT :: HID_T, SIZE_T
INTEGER(HID_T), INTENT(IN) :: obj_id
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(OUT) :: buf
INTEGER(SIZE_T), INTENT(INOUT) :: nalloc
INTEGER(HID_T) :: fapl_id_default
END FUNCTION h5sencode_c
END INTERFACE
hdferr = h5sencode_c(buf, obj_id, nalloc)
fapl_id_default = H5P_DEFAULT_F
IF(PRESENT(fapl_id)) fapl_id_default = fapl_id
hdferr = h5sencode_c(buf, obj_id, nalloc, fapl_id_default)
END SUBROUTINE h5sencode_f

View File

@ -121,7 +121,7 @@ H5_FCDLL int_f h5sselect_hyperslab_c( hid_t_f *space_id , int_f *op, hsize_t_f *
H5_FCDLL int_f h5sget_select_type_c( hid_t_f *space_id , int_f *op);
H5_FCDLL int_f h5sselect_elements_c( hid_t_f *space_id , int_f *op, size_t_f *nelements, hsize_t_f *coord);
H5_FCDLL int_f h5sdecode_c( _fcd buf, hid_t_f *obj_id );
H5_FCDLL int_f h5sencode_c(_fcd buf, hid_t_f *obj_id, size_t_f *nalloc );
H5_FCDLL int_f h5sencode_c(_fcd buf, hid_t_f *obj_id, size_t_f *nalloc, hid_t_f *fapl_id );
H5_FCDLL int_f h5sextent_equal_c( hid_t_f * space1_id, hid_t_f *space2_id, hid_t_f *c_equal);
/*

View File

@ -189,8 +189,9 @@ SUBROUTINE test_h5s_encode(total_error)
INTEGER(hid_t) :: sid1, sid3! Dataspace ID
INTEGER(hid_t) :: decoded_sid1, decoded_sid3
INTEGER(hid_t) :: fapl ! File access property
INTEGER :: rank ! LOGICAL rank of dataspace
INTEGER(size_t) :: sbuf_size=0, scalar_size=0
INTEGER(size_t) :: new_size = 0, old_size = 0, orig_size=0, scalar_size=0
! Make sure the size is large
CHARACTER(LEN=288) :: sbuf
@ -228,18 +229,36 @@ SUBROUTINE test_h5s_encode(total_error)
! Encode simple data space in a buffer
! First find the buffer size
CALL H5Sencode_f(sid1, sbuf, sbuf_size, error)
CALL check("H5Sencode", error, total_error)
! Find the buffer size without fapl
CALL H5Sencode_f(sid1, sbuf, orig_size, error)
CALL check("H5Sencode_f", error, total_error)
CALL verify("H5Sencode_f", INT(orig_size), 279, total_error)
! Create file access property list
CALL h5pcreate_f(H5P_FILE_ACCESS_F, fapl, error)
CALL check("h5pcreate_f", error, total_error)
! Find the buffer size with fapl (default old format)
CALL H5Sencode_f(sid1, sbuf, old_size, error, fapl)
CALL check("H5Sencode_f", error, total_error)
CALL verify("H5Sencode_f", INT(old_size), 279, total_error)
! Set fapl to latest file format
CALL H5Pset_libver_bounds_f(fapl, H5F_LIBVER_LATEST_F, H5F_LIBVER_LATEST_F, error)
CALL check("H5Pset_libver_bounds_f",error, total_error)
! Find the buffer size with fapl set to latest format
CALL H5Sencode_f(sid1, sbuf, new_size, error, fapl)
CALL check("H5Sencode_f", error, total_error)
CALL verify("H5Sencode_f", INT(new_size), 101, total_error)
! Try decoding bogus buffer
CALL H5Sdecode_f(sbuf, decoded_sid1, error)
CALL verify("H5Sdecode", error, -1, total_error)
CALL H5Sencode_f(sid1, sbuf, sbuf_size, error)
CALL check("H5Sencode", error, total_error)
! Encode according to the latest file format
CALL H5Sencode_f(sid1, sbuf, new_size, error, fapl)
CALL check("H5Sencode_f", error, total_error)
! Decode from the dataspace buffer and return an object handle
CALL H5Sdecode_f(sbuf, decoded_sid1, error)

View File

@ -1141,7 +1141,7 @@ Java_hdf_hdf5lib_H5_H5Sencode
if (obj_id < 0)
H5_BAD_ARGUMENT_ERROR(ENVONLY, "H5Sencode: invalid object ID");
if ((status = H5Sencode(obj_id, NULL, &buf_size)) < 0)
if ((status = H5Sencode2(obj_id, NULL, &buf_size, H5P_DEFAULT)) < 0)
H5_LIBRARY_ERROR(ENVONLY);
if (buf_size == 0)
@ -1150,7 +1150,7 @@ Java_hdf_hdf5lib_H5_H5Sencode
if (NULL == (bufPtr = (unsigned char *) HDcalloc((size_t) 1, buf_size)))
H5_JNI_FATAL_ERROR(ENVONLY, "H5Sencode: failed to allocate encoding buffer");
if ((status = H5Sencode((hid_t) obj_id, bufPtr, &buf_size)) < 0)
if ((status = H5Sencode2((hid_t) obj_id, bufPtr, &buf_size, H5P_DEFAULT)) < 0)
H5_LIBRARY_ERROR(ENVONLY);
if (NULL == (returnedArray = ENVPTR->NewByteArray(ENVONLY, (jsize) buf_size)))

View File

@ -533,6 +533,7 @@ set (H5S_SOURCES
${HDF5_SRC_DIR}/H5S.c
${HDF5_SRC_DIR}/H5Sall.c
${HDF5_SRC_DIR}/H5Sdbg.c
${HDF5_SRC_DIR}/H5Sdeprec.c
${HDF5_SRC_DIR}/H5Shyper.c
${HDF5_SRC_DIR}/H5Smpio.c
${HDF5_SRC_DIR}/H5Snone.c

View File

@ -2742,6 +2742,9 @@ H5D__chunk_redistribute_shared_chunks(const H5D_io_info_t *io_info, const H5D_ty
if ((mpi_size = H5F_mpi_get_size(io_info->dset->oloc.file)) < 0)
HGOTO_ERROR(H5E_IO, H5E_MPI, FAIL, "unable to obtain mpi size")
/* Set to latest format for encoding dataspace */
H5CX_set_libver_bounds(NULL);
if (*local_chunk_array_num_entries)
if (NULL == (send_requests = (MPI_Request *) H5MM_malloc(*local_chunk_array_num_entries * sizeof(MPI_Request))))
HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "couldn't allocate send requests buffer")

View File

@ -430,6 +430,10 @@ H5D__virtual_store_layout(H5F_t *f, H5O_layout_t *layout)
/* Create block if # of used entries > 0 */
if(layout->storage.u.virt.list_nused > 0) {
/* Set the low/high bounds according to 'f' for the API context */
H5CX_set_libver_bounds(f);
/* Allocate array for caching results of strlen */
if(NULL == (str_size = (size_t *)H5MM_malloc(2 * layout->storage.u.virt.list_nused * sizeof(size_t))))
HGOTO_ERROR(H5E_OHDR, H5E_RESOURCE, FAIL, "unable to allocate string length array")

View File

@ -817,14 +817,17 @@ done:
/*--------------------------------------------------------------------------
NAME
H5Pencode
H5Pencode2
PURPOSE
Routine to convert the property values in a property list into a binary buffer
Routine to convert the property values in a property list into a binary buffer.
The encoding of property values will be done according to the file format
setting in fapl_id.
USAGE
herr_t H5Pencode(plist_id, buf, nalloc)
herr_t H5Pencode(plist_id, buf, nalloc, fapl_id)
hid_t plist_id; IN: Identifier to property list to encode
void *buf: OUT: buffer to gold the encoded plist
size_t *nalloc; IN/OUT: size of buffer needed to encode plist
hid_t fapl_id; IN: File access property list ID
RETURNS
Returns non-negative on success, negative on failure.
DESCRIPTION
@ -837,25 +840,29 @@ done:
REVISION LOG
--------------------------------------------------------------------------*/
herr_t
H5Pencode(hid_t plist_id, void *buf, size_t *nalloc)
H5Pencode2(hid_t plist_id, void *buf, size_t *nalloc, hid_t fapl_id)
{
H5P_genplist_t *plist; /* Property list to query */
herr_t ret_value = SUCCEED; /* return value */
FUNC_ENTER_API(FAIL)
H5TRACE3("e", "i*x*z", plist_id, buf, nalloc);
H5TRACE4("e", "i*x*zi", plist_id, buf, nalloc, fapl_id);
/* Check arguments. */
if(NULL == (plist = (H5P_genplist_t *)H5I_object_verify(plist_id, H5I_GENPROP_LST)))
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "not a property list");
/* Verify access property list and set up collective metadata if appropriate */
if(H5CX_set_apl(&fapl_id, H5P_CLS_FACC, H5I_INVALID_HID, TRUE) < 0)
HGOTO_ERROR(H5E_FILE, H5E_CANTSET, H5I_INVALID_HID, "can't set access property list info")
/* Call the internal encode routine */
if((ret_value = H5P__encode(plist, TRUE, buf, nalloc)) < 0)
HGOTO_ERROR(H5E_PLIST, H5E_CANTENCODE, FAIL, "unable to encode property list");
done:
FUNC_LEAVE_API(ret_value)
} /* H5Pencode() */
} /* H5Pencode2() */
/*--------------------------------------------------------------------------

View File

@ -486,6 +486,54 @@ done:
FUNC_LEAVE_API(ret_value)
} /* end H5Pget_version() */
/*--------------------------------------------------------------------------
NAME
H5Pencode1
PURPOSE
Routine to convert the property values in a property list into a binary buffer
USAGE
herr_t H5Pencode1(plist_id, buf, nalloc)
hid_t plist_id; IN: Identifier to property list to encode
void *buf: OUT: buffer to gold the encoded plist
size_t *nalloc; IN/OUT: size of buffer needed to encode plist
RETURNS
Returns non-negative on success, negative on failure.
DESCRIPTION
Encodes a property list into a binary buffer. If the buffer is NULL, then
the call will set the size needed to encode the plist in nalloc. Otherwise
the routine will encode the plist in buf.
GLOBAL VARIABLES
COMMENTS, BUGS, ASSUMPTIONS
EXAMPLES
REVISION LOG
--------------------------------------------------------------------------*/
herr_t
H5Pencode1(hid_t plist_id, void *buf, size_t *nalloc)
{
H5P_genplist_t *plist; /* Property list to query */
hid_t temp_fapl_id = H5P_DEFAULT;
herr_t ret_value = SUCCEED; /* return value */
FUNC_ENTER_API(FAIL)
H5TRACE3("e", "i*x*z", plist_id, buf, nalloc);
/* Check arguments. */
if(NULL == (plist = (H5P_genplist_t *)H5I_object_verify(plist_id, H5I_GENPROP_LST)))
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "not a property list");
/* Verify access property list and set up collective metadata if appropriate */
if(H5CX_set_apl(&temp_fapl_id, H5P_CLS_FACC, H5I_INVALID_HID, TRUE) < 0)
HGOTO_ERROR(H5E_FILE, H5E_CANTSET, H5I_INVALID_HID, "can't set access property list info")
/* Call the internal encode routine */
if((ret_value = H5P__encode(plist, TRUE, buf, nalloc)) < 0)
HGOTO_ERROR(H5E_PLIST, H5E_CANTENCODE, FAIL, "unable to encode property list");
done:
FUNC_LEAVE_API(ret_value)
} /* H5Pencode1() */
/*-------------------------------------------------------------------------
* Function: H5Pset_file_space
*

View File

@ -236,7 +236,7 @@ H5_DLL herr_t H5Pinsert2(hid_t plist_id, const char *name, size_t size,
H5P_prp_compare_func_t prp_cmp, H5P_prp_close_func_t prp_close);
H5_DLL herr_t H5Pset(hid_t plist_id, const char *name, const void *value);
H5_DLL htri_t H5Pexist(hid_t plist_id, const char *name);
H5_DLL herr_t H5Pencode(hid_t plist_id, void *buf, size_t *nalloc);
H5_DLL herr_t H5Pencode2(hid_t plist_id, void *buf, size_t *nalloc, hid_t fapl_id);
H5_DLL hid_t H5Pdecode(const void *buf);
H5_DLL herr_t H5Pget_size(hid_t id, const char *name, size_t *size);
H5_DLL herr_t H5Pget_nprops(hid_t id, size_t *nprops);
@ -536,6 +536,7 @@ H5_DLL herr_t H5Pinsert1(hid_t plist_id, const char *name, size_t size,
void *value, H5P_prp_set_func_t prp_set, H5P_prp_get_func_t prp_get,
H5P_prp_delete_func_t prp_delete, H5P_prp_copy_func_t prp_copy,
H5P_prp_close_func_t prp_close);
H5_DLL herr_t H5Pencode1(hid_t plist_id, void *buf, size_t *nalloc);
H5_DLL H5Z_filter_t H5Pget_filter1(hid_t plist_id, unsigned filter,
unsigned int *flags/*out*/, size_t *cd_nelmts/*out*/,
unsigned cd_values[]/*out*/, size_t namelen, char name[]);

View File

@ -215,6 +215,9 @@ H5R__create(void *_ref, H5G_loc_t *loc, const char *name, H5R_type_t ref_type, H
obj_loc.path = &path;
H5G_loc_reset(&obj_loc);
/* Set the FAPL for the API context */
H5CX_set_libver_bounds(loc->oloc->file);
/* Find the object */
if(H5G_loc_find(loc, name, &obj_loc) < 0)
HGOTO_ERROR(H5E_REFERENCE, H5E_NOTFOUND, FAIL, "object not found")

View File

@ -23,6 +23,7 @@
/***********/
#include "H5private.h" /* Generic Functions */
#include "H5Eprivate.h" /* Error handling */
#include "H5CXprivate.h" /* API Contexts */
#include "H5Fprivate.h" /* Files */
#include "H5FLprivate.h" /* Free lists */
#include "H5Iprivate.h" /* IDs */
@ -1487,13 +1488,15 @@ done:
/*-------------------------------------------------------------------------
* Function: H5Sencode
* Function: H5Sencode2
*
* Purpose: Given a dataspace ID, converts the object description
* (including selection) into binary in a buffer.
* The selection will be encoded according to the file
* format setting in fapl.
*
* Return: Success: non-negative
* Failure: negative
* Failure: negative
*
* Programmer: Raymond Lu
* slu@ncsa.uiuc.edu
@ -1502,24 +1505,29 @@ done:
*-------------------------------------------------------------------------
*/
herr_t
H5Sencode(hid_t obj_id, void *buf, size_t *nalloc)
H5Sencode2(hid_t obj_id, void *buf, size_t *nalloc, hid_t fapl_id)
{
H5S_t *dspace;
herr_t ret_value=SUCCEED;
FUNC_ENTER_API(FAIL)
H5TRACE3("e", "i*x*z", obj_id, buf, nalloc);
H5TRACE4("e", "i*x*zi", obj_id, buf, nalloc, fapl_id);
/* Check argument and retrieve object */
if(NULL == (dspace = (H5S_t *)H5I_object_verify(obj_id, H5I_DATASPACE)))
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "not a dataspace")
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "not a dataspace")
/* Verify access property list and set up collective metadata if appropriate */
if(H5CX_set_apl(&fapl_id, H5P_CLS_FACC, H5I_INVALID_HID, TRUE) < 0)
HGOTO_ERROR(H5E_FILE, H5E_CANTSET, H5I_INVALID_HID, "can't set access property list info")
if(H5S_encode(dspace, (unsigned char **)&buf, nalloc) < 0)
HGOTO_ERROR(H5E_DATASPACE, H5E_CANTENCODE, FAIL, "can't encode dataspace")
HGOTO_ERROR(H5E_DATASPACE, H5E_CANTENCODE, FAIL, "can't encode dataspace")
done:
FUNC_LEAVE_API(ret_value)
} /* end H5Sencode() */
} /* H5Sencode2() */
/*-------------------------------------------------------------------------

View File

@ -629,7 +629,7 @@ H5S__all_serialize(const H5S_t *space, uint8_t **p)
/* Store the preamble information */
UINT32ENCODE(pp, (uint32_t)H5S_GET_SELECT_TYPE(space)); /* Store the type of selection */
UINT32ENCODE(pp, (uint32_t)1); /* Store the version number */
UINT32ENCODE(pp, (uint32_t)H5S_ALL_VERSION_1); /* Store the version number */
UINT32ENCODE(pp, (uint32_t)0); /* Store the un-used padding */
UINT32ENCODE(pp, (uint32_t)0); /* Store the additional information length */

121
src/H5Sdeprec.c Normal file
View File

@ -0,0 +1,121 @@
/* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
* Copyright by The HDF Group. *
* Copyright by the Board of Trustees of the University of Illinois. *
* All rights reserved. *
* *
* This file is part of HDF5. The full HDF5 copyright notice, including *
* terms governing use, modification, and redistribution, is contained in *
* the COPYING file, which can be found at the root of the source code *
* distribution tree, or in https://support.hdfgroup.org/ftp/HDF5/releases. *
* If you do not have access to either file, you may request a copy from *
* help@hdfgroup.org. *
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */
/*-------------------------------------------------------------------------
*
* Created: H5Sdeprec.c
*
* Purpose: Deprecated functions from the H5S interface. These
* functions are here for compatibility purposes and may be
* removed in the future. Applications should switch to the
* newer APIs.
*
*-------------------------------------------------------------------------
*/
/****************/
/* Module Setup */
/****************/
#include "H5Smodule.h" /* This source code file is part of the H5S module */
/***********/
/* Headers */
/***********/
#include "H5private.h" /* Generic Functions */
#include "H5CXprivate.h" /* API Contexts */
#include "H5Spkg.h" /* Dataspaces */
#include "H5Eprivate.h" /* Error handling */
#include "H5Iprivate.h" /* IDs */
/****************/
/* Local Macros */
/****************/
/******************/
/* Local Typedefs */
/******************/
/********************/
/* Package Typedefs */
/********************/
/********************/
/* Local Prototypes */
/********************/
/*********************/
/* Package Variables */
/*********************/
/*****************************/
/* Library Private Variables */
/*****************************/
/*******************/
/* Local Variables */
/*******************/
#ifndef H5_NO_DEPRECATED_SYMBOLS
/*-------------------------------------------------------------------------
* Function: H5Sencode1
*
* Purpose: Given a dataspace ID, converts the object description
* (including selection) into binary in a buffer.
*
* Return: Success: non-negative
* Failure: negative
*
* Programmer: Raymond Lu
* slu@ncsa.uiuc.edu
* July 14, 2004
*
*-------------------------------------------------------------------------
*/
herr_t
H5Sencode1(hid_t obj_id, void *buf, size_t *nalloc)
{
H5S_t *dspace;
hid_t temp_fapl_id = H5P_DEFAULT;
herr_t ret_value=SUCCEED;
FUNC_ENTER_API(FAIL)
H5TRACE3("e", "i*x*z", obj_id, buf, nalloc);
/* Check argument and retrieve object */
if (NULL == (dspace = (H5S_t *)H5I_object_verify(obj_id, H5I_DATASPACE)))
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "not a dataspace")
/* Verify access property list and set up collective metadata if appropriate */
if(H5CX_set_apl(&temp_fapl_id, H5P_CLS_FACC, H5I_INVALID_HID, TRUE) < 0)
HGOTO_ERROR(H5E_FILE, H5E_CANTSET, H5I_INVALID_HID, "can't set access property list info")
/* Use (earliest, latest) i.e. not latest format */
if(H5S_encode(dspace, (unsigned char **)&buf, nalloc)<0)
HGOTO_ERROR(H5E_DATASPACE, H5E_CANTENCODE, FAIL, "can't encode dataspace")
done:
FUNC_LEAVE_API(ret_value)
} /* H5Sencode1() */
#endif /* H5_NO_DEPRECATED_SYMBOLS */

File diff suppressed because it is too large Load Diff

View File

@ -583,7 +583,7 @@ H5S__none_serialize(const H5S_t *space, uint8_t **p)
/* Store the preamble information */
UINT32ENCODE(pp, (uint32_t)H5S_GET_SELECT_TYPE(space)); /* Store the type of selection */
UINT32ENCODE(pp, (uint32_t)1); /* Store the version number */
UINT32ENCODE(pp, (uint32_t)H5S_NONE_VERSION_1); /* Store the version number */
UINT32ENCODE(pp, (uint32_t)0); /* Store the un-used padding */
UINT32ENCODE(pp, (uint32_t)0); /* Store the additional information length */

View File

@ -37,8 +37,35 @@
#define H5S_VALID_PERM 0x02
/* Flags for serialization of selections */
#define H5S_SELECT_FLAG_UNLIM 0x01
#define H5S_SELECT_FLAG_BITS (H5S_SELECT_FLAG_UNLIM)
#define H5S_HYPER_REGULAR 0x01
#define H5S_SELECT_FLAG_BITS (H5S_HYPER_REGULAR)
/* Versions for H5S_SEL_HYPER selection info */
#define H5S_HYPER_VERSION_1 1
#define H5S_HYPER_VERSION_2 2
#define H5S_HYPER_VERSION_3 3
/* Versions for H5S_SEL_POINTS selection info */
#define H5S_POINT_VERSION_1 1
#define H5S_POINT_VERSION_2 2
/* Versions for H5S_SEL_NONE selection info */
#define H5S_NONE_VERSION_1 1
/* Versions for H5S_SEL_ALL selection info */
#define H5S_ALL_VERSION_1 1
/* Encoded size of selection info for H5S_SEL_POINTS/H5S_SEL_HYPER */
#define H5S_SELECT_INFO_ENC_SIZE_2 0x02 /* 2 bytes: 16 bits */
#define H5S_SELECT_INFO_ENC_SIZE_4 0x04 /* 4 bytes: 32 bits */
#define H5S_SELECT_INFO_ENC_SIZE_8 0x08 /* 8 bytes: 64 bits */
#define H5S_SELECT_INFO_ENC_SIZE_BITS ( H5S_SELECT_INFO_ENC_SIZE_2 | \
H5S_SELECT_INFO_ENC_SIZE_4 | \
H5S_SELECT_INFO_ENC_SIZE_8 )
#define H5S_UINT16_MAX 0x0000FFFF /* 2^16 - 1 = 65,535 */
#define H5S_UINT32_MAX 0xFFFFFFFF /* 2^32 - 1 = 4,294,967,295 */
#define H5S_UINT64_MAX ((hsize_t)(-1L)) /* 2^64 - 1 = 18,446,744,073,709,551,615 */
/* Length of stack-allocated sequences for "project intersect" routines */
#define H5S_PROJECT_INTERSECT_NSEQS 256

View File

@ -28,13 +28,14 @@
/***********/
/* Headers */
/***********/
#include "H5private.h" /* Generic Functions */
#include "H5private.h" /* Generic Functions */
#include "H5CXprivate.h" /* API Contexts */
#include "H5Eprivate.h" /* Error handling */
#include "H5FLprivate.h" /* Free Lists */
#include "H5Iprivate.h" /* ID Functions */
#include "H5MMprivate.h" /* Memory management */
#include "H5Spkg.h" /* Dataspace functions */
#include "H5VMprivate.h" /* Vector functions */
#include "H5Iprivate.h" /* ID Functions */
#include "H5MMprivate.h" /* Memory management */
#include "H5Spkg.h" /* Dataspace functions */
#include "H5VMprivate.h" /* Vector functions */
/****************/
@ -72,6 +73,8 @@ static herr_t H5S__point_project_scalar(const H5S_t *space, hsize_t *offset);
static herr_t H5S__point_project_simple(const H5S_t *space, H5S_t *new_space,
hsize_t *offset);
static herr_t H5S__point_iter_init(H5S_sel_iter_t *iter, const H5S_t *space);
static herr_t
H5S__point_get_version_enc_size(const H5S_t *space, uint32_t *version, uint8_t *enc_size);
/* Selection iteration callbacks */
static herr_t H5S__point_iter_coords(const H5S_sel_iter_t *iter, hsize_t *coords);
@ -118,6 +121,13 @@ const H5S_select_class_t H5S_sel_point[1] = {{
H5S__point_iter_init,
}};
/* Format version bounds for dataspace hyperslab selection */
const unsigned H5O_sds_point_ver_bounds[] = {
H5S_POINT_VERSION_1, /* H5F_LIBVER_EARLIEST */
H5S_POINT_VERSION_1, /* H5F_LIBVER_V18 */
H5S_POINT_VERSION_1, /* H5F_LIBVER_V110 */
H5S_POINT_VERSION_2 /* H5F_LIBVER_LATEST */
};
/*******************/
/* Local Variables */
@ -919,6 +929,124 @@ done:
FUNC_LEAVE_API(ret_value)
} /* end H5Sget_select_elem_npoints() */
/*--------------------------------------------------------------------------
NAME
H5S__point_get_version_enc_size
PURPOSE
Determine the version and the size (2, 4 or 8 bytes) to encode point selection info
USAGE
hssize_t H5S__point_set_enc_size(space, version, enc_size)
const H5S_t *space: IN: Dataspace ID of selection to query
uint32_t *version: OUT: The version to use for encoding
uint8_t *enc_size: OUT: The size to use for encoding
RETURNS
The version and the size to encode point selection info
DESCRIPTION
Determine the version to use for encoding points selection info based
on the following:
(1) the low/high bounds setting in fapl
(2) whether the number of points or selection high bounds exceeds H5S_UINT32_MAX or not
Determine the encoded size based on version:
--For version 2, the encoded size of point selection info is determined
by the maximum size for:
(a) storing the number of points
(b) storing the selection high bounds
GLOBAL VARIABLES
COMMENTS, BUGS, ASSUMPTIONS
EXAMPLES
REVISION LOG
--------------------------------------------------------------------------*/
static herr_t
H5S__point_get_version_enc_size(const H5S_t *space, uint32_t *version, uint8_t *enc_size)
{
hbool_t count_up_version = FALSE; /* Whether number of points exceed H5S_UINT32_MAX */
hbool_t bound_up_version = FALSE; /* Whether high bounds exceed H5S_UINT32_MAX */
H5F_libver_t low_bound; /* The 'low' bound of library format versions */
H5F_libver_t high_bound; /* The 'high' bound of library format versions */
uint32_t tmp_version; /* Local temporary version */
hsize_t bounds_start[H5S_MAX_RANK]; /* Starting coordinate of bounding box */
hsize_t bounds_end[H5S_MAX_RANK]; /* Opposite coordinate of bounding box */
hsize_t max_size = 0; /* Maximum selection size */
unsigned u; /* Local index veriable */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_STATIC
/* Get bounding box for the selection */
HDmemset(bounds_end, 0, sizeof(bounds_end));
if(H5S__point_bounds(space, bounds_start, bounds_end) < 0)
HGOTO_ERROR(H5E_DATASPACE, H5E_CANTGET, FAIL, "can't get selection bounds")
/* Determine whether number of points or high bounds exceeds (2^32 - 1) */
if(space->select.num_elem > H5S_UINT32_MAX)
count_up_version = TRUE;
else {
for(u = 0; u < space->extent.rank; u++)
if(bounds_end[u] > H5S_UINT32_MAX) {
bound_up_version = TRUE;
break;
}
}
/* If exceed (2^32 -1) */
if(count_up_version || bound_up_version)
tmp_version = H5S_POINT_VERSION_2;
else
tmp_version = H5S_POINT_VERSION_1;
/* Get the file's low/high bounds */
if(H5CX_get_libver_bounds(&low_bound, &high_bound) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTGET, FAIL, "can't get low/high bounds from API context")
/* Upgrade to the version indicated by the file's low bound if higher */
tmp_version = MAX(tmp_version, H5O_sds_point_ver_bounds[low_bound]);
/* Version bounds check */
if(tmp_version > H5O_sds_point_ver_bounds[high_bound]) {
if(count_up_version)
HGOTO_ERROR(H5E_DATASPACE, H5E_BADVALUE, FAIL, "The number of points in point selection exceeds 2^32")
else if(bound_up_version)
HGOTO_ERROR(H5E_DATASPACE, H5E_BADVALUE, FAIL, "The end of bounding box in point selection exceeds 2^32")
else
HGOTO_ERROR(H5E_DATASPACE, H5E_BADRANGE, FAIL, "Dataspace point selection version out of bounds")
}
/* Set the version to return */
*version = tmp_version;
/* Get the encoded size use based on version */
switch(tmp_version) {
case H5S_POINT_VERSION_1:
*enc_size = H5S_SELECT_INFO_ENC_SIZE_4;
break;
case H5S_POINT_VERSION_2:
/* Find max for num_elem and bounds_end[] */
max_size = space->select.num_elem;
for(u = 0; u < space->extent.rank; u++)
if(bounds_end[u] > max_size)
max_size = bounds_end[u];
/* Determine the encoding size */
if(max_size > H5S_UINT32_MAX)
*enc_size = H5S_SELECT_INFO_ENC_SIZE_8;
else if(max_size > H5S_UINT16_MAX)
*enc_size = H5S_SELECT_INFO_ENC_SIZE_4;
else
*enc_size = H5S_SELECT_INFO_ENC_SIZE_2;
break;
default:
HGOTO_ERROR(H5E_DATASPACE, H5E_UNSUPPORTED, FAIL, "unknown point info size")
break;
} /* end switch */
done:
FUNC_LEAVE_NOAPI(ret_value)
} /* H5S__point_get_version_enc_size() */
/*--------------------------------------------------------------------------
NAME
@ -942,22 +1070,39 @@ done:
static hssize_t
H5S__point_serial_size(const H5S_t *space)
{
uint32_t version; /* Version number */
uint8_t enc_size; /* Encoded size of point selection info */
hssize_t ret_value = -1; /* Return value */
FUNC_ENTER_STATIC_NOERR
FUNC_ENTER_STATIC
HDassert(space);
/* Basic number of bytes required to serialize point selection:
* <type (4 bytes)> + <version (4 bytes)> + <padding (4 bytes)> +
* <length (4 bytes)> + <rank (4 bytes)> + <# of points (4 bytes)> = 24 bytes
*/
ret_value = 24;
/* Determine the version and encoded size for point selection */
if(H5S__point_get_version_enc_size(space, &version, &enc_size) < 0)
HGOTO_ERROR(H5E_DATASPACE, H5E_CANTGET, FAIL, "can't determine hyper version")
/* Basic number of bytes required to serialize point selection: */
if(version >= H5S_POINT_VERSION_2)
/*
* <type (4 bytes)> + <version (4 bytes)> +
* <size of point info (1 byte)> + rank (4 bytes)>
*/
ret_value=13;
else
/*
* <type (4 bytes)> + <version (4 bytes)> + <padding (4 bytes)> +
* <length (4 bytes)> + <rank (4 bytes)>
*/
ret_value = 20;
/* <num points (depend on enc_size)> */
ret_value += enc_size;
/* Count points in selection */
/* (Add 4 bytes times the rank for each element selected) */
ret_value += (4 * space->extent.rank) * (hssize_t)H5S_GET_SELECT_NPOINTS(space);
ret_value += (hssize_t) (enc_size * space->extent.rank * space->select.num_elem);
done:
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5S__point_serial_size() */
@ -987,12 +1132,15 @@ static herr_t
H5S__point_serialize(const H5S_t *space, uint8_t **p)
{
H5S_pnt_node_t *curr; /* Point information nodes */
uint8_t *pp; /* Local pointer for encoding */
uint8_t *lenp; /* Pointer to length location for later storage */
uint32_t len = 0; /* Number of bytes used */
unsigned u; /* Local counting variable */
uint8_t *pp; /* Local pointer for decoding */
uint8_t *lenp = NULL; /* pointer to length location for later storage */
uint32_t len=0; /* number of bytes used */
unsigned u; /* local counting variable */
uint32_t version; /* Version number */
uint8_t enc_size; /* Encoded size of point selection info */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_STATIC_NOERR
FUNC_ENTER_STATIC
/* Check args */
HDassert(space);
@ -1000,42 +1148,96 @@ H5S__point_serialize(const H5S_t *space, uint8_t **p)
pp = (*p);
HDassert(pp);
/* Determine the version and encoded size for point selection info */
if(H5S__point_get_version_enc_size(space, &version, &enc_size) < 0)
HGOTO_ERROR(H5E_DATASPACE, H5E_CANTGET, FAIL, "can't determine hyper version")
/* Store the preamble information */
UINT32ENCODE(pp, (uint32_t)H5S_GET_SELECT_TYPE(space)); /* Store the type of selection */
UINT32ENCODE(pp, (uint32_t)1); /* Store the version number */
UINT32ENCODE(pp, (uint32_t)0); /* Store the un-used padding */
lenp = pp; /* Keep the pointer to the length location for later */
pp += 4; /* Skip over space for length */
UINT32ENCODE(pp, version); /* Store the version number */
if(version >= 2) {
*(pp)++ = enc_size; /* Store size of point info */
} else {
HDassert(version == H5S_POINT_VERSION_1);
UINT32ENCODE(pp, (uint32_t)0); /* Store the un-used padding */
lenp = pp; /* Keep the pointer to the length location for later */
pp += 4; /* Skip over space for length */
len += 8; /* Add in advance # of bytes for num of dimensions and num elements */
}
/* Encode number of dimensions */
UINT32ENCODE(pp, (uint32_t)space->extent.rank);
len += 4;
/* Encode number of elements */
UINT32ENCODE(pp, (uint32_t)space->select.num_elem);
len += 4;
switch(enc_size) {
case H5S_SELECT_INFO_ENC_SIZE_2:
HDassert(version == H5S_POINT_VERSION_2);
/* Encode each point in selection */
curr = space->select.sel_info.pnt_lst->head;
while(curr != NULL) {
/* Add 4 bytes times the rank for each element selected */
len += 4 * space->extent.rank;
/* Encode number of elements */
UINT16ENCODE(pp, (uint16_t)space->select.num_elem);
/* Encode each point */
for(u = 0; u < space->extent.rank; u++)
UINT32ENCODE(pp, (uint32_t)curr->pnt[u]);
/* Encode each point in selection */
curr=space->select.sel_info.pnt_lst->head;
while(curr!=NULL) {
/* Encode each point */
for(u=0; u<space->extent.rank; u++)
UINT16ENCODE(pp, (uint16_t)curr->pnt[u]);
curr=curr->next;
} /* end while */
break;
curr = curr->next;
} /* end while */
case H5S_SELECT_INFO_ENC_SIZE_4:
HDassert(version == H5S_POINT_VERSION_1 || version == H5S_POINT_VERSION_2);
/* Encode length */
UINT32ENCODE(lenp, (uint32_t)len); /* Store the length of the extra information */
/* Encode number of elements */
UINT32ENCODE(pp, (uint32_t)space->select.num_elem);
/* Encode each point in selection */
curr=space->select.sel_info.pnt_lst->head;
while(curr!=NULL) {
/* Encode each point */
for(u=0; u<space->extent.rank; u++)
UINT32ENCODE(pp, (uint32_t)curr->pnt[u]);
curr=curr->next;
} /* end while */
/* Add 4 bytes times the rank for each element selected */
if(version == H5S_POINT_VERSION_1)
len += (uint32_t)space->select.num_elem * 4 * space->extent.rank;
break;
case H5S_SELECT_INFO_ENC_SIZE_8:
HDassert(version == H5S_POINT_VERSION_2);
/* Encode number of elements */
UINT64ENCODE(pp, space->select.num_elem);
/* Encode each point in selection */
curr=space->select.sel_info.pnt_lst->head;
while(curr!=NULL) {
/* Encode each point */
for(u=0; u<space->extent.rank; u++)
UINT64ENCODE(pp, curr->pnt[u]);
curr=curr->next;
} /* end while */
break;
default:
HGOTO_ERROR(H5E_DATASPACE, H5E_UNSUPPORTED, FAIL, "unknown point info size")
break;
} /* end switch */
if(version == H5S_POINT_VERSION_1)
UINT32ENCODE(lenp, (uint32_t)len); /* Store the length of the extra information */
/* Update encoding pointer */
*p = pp;
FUNC_LEAVE_NOAPI(SUCCEED)
} /* end H5S__point_serialize() */
done:
FUNC_LEAVE_NOAPI(ret_value)
} /* H5S__point_serialize() */
/*--------------------------------------------------------------------------
@ -1067,9 +1269,10 @@ H5S__point_deserialize(H5S_t **space, const uint8_t **p)
either *space or a newly allocated one */
hsize_t dims[H5S_MAX_RANK]; /* Dimension sizes */
uint32_t version; /* Version number */
uint8_t enc_size = 0; /* Encoded size of selection info */
hsize_t *coord = NULL, *tcoord; /* Pointer to array of elements */
const uint8_t *pp; /* Local pointer for decoding */
size_t num_elem = 0; /* Number of elements in selection */
uint64_t num_elem = 0; /* Number of elements in selection */
unsigned rank; /* Rank of points */
unsigned i, j; /* local counting variables */
herr_t ret_value = SUCCEED; /* Return value */
@ -1096,8 +1299,18 @@ H5S__point_deserialize(H5S_t **space, const uint8_t **p)
/* Decode version */
UINT32DECODE(pp, version);
/* Skip over the remainder of the header */
pp += 8;
if(version >= (uint32_t)H5S_POINT_VERSION_2)
/* Decode size of point info */
enc_size = *(pp)++;
else {
/* Skip over the remainder of the header */
pp += 8;
enc_size = H5S_SELECT_INFO_ENC_SIZE_4;
}
/* Check encoded size */
if(enc_size & ~H5S_SELECT_INFO_ENC_SIZE_BITS)
HGOTO_ERROR(H5E_DATASPACE, H5E_CANTLOAD, FAIL, "unknown size of point/offset info for selection")
/* Decode the rank of the point selection */
UINT32DECODE(pp,rank);
@ -1113,8 +1326,22 @@ H5S__point_deserialize(H5S_t **space, const uint8_t **p)
if(rank != tmp_space->extent.rank)
HGOTO_ERROR(H5E_DATASPACE, H5E_BADRANGE, FAIL, "rank of serialized selection does not match dataspace")
/* Deserialize points to select */
UINT32DECODE(pp, num_elem); /* decode the number of points */
/* decode the number of points */
switch(enc_size) {
case H5S_SELECT_INFO_ENC_SIZE_2:
UINT16DECODE(pp, num_elem);
break;
case H5S_SELECT_INFO_ENC_SIZE_4:
UINT32DECODE(pp, num_elem);
break;
case H5S_SELECT_INFO_ENC_SIZE_8:
UINT64DECODE(pp, num_elem);
break;
default:
HGOTO_ERROR(H5E_DATASPACE, H5E_UNSUPPORTED, FAIL, "unknown point info size")
break;
} /* end switch */
/* Allocate space for the coordinates */
if(NULL == (coord = (hsize_t *)H5MM_malloc(num_elem * rank * sizeof(hsize_t))))
@ -1123,7 +1350,22 @@ H5S__point_deserialize(H5S_t **space, const uint8_t **p)
/* Retrieve the coordinates from the buffer */
for(tcoord = coord, i = 0; i < num_elem; i++)
for(j = 0; j < (unsigned)rank; j++, tcoord++)
UINT32DECODE(pp, *tcoord);
switch(enc_size) {
case H5S_SELECT_INFO_ENC_SIZE_2:
UINT16DECODE(pp, *tcoord);
break;
case H5S_SELECT_INFO_ENC_SIZE_4:
UINT32DECODE(pp, *tcoord);
break;
case H5S_SELECT_INFO_ENC_SIZE_8:
UINT64DECODE(pp, *tcoord);
break;
default:
HGOTO_ERROR(H5E_DATASPACE, H5E_UNSUPPORTED, FAIL, "unknown point info size")
break;
} /* end switch */
/* Select points */
if(H5S_select_elements(tmp_space, H5S_SELECT_SET, num_elem, (const hsize_t *)coord) < 0)

View File

@ -97,7 +97,7 @@ H5_DLL herr_t H5Sset_extent_simple(hid_t space_id, int rank,
const hsize_t dims[], const hsize_t max[]);
H5_DLL hid_t H5Scopy(hid_t space_id);
H5_DLL herr_t H5Sclose(hid_t space_id);
H5_DLL herr_t H5Sencode(hid_t obj_id, void *buf, size_t *nalloc);
H5_DLL herr_t H5Sencode2(hid_t obj_id, void *buf, size_t *nalloc, hid_t fapl);
H5_DLL hid_t H5Sdecode(const void *buf);
H5_DLL hssize_t H5Sget_simple_extent_npoints(hid_t space_id);
H5_DLL int H5Sget_simple_extent_ndims(hid_t space_id);
@ -134,6 +134,16 @@ H5_DLL hssize_t H5Sget_select_hyper_nblocks(hid_t spaceid);
H5_DLL herr_t H5Sget_select_hyper_blocklist(hid_t spaceid, hsize_t startblock,
hsize_t numblocks, hsize_t buf[/*numblocks*/]);
/* Symbols defined for compatibility with previous versions of the HDF5 API.
*
* Use of these symbols is deprecated.
*/
#ifndef H5_NO_DEPRECATED_SYMBOLS
/* Function prototypes */
H5_DLL herr_t H5Sencode1(hid_t obj_id, void *buf, size_t *nalloc);
#endif /* H5_NO_DEPRECATED_SYMBOLS */
#ifdef __cplusplus
}
#endif

View File

@ -61,12 +61,14 @@ FUNCTION: H5Oget_info_by_name; ; v18, v112
FUNCTION: H5Oget_info_by_idx; ; v18, v112
FUNCTION: H5Ovisit; ; v18, v112
FUNCTION: H5Ovisit_by_name; ; v18, v112
FUNCTION: H5Pencode; ; v110, v112
FUNCTION: H5Pget_filter; ; v10, v18
FUNCTION: H5Pget_filter_by_id; ; v16, v18
FUNCTION: H5Pinsert; ; v14, v18
FUNCTION: H5Pregister; ; v14, v18
FUNCTION: H5Rdereference; ; v10, v110
FUNCTION: H5Rget_obj_type; ; v16, v18
FUNCTION: H5Sencode; ; v18, v112
FUNCTION: H5Tarray_create; ; v14, v18
FUNCTION: H5Tcommit; ; v10, v18
FUNCTION: H5Tget_array_dims; ; v14, v18

View File

@ -102,7 +102,7 @@ libhdf5_la_SOURCES= H5.c H5checksum.c H5dbg.c H5system.c H5timer.c H5trace.c \
H5R.c H5Rint.c H5Rdeprec.c \
H5UC.c \
H5RS.c \
H5S.c H5Sall.c H5Sdbg.c H5Shyper.c H5Snone.c H5Spoint.c \
H5S.c H5Sall.c H5Sdbg.c H5Sdeprec.c H5Shyper.c H5Snone.c H5Spoint.c \
H5Sselect.c H5Stest.c \
H5SL.c \
H5SM.c H5SMbtree2.c H5SMcache.c H5SMmessage.c H5SMtest.c \

File diff suppressed because it is too large Load Diff

View File

@ -466,13 +466,13 @@ encode_plist(hid_t plist_id, int little_endian, int word_length, const char *fil
HDassert(ret > 0);
/* first call to encode returns only the size of the buffer needed */
if((ret = H5Pencode(plist_id, NULL, &temp_size)) < 0)
if((ret = H5Pencode2(plist_id, NULL, &temp_size, H5P_DEFAULT)) < 0)
HDassert(ret > 0);
temp_buf = (void *)HDmalloc(temp_size);
HDassert(temp_buf);
if((ret = H5Pencode(plist_id, temp_buf, &temp_size)) < 0)
if((ret = H5Pencode2(plist_id, temp_buf, &temp_size, H5P_DEFAULT)) < 0)
HDassert(ret > 0);
fd = HDopen(filename, O_RDWR | O_CREAT | O_TRUNC, H5_POSIX_CREATE_MODE_RW);

File diff suppressed because it is too large Load Diff

View File

@ -490,16 +490,20 @@ test_reference_obj(void)
** test_reference_region(): Test basic H5R (reference) object reference code.
** Tests references to various kinds of objects
**
** Note: The libver_low/libver_high parameters are added to create the file
** with the low and high bounds setting in fapl.
** Please see the RFC for "H5Sencode/H5Sdecode Format Change".
**
****************************************************************/
static void
test_reference_region(H5F_libver_t libver_low, H5F_libver_t libver_high)
{
hid_t fid1; /* HDF5 File IDs */
hid_t fid1; /* HDF5 File IDs */
hid_t fapl = -1; /* File access property list */
hid_t dset1, /* Dataset ID */
hid_t dset1, /* Dataset ID */
dset2; /* Dereferenced dataset ID */
hid_t sid1, /* Dataspace ID #1 */
sid2; /* Dataspace ID #2 */
hid_t sid1, /* Dataspace ID #1 */
sid2; /* Dataspace ID #2 */
hid_t dapl_id; /* Dataset access property list */
hsize_t dims1[] = {SPACE1_DIM1},
dims2[] = {SPACE2_DIM1, SPACE2_DIM2};
@ -508,24 +512,24 @@ test_reference_region(H5F_libver_t libver_low, H5F_libver_t libver_high)
hsize_t count[SPACE2_RANK]; /* Element count of hyperslab */
hsize_t block[SPACE2_RANK]; /* Block size of hyperslab */
hsize_t coord1[POINT1_NPOINTS][SPACE2_RANK]; /* Coordinates for point selection */
hsize_t *coords; /* Coordinate buffer */
hsize_t low[SPACE2_RANK]; /* Selection bounds */
hsize_t high[SPACE2_RANK]; /* Selection bounds */
hdset_reg_ref_t *wbuf, /* buffer to write to disk */
*rbuf; /* buffer read from disk */
hdset_reg_ref_t nvrbuf[3]={{0},{101},{255}}; /* buffer with non-valid refs */
uint8_t *dwbuf, /* Buffer for writing numeric data to disk */
*drbuf; /* Buffer for reading numeric data from disk */
uint8_t *tu8; /* Temporary pointer to uint8 data */
H5O_type_t obj_type; /* Type of object */
int i, j; /* counting variables */
hssize_t hssize_ret; /* hssize_t return value */
htri_t tri_ret; /* htri_t return value */
herr_t ret; /* Generic return value */
haddr_t addr = HADDR_UNDEF; /* test for undefined reference */
hid_t dset_NA; /* Dataset id for undefined reference */
hid_t space_NA; /* Dataspace id for undefined reference */
hsize_t dims_NA[1] = {1}; /* Dims array for undefined reference */
hsize_t *coords; /* Coordinate buffer */
hsize_t low[SPACE2_RANK]; /* Selection bounds */
hsize_t high[SPACE2_RANK]; /* Selection bounds */
hdset_reg_ref_t *wbuf, /* buffer to write to disk */
*rbuf; /* buffer read from disk */
hdset_reg_ref_t nvrbuf[3]={{0},{101},{255}}; /* buffer with non-valid refs */
uint8_t *dwbuf, /* Buffer for writing numeric data to disk */
*drbuf; /* Buffer for reading numeric data from disk */
uint8_t *tu8; /* Temporary pointer to uint8 data */
H5O_type_t obj_type; /* Type of object */
int i, j; /* counting variables */
hssize_t hssize_ret; /* hssize_t return value */
htri_t tri_ret; /* htri_t return value */
herr_t ret; /* Generic return value */
haddr_t addr = HADDR_UNDEF; /* test for undefined reference */
hid_t dset_NA; /* Dataset id for undefined reference */
hid_t space_NA; /* Dataspace id for undefined reference */
hsize_t dims_NA[1] = {1}; /* Dims array for undefined reference */
hdset_reg_ref_t wdata_NA[1], /* Write buffer */
rdata_NA[1]; /* Read buffer */
@ -634,8 +638,14 @@ test_reference_region(H5F_libver_t libver_low, H5F_libver_t libver_high)
VERIFY(hssize_ret, (hssize_t)H5S_UNLIMITED, "H5Sget_select_npoints");
/* Store third dataset region */
ret = H5Rcreate(&wbuf[2], fid1, "/Dataset2", H5R_DATASET_REGION, sid2);
CHECK(ret, FAIL, "H5Rcreate");
H5E_BEGIN_TRY {
ret = H5Rcreate(&wbuf[2], fid1, "/Dataset2", H5R_DATASET_REGION, sid2);
} H5E_END_TRY;
if(libver_high < H5F_LIBVER_V110)
VERIFY(ret, FAIL, "H5Rcreate");
else
CHECK(ret, FAIL, "H5Rcreate");
ret = H5Rget_obj_type2(dset1, H5R_DATASET_REGION, &wbuf[0], &obj_type);
CHECK(ret, FAIL, "H5Rget_obj_type2");

View File

@ -420,11 +420,11 @@ test_api_get_ex_dcpl(test_api_config_t config, hid_t fapl, hid_t dcpl,
size_t plist_buf_size;
/* Encode property list to plist_buf */
if(H5Pencode(dcpl, NULL, &plist_buf_size) < 0)
if(H5Pencode2(dcpl, NULL, &plist_buf_size, fapl) < 0)
TEST_ERROR
if(NULL == (plist_buf = HDmalloc(plist_buf_size)))
TEST_ERROR
if(H5Pencode(dcpl, plist_buf, &plist_buf_size) < 0)
if(H5Pencode2(dcpl, plist_buf, &plist_buf_size, fapl) < 0)
TEST_ERROR
/* Decode serialized property list to *ex_dcpl */
@ -469,7 +469,7 @@ error:
/* Main test function */
static int
test_api(test_api_config_t config, hid_t fapl)
test_api(test_api_config_t config, hid_t fapl, H5F_libver_t low)
{
char filename[FILENAME_BUF_SIZE];
hid_t dcpl = -1; /* Dataset creation property list */
@ -618,7 +618,8 @@ test_api(test_api_config_t config, hid_t fapl)
TEST_ERROR
/* Get examination DCPL */
if(test_api_get_ex_dcpl(config, fapl, dcpl, &ex_dcpl, vspace[0], filename, (hsize_t)213) < 0)
if(test_api_get_ex_dcpl(config, fapl, dcpl, &ex_dcpl, vspace[0], filename,
(low >= H5F_LIBVER_V112)?(hsize_t)99:(low >= H5F_LIBVER_V110?174:213)) < 0)
TEST_ERROR
/* Test H5Pget_virtual_count */
@ -1025,7 +1026,8 @@ test_api(test_api_config_t config, hid_t fapl)
}
/* Get examination DCPL */
if(test_api_get_ex_dcpl(config, fapl, dcpl, &ex_dcpl, vspace[0], filename, (hsize_t)697) < 0)
if(test_api_get_ex_dcpl(config, fapl, dcpl, &ex_dcpl, vspace[0], filename,
(low >= H5F_LIBVER_V112)?(hsize_t)607:(hsize_t)697) < 0)
TEST_ERROR
/* Test H5Pget_virtual_count */
@ -11410,6 +11412,11 @@ test_dapl_values(hid_t fapl_id)
*
* Purpose: Tests datasets with virtual layout
*
* Note:
* Tests are modified to test with the low/high bounds combination
* set in fapl.
* Please see RFC for "H5Sencode/H5Sdecode Format Change".
*
* Return: EXIT_SUCCESS/EXIT_FAILURE
*-------------------------------------------------------------------------
*/
@ -11418,8 +11425,11 @@ main(void)
{
char filename[FILENAME_BUF_SIZE];
hid_t fapl;
hid_t my_fapl = -1; /* File access property list */
int test_api_config;
unsigned bit_config;
unsigned latest = FALSE; /* Using the latest library version bound */
H5F_libver_t low, high; /* Low and high bounds */
int nerrors = 0;
/* Testing setup */
@ -11428,21 +11438,59 @@ main(void)
h5_fixname(FILENAME[0], fapl, filename, sizeof(filename));
for(test_api_config = (int)TEST_API_BASIC; test_api_config < (int)TEST_API_NTESTS; test_api_config++)
nerrors += test_api((test_api_config_t)test_api_config, fapl);
for(bit_config = 0; bit_config < TEST_IO_NTESTS; bit_config++) {
HDprintf("Config: %s%s%s\n", bit_config & TEST_IO_CLOSE_SRC ? "closed source dataset, " : "", bit_config & TEST_IO_DIFFERENT_FILE ? "different source file" : "same source file", bit_config & TEST_IO_REOPEN_VIRT ? ", reopen virtual file" : "");
nerrors += test_basic_io(bit_config, fapl);
nerrors += test_vds_prefix_first(bit_config, fapl);
nerrors += test_unlim(bit_config, fapl);
nerrors += test_printf(bit_config, fapl);
nerrors += test_all(bit_config, fapl);
}
/* Set to use the latest file format */
if((my_fapl = H5Pcopy(fapl)) < 0) TEST_ERROR
nerrors += test_dapl_values(fapl);
/* Loop through all the combinations of low/high version bounds */
for(low = H5F_LIBVER_EARLIEST; low < H5F_LIBVER_NBOUNDS; low++) {
for(high = H5F_LIBVER_EARLIEST; high < H5F_LIBVER_NBOUNDS; high++) {
char msg[80]; /* Message for file version bounds */
char *low_string; /* The low bound string */
char *high_string; /* The high bound string */
/* Verify symbol table messages are cached */
nerrors += (h5_verify_cached_stabs(FILENAME, fapl) < 0 ? 1 : 0);
/* Invalid combinations, just continue */
if(high == H5F_LIBVER_EARLIEST || high < low)
continue;
/* Test virtual dataset only for V110 and above */
if(high < H5F_LIBVER_V110)
continue;
/* Whether to use latest hyperslab/point selection version */
if(low >= H5F_LIBVER_V112)
latest = TRUE;
/* Set the low/high version bounds */
if(H5Pset_libver_bounds(my_fapl, low, high) < 0)
TEST_ERROR
/* Display testing info */
low_string = h5_get_version_string(low);
high_string = h5_get_version_string(high);
HDsprintf(msg, "Testing virtual dataset with file version bounds: (%s, %s):", low_string, high_string);
HDputs(msg);
for(test_api_config = (int)TEST_API_BASIC; test_api_config < (int)TEST_API_NTESTS; test_api_config++)
nerrors += test_api((test_api_config_t)test_api_config, my_fapl, low);
for(bit_config = 0; bit_config < TEST_IO_NTESTS; bit_config++) {
HDprintf("Config: %s%s%s\n", bit_config & TEST_IO_CLOSE_SRC ? "closed source dataset, " : "", bit_config & TEST_IO_DIFFERENT_FILE ? "different source file" : "same source file", bit_config & TEST_IO_REOPEN_VIRT ? ", reopen virtual file" : "");
nerrors += test_basic_io(bit_config, my_fapl);
nerrors += test_vds_prefix_first(bit_config, my_fapl);
nerrors += test_unlim(bit_config, my_fapl);
nerrors += test_printf(bit_config, my_fapl);
nerrors += test_all(bit_config, my_fapl);
}
nerrors += test_dapl_values(my_fapl);
/* Verify symbol table messages are cached */
nerrors += (h5_verify_cached_stabs(FILENAME, my_fapl) < 0 ? 1 : 0);
} /* end for high */
} /* end for low */
if(H5Pclose(my_fapl) < 0)
TEST_ERROR
if(nerrors)
goto error;

View File

@ -33,12 +33,12 @@ test_encode_decode(hid_t orig_pl, int mpi_rank, int recv_proc)
int send_size = 0;
/* first call to encode returns only the size of the buffer needed */
ret = H5Pencode(orig_pl, NULL, &buf_size);
ret = H5Pencode2(orig_pl, NULL, &buf_size, H5P_DEFAULT);
VRFY((ret >= 0), "H5Pencode succeeded");
sbuf = (uint8_t *)HDmalloc(buf_size);
ret = H5Pencode(orig_pl, sbuf, &buf_size);
ret = H5Pencode2(orig_pl, sbuf, &buf_size, H5P_DEFAULT);
VRFY((ret >= 0), "H5Pencode succeeded");
/* this is a temp fix to send this size_t */