The FORTRAN 90 API to HDF5
h5d: Datasets

 

 


 

 

FORTRAN interface:   h5dclose_f
          SUBROUTINE h5dclose_f(dset_id, hdferr)
            IMPLICIT NONE
            INTEGER(HID_T), INTENT(IN) :: dset_id ! Dataset identifier  
            INTEGER, INTENT(OUT) :: hdferr       ! Error code  
                                                 ! 0 on success and -1 on failure
          END SUBROUTINE h5dclose_f

 

 


 

 

FORTRAN interface:   h5dcreate_f
          SUBROUTINE h5dcreate_f(loc_id, name, type_id, space_id, dset_id, & 
                                 hdferr, creation_prp) 
            IMPLICIT NONE 
            INTEGER(HID_T), INTENT(IN) :: loc_id   ! File or group identifier
            CHARACTER(LEN=*), INTENT(IN) :: name   ! Name of the dataset 
            INTEGER(HID_T), INTENT(IN) :: type_id  ! Datatype identifier 
            INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
            INTEGER(HID_T), INTENT(OUT) :: dset_id ! Dataset identifier
            INTEGER, INTENT(OUT) :: hdferr       ! Error code 
                                                 ! 0 on success and -1 on failure
            INTEGER(HID_T), OPTIONAL, INTENT(IN) :: creation_prp
                                                   ! Dataset creation propertly 
                                                   ! list identifier , default
                                                   ! value is H5P_DEFAULT_F (6) 
          END SUBROUTINE h5dcreate_f  

 

 


 

 

FORTRAN interface:   h5dextend_f
          SUBROUTINE h5dextend_f(dataset_id, size, hdferr) 
            IMPLICIT NONE 
            INTEGER(HID_T), INTENT(IN) :: dataset_id      ! Dataset identifier
            INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN)  :: size
                                                          ! Array containing 
                                                          ! dimensions' sizes 
            INTEGER, INTENT(OUT) :: hdferr       ! Error code 
                                                 ! 0 on success and -1 on failure
          END SUBROUTINE h5dextend_f  

 

 


 

 

FORTRAN interface:   h5dget_create_plist_f
          SUBROUTINE h5dget_create_plist_f(dataset_id, creation_prp, hdferr) 
            IMPLICIT NONE 
            INTEGER(HID_T), INTENT(IN) :: dataset_id      ! Dataset identifier
            INTEGER(HID_T), INTENT(OUT) :: creation_id    ! Dataset creation
                                                          ! property list identifier
            INTEGER, INTENT(OUT) :: hdferr       ! Error code 
                                                 ! 0 on success and -1 on failure
          END SUBROUTINE h5dget_create_plist_f  

 

 


 

 

FORTRAN interface:   h5dget_space_f
          SUBROUTINE h5dget_space_f(dataset_id, dataspace_id, hdferr) 
            IMPLICIT NONE 
            INTEGER(HID_T), INTENT(IN) :: dataset_id      ! Dataset identifier
            INTEGER(HID_T), INTENT(OUT) :: dataspace_id   ! Dataspace identifier
            INTEGER, INTENT(OUT) :: hdferr       ! Error code 
                                                 ! 0 on success and -1 on failure
          END SUBROUTINE h5dget_space_f  

 

 


 

 

FORTRAN interface:   h5dget_type_f
          SUBROUTINE h5dget_type_f(dataset_id, datatype_id, hdferr) 
            IMPLICIT NONE 
            INTEGER(HID_T), INTENT(IN) :: dataset_id      ! Dataset identifier
            INTEGER(HID_T), INTENT(OUT) :: datatype_id    ! Datatype identifier
            INTEGER, INTENT(OUT) :: hdferr       ! Error code 
                                                 ! 0 on success and -1 on failure
          END SUBROUTINE h5dget_type_f  

 

 


 

 

FORTRAN interface:   h5dopen_f
          SUBROUTINE h5dopen_f(loc_id, name, dset_id, hdferr) 
            IMPLICIT NONE 
            INTEGER(HID_T), INTENT(IN) :: loc_id   ! File or group identifier
            CHARACTER(LEN=*), INTENT(IN) :: name   ! Name of the dataset 
            INTEGER(HID_T), INTENT(OUT) :: dset_id ! Dataset identifier
            INTEGER, INTENT(OUT) :: hdferr       ! Error code 
                                                 ! 0 on success and -1 on failure
          END SUBROUTINE h5dopen_f  

 

 


 

 

FORTRAN interface:   h5dread_f (for all datatypes except object and dataset region references)

          SUBROUTINE h5dread_f(dset_id, mem_type_id, buf, dims, hdferr, &
                               mem_space_id, file_space_id, xfer_prp)

            IMPLICIT NONE
            INTEGER(HID_T), INTENT(IN) :: dset_id   ! Dataset identifier
            INTEGER(HID_T), INTENT(IN) :: mem_type_id ! Memory datatype identifier
            TYPE, INTENT(INOUT) :: buf          ! Data buffer; may be a scalar or an array
            DIMENSION(*), INTEGER(HSIZE_T), INTENT(IN)  :: dims 
                                                ! Array to hold corresponding dimension 
                                                ! sizes of data buffer buf; dim(k) has 
                                                ! value of the k-th dimension of buffer buf;
                                                ! values are ignored if buf is a scalar
                                                ! 
                                                ! Deprecated type, will be removed in 
                                                ! Release 1.6:
                                                ! INTEGER, INTENT(IN)  :: dims(7)     
            INTEGER, INTENT(OUT) :: hdferr      ! Error code 
                                                ! 0 on success and -1 on failure
            INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id 
                                                ! Memory dataspace identfier 
                                                ! Default value is H5S_ALL_F 
            INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id 
                                                ! File dataspace identfier 
                                                ! Default value is H5S_ALL_F
            INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp 
                                                ! Transfer property list identifier 
                                                ! Default value is H5P_DEFAULT_F 
            
          END SUBROUTINE h5dread_f

 

FORTRAN interface:   h5dread_f (for object reference and dataset region reference datatypes)

          SUBROUTINE h5dread_f(dset_id, mem_type_id, buf, n, hdferr, &
                               mem_space_id, file_space_id, xfer_prp)

            IMPLICIT NONE
            INTEGER(HID_T), INTENT(IN) :: dset_id   ! Dataset identifier
            INTEGER(HID_T), INTENT(IN) :: mem_type_id ! Memory datatype identifier
            DIMENSION(*), INTEGER(HSIZE_T), INTENT(IN)  :: dims 
                                                ! Array to hold corresponding dimension 
                                                ! sizes of data buffer buf; dim(k) has 
                                                ! value of the k-th dimension of buffer buf;
                                                ! values are ignored if buf is a scalar
                                                ! 
                                                ! Deprecated type, will be removed in 
                                                ! Release 1.6:
                                                ! INTEGER, DIMENSION(7), INTENT(IN) :: dims
            TYPE(hobj_ref_t_f), DIMENSION(dims(1)), INTENT(INOUT) :: buf
                                                ! Data buffer of rank 1
            INTEGER, INTENT(OUT) :: hdferr      ! Error code 
                                                ! 0 on success and -1 on failure
            INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id 
                                                ! Memory dataspace identfier 
                                                ! Default value is H5S_ALL_F 
            INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id 
                                                ! File dataspace identfier 
                                                ! Default value is H5S_ALL_F
            INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp 
                                                ! Transfer property list identifier 
                                                ! Default value is H5P_DEFAULT_F 
            
          END SUBROUTINE h5dread_f

 

 


 

 

FORTRAN interface:   h5dwrite_f (for all datatypes except object and dataset region references)

          SUBROUTINE h5dwrite_f(dset_id, mem_type_id, buf, dims, hdferr, &
                                mem_space_id, file_space_id, xfer_prp)

            IMPLICIT NONE
            INTEGER(HID_T), INTENT(IN) :: dset_id   ! Dataset identifier
            INTEGER(HID_T), INTENT(IN) :: mem_type_id ! Memory datatype identifier
            TYPE, INTENT(IN) :: buf             ! Data buffer; may be a scalar or an array
            DIMENSION(*), INTEGER(HSIZE_T), INTENT(IN)  :: dims 
                                                ! Array to hold corresponding dimension 
                                                ! sizes of data buffer buf; dim(k) has 
                                                ! value of the k-th dimension of buffer buf;
                                                ! values are ignored if buf is a scalar
                                                ! 
                                                ! Deprecated type, will be removed in 
                                                ! Release 1.6:
                                                ! INTEGER, INTENT(IN)  :: dims(7)     
            INTEGER, INTENT(OUT) :: hdferr      ! Error code 
                                                ! 0 on success and -1 on failure
            INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id 
                                                ! Memory dataspace identfier 
                                                ! Default value is H5S_ALL_F
            INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id 
                                                ! File dataspace identfier 
                                                ! Default value is H5S_ALL_F
            INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp 
                                                ! Transfer property list identifier 
                                                ! Default value is H5P_DEFAULT_F 
            
          END SUBROUTINE h5dwrite_f

 

FORTRAN interface:   h5dwrite_f (for object reference and dataset region reference datatypes)

          SUBROUTINE h5dwrite_f(dset_id, mem_type_id, buf, n, hdferr, &
                                mem_space_id, file_space_id, xfer_prp)

            IMPLICIT NONE
            INTEGER(HID_T), INTENT(IN) :: dset_id   ! Dataset identifier
            INTEGER(HID_T), INTENT(IN) :: mem_type_id ! Memory datatype identifier
            DIMENSION(*), INTEGER(HSIZE_T), INTENT(IN)  :: dims 
                                                ! Array to hold corresponding dimension 
                                                ! sizes of data buffer buf; dim(k) has 
                                                ! value of the k-th dimension of buffer buf;
                                                ! values are ignored if buf is a scalar
                                                ! 
                                                ! Deprecated type, will be removed in 
                                                ! Release 1.6:
                                                ! INTEGER, DIMENSION(7), INTENT(IN) :: dims
            TYPE(hobj_ref_t_f), DIMENSION(dims(1)), INTENT(INOUT) :: buf
                                                ! Data buffer of rank 1
            INTEGER, INTENT(OUT) :: hdferr      ! Error code 
                                                ! 0 on success and -1 on failure
            INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id 
                                                ! Memory dataspace identfier 
                                                ! Default value is H5S_ALL_F
            INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id 
                                                ! File dataspace identfier 
                                                ! Default value is H5S_ALL_F
            INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp 
                                                ! Transfer property list identifier 
                                                ! Default value is H5P_DEFAULT_F 
            
          END SUBROUTINE h5dwrite_f

 

 


 

 

FORTRAN interface:   h5dget_storage_size_f
          SUBROUTINE h5dget_storage_size_f(dset_id, size, hdferr)
            IMPLICIT NONE
            INTEGER(HID_T), INTENT(IN) :: dset_id  ! Dataset identifier  
            INTEGER(HSIZE_T), INTENT(OUT)  :: size ! Amount of storage required for dataset
            INTEGER, INTENT(OUT) :: hdferr         ! Error code  
                                                   ! 0 on success and -1 on failure
          END SUBROUTINE h5dget_storage_size_f

 

 


 

 

FORTRAN interface:   h5dvlen_get_max_len_f
          SUBROUTINE h5dvlen_get_max_len_f(dset_id, size, hdferr)
            IMPLICIT NONE
            INTEGER(HID_T), INTENT(IN) :: dset_id  ! Dataset identifier  
            INTEGER(HID_T), INTENT(IN) :: type_id  ! Datatype identifier  
            INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier  
            
            INTEGER(SIZE_T), INTENT(OUT)  :: elem_len ! Maximum length of the element
            INTEGER, INTENT(OUT) :: hdferr         ! Error code  
                                                   ! 0 on success and -1 on failure
          END SUBROUTINE h5dvlen_get_max_len_f

 

 


 

 

FORTRAN interface:   h5dfill_f
          SUBROUTINE h5dfill_f(fill_value, space_id, buf, hdferr)
            IMPLICIT NONE
            TYPE, INTENET(IN) :: fill_value        ! Fill value; may be have one of the
                                                   ! following types:
                                                   ! INTEGER, REAL, DOUBLE PRECISION, CHARACTER
            INTEGER(HID_T), INTENT(IN) :: space_id ! Memory dataspace selection identifier 
            TYPE, DIMENSION(*) :: buf              ! Memory buffer to fill in; must have
                                                   ! the same datatype as fill value
            INTEGER, INTENT(OUT) :: hdferr         ! Error code  
                                                   ! 0 on success and -1 on failure
          END SUBROUTINE h5dfill_f

 

 


 

 

FORTRAN interface:   h5dget_space_status_f
          SUBROUTINE h5dget_space_status_f(dset_id, flag, hdferr)
            IMPLICIT NONE
            INTEGER(HID_T), INTENT(IN) :: dset_id  ! Dataset identifier 
            INTEGER, INTENET(OUT)      :: flag     ! Status flag ; possible values:
                                                   ! H5D_SPACE_STS_ERROR_F
                                                   ! H5D_SPACE_STS_NOT_ALLOCATED_F
                                                   ! H5D_SPACE_STS_PART_ALLOCATED_F
                                                   ! H5D_SPACE_STS_ALLOCATED_F
            INTEGER, INTENT(OUT) :: hdferr         ! Error code  
                                                   ! 0 on success and -1 on failure
          END SUBROUTINE h5dget_space_status_f

 

 


HDF Help Desk
Describes HDF5 Release 1.5, Unreleased Development Branch
Last modified: 19 March 2003