Search code examples
fortranhdf5

How do I identify which dataspace was left open and not closed in HDF5 fortran interface?


While using the fortran interface for HDF5, I created a file using:

      CALL h5fcreate_f(filename(1:len_file)                               &
   &          , H5F_ACC_TRUNC_F, file_id, error)

and closed datapace/datasets with

       CALL h5dclose_f(dataspace_id, error)
       CALL h5sclose_f(dataspace_id, error)

finally closed the file with

       CALL h5fclose_f(file_id, error)   

But the file is not being written immediately. I suspect this is because some dataset/dataspace is still open. Is there a routine to identify or close all open datasets/dataspaces. so the file can be closed?


Solution

  • You can query the number of open identifiers using H5Fget_obj_count_f. You can query the open identifiers themselves using H5Fget_obj_ids. The H5I* procedures then let you query the nature of those open identifiers.

    For example:

    PROGRAM test_hdf5_get_obj_ids
      USE HDF5
      IMPLICIT NONE
      
      INTEGER(HID_T) :: file_id
      INTEGER(HID_T) :: group_id
      INTEGER(HID_T) :: space_id
      INTEGER(HID_T) :: set_id
      INTEGER :: error
      
      REAL, ALLOCATABLE, TARGET :: data(:)
      
      data = [1.0, 2.0, 3.0]
      
      CALL H5open_f(error)
      IF (error < 0) ERROR STOP 'H5open_f failed'
      
      CALL H5Fcreate_f(  &
          NAME='test_hdf5.h5',  &
          ACCESS_FLAGS=H5F_ACC_TRUNC_F,  &   ! HDF5 docs dummy argument spelling error.
          FILE_ID=file_id,  &
          HDFERR=error )
      IF (error < 0) ERROR STOP 'H5Fcreate_f failed'
      
      CALL H5Gcreate_f(  &
          LOC_ID=file_id,  &
          NAME='Group',  &
          GRP_ID=group_id,  &
          HDFERR=error )
      IF (error < 0) ERROR STOP 'H5Gcreate_f failed'
      
      CALL H5Screate_simple_f(  &
          RANK=1,  &
          DIMS=SHAPE(data, KIND=HSIZE_T),  &
          SPACE_ID=space_id,  &
          HDFERR=error )
      IF (error < 0) ERROR STOP 'H5Screate_simple_f failed'
      
      CALL H5Dcreate_f(  &
          LOC_ID=group_id,  &
          NAME='Dataset',  &
          TYPE_ID=H5T_NATIVE_REAL,  &
          SPACE_ID=space_id,  &
          DSET_ID=set_id,  &
          HDFERR=error )
      IF (error < 0) ERROR STOP 'H5Dcreate_f failed'
      
      CALL H5Dwrite_f(  &
          DSET_ID=set_id,  &
          MEM_TYPE_ID=H5T_NATIVE_REAL,  &
          BUF=C_LOC(data),  &
          HDFERR=error )
      IF (error < 0) ERROR STOP 'H5Dwrite_f failed'
      
      CALL H5Dclose_f(set_id, error)
      CALL H5Sclose_f(space_id, error)
      ! CALL H5Gclose_f(group_id, error)    ! Oops - forgot this one.
      CALL H5Fclose_f(file_id, error)
      
      BLOCK
        INTEGER(SIZE_T) :: obj_count
        
        CALL H5Fget_obj_count_f(  &
            FILE_ID=INT(H5F_OBJ_ALL_F, HID_T),  &
            OBJ_TYPE=H5F_OBJ_ALL_F,  &
            OBJ_COUNT=obj_count,  &
            HDFERR=error )
        IF (error < 0) ERROR STOP 'H5Fget_obj_count_f failed'
        
        PRINT "(I0,' open identifiers')", obj_count
        
        BLOCK
          INTEGER(HID_T) :: obj_ids(obj_count)
          INTEGER :: i
          INTEGER :: type
          CHARACTER(:), ALLOCATABLE :: type_text
          
          CALL H5Fget_obj_ids_f(  &
            FILE_ID=INT(H5F_OBJ_ALL_F, HID_T),  &
            OBJ_TYPE=H5F_OBJ_ALL_F,  &
            MAX_OBJS=obj_count,  &
            OBJ_IDS=obj_ids,  &
            HDFERR=error )
          IF (error < 0) ERROR STOP 'H5F_get_obj_ids_f failed'
          
          DO i = 1, SIZE(obj_ids)
            CALL H5Iget_type_f(obj_ids(i), type, error)
            IF (error < 0) ERROR STOP 'H5Iget_type_f failed'
            
            IF (type == H5I_FILE_F) THEN
              type_text = 'file'
            ELSE IF (type == H5I_GROUP_F) THEN
              type_text = 'group'
            ELSE IF (type == H5I_DATATYPE_F) THEN
              type_text = 'datatype'
            ELSE IF (type == H5I_DATASPACE_F) THEN
              type_text = 'dataspace'
            ELSE IF (type == H5I_DATASET_F) THEN
              type_text = 'dataset'
            ELSE IF (type == H5I_ATTR_F) THEN
              type_text = 'attribute'
            ELSE
              type_text = 'unknown'
            END IF
            PRINT "('Open identifier ',I0,' is a ',A)", i, type_text
          END DO
        END BLOCK
      END BLOCK
      
      CALL H5close_f(error)
    END PROGRAM test_hdf5_get_obj_ids