summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorDana Robinson <derobins@hdfgroup.org>2019-01-08 15:34:58 (GMT)
committerDana Robinson <derobins@hdfgroup.org>2019-01-08 15:34:58 (GMT)
commit905766fa3e51a470c02328a63d92182d4a8481bf (patch)
tree3999be21febfadfda29ca306623c9c2c23aca07e
parentd9b1ec3ce8672cd9c308f72baedc8a6f7bb9474c (diff)
downloadhdf5-905766fa3e51a470c02328a63d92182d4a8481bf.zip
hdf5-905766fa3e51a470c02328a63d92182d4a8481bf.tar.gz
hdf5-905766fa3e51a470c02328a63d92182d4a8481bf.tar.bz2
Fortran wrappers for dataset obj header minimization API calls.
-rw-r--r--fortran/src/H5Fff.F9093
-rw-r--r--fortran/src/H5Pff.F9091
-rw-r--r--fortran/src/hdf5_fortrandll.def.in4
-rw-r--r--fortran/test/tH5F.F901
-rw-r--r--fortran/test/tH5P.F9052
-rw-r--r--src/H5Fpublic.h2
6 files changed, 240 insertions, 3 deletions
diff --git a/fortran/src/H5Fff.F90 b/fortran/src/H5Fff.F90
index 9c8b941..cc51f37 100644
--- a/fortran/src/H5Fff.F90
+++ b/fortran/src/H5Fff.F90
@@ -946,4 +946,97 @@ CONTAINS
END SUBROUTINE h5fget_file_image_f
+!****s* H5F (F03)/h5fget_dset_no_attrs_hint_f_F03
+!
+! NAME
+! h5fget_dset_no_attrs_hint_f
+!
+! PURPOSE
+! Gets the value of the "minimize dataset headers" value which creates
+! smaller dataset object headers when its set and no attributes are present.
+!
+! INPUTS
+! file_id - Target file identifier.
+!
+! OUTPUTS
+! minimize - Value of the setting.
+! hdferr - error code:
+! 0 on success and -1 on failure
+!
+! AUTHOR
+! Dana Robinson
+! January 2019
+!
+! Fortran2003 Interface:
+ SUBROUTINE h5fget_dset_no_attrs_hint_f(file_id, minimize, hdferr)
+ IMPLICIT NONE
+ INTEGER(HID_T) , INTENT(IN) :: file_id
+ LOGICAL , INTENT(OUT) :: minimize
+ INTEGER , INTENT(OUT) :: hdferr
+!*****
+ LOGICAL(C_BOOL) :: c_minimize
+
+ INTERFACE
+ INTEGER FUNCTION h5fget_dset_no_attrs_hint_c(file_id, minimize) BIND(C, NAME='H5Fget_dset_no_attrs_hint')
+ IMPORT :: HID_T, C_BOOL
+ IMPLICIT NONE
+ INTEGER(HID_T), INTENT(IN), VALUE :: file_id
+ LOGICAL(C_BOOL), INTENT(OUT) :: minimize
+ END FUNCTION h5fget_dset_no_attrs_hint_c
+ END INTERFACE
+
+ hdferr = INT(h5fget_dset_no_attrs_hint_c(file_id, c_minimize))
+
+ ! Transfer value of C C_BOOL type to Fortran LOGICAL
+ minimize = c_minimize
+
+ END SUBROUTINE h5fget_dset_no_attrs_hint_f
+
+!****s* H5F (F03)/h5fset_dset_no_attrs_hint_f_F03
+!
+! NAME
+! h5fset_dset_no_attrs_hint_f
+!
+! PURPOSE
+! Sets the value of the "minimize dataset headers" value which creates
+! smaller dataset object headers when its set and no attributes are present.
+!
+! INPUTS
+! file_id - Target file identifier.
+! minimize - Value of the setting.
+!
+! OUTPUTS
+! hdferr - error code:
+! 0 on success and -1 on failure
+!
+! AUTHOR
+! Dana Robinson
+! January 2019
+!
+! Fortran2003 Interface:
+ SUBROUTINE h5fset_dset_no_attrs_hint_f(file_id, minimize, hdferr)
+ IMPLICIT NONE
+ INTEGER(HID_T) , INTENT(IN) :: file_id
+ LOGICAL , INTENT(IN) :: minimize
+ INTEGER , INTENT(OUT) :: hdferr
+!*****
+ LOGICAL(C_BOOL) :: c_minimize
+
+ INTERFACE
+ INTEGER FUNCTION h5fset_dset_no_attrs_hint_c(file_id, minimize) BIND(C, NAME='H5Fset_dset_no_attrs_hint')
+ IMPORT :: HID_T, C_BOOL
+ IMPLICIT NONE
+ INTEGER(HID_T), INTENT(IN), VALUE :: file_id
+ LOGICAL(C_BOOL), INTENT(IN), VALUE :: minimize
+ END FUNCTION h5fset_dset_no_attrs_hint_c
+ END INTERFACE
+
+ ! Transfer value of Fortran LOGICAL to C C_BOOL type
+ c_minimize = minimize
+
+ hdferr = INT(h5fset_dset_no_attrs_hint_c(file_id, c_minimize))
+
+ END SUBROUTINE h5fset_dset_no_attrs_hint_f
+
END MODULE H5F
+
diff --git a/fortran/src/H5Pff.F90 b/fortran/src/H5Pff.F90
index 455c72e..13a2953 100644
--- a/fortran/src/H5Pff.F90
+++ b/fortran/src/H5Pff.F90
@@ -8023,8 +8023,97 @@ SUBROUTINE h5pget_virtual_dsetname_f(dcpl_id, index, name, hdferr, name_len)
END SUBROUTINE h5pget_virtual_dsetname_f
+!****s* H5P (F03)/h5pget_dset_no_attrs_hint_f_F03
+!
+! NAME
+! h5pget_dset_no_attrs_hint_f
+!
+! PURPOSE
+! Gets the value of the "minimize dataset headers" value which creates
+! smaller dataset object headers when its set and no attributes are present.
+!
+! INPUTS
+! dcpl_id - Target dataset creation property list identifier.
+!
+! OUTPUTS
+! minimize - Value of the setting.
+! hdferr - error code:
+! 0 on success and -1 on failure
+!
+! AUTHOR
+! Dana Robinson
+! January 2019
+!
+! Fortran2003 Interface:
+ SUBROUTINE h5pget_dset_no_attrs_hint_f(dcpl_id, minimize, hdferr)
+ IMPLICIT NONE
+ INTEGER(HID_T) , INTENT(IN) :: dcpl_id
+ LOGICAL , INTENT(OUT) :: minimize
+ INTEGER , INTENT(OUT) :: hdferr
+!*****
+ LOGICAL(C_BOOL) :: c_minimize
-END MODULE H5P
+ INTERFACE
+ INTEGER FUNCTION h5pget_dset_no_attrs_hint_c(dcpl_id, minimize) BIND(C, NAME='H5Pget_dset_no_attrs_hint')
+ IMPORT :: HID_T, C_BOOL
+ IMPLICIT NONE
+ INTEGER(HID_T), INTENT(IN), VALUE :: dcpl_id
+ LOGICAL(C_BOOL), INTENT(OUT) :: minimize
+ END FUNCTION h5pget_dset_no_attrs_hint_c
+ END INTERFACE
+
+ hdferr = INT(h5pget_dset_no_attrs_hint_c(dcpl_id, c_minimize))
+ ! Transfer value of C C_BOOL type to Fortran LOGICAL
+ minimize = c_minimize
+ END SUBROUTINE h5pget_dset_no_attrs_hint_f
+
+!****s* H5P (F03)/h5pset_dset_no_attrs_hint_f_F03
+!
+! NAME
+! h5pset_dset_no_attrs_hint_f
+!
+! PURPOSE
+! Sets the value of the "minimize dataset headers" value which creates
+! smaller dataset object headers when its set and no attributes are present.
+!
+! INPUTS
+! dcpl_id - Target dataset creation property list identifier.
+! minimize - Value of the setting.
+!
+! OUTPUTS
+! hdferr - error code:
+! 0 on success and -1 on failure
+!
+! AUTHOR
+! Dana Robinson
+! January 2019
+!
+! Fortran2003 Interface:
+ SUBROUTINE h5pset_dset_no_attrs_hint_f(dcpl_id, minimize, hdferr)
+ IMPLICIT NONE
+ INTEGER(HID_T) , INTENT(IN) :: dcpl_id
+ LOGICAL , INTENT(IN) :: minimize
+ INTEGER , INTENT(OUT) :: hdferr
+!*****
+ LOGICAL(C_BOOL) :: c_minimize
+
+ INTERFACE
+ INTEGER FUNCTION h5pset_dset_no_attrs_hint_c(dcpl_id, minimize) BIND(C, NAME='H5Pset_dset_no_attrs_hint')
+ IMPORT :: HID_T, C_BOOL
+ IMPLICIT NONE
+ INTEGER(HID_T), INTENT(IN), VALUE :: dcpl_id
+ LOGICAL(C_BOOL), INTENT(IN), VALUE :: minimize
+ END FUNCTION h5pset_dset_no_attrs_hint_c
+ END INTERFACE
+
+ ! Transfer value of Fortran LOGICAL to C C_BOOL type
+ c_minimize = minimize
+
+ hdferr = INT(h5pset_dset_no_attrs_hint_c(dcpl_id, c_minimize))
+
+ END SUBROUTINE h5pset_dset_no_attrs_hint_f
+
+END MODULE H5P
diff --git a/fortran/src/hdf5_fortrandll.def.in b/fortran/src/hdf5_fortrandll.def.in
index 2edba5a..f3458cb 100644
--- a/fortran/src/hdf5_fortrandll.def.in
+++ b/fortran/src/hdf5_fortrandll.def.in
@@ -99,6 +99,8 @@ H5F_mp_H5FIS_HDF5_F
H5F_mp_H5FGET_NAME_F
H5F_mp_H5FGET_FILESIZE_F
H5F_mp_H5FGET_FILE_IMAGE_F
+H5F_mp_H5FGET_DSET_NO_ATTRS_HINT_F
+H5F_mp_H5FSET_DSET_NO_ATTRS_HINT_F
; H5G
H5G_mp_H5GOPEN_F
H5G_mp_H5GCREATE_F
@@ -329,6 +331,8 @@ H5P_mp_H5PGET_VIRTUAL_VSPACE_F
H5P_mp_H5PGET_VIRTUAL_SRCSPACE_F
H5P_mp_H5PGET_VIRTUAL_FILENAME_F
H5P_mp_H5PGET_VIRTUAL_DSETNAME_F
+H5P_mp_H5PGET_DSET_NO_ATTRS_HINT_F
+H5P_mp_H5PSET_DSET_NO_ATTRS_HINT_F
; Parallel
@H5_NOPAREXP@H5P_mp_H5PSET_FAPL_MPIO_F
@H5_NOPAREXP@H5P_mp_H5PGET_FAPL_MPIO_F
diff --git a/fortran/test/tH5F.F90 b/fortran/test/tH5F.F90
index d51803b..2501996 100644
--- a/fortran/test/tH5F.F90
+++ b/fortran/test/tH5F.F90
@@ -858,5 +858,4 @@ CONTAINS
END SUBROUTINE file_space
-
END MODULE TH5F
diff --git a/fortran/test/tH5P.F90 b/fortran/test/tH5P.F90
index 563926b..ed35b63 100644
--- a/fortran/test/tH5P.F90
+++ b/fortran/test/tH5P.F90
@@ -444,6 +444,7 @@ SUBROUTINE test_chunk_cache(cleanup, total_error)
INTEGER(size_t) rdcc_nelmts
INTEGER(size_t) rdcc_nbytes
REAL :: rdcc_w0
+ LOGICAL :: minimize ! Flag for minimized headers
CALL h5_fixname_f(filename, fix_filename, H5P_DEFAULT_F, error)
IF (error .NE. 0) THEN
@@ -648,6 +649,57 @@ SUBROUTINE test_chunk_cache(cleanup, total_error)
CALL verify("H5Pget_chunk_cache_f", INT(nbytes_2), INT(nbytes_4), total_error)
CALL verify("H5Pget_chunk_cache_f", w0_3, w0_4, total_error)
+ ! Check that the dataset object header minimization hint
+ ! can be set and retrieved.
+
+ ! H5P version
+ ! Check the default value
+ minimize = .TRUE.
+ CALL h5pget_dset_no_attrs_hint_f(dcpl, minimize, error)
+ CALL check("h5pget_dset_no_attrs_hint_f",error,total_error)
+ if(error .eq. 0 .and. minimize .neqv. .FALSE.) then
+ total_error = total_error + 1
+ write(*,*) "Default dataset minimize flag was incorrect (H5P)"
+ endif
+
+ ! Check setter
+ minimize = .TRUE.
+ CALL h5pset_dset_no_attrs_hint_f(dcpl, minimize, error)
+ CALL check("h5pset_dset_no_attrs_hint_f",error,total_error)
+
+ ! Check getter
+ minimize = .FALSE.
+ CALL h5pget_dset_no_attrs_hint_f(dcpl, minimize, error)
+ CALL check("h5pget_dset_no_attrs_hint_f",error,total_error)
+ if(error .eq. 0 .and. minimize .neqv. .TRUE.) then
+ total_error = total_error + 1
+ write(*,*) "Unable to get correct dataset minimize flag (H5P)"
+ endif
+
+ ! H5F version
+ ! Check the default value
+ minimize = .TRUE.
+ CALL h5fget_dset_no_attrs_hint_f(fid, minimize, error)
+ CALL check("h5fget_dset_no_attrs_hint_f",error,total_error)
+ if(error .eq. 0 .and. minimize .neqv. .FALSE.) then
+ total_error = total_error + 1
+ write(*,*) "Default dataset minimize flag was incorrect (H5F)"
+ endif
+
+ ! Check setter
+ minimize = .TRUE.
+ CALL h5fset_dset_no_attrs_hint_f(fid, minimize, error)
+ CALL check("h5fset_dset_no_attrs_hint_f",error,total_error)
+
+ ! Check getter
+ minimize = .FALSE.
+ CALL h5fget_dset_no_attrs_hint_f(fid, minimize, error)
+ CALL check("h5fget_dset_no_attrs_hint_f",error,total_error)
+ if(error .eq. 0 .and. minimize .neqv. .TRUE.) then
+ total_error = total_error + 1
+ write(*,*) "Unable to get correct dataset minimize flag (H5F)"
+ endif
+
! Close
CALL H5Dclose_f(dsid, error)
diff --git a/src/H5Fpublic.h b/src/H5Fpublic.h
index c4bf0b4..9f1ed01 100644
--- a/src/H5Fpublic.h
+++ b/src/H5Fpublic.h
@@ -234,7 +234,7 @@ H5_DLL herr_t H5Fflush(hid_t object_id, H5F_scope_t scope);
H5_DLL herr_t H5Fclose(hid_t file_id);
H5_DLL hid_t H5Fget_create_plist(hid_t file_id);
H5_DLL hid_t H5Fget_access_plist(hid_t file_id);
-H5_DLL herr_t H5Fget_intent(hid_t file_id, unsigned * intent);
+H5_DLL herr_t H5Fget_intent(hid_t file_id, unsigned *intent);
H5_DLL ssize_t H5Fget_obj_count(hid_t file_id, unsigned types);
H5_DLL ssize_t H5Fget_obj_ids(hid_t file_id, unsigned types, size_t max_objs, hid_t *obj_id_list);
H5_DLL herr_t H5Fget_vfd_handle(hid_t file_id, hid_t fapl, void **file_handle);