HDFFV-10405: Using h5fget_obj_count_f with a file id of H5F_OBJ_ALL_F does not work properly

h5fget_obj_count_f with H5F_OBJ_ALL_F counted objects created in h5open_f, which should not be included in the count. The function now returns the correct number of objects (i.e., objects created in h5open are not included in the total).
This commit is contained in:
M. Scot Breitenfeld 2018-06-08 14:19:11 -05:00
parent e87be2e9e7
commit c52d04320b
3 changed files with 90 additions and 2 deletions

View File

@ -42,6 +42,9 @@ MODULE H5F
USE H5GLOBAL
IMPLICIT NONE
! Number of objects opened in H5open_f
INTEGER(SIZE_T) :: H5OPEN_NUM_OPEN_OBJ
CONTAINS
!****s* H5F/h5fcreate_f
!
@ -616,9 +619,14 @@ CONTAINS
INTEGER(SIZE_T), INTENT(OUT) :: obj_count
END FUNCTION h5fget_obj_count_c
END INTERFACE
hdferr = h5fget_obj_count_c(file_id, obj_type, obj_count)
! Don't include objects created by H5open in the H5F_OBJ_ALL_F count
IF(file_id.EQ.INT(H5F_OBJ_ALL_F,HID_T))THEN
obj_count = obj_count - H5OPEN_NUM_OPEN_OBJ
ENDIF
END SUBROUTINE h5fget_obj_count_f
!****s* H5F/h5fget_obj_ids_f

View File

@ -169,8 +169,10 @@ CONTAINS
! October 13, 2011
! Fortran90 Interface:
SUBROUTINE h5open_f(error)
USE H5F, ONLY : h5fget_obj_count_f, H5OPEN_NUM_OPEN_OBJ
IMPLICIT NONE
INTEGER, INTENT(OUT) :: error
INTEGER(SIZE_T) :: H5OPEN_NUM_OPEN_OBJ_LOC = 0
!*****
INTERFACE
@ -612,6 +614,10 @@ CONTAINS
H5_SZIP_EC_OM_F = H5LIB_flags(1)
H5_SZIP_NN_OM_F = H5LIB_flags(2)
CALL h5fget_obj_count_f(INT(H5F_OBJ_ALL_F,HID_T), H5F_OBJ_ALL_F, H5OPEN_NUM_OPEN_OBJ_LOC, error)
H5OPEN_NUM_OPEN_OBJ = H5OPEN_NUM_OPEN_OBJ_LOC
END SUBROUTINE h5open_f
!****s* H5LIB/h5close_f

View File

@ -103,6 +103,10 @@ CONTAINS
!
INTEGER :: i, j
!number of objects
INTEGER(SIZE_T) :: obj_count
INTEGER(HID_T) :: t1, t2, t3, t4
!
!data buffers
!
@ -133,11 +137,51 @@ CONTAINS
CALL h5_fixname_f(filename2, fix_filename2, H5P_DEFAULT_F, error)
if(error .ne. 0) stop
! Test object counts
CALL h5tcopy_f(H5T_NATIVE_CHARACTER, t1, error)
CALL check(" h5tcopy_f",error,total_error)
CALL h5tcopy_f(H5T_NATIVE_CHARACTER, t2, error)
CALL check(" h5tcopy_f",error,total_error)
CALL h5tcopy_f(H5T_NATIVE_CHARACTER, t3, error)
CALL check(" h5tcopy_f",error,total_error)
CALL h5tcopy_f(H5T_NATIVE_CHARACTER, t4, error)
CALL check(" h5tcopy_f",error,total_error)
CALL h5fget_obj_count_f(INT(H5F_OBJ_ALL_F,HID_T), H5F_OBJ_ALL_F, obj_count, error)
CALL check(" h5fget_obj_count_f",error,total_error)
IF(obj_count.NE.4)THEN
total_error = total_error + 1
ENDIF
!
!Create first file "mount1.h5" using default properties.
!
CALL h5fcreate_f(fix_filename1, H5F_ACC_TRUNC_F, file1_id, error)
CALL check("h5fcreate_f",error,total_error)
CALL check("h5fcreate_f",error,total_error)
CALL h5fget_obj_count_f(INT(H5F_OBJ_ALL_F,HID_T), H5F_OBJ_ALL_F, obj_count, error)
CALL check(" h5fget_obj_count_f",error,total_error)
IF(obj_count.NE.5)THEN
total_error = total_error + 1
ENDIF
CALL h5tclose_f(t1, error)
CALL check("h5tclose_f",error,total_error)
CALL h5tclose_f(t2, error)
CALL check("h5tclose_f",error,total_error)
CALL h5tclose_f(t3, error)
CALL check("h5tclose_f",error,total_error)
CALL h5tclose_f(t4, error)
CALL check("h5tclose_f",error,total_error)
CALL h5fget_obj_count_f(INT(H5F_OBJ_ALL_F,HID_T), H5F_OBJ_ALL_F, obj_count, error)
CALL check(" h5fget_obj_count_f",error,total_error)
IF(obj_count.NE.1)THEN
total_error = total_error + 1
ENDIF
!
!Create group "/G" inside file "mount1.h5".
@ -211,9 +255,23 @@ CONTAINS
!
CALL h5fopen_f (fix_filename1, H5F_ACC_RDWR_F, file1_id, error)
CALL check("hfopen_f",error,total_error)
CALL h5fget_obj_count_f(INT(H5F_OBJ_ALL_F,HID_T), H5F_OBJ_ALL_F, obj_count, error)
CALL check(" h5fget_obj_count_f",error,total_error)
IF(obj_count.NE.1)THEN
total_error = total_error + 1
ENDIF
CALL h5fopen_f (fix_filename2, H5F_ACC_RDWR_F, file2_id, error)
CALL check("h5fopen_f",error,total_error)
CALL h5fget_obj_count_f(INT(H5F_OBJ_ALL_F,HID_T), H5F_OBJ_ALL_F, obj_count, error)
CALL check(" h5fget_obj_count_f",error,total_error)
IF(obj_count.NE.2)THEN
total_error = total_error + 1
ENDIF
!
!mount the second file under the first file's "/G" group.
!
@ -245,6 +303,7 @@ CONTAINS
do i = 1, NX
do j = 1, NY
IF (data_out(i,j) .NE. data_in(i, j)) THEN
total_error = total_error + 1
END IF
end do
end do
@ -267,11 +326,26 @@ CONTAINS
!
!Close both files.
!
CALL h5fget_obj_count_f(INT(H5F_OBJ_ALL_F,HID_T), H5F_OBJ_ALL_F, obj_count, error)
CALL check(" h5fget_obj_count_f",error,total_error)
IF(obj_count.NE.2)THEN
total_error = total_error + 1
ENDIF
CALL h5fclose_f(file1_id, error)
CALL check("h5fclose_f",error,total_error)
CALL h5fclose_f(file2_id, error)
CALL check("h5fclose_f",error,total_error)
CALL h5fget_obj_count_f(INT(H5F_OBJ_ALL_F,HID_T), H5F_OBJ_ALL_F, obj_count, error)
CALL check(" h5fget_obj_count_f",error,total_error)
IF(obj_count.NE.0)THEN
total_error = total_error + 1
ENDIF
if(cleanup) CALL h5_cleanup_f(filename1, H5P_DEFAULT_F, error)
CALL check("h5_cleanup_f", error, total_error)
if(cleanup) CALL h5_cleanup_f(filename2, H5P_DEFAULT_F, error)