Hi,
I am transitioning to HDF5 1.10.0 to use some of the new features in the
library, but noticed that some old subroutines I had in place for
writing integer attributes no longer compiled. Specifically, the
compiler complained that there was no subroutine matching my call to
H5AWRITE_F (using the Fortran 90 interface).
I am attaching a Fortran program which writes attributes to a test file
using two approaches. First, an attribute is written in the main body of
the program. Second, I call a subroutine and pass the desired value of
the attribute. In the second approach, the code does not compile with
HDF5 1.10.0 because the INTENT of the variable is IN (which in theory
should work). If the INTENT is changed to OUT or INOUT, the code
compiles and runs without any problem.
I have tested the same program using HDF5 1.8.17, and it works as
expected with INTENT(IN) for the subroutine interface. Checking the
online documentation
(www.hdfgroup.org/HDF5/doc/RM/RM_H5A.html#Annot-Write), the interface
does specify INTENT(IN) for the buf argument.
The HDF5 source code is a mystery to me, but I did some digging in the
build directories to see if I could find anything suspicious. In the
1.8.17 build, I found a file H5Aff_F90.f90 which looks like it contains
the interfaces for H5AWRITE_F. The argument buf does have INTENT(IN). In
the 1.10.0 build, I found a similar file H5_gen.F90. Here, all of the
routines, e.g., h5awrite_ikind_1_rank_0, have INTENT(INOUT) for buf.
Platforms tested: Personal linux desktop with gcc 4.9.3. Cray machine
with Cray compiler version 8.4.2. HDF5 installed with MPI support.
Thanks,
Matthew
!> @file ATTRIBUTE.F90
!> @author MPC
!> @brief Test writing integer attribute from subroutine call.
PROGRAM ATTRIBUTE_TEST
! Required modules.
USE ISO_FORTRAN_ENV,ONLY: INT32
USE HDF5
IMPLICIT NONE
! Data we want to write out.
INTEGER(KIND=INT32) :: dat = 1_INT32
! HDF5 file, attribute, and dataspace identifiers.
INTEGER(KIND=HID_T) :: file_id, att_id, spc_id
! Dimensions of the dataspace for the attribute.
INTEGER(KIND=HSIZE_T),DIMENSION(1) :: dims = [1]
! Used to determine HDF5 type parameters.
INTEGER(KIND=HID_T) :: h5prec
! Error handling.
INTEGER :: ierr
!
! Initialize the Fortran-HDF5 interface.
CALL H5OPEN_F(ierr)
!
! HDF5 type corresponding to INT32.
h5prec = H5KIND_TO_TYPE(INT32, H5_INTEGER_KIND)
!
! Create the HDF5 file.
CALL H5FCREATE_F('TEST.h5', H5F_ACC_TRUNC_F, file_id, ierr)
!
! Create the dataspace for the attribute.
CALL H5SCREATE_F(H5S_SCALAR_F, spc_id, ierr)
!
! Create the attribute.
CALL H5ACREATE_F(file_id, 'TEST1', h5prec, spc_id, att_id, ierr)
!
! Write out the attribute.
CALL H5AWRITE_F(att_id, h5prec, dat, dims, ierr)
!
! Close the attribute.
CALL H5ACLOSE_F(att_id, ierr)
!
! Close the attribute dataspace.
CALL H5SCLOSE_F(spc_id, ierr)
!
! Write out another attribute with a subroutine.
dat = 100_INT32
CALL WRITE_ATTRIBUTE(file_id, 'TEST2', dat)
!
! Close the HDF5 file.
CALL H5FCLOSE_F(file_id, ierr)
!
! Close the Fortran-HDF5 interface.
CALL H5CLOSE_F(ierr)
CONTAINS
!> Subroutine to write attribute to a given HDF5 object.
!!
!> @param[in] hdf5_id Object to attach the attribute to.
!> @param[in] nme Name for the attribute.
!> @param[in] var Data to write as the attribute.
SUBROUTINE WRITE_ATTRIBUTE(hdf5_id, nme, var)
USE ISO_FORTRAN_ENV,ONLY: INT32
USE HDF5
IMPLICIT NONE
! Calling arguments.
INTEGER(KIND=HID_T),INTENT(IN) :: hdf5_id
CHARACTER(LEN=*),INTENT(IN) :: nme
INTEGER(KIND=INT32),INTENT(IN) :: var
! Local variables.
! HDF5 identifiers for the dataspace and attribute.
INTEGER(KIND=HID_T) :: att_id, spc_id
! Dimensions of the dataspace for the attribute.
INTEGER(KIND=HSIZE_T),DIMENSION(1) :: dims = [1]
! Precision for the datatype in HDF5.
INTEGER(KIND=HID_T) :: h5prec
! Error handling.
INTEGER :: ierr
!
! Determine HDF5 datatype corresponding to INT32.
h5prec = H5KIND_TO_TYPE(INT32, H5_INTEGER_KIND)
!
! Create the dataspace for the attribute.
CALL H5SCREATE_F(H5S_SCALAR_F, spc_id, ierr)
!
! Create the attribute.
CALL H5ACREATE_F(hdf5_id, nme, h5prec, spc_id, att_id, ierr)
!
! Write out the attribute.
CALL H5AWRITE_F(att_id, h5prec, var, dims, ierr)
!
! Close the attribute.
CALL H5ACLOSE_F(att_id, ierr)
!
! Close the attribute dataspace.
CALL H5SCLOSE_F(spc_id, ierr)
END SUBROUTINE WRITE_ATTRIBUTE
END PROGRAM ATTRIBUTE_TEST
_______________________________________________
Hdf-forum is for HDF software users discussion.
[email protected]
http://lists.hdfgroup.org/mailman/listinfo/hdf-forum_lists.hdfgroup.org
Twitter: https://twitter.com/hdf5