SUBROUTINE h5pclose_f(prp_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pclose_f
SUBROUTINE h5pcopy_f(prp_id, new_prp_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(OUT) :: new_prp_id
! Identifier of property list
! copy
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pcopy_f
SUBROUTINE h5pcreate_f(classtype, prp_id, hdferr)
IMPLICIT NONE
INTEGER, INTENT(IN) :: classtype ! The type of the property list
! to be created. Possible values
! are:
! H5P_FILE_CREATE_F
! H5P_FILE_ACCESS_F
! H5P_DATASET_CREATE_F
! H5P_DATASET_XFER_F
! H5P_MOUNT_F
INTEGER(HID_T), INTENT(OUT) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pcreate_f
SUBROUTINE h5pget_chunk_f(prp_id, ndims, dims, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: ndims ! Number of chunk dimensions to
! to return
INTEGER(HSIZE_T), DIMENSION(ndims), INTENT(OUT) :: dims
! Array containing sizes of
! chunk dimensions
INTEGER, INTENT(OUT) :: hdferr ! Error code
! chunk rank on success and -1 on failure
END SUBROUTINE h5pget_chunk_f
SUBROUTINE h5pget_class_f(prp_id, classtype, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: classtype ! The type of the property list
! to be created. Possible values
! are:
! H5P_NO_CLASS
! H5P_FILE_CREATE_F
! H5P_FILE_ACCESS_F
! H5PE_DATASET_CREATE_F
! H5P_DATASET_XFER_F
! H5P_MOUNT_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_class_f
SUBROUTINE h5pget_fill_value_f(prp_id, type_id, fillvalue, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier of
! of fillvalue datatype
! (in memory)
TYPE(VOID), INTENT(IN) :: fillvalue ! Fillvalue
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_fill_value_f
SUBROUTINE h5pset_chunk_f(prp_id, ndims, dims, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: ndims ! Number of chunk dimensions
INTEGER(HSIZE_T), DIMENSION(ndims), INTENT(IN) :: dims
! Array containing sizes of
! chunk dimensions
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_chunk_f
SUBROUTINE h5pset_deflate_f(prp_id, level, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: level ! Compression level
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_deflate_f
SUBROUTINE h5pset_fill_value_f(prp_id, type_id, fillvalue, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier of
! of fillvalue datatype
! (in memory)
TYPE(VOID), INTENT(IN) :: fillvalue ! Fillvalue
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_fill_value_f
SUBROUTINE h5pget_version_f(prp_id, boot, freelist, &
stab, shhdr, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, DIMENSION(:), INTENT(OUT) :: boot !array to put boot
!block version number
INTEGER, DIMENSION(:), INTENT(OUT) :: freelist !array to put global
!freelist version number
INTEGER, DIMENSION(:), INTENT(OUT) :: stab !array to put symbol
!table version number
INTEGER, DIMENSION(:), INTENT(OUT) :: shhdr !array to put shared
!object header version number
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_version_f
SUBROUTINE h5pset_userblock_f (prp_id, size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: size ! Size of the user-block in bytes
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_userblock_f
SUBROUTINE h5pget_userblock_f(prp_id, block_size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), DIMENSION(:), INTENT(OUT) :: block_size
! Size of the user-block in bytes
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_userblock_f
SUBROUTINE h5pset_sizes_f (prp_id, sizeof_addr, sizeof_size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(SIZE_T), INTENT(IN) :: sizeof_addr ! Size of an object
! offset in bytes
INTEGER(SIZE_T), INTENT(IN) :: sizeof_size ! Size of an object
! length in bytes
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_sizes_f
SUBROUTINE h5pget_sizes_f(prp_id, sizeof_addr, sizeof_size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(SIZE_T), DIMENSION(:), INTENT(OUT) :: sizeof_addr
! Size of an object address
! in bytes
INTEGER(SIZE_T), DIMENSION(:), INTENT(OUT) :: sizeof_size
! Size of an object in bytes
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_sizes_f
SUBROUTINE h5pset_sym_k_f (prp_id, ik, lk, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: ik ! Symbol table tree rank
INTEGER, INTENT(IN) :: lk ! Symbol table node size
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_sym_k_f
SUBROUTINE h5pget_sym_k_f(prp_id, ik, lk, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: ik ! Symbol table tree rank
INTEGER, INTENT(OUT) :: lk ! Symbol table node size
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_sym_k_f
SUBROUTINE h5pset_istore_k_f (prp_id, ik, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: ik ! 1/2 rank of chunked storage
! B-tree
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_istore_k_f
SUBROUTINE h5pget_istore_k_f(prp_id, ik, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: ik ! 1/2 rank of chunked storage B-tree
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_istore_k_f
SUBROUTINE h5pget_driver_f(prp_id, driver, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: driver ! Low-level file driver identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_driver_f
SUBROUTINE h5pset_alignment_f(prp_id, threshold, alignment, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: threshold ! Threshold value
INTEGER(HSIZE_T), INTENT(IN) :: alignment ! alignment value
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_alignment_f
SUBROUTINE h5pget_alignment_f(prp_id, threshold, alignment, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: threshold ! Threshold value
INTEGER(HSIZE_T), INTENT(OUT) :: alignment ! alignment value
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_alignment_f
SUBROUTINE h5pset_cache_f(prp_id, mdc_nelmts,rdcc_nelmts, rdcc_nbytes, rdcc_w0, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: mdc_nelmts ! Number of elements (objects)
! in the meta data cache
INTEGER(SIZE_T), INTENT(IN) :: rdcc_nelmts ! Number of elements (objects)
! in the meta data cache
INTEGER(SIZE_T), INTENT(IN) :: rdcc_nbytes ! Total size of the raw data
! chunk cache, in bytes
REAL, INTENT(IN) :: rdcc_w0 ! Preemption policy
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_cache_f
SUBROUTINE h5pget_cache_f(prp_id, mdc_nelmts, rdcc_nelmts, rdcc_nbytes, rdcc_w0, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: mdc_nelmts ! Number of elements (objects)
! in the meta data cache
INTEGER(SIZE_T), INTENT(OUT) :: rdcc_nelmts ! Number of elements (objects)
! in the meta data cache
INTEGER(SIZE_T), INTENT(OUT) :: rdcc_nbytes ! Total size of the raw data
! chunk cache, in bytes
REAL, INTENT(OUT) :: rdcc_w0 ! Preemption policy
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_cache_f
SUBROUTINE h5pset_fapl_split_f(prp_id, meta_ext, meta_plist, raw_ext, raw_plist, hdferr)
IMPLICIT NONE
INTEGER(HID_T),INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*),INTENT(IN) :: meta_ext ! Name of the extension for
! the metafile filename
INTEGER(HID_T),INTENT(IN) :: meta_plist ! Identifier of the meta file
! access property list
CHARACTER(LEN=*),INTENT(IN) :: raw_ext ! Name extension for the raw file filename
INTEGER(HID_T),INTENT(IN) :: raw_plist ! Identifier of the raw file
! access property list
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_fapl_split_f
SUBROUTINE h5pset_gc_references_f (prp_id, gc_reference, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: gc_reference ! the flag for garbage collecting
! references for the file
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_gc_references_f
SUBROUTINE h5pget_gc_references_f (prp_id, gc_reference, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: gc_reference ! the flag for garbage collecting
! references for the file
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_gc_references_f
SUBROUTINE h5pset_layout_f (prp_id, layout, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: layout ! Type of storage layout for raw data
! possible values are:
! H5D_COMPACT_F
! H5D_CONTIGUOUS_F
! H5D_CHUNKED_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_layout_f
SUBROUTINE h5pget_layout_f (prp_id, layout, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: layout ! Type of storage layout for raw data
! possible values are:
! H5D_COMPACT_F
! H5D_CONTIGUOUS_F
! H5D_CHUNKED_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
SUBROUTINE h5pset_filter_f(prp_id, filter, flags, cd_nelmts, cd_values, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: filter ! Filter to be added to the pipeline.
INTEGER, INTENT(IN) :: flags ! Bit vector specifying certain general
! properties of the filter.
INTEGER(SIZE_T), INTENT(IN) :: cd_nelmts ! Number of elements in cd_values.
INTEGER, DIMENSION(*), INTENT(IN) :: cd_values ! Auxiliary data for the filter.
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_filter_f
SUBROUTINE h5pget_filter_f(prp_id, filter_number, flags, cd_nelmts, cd_values, namelen, name, filter_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: filter_number ! Sequence number within the filter
! pipeline of the filter for which
! information is sought
INTEGER, DIMENSION(*), INTENT(OUT) :: cd_values ! Auxiliary data for the filter.
INTEGER, INTENT(OUT) :: flags ! Bit vector specifying certain general
! properties of the filter.
INTEGER(SIZE_T), INTENT(INOUT) :: cd_nelmts ! Number of elements in cd_values.
INTEGER(SIZE_T), INTENT(IN) :: namelen ! Anticipated number of characters in name.
CHARACTER(LEN=*), INTENT(OUT) :: name ! Name of the filter
INTEGER, INTENT(OUT) :: filter_id ! filter identification number
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_filter_f
SUBROUTINE h5pset_external_f(prp_id, name, offset,bytes, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of an external file
INTEGER, INTENT(IN) :: offset ! Offset, in bytes, from the beginning
! of the file to the location in the file
! where the data starts.
INTEGER(HSIZE_T), INTENT(IN) :: bytes ! Number of bytes reserved in the
! file for the data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_external_f
SUBROUTINE h5pget_external_count_f (prp_id, count, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: count ! number of external files for the
! specified dataset
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_external_count_f
SUBROUTINE h5pget_external_f(prp_id, idx, name_size, name, offset,bytes, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: idx ! External file index.
INTEGER, INTENT(IN) :: name_size ! Maximum length of name array
CHARACTER(LEN=*), INTENT(OUT) :: name ! Name of an external file
INTEGER, INTENT(OUT) :: offset ! Offset, in bytes, from the beginning
! of the file to the location in the file
! where the data starts.
INTEGER(HSIZE_T), INTENT(OUT) :: bytes ! Number of bytes reserved in the
! file for the data
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_external_f
SUBROUTINE h5pset_hyper_cache_f(prp_id, cache, limit, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: cache !
INTEGER, INTENT(IN) :: limit ! Maximum size of the hyperslab block to
!cache. 0 (zero) indicates no limit.
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_hyper_cache_f
SUBROUTINE h5pget_hyper_cache_f(prp_id, cache, limit, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: cache !
INTEGER, INTENT(OUT) :: limit ! Maximum size of the hyperslab block to
!cache. 0 (zero) indicates no limit.
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_hyper_cache_f
SUBROUTINE h5pset_btree_ratios_f(prp_id, left, middle, right, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
REAL, INTENT(IN) :: left ! The B-tree split ratio for left-most nodes.
REAL, INTENT(IN) :: middle ! The B-tree split ratio for all other nodes
REAL, INTENT(IN) :: right ! The B-tree split ratio for right-most
! nodes and lone nodes.
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_btree_ratios_f
SUBROUTINE h5pget_btree_ratios_f(prp_id, left, middle, right, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
REAL, INTENT(OUT) :: left ! The B-tree split ratio for left-most nodes.
REAL, INTENT(OUT) :: middle ! The B-tree split ratio for all other nodes
REAL, INTENT(OUT) :: right ! The B-tree split ratio for right-most
! nodes and lone nodes.
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_btree_ratios_f
SUBROUTINE h5pset_fapl_mpio_f(prp_id, comm, info, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: comm ! MPI communicator to be used for file open
! as defined in MPI_FILE_OPEN of MPI-2
INTEGER, INTENT(IN) :: info ! MPI info object to be used for file open
! as defined in MPI_FILE_OPEN of MPI-2
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_fapl_mpio_f
SUBROUTINE h5pget_fapl_mpio_f(prp_id, comm, info, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: comm ! buffer to return communicator
INTEGER, INTENT(IN) :: info ! buffer to return info object
! as defined in MPI_FILE_OPEN of MPI-2
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_fapl_mpio_f
SUBROUTINE h5pset_dxpl_mpio_f(prp_id, data_xfer_mode, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: data_xfer_mode ! Data transfer mode.
! Possible values are:
! H5FD_MPIO_INDEPENDENT_F
! H5FD_MPIO_COLLECTIVE_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_dxpl_mpio_f
SUBROUTINE h5pget_dxpl_mpio_f(prp_id, data_xfer_mode, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: data_xfer_mode ! Data transfer mode.
! Possible values are:
! H5FD_MPIO_INDEPENDENT_F
! H5FD_MPIO_COLLECTIVE_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_dxpl_mpio_f
SUBROUTINE h5pset_fapl_core_f(prp_id, increment, backing_store, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(SIZE_T), INTENT(IN) :: increment ! File block size in bytes
LOGICAL, INTENT(IN) :: backing_store ! flag to indicate that
! entire file contents are flushed to a file
! with the same name as this core file
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_fapl_core_f
SUBROUTINE h5pget_fapl_core_f(prp_id, increment, backing_store, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(SIZE_T), INTENT(OUT) :: increment ! File block size in bytes
LOGICAL, INTENT(OUT) :: backing_store ! flag to indicate that
! entire file contents are flushed to a file
! with the same name as this core file
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_fapl_core_f
SUBROUTINE h5pset_fapl_multi_f(prp_id, memb_map, memb_fapl, memb_name, &
memb_addr, relax, hdferr)
IMPLICIT NONE
INTEGER(HID_T),INTENT(IN) :: prp_id ! Property list identifier
INTEGER,DIMENSION(0:H5FD_MEM_NTYPES_F-1),INTENT(IN) :: memb_map
INTEGER(HID_T),DIMENSION(0:H5FD_MEM_NTYPES_F-1),INTENT(IN) :: memb_fapl
CHARACTER(LEN=*),DIMENSION(0:H5FD_MEM_NTYPES_F-1),INTENT(IN) :: memb_name
REAL, DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(IN) :: memb_addr
! Numbers in the interval [0,1) (e.g. 0.0 0.1 0.5 0.2 0.3 0.4)
! real address in the file will be calculated as X*HADDR_MAX
LOGICAL, INTENT(IN) :: relax
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_fapl_multi_f
SUBROUTINE h5pset_fapl_multi_f(prp_id, relax, hdferr)
IMPLICIT NONE
INTEGER(HID_T),INTENT(IN) :: prp_id ! Property list identifier
LOGICAL, INTENT(IN) :: relax
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_fapl_multi_f
SUBROUTINE h5pget_fapl_multi_f(prp_id, memb_map, memb_fapl, memb_name, &
memb_addr, relax, hdferr)
IMPLICIT NONE
INTEGER(HID_T),INTENT(IN) :: prp_id ! Property list identifier
INTEGER,DIMENSION(0:H5FD_MEM_NTYPES_F-1),INTENT(OUT) :: memb_map
INTEGER(HID_T),DIMENSION(0:H5FD_MEM_NTYPES_F-1),INTENT(OUT) :: memb_fapl
CHARACTER(LEN=*),DIMENSION(0:H5FD_MEM_NTYPES_F-1),INTENT(OUT) :: memb_name
REAL, DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(OUT) :: memb_addr
! Numbers in the interval [0,1) (e.g. 0.0 0.1 0.5 0.2 0.3 0.4)
! real address in the file will be calculated as X*HADDR_MAX
LOGICAL, INTENT(OUT) :: relax
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_fapl_multi_f
SUBROUTINE h5pset_fapl_family_f(prp_id, imemb_size, memb_plist, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: memb_size ! Logical size, in bytes,
! of each family member
INTEGER(HID_T), INTENT(IN) :: memb_plist ! identifier of the file
! access property list to
! be used for each family
! member
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_fapl_family_f
SUBROUTINE h5pget_fapl_family_f(prp_id, imemb_size, memb_plist, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: memb_size ! Logical size, in bytes,
! of each family member
INTEGER(HID_T), INTENT(OUT) :: memb_plist ! identifier of the file
! access property list to
! be used for each family
! member
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_fapl_family_f
SUBROUTINE h5pset_fapl_sec2_f(prp_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_fapl_sec2_f
SUBROUTINE h5pset_fapl_stdio_f(prp_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_fapl_stdio_f
SUBROUTINE h5pget_fclose_degree_f(fapl_id, degree, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: fapl_id ! File access property list identifier
INTEGER, INTENT(OUT) :: degree ! Info about file close behavior,
! possible values:
! H5F_CLOSE_DEFAULT_F
! H5F_CLOSE_WEAK_F
! H5F_CLOSE_SEMI_F
! H5F_CLOSE_STRONG_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_fclose_degree_f
SUBROUTINE h5pset_fclose_degree_f(fapl_id, degree, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: fapl_id ! File access property list identifier
INTEGER, INTENT(IN) :: degree ! Info about file close behavior,
! possible values:
! H5F_CLOSE_DEFAULT_F
! H5F_CLOSE_WEAK_F
! H5F_CLOSE_SEMI_F
! H5F_CLOSE_STRONG_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_fclose_degree_f
SUBROUTINE h5pequal_f(plist1_id, plist2_id, flag, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist1_id ! property list identifier
INTEGER(HID_T), INTENT(IN) :: plist2_id ! property list identifier
LOGICAL, INTENET(OUT) :: flag ! flag, equals to .TRUE. if
! if lists are equal, otherwise
! equals to .FALSE.
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pequal_f
SUBROUTINE h5pget_driver_f(prp_id, driver_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! File access or data
! transfer property list
! identifier
INTEGER(HID_T), INTENT(OUT) :: driver_id ! low-level file driver identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_driver_f
SUBROUTINE h5pset_buffer_f(plist_id, size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset trasfer
! property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: size ! Conversion buffer size
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_buffer_f
SUBROUTINE h5pget_buffer_f(plist_id, size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset trasfer
! property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: size ! Conversion buffer size
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_buffer_f
SUBROUTINE h5pfill_value_defined_f(plist_id, flag, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset creaton
! property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: flag ! fill value status flag
! H5D_FILL_VALUE_ERROR_F
! H5D_FILL_VALUE_UNDEFINED_F
! H5D_FILL_VALUE_DEFAULT_F
! H5D_FILL_VALUE_USER_DEFINED_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pfill_value_defined_f
SUBROUTINE h5pget_alloc_time_f(plist_id, flag, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset creaton
! property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: flag ! allocation time flag
! Possible values are:
! H5D_ALLOC_TIME_ERROR_F
! H5D_ALLOC_TIME_DEFAULT_F
! H5D_ALLOC_TIME_EARLY_F
! H5D_ALLOC_TIME_LATE_F
! H5D_ALLOC_TIME_INCR_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_alloc_time_f
SUBROUTINE h5pset_alloc_time_f(plist_id, flag, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset creaton
! property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: flag ! allocation time flag
! Possible values are:
! H5D_ALLOC_TIME_ERROR_F
! H5D_ALLOC_TIME_DEFAULT_F
! H5D_ALLOC_TIME_EARLY_F
! H5D_ALLOC_TIME_LATE_F
! H5D_ALLOC_TIME_INCR_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_alloc_time_f
SUBROUTINE h5pget_fill_time_f(plist_id, flag, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset creaton
! property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: flag ! fill time flag
! Possible values are:
! H5D_FILL_TIME_ERROR_F
! H5D_FILL_TIME_ALLOC_F
! H5D_FILL_TIME_NEVER_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_fill_time_f
SUBROUTINE h5pset_fill_time_f(plist_id, flag, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset creaton
! property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: flag ! file time flag
! Possible values are:
! H5D_FILL_TIME_ERROR_F
! H5D_FILL_TIME_ALLOC_F
! H5D_FILL_TIME_NEVER_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_fill_time_f
SUBROUTINE h5pset_meta_block_size_f(plist_id, size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! File access
! property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: size ! Metadata block size
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_meta_block_size_f
SUBROUTINE h5pget_meta_block_size_f(plist_id, size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! File access
! property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: size ! Metadata block size
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_meta_block_size_f
SUBROUTINE h5pset_sieve_buf_size_f(plist_id, size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! File access
! property list identifier
INTEGER(SIZE_T), INTENT(IN) :: size ! Sieve buffer size
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_sieve_buf_size_f
SUBROUTINE h5pget_sieve_buf_size_f(plist_id, size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! File access
! property list identifier
INTEGER(SIZE_T), INTENT(OUT) :: size ! Sieve buffer size
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_sieve_buf_size_f
SUBROUTINE h5pset_hyper_vector_size_f(plist_id, size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset transfer
! property list identifier
INTEGER(SIZE_T), INTENT(IN) :: size ! Vector size
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_hyper_vector_size_f
SUBROUTINE h5pget_hyper_vector_size_f(plist_id, size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset transfer
! property list identifier
INTEGER(SIZE_T), INTENT(OUT) :: size ! Vector size
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_hyper_vector_size_f
SUBROUTINE h5pset_small_data_block_size_f(plist_id, size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! File access
! property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: size ! Small raw data block size
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_small_data_block_size_f
SUBROUTINE h5pget_small_data_block_size_f(plist_id, size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! File access
! property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: size ! Small raw data block size
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_small_data_block_size_f
SUBROUTINE h5pcreate_class_f(parent, name, class, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: parent ! parent property list class
! identifier
! Possible values include:
! H5P_NO_CLASS_F
! H5P_FILE_CREATE_F
! H5P_FILE_ACCESS_F
! H5P_DATASET_CREATE_F
! H5P_DATASET_XFER_F
! H5P_MOUNT_F
CHARACTER(LEN=*), INTENT(IN) :: name ! name of property tocreate
INTEGER(HID_T), INTENT(OUT) :: class ! property list class identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pcreate_class_f
SUBROUTINE h5pregister_f
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: class ! Property list class identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to register
INTEGER(SIZE_T), INTENT(IN) :: size ! Size of the property value
TYPE, INTENT(IN) :: value ! Property value
! Supported types are:
! INTEGER, REAL, DOUBLE PRECISION
! and CHARACTER(LEN=*)
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pregister_f
SUBROUTINE h5pinsert_f
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist ! Property list class identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to insert
INTEGER(SIZE_T), INTENT(IN) :: size ! Size of the property value
TYPE, INTENT(IN) :: value ! Property value
! Supported types are:
! INTEGER, REAL, DOUBLE PRECISION
! and CHARACTER(LEN=*)
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pinsert_f
SUBROUTINE h5pset_f(plid, name, value, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plid ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to set
TYPE, INTENT(IN) :: value ! Property value
! Supported types are:
! INTEGER, REAL, DOUBLE PRECISION
! and CHARACTER(LEN=*)
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_f
SUBROUTINE h5pget_f(plid, name, value, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plid ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to get
TYPE, INTENT(OUT) :: value ! Property value
! Supported types are:
! INTEGER, REAL, DOUBLE PRECISION
! and CHARACTER(LEN=*)
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_f
SUBROUTINE h5pexist_f(prp_id, name, flag, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
LOGICAL, INTENT(OUT) :: flag ! .TRUE. if exists, .FALSE.
! otherwise
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pexist_f
SUBROUTINE h5pget_size_f(prp_id, name, size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to query
INTEGER(SIZE_T), INTENT(OUT) :: size ! Size in bytes
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_size_f
SUBROUTINE h5pget_nprops_f(prp_id, nprops, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(SIZE_T), INTENT(OUT) :: nporps ! Number of properties
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_nprops_f
SUBROUTINE h5pget_class_parent_f(prp_id, parent_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(OUT) :: parent_id ! Parent class property list
! identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_class_parent_f
SUBROUTINE h5pisa_class_f(plist, pclass, flag, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist ! Property list identifier
INTEGER(HID_T), INTENT(IN) :: pclass ! Class identifier
LOGICAL, INTENT(OUT) :: flag ! Logical flag
! .TRUE. if a member,
! .FALSE. otherwise
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pisa_class_f
SUBROUTINE h5pequal_f(id1, id2, flag, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: id1 ! Property list identifier
INTEGER(HID_T), INTENT(IN) :: id2 ! Property list identifier
LOGICAL, INTENT(OUT) :: flag ! Logical flag
! .TRUE. if porperty lists or
! classes are equal,
! .FALSE. otherwise
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pequal_f
SUBROUTINE h5pcopy_prop_f(dst_id, src_id, name, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dst_id ! Destination property list
! identifier
INTEGER(HID_T), INTENT(IN) :: src_id ! Source property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Property name
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pcopy_prop_f
SUBROUTINE h5premove_f(plid, name, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plid ! property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! name of property to remove
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5premove_f
SUBROUTINE h5punregister_f(class, name, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: class ! property list class identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! name of property to remove
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5punregister_f
SUBROUTINE h5pclose_list_f(plist, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist ! Property list identifier to close
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pclose_list_f
SUBROUTINE h5pclose_class_f(class, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: class ! Property list class
! identifier to close
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pclose_close_f
SUBROUTINE h5pget_class_name_f(prp_id, name, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier to
! query
CHARACTER(LEN=*), INTENT(INOUT) :: name ! Buffer to retireve class name
INTEGER, INTENT(OUT) :: hdferr ! Error code, possible values:
! Success: Actual lenght of the class name
! If provided buffer "name" is
! smaller, than name will be
! truncated to fit into
! provided user buffer
! Failure: -1
END SUBROUTINE h5pget_class_name_f
SUBROUTINE h5pset_shuffle_f(prp_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_shuffle_f
SUBROUTINE h5pset_preserve_f(prp_id, flag, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset transfer property
! list identifier
LOGICAL, INTENT(IN) :: flag ! Status of for the dataset
! transfer property list
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_preserve_f
SUBROUTINE h5pget_preserve_f(prp_id, flag, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset transfer property
! list identifier
LOGICAL, INTENT(OUT) :: flag ! Status of for the dataset
! transfer property list
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_preserve_f
SUBROUTINE h5pset_edc_check_f(prp_id, flag, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset transfer property list identifier
INTEGER, INTENT(IN) :: flag ! EDC flag; possible values
! H5Z_DISABLE_EDC_F
! H5Z_ENABLE_EDC_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_edc_check_f
SUBROUTINE h5pget_edc_check_f(prp_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset transfer property list identifier
INTEGER, INTENT(OUT) :: flag ! EDC flag; possible values
! H5Z_DISABLE_EDC_F
! H5Z_ENABLE_EDC_F
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_edc_check_f
SUBROUTINE h5pset_szip_f(prp_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset creation property
! list identifier
INTEGER, INTENT(IN) :: options_mask ! A bit-mask conveying the
! desired SZIP options.
! Current valid values
! in Fortran are:
! H5_SZIP_AK13_OM_F
! H5_SZIP_CHIP_OM_F
! H5_SZIP_EC_OM_F
! H5_SZIP_NN_OM_F
! Or the sum of any combination
! of the above, e.g.,
! (H5_SZIP_AK13_OM_F + H5_SZIP_NN_OM_F).
! Check C reference manual
! regarding mutually-exclusive
! options.
INTEGER, INTENT(IN) :: pixels_per_block ! The number of pixels or data
! elements in each data block
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_szip_f
SUBROUTINE h5pset_fletcher32_f(prp_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset creation property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_fletcher32_f
SUBROUTINE h5pget_nfilters_f(prp_id, nfilters, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset creation property
! list identifier
INTEGER, INTENT(OUT) :: nfilters ! The number of filters in
! the pipeline
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_nfilters_f
SUBROUTINE h5pmodify_filter_f(prp_id, filter, flags, cd_nelmts, cd_values, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: filter ! Filter to be modified
INTEGER, INTENT(IN) :: flags ! Bit vector specifying certain general
! properties of the filter
INTEGER(SIZE_T), INTENT(IN) :: cd_nelmts ! Number of elements in cd_values
INTEGER, DIMENSION(*), INTENT(IN) :: cd_values ! Auxiliary data for the filter
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pmodify_filter_f
SUBROUTINE h5pget_filter_by_id_f(prp_id, filter_id, flags, cd_nelmts, cd_values, namelen, &
name, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: filter_id ! Filter identifier
INTEGER(SIZE_T), INTENT(INOUT) :: cd_nelmts ! Number of elements in cd_values
INTEGER, DIMENSION(*), INTENT(OUT) :: cd_values ! Auxiliary data for the filter
INTEGER, INTENT(OUT) :: flags ! Bit vector specifying certain general
! properties of the filter
INTEGER(SIZE_T), INTENT(IN) :: namelen ! Anticipated number of characters in name
CHARACTER(LEN=*), INTENT(OUT) :: name ! Name of the filter
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pget_filter_by_id_f
SUBROUTINE h5pset_family_offset_f(prp_id, offset, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: offset ! Offset in bytes
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
END SUBROUTINE h5pset_family_offset_f