diff options
author | Scot Breitenfeld <brtnfld@hdfgroup.org> | 2008-04-30 19:23:26 (GMT) |
---|---|---|
committer | Scot Breitenfeld <brtnfld@hdfgroup.org> | 2008-04-30 19:23:26 (GMT) |
commit | 5773fd34bc5adf59b4530d95ac9f0c0585902803 (patch) | |
tree | 456ad239799382e1f083fb7fc74399e43b471912 /fortran/src/H5Pff.f90 | |
parent | 0138995d1ce2068db1f790503435a2121132d3ad (diff) | |
download | hdf5-5773fd34bc5adf59b4530d95ac9f0c0585902803.zip hdf5-5773fd34bc5adf59b4530d95ac9f0c0585902803.tar.gz hdf5-5773fd34bc5adf59b4530d95ac9f0c0585902803.tar.bz2 |
[svn-r14902] Merged fortran_1_8 branch changes r14505:14901 into the trunk. New fortran wrappers added.
Diffstat (limited to 'fortran/src/H5Pff.f90')
-rw-r--r-- | fortran/src/H5Pff.f90 | 1794 |
1 files changed, 1780 insertions, 14 deletions
diff --git a/fortran/src/H5Pff.f90 b/fortran/src/H5Pff.f90 index 1c1fb90..ed935e9 100644 --- a/fortran/src/H5Pff.f90 +++ b/fortran/src/H5Pff.f90 @@ -1943,7 +1943,7 @@ hdferr = h5pget_fapl_core_c(prp_id, increment, backing_store_flag) backing_store =.FALSE. - if (backing_store_flag .eq. 1) backing_store =.TRUE. + IF (backing_store_flag .EQ. 1) backing_store =.TRUE. END SUBROUTINE h5pget_fapl_core_f !---------------------------------------------------------------------- @@ -4665,19 +4665,18 @@ !---------------------------------------------------------------------- ! Name: h5pget_class_name_f ! -! Purpose: Queries the ithe name of a class. +! Purpose: Queries the name of a class. ! ! Inputs: ! prp_id - property list identifier to query ! Outputs: ! name - name of a class -! hdferr: - error code -! -! Success: Actual lenght of the class name -! If provided buffer "name" is -! smaller, than name will be -! truncated to fit into -! provided user buffer +! size - Actual length of the class name +! If provided buffer "name" is smaller, +! than name will be truncated to fit into +! provided user buffer +! hdferr: - error code +! Success: 0 ! Failure: -1 ! Optional parameters: ! NONE @@ -4685,12 +4684,12 @@ ! Programmer: Elena Pourmal ! October 9, 2002 ! -! Modifications: +! Modifications: Returned the size of name as an argument ! ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5pget_class_name_f(prp_id, name, hdferr) + SUBROUTINE h5pget_class_name_f(prp_id, name, size, hdferr) ! !This definition is needed for Windows DLLs !DEC$if defined(BUILD_HDF5_DLL) @@ -4699,7 +4698,9 @@ ! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier - CHARACTER(LEN=*), INTENT(INOUT) :: name ! Buffer to retireve class name + CHARACTER(LEN=*), INTENT(OUT) :: name ! Buffer to retireve class name + + INTEGER, INTENT(OUT) :: size ! Actual length of the class name INTEGER, INTENT(OUT) :: hdferr ! Error code INTEGER :: name_len @@ -4715,8 +4716,13 @@ INTEGER, INTENT(IN) :: name_len END FUNCTION h5pget_class_name_c END INTERFACE + name_len = LEN(name) - hdferr = h5pget_class_name_c(prp_id, name , name_len) + size = h5pget_class_name_c(prp_id, name, name_len) + + hdferr = 0 + IF(size.LT.0) hdferr = -1 + END SUBROUTINE h5pget_class_name_f !---------------------------------------------------------------------- @@ -6387,4 +6393,1764 @@ hdferr = h5premove_filter_c(prp_id, filter) END SUBROUTINE h5premove_filter_f - END MODULE H5P +!---------------------------------------------------------------------- +! Name: H5Pget_attr_phase_change_f +! +! Purpose: Retrieves attribute storage phase change thresholds +! +! Inputs: +! ocpl_id - Object (dataset or group) creation property list identifier +! Outputs: +! max_compact - Maximum number of attributes to be stored in compact storage +! (Default: 8) +! min_dense - Minimum number of attributes to be stored in dense storage +! (Default: 6) +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! January, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pget_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pget_attr_phase_change_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: ocpl_id ! Object (dataset or group) creation property list identifier + INTEGER, INTENT(OUT) :: max_compact ! Maximum number of attributes to be stored in compact storage + !(Default: 8) + INTEGER, INTENT(OUT) :: min_dense ! Minimum number of attributes to be stored in dense storage + ! (Default: 6) + INTEGER, INTENT(OUT) :: hdferr ! Error code +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pget_attr_phase_change_c(ocpl_id, max_compact, min_dense) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PGET_ATTR_PHASE_CHANGE_C'::h5pget_attr_phase_change_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: ocpl_id + INTEGER, INTENT(OUT) :: max_compact + INTEGER, INTENT(OUT) :: min_dense + + END FUNCTION h5pget_attr_phase_change_c + END INTERFACE + + hdferr = h5pget_attr_phase_change_c(ocpl_id, max_compact, min_dense) + END SUBROUTINE h5pget_attr_phase_change_f + +!---------------------------------------------------------------------- +! Name: H5Pset_attr_creation_order_f +! +! Purpose: Sets tracking and indexing of attribute creation order +! +! Inputs: +! ocpl_id - Object creation property list identifier +! crt_order_flags - Flags specifying whether to track and index attribute creation order +! Outputs: +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! January, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pset_attr_creation_order_f(ocpl_id, crt_order_flags , hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_attr_creation_order_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: ocpl_id ! Object (dataset or group) creation property list identifier + INTEGER, INTENT(IN) :: crt_order_flags ! Flags specifying whether to track and index attribute creation order + + INTEGER, INTENT(OUT) :: hdferr ! Error code +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION H5Pset_attr_creation_order_c(ocpl_id, crt_order_flags) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_ATTR_CREATION_ORDER_C'::h5pset_attr_creation_order_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: ocpl_id + INTEGER, INTENT(IN) :: crt_order_flags + + END FUNCTION H5Pset_attr_creation_order_c + END INTERFACE + + hdferr = H5Pset_attr_creation_order_c(ocpl_id, crt_order_flags) + END SUBROUTINE h5pset_attr_creation_order_f + + +!---------------------------------------------------------------------- +! Name: H5Pset_shared_mesg_nindexes_f +! +! Purpose: Sets number of shared object header message indexes +! +! Inputs: +! plist_id - file creation property list +! nindexes - Number of shared object header message indexes to be available in files created with this property list +! Outputs: +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! January, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pset_shared_mesg_nindexes_f( plist_id, nindexes, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_shared_mesg_nindexes_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: plist_id ! file creation property list + INTEGER, INTENT(IN) :: nindexes ! Number of shared object header message indexes + ! available in files created WITH this property list + INTEGER, INTENT(OUT) :: hdferr ! Error code +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pset_shared_mesg_nindexes_c(plist_id, nindexes) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_SHARED_MESG_NINDEXES_C'::h5pset_shared_mesg_nindexes_c + !DEC$ ENDIF + + INTEGER(HID_T), INTENT(IN) :: plist_id + INTEGER, INTENT(IN) :: nindexes + + END FUNCTION H5pset_shared_mesg_nindexes_c + END INTERFACE + + hdferr = h5pset_shared_mesg_nindexes_c(plist_id, nindexes) + + END SUBROUTINE h5pset_shared_mesg_nindexes_f + +!---------------------------------------------------------------------- +! Name: H5Pset_shared_mesg_index_f +! +! Purpose: Configures the specified shared object header message index +! +! Inputs: +! fcpl_id - File creation property list identifier. +! index_num - Index being configured. +! mesg_type_flags - Types of messages that should be stored in this index. +! min_mesg_size - Minimum message size. +! +! Outputs: +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! January, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pset_shared_mesg_index_f(fcpl_id, index_num, mesg_type_flags, min_mesg_size, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_shared_mesg_index_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: fcpl_id ! file creation property list + INTEGER, INTENT(IN) :: index_num ! Index being configured. + INTEGER, INTENT(IN) :: mesg_type_flags ! Types of messages that should be stored in this index. + INTEGER, INTENT(IN) :: min_mesg_size ! Minimum message size. + INTEGER, INTENT(OUT) :: hdferr ! Error code +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pset_shared_mesg_index_c(fcpl_id, index_num, mesg_type_flags, min_mesg_size) + + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_SHARED_MESG_INDEX_C'::h5pset_shared_mesg_index_c + !DEC$ ENDIF + + INTEGER(HID_T), INTENT(IN) :: fcpl_id + INTEGER, INTENT(IN) :: index_num + INTEGER, INTENT(IN) :: mesg_type_flags + INTEGER, INTENT(IN) :: min_mesg_size + + END FUNCTION H5pset_shared_mesg_index_c + END INTERFACE + + hdferr = h5pset_shared_mesg_index_c(fcpl_id, index_num, mesg_type_flags, min_mesg_size) + + END SUBROUTINE h5pset_shared_mesg_index_f + +!---------------------------------------------------------------------- +! Name: H5Pget_attr_creation_order_f +! +! Purpose: Retrieves tracking and indexing settings for attribute creation order +! +! Inputs: +! ocpl_id - Object (group or dataset) creation property list identifier +! +! Outputs: +! crt_order_flags - Flags specifying whether to track and index attribute creation order +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! February, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pget_attr_creation_order_f(ocpl_id, crt_order_flags, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pget_attr_creation_order_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: ocpl_id ! Object (group or dataset) creation property list identifier + INTEGER, INTENT(OUT) :: crt_order_flags ! Flags specifying whether to track and index attribute creation order + INTEGER, INTENT(OUT) :: hdferr ! Error code +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pget_attr_creation_order_c(ocpl_id, crt_order_flags) + + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PGET_ATTR_CREATION_ORDER_C'::h5pget_attr_creation_order_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: ocpl_id + INTEGER, INTENT(OUT) :: crt_order_flags + + END FUNCTION H5pget_attr_creation_order_c + END INTERFACE + + hdferr = h5pget_attr_creation_order_c(ocpl_id, crt_order_flags) + + END SUBROUTINE h5pget_attr_creation_order_f + +!---------------------------------------------------------------------- +! Name: H5Pset_libver_bounds_f +! +! Purpose: Sets bounds on library versions, and indirectly format versions, to be used when creating objects. +! +! Inputs: +! fapl_id - File access property list identifier +! low - The earliest version of the library that will be used for writing objects. +! high - The latest version of the library that will be used for writing objects. +! +! Outputs: +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! February 18, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pset_libver_bounds_f(fapl_id, low, high, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_libver_bounds_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: fapl_id ! File access property list identifier + INTEGER(HID_T), INTENT(IN) :: low ! The earliest version of the library that will be used for writing objects. + ! Currently, low must be one of two pre-defined values: + ! HDF_LIBVER_EARLIEST_F + ! HDF_LIBVER_LATEST_F + INTEGER(HID_T), INTENT(IN) :: high ! The latest version of the library that will be used for writing objects. + ! Currently, low must set to the pre-defined value: + ! HDF_LIBVER_LATEST_F + INTEGER, INTENT(OUT) :: hdferr ! Error code +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pset_libver_bounds_c(fapl_id, low, high) + + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_LIBVER_BOUNDS_C'::h5pset_libver_bounds_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: fapl_id + INTEGER(HID_T), INTENT(IN) :: low + INTEGER(HID_T), INTENT(IN) :: high + + END FUNCTION H5pset_libver_bounds_c + END INTERFACE + + hdferr = h5pset_libver_bounds_c(fapl_id, low, high) + + END SUBROUTINE h5pset_libver_bounds_f + +!---------------------------------------------------------------------- +! Name: H5Pset_link_creation_order_f +! +! Purpose: Sets creation order tracking and indexing for links in a group. +! +! Inputs: +! gcpl_id - Group creation property list identifier +! crt_order_flags - Creation order flag(s) +! +! Outputs: +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! February 18, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pset_link_creation_order_f(gcpl_id, crt_order_flags, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_libver_bounds_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: gcpl_id ! File access property list identifier + INTEGER(HID_T), INTENT(IN) :: crt_order_flags ! Creation order flag(s) + INTEGER, INTENT(OUT) :: hdferr ! Error code +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pset_link_creation_order_c(gcpl_id, crt_order_flags) + + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_LINK_CREATION_ORDER_C'::h5pset_link_creation_order_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: gcpl_id + INTEGER(HID_T), INTENT(IN) :: crt_order_flags + + END FUNCTION H5pset_link_creation_order_c + END INTERFACE + + hdferr = h5pset_link_creation_order_c(gcpl_id, crt_order_flags) + + END SUBROUTINE h5pset_link_creation_order_f + +!---------------------------------------------------------------------- +! Name: H5Pget_link_phase_change_f +! +! Purpose: Queries the settings for conversion between compact and dense groups. +! +! Inputs: +! gcpl_id - Group creation property list identifier +! Outputs: +! max_compact - Maximum number of attributes to be stored in compact storage +! min_dense - Minimum number of attributes to be stored in dense storage +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! February 20, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pget_link_phase_change_f(gcpl_id, max_compact, min_dense, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pget_link_phase_change_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: gcpl_id ! Group creation property list identifier + INTEGER, INTENT(OUT) :: max_compact ! Maximum number of attributes to be stored in compact storage + INTEGER, INTENT(OUT) :: min_dense ! Minimum number of attributes to be stored in dense storage + INTEGER, INTENT(OUT) :: hdferr ! Error code +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pget_link_phase_change_c(gcpl_id, max_compact, min_dense) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PGET_LINK_PHASE_CHANGE_C'::h5pget_link_phase_change_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: gcpl_id + INTEGER, INTENT(OUT) :: max_compact + INTEGER, INTENT(OUT) :: min_dense + + END FUNCTION h5pget_link_phase_change_c + END INTERFACE + + hdferr = h5pget_link_phase_change_c(gcpl_id, max_compact, min_dense) + END SUBROUTINE h5pget_link_phase_change_f + +!---------------------------------------------------------------------- +! Name: H5Pget_obj_track_times_f +! +! Purpose: Returns whether times are tracked for an object. +! +! Inputs: +! plist_id - property list id +! flag - object timestamp setting +! .TRUE.,.FALSE. +! Outputs: +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! February 22, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pget_obj_track_times_f(plist_id, flag, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pget_obj_track_times_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset creation property + ! list identifier + LOGICAL, INTENT(OUT) :: flag ! Object timestamp setting + INTEGER, INTENT(OUT) :: hdferr ! Error code + INTEGER :: status +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pget_obj_track_times_c(plist_id, status) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PGET_OBJ_TRACK_TIMES_C'::h5pget_obj_track_times_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: plist_id ! File creation property list identifier + INTEGER, INTENT(OUT) :: status + END FUNCTION h5pget_obj_track_times_c + END INTERFACE + flag = .TRUE. + hdferr = h5pget_obj_track_times_c(plist_id, status) + IF(status.EQ.0) flag = .FALSE. + + END SUBROUTINE h5pget_obj_track_times_f + +!---------------------------------------------------------------------- +! Name: H5Pset_obj_track_times_f +! +! Purpose: Set whether the birth, access, modification & change times for +! an object are stored. +! +! Birth time is the time the object was created. Access time is +! the last time that metadata or raw data was read from this +! object. Modification time is the last time the data for +! this object was changed (either writing raw data to a dataset +! or inserting/modifying/deleting a link in a group). Change +! time is the last time the metadata for this object was written +! (adding/modifying/deleting an attribute on an object, extending +! the size of a dataset, etc). +! +! If these times are not tracked, they will be reported as +! 12:00 AM UDT, Jan. 1, 1970 (i.e. 0 seconds past the UNIX +! epoch) when queried. +! +! Inputs: +! plist_id - property list id +! flag - object timestamp setting +! .TRUE.,.FALSE. +! Outputs: +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! February 22, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pset_obj_track_times_f(plist_id, flag, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_obj_track_times_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset creation property + ! list identifier + LOGICAL, INTENT(IN) :: flag ! Object timestamp setting + INTEGER, INTENT(OUT) :: hdferr ! Error code + INTEGER :: status +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pset_obj_track_times_c(plist_id, status) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_OBJ_TRACK_TIMES_C'::h5pset_obj_track_times_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: plist_id ! File creation property list identifier + INTEGER, INTENT(IN) :: status + END FUNCTION h5pset_obj_track_times_c + END INTERFACE + + status = 0 + IF(flag) status = 1 + + hdferr = h5pset_obj_track_times_c(plist_id, status) + + END SUBROUTINE h5pset_obj_track_times_f + +!---------------------------------------------------------------------- +! Name: H5Pset_create_inter_group_f +! +! Purpose: Specifies in property list whether to create missing intermediate groups. +! +! Inputs: +! lcpl_id - Link creation property list identifier +! crt_intermed_group - crt_intermed_group specifying whether +! to create intermediate groups upon the creation +! of an object +! Outputs: +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! February 22, 2008 +! +! Modifications: +! +! Comment: The long subroutine name (>31) on older f90 compilers causes problems +! so had to shorten the name +!-------------------------------------------------------------------------------------- + + SUBROUTINE h5pset_create_inter_group_f(lcpl_id, crt_intermed_group, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_create_inter_group_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: lcpl_id ! Link creation property list identifier + INTEGER, INTENT(IN) :: crt_intermed_group ! specifying whether to create intermediate groups + ! upon the creation of an object + INTEGER, INTENT(OUT) :: hdferr ! Error code +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pset_create_inter_group_c(lcpl_id, crt_intermed_group) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_CREATE_INTER_GROUP_C'::h5pset_create_inter_group_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: lcpl_id + INTEGER(HID_T), INTENT(IN) :: crt_intermed_group + END FUNCTION h5pset_create_inter_group_c + END INTERFACE + + hdferr = h5pset_create_inter_group_c(lcpl_id, crt_intermed_group) + + END SUBROUTINE h5pset_create_inter_group_f + +!---------------------------------------------------------------------- +! Name: H5Pget_link_creation_order_f +! +! Purpose: Queries whether link creation order is tracked and/or indexed in a group. +! +! Inputs: +! gcpl_id - Group creation property list identifier +! +! Outputs: +! crt_order_flags - Creation order flag(s) +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 3, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pget_link_creation_order_f(gcpl_id, crt_order_flags, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pget_link_creation_order_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: gcpl_id ! Group creation property list identifier + INTEGER, INTENT(OUT) :: crt_order_flags ! Creation order flag(s) + INTEGER, INTENT(OUT) :: hdferr ! Error code +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pget_link_creation_order_c(gcpl_id, crt_order_flags) + + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PGET_LINK_CREATION_ORDER_C'::h5pget_link_creation_order_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: gcpl_id + INTEGER, INTENT(OUT) :: crt_order_flags + + END FUNCTION H5pget_link_creation_order_c + END INTERFACE + + hdferr = h5pget_link_creation_order_c(gcpl_id, crt_order_flags) + + END SUBROUTINE h5pget_link_creation_order_f + +!---------------------------------------------------------------------- +! Name: H5Pset_char_encoding +! +! Purpose: Sets the character encoding used to encode a string. +! +! Inputs: +! plist_id - Property list identifier +! encoding - Valid values for encoding are: +! H5T_CSET_ASCII_F -> US ASCII +! H5T_CSET_UTF8_F -> UTF-8 Unicode encoding +! +! Outputs: +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 3, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pset_char_encoding_f(plist_id, encoding, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_attr_creation_order_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: plist_id ! Property list identifier + + INTEGER, INTENT(IN) :: encoding ! String encoding character set: +! H5T_CSET_ASCII_F -> US ASCII +! H5T_CSET_UTF8_F -> UTF-8 Unicode encoding + INTEGER, INTENT(OUT) :: hdferr ! Error code +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pset_char_encoding_c(plist_id, encoding) + + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_CHAR_ENCODING_C'::h5pset_char_encoding_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: plist_id + INTEGER, INTENT(IN) :: encoding + + END FUNCTION H5pset_char_encoding_c + END INTERFACE + + hdferr = h5pset_char_encoding_c(plist_id, encoding) + + END SUBROUTINE h5pset_char_encoding_f + +!---------------------------------------------------------------------- +! Name: H5Pget_char_encoding +! +! Purpose: Retrieves the character encoding used to create a string +! +! Inputs: +! plist_id - Property list identifier +! +! Outputs: +! encoding - Valid values for encoding are: +! H5T_CSET_ASCII_F -> US ASCII +! H5T_CSET_UTF8_F -> UTF-8 Unicode encoding +! hdferr - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 3, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pget_char_encoding_f(plist_id, encoding, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pget_char_encoding_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: plist_id ! Property list identifier + + INTEGER, INTENT(OUT) :: encoding ! Valid values for encoding are: +! H5T_CSET_ASCII_F -> US ASCII +! H5T_CSET_UTF8_F -> UTF-8 Unicode encoding + INTEGER, INTENT(OUT) :: hdferr ! Error code +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pget_char_encoding_c(plist_id, encoding) + + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PGET_CHAR_ENCODING_C'::h5pget_char_encoding_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: plist_id + INTEGER, INTENT(OUT) :: encoding + + END FUNCTION H5pget_char_encoding_c + END INTERFACE + + hdferr = h5pget_char_encoding_c(plist_id, encoding) + + END SUBROUTINE h5pget_char_encoding_f + +!---------------------------------------------------------------------- +! Name: h5pset_copy_object_f +! +! Purpose: Sets properties to be used when an object is copied. +! +! Inputs: +! ocp_plist_id - Object copy property list identifier +! copy_options - Copy option(s) to be set +! Outputs: +! hdferr - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 3, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pset_copy_object_f(ocp_plist_id, copy_options, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_copy_object_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: ocp_plist_id ! Object copy property list identifier + INTEGER, INTENT(IN) :: copy_options ! Copy option(s) to be set, valid options are: + ! H5O_COPY_SHALLOW_HIERARCHY_F + ! H5O_COPY_EXPAND_SOFT_LINK_F + ! H5O_COPY_EXPAND_EXT_LINK_F + ! H5O_COPY_EXPAND_REFERENCE_F + ! H5O_COPY_WITHOUT_ATTR_FLAG_F + INTEGER, INTENT(OUT) :: hdferr ! Error code + +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pset_copy_object_c(ocp_plist_id, copy_options) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_COPY_OBJECT_C'::h5pset_copy_object_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: ocp_plist_id + INTEGER, INTENT(IN) :: copy_options + END FUNCTION h5pset_copy_object_c + END INTERFACE + hdferr = h5pset_copy_object_c(ocp_plist_id, copy_options) + END SUBROUTINE h5pset_copy_object_f + +!---------------------------------------------------------------------- +! Name: h5pget_copy_object_f +! +! Purpose: Retrieves the properties to be used when an object is copied. +! +! Inputs: +! ocp_plist_id - Object copy property list identifier +! Outputs: +! copy_options - Copy option(s) to be get +! hdferr - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 3, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pget_copy_object_f(ocp_plist_id, copy_options, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pget_copy_object_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: ocp_plist_id ! Object copy property list identifier + INTEGER, INTENT(OUT) :: copy_options ! valid copy options returned are: + ! H5O_COPY_SHALLOW_HIERARCHY_F + ! H5O_COPY_EXPAND_SOFT_LINK_F + ! H5O_COPY_EXPAND_EXT_LINK_F + ! H5O_COPY_EXPAND_REFERENCE_F + ! H5O_COPY_WITHOUT_ATTR_FLAG_F + INTEGER, INTENT(OUT) :: hdferr ! Error code + +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pget_copy_object_c(ocp_plist_id, copy_options) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PGET_COPY_OBJECT_C'::h5pget_copy_object_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: ocp_plist_id + INTEGER, INTENT(OUT) :: copy_options + END FUNCTION h5pget_copy_object_c + END INTERFACE + hdferr = h5pget_copy_object_c(ocp_plist_id, copy_options) + END SUBROUTINE h5pget_copy_object_f + +!---------------------------------------------------------------------- +! Name: h5pget_data_transform_f +! +! Purpose: Retrieves a data transform expression. +! +! Inputs: +! plist_id - Identifier of the property list or class +! Outputs: +! expression - buffer to hold transform expression +! hdferr - error code +! Success: Actual lenght of the expression +! If provided buffer "expression" is +! smaller, than expression will be +! truncated to fit into +! provided user buffer +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 19, 2008 +! +! Modifications: +! +! Comment: Should hdferr return just 0 or 1 and add another arguement for the size? +!---------------------------------------------------------------------- + + SUBROUTINE h5pget_data_transform_f(plist_id, expression, hdferr, size) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pget_data_transform_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: plist_id ! Identifier of the property list or class + CHARACTER(LEN=*), INTENT(OUT) :: expression ! Buffer to hold transform expression + + INTEGER(SIZE_T), INTENT(OUT), OPTIONAL :: size ! registered size of the transform expression + + INTEGER, INTENT(OUT) :: hdferr ! Error code + INTEGER :: expression_len + INTEGER(SIZE_T) :: size_default + + +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pget_data_transform_c(plist_id, expression, expression_len, size_default) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PGET_DATA_TRANSFORM_C'::h5pget_data_transform_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: plist_id + CHARACTER(LEN=*), INTENT(OUT) :: expression + INTEGER(SIZE_T) :: size_default + INTEGER :: expression_len + END FUNCTION h5pget_data_transform_c + END INTERFACE + + size_default = 0 + expression_len = LEN(expression) + + hdferr = h5pget_data_transform_c(plist_id, expression, expression_len, size_default) + + IF(present(size)) size = size_default + + END SUBROUTINE h5pget_data_transform_f + +!---------------------------------------------------------------------- +! Name: h5pset_data_transform_f +! +! Purpose: Sets a data transform expression. +! +! Inputs: +! plist_id - Identifier of the property list or class +! expression - buffer to hold transform expression +! Outputs: +! hdferr - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 19, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pset_data_transform_f(plist_id, expression, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_data_transform_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: plist_id ! Identifier of the property list or class + CHARACTER(LEN=*), INTENT(IN) :: expression ! Buffer to hold transform expression + INTEGER, INTENT(OUT) :: hdferr ! Error code + INTEGER :: expression_len + +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pset_data_transform_c(plist_id, expression, expression_len) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_DATA_TRANSFORM_C'::h5pset_data_transform_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: plist_id + CHARACTER(LEN=*), INTENT(IN) :: expression + INTEGER :: expression_len + END FUNCTION h5pset_data_transform_c + END INTERFACE + + expression_len = LEN(expression) + hdferr = h5pset_data_transform_c(plist_id, expression, expression_len) + + END SUBROUTINE h5pset_data_transform_f + +!---------------------------------------------------------------------- +! Name: H5Pget_local_heap_size_hint_f +! +! Purpose: Queries the local heap size hint for original-style groups. +! +! Inputs: +! gcpl_id - Group creation property list identifier +! Outputs: +! size_hint - Hint for size of local heap +! hdferr - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 21, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE H5Pget_local_heap_size_hint_f(gcpl_id, size_hint, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pget_local_heap_size_hint_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: gcpl_id ! Group creation property list identifier + INTEGER(SIZE_T), INTENT(OUT) :: size_hint ! Hint for size of local heap + INTEGER, INTENT(OUT) :: hdferr ! Error code + +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION H5Pget_local_heap_size_hint_c(gcpl_id, size_hint) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PGET_LOCAL_HEAP_SIZE_HINT_C'::h5pget_local_heap_size_hint_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: gcpl_id + INTEGER(SIZE_T), INTENT(OUT) :: size_hint + END FUNCTION H5Pget_local_heap_size_hint_c + END INTERFACE + + hdferr = H5Pget_local_heap_size_hint_c(gcpl_id, size_hint) + + END SUBROUTINE H5Pget_local_heap_size_hint_f + +!---------------------------------------------------------------------- +! Name: H5Pget_est_link_info_f +! +! Purpose: Queries data required to estimate required local heap or object header size. +! +! Inputs: +! gcpl_id - Group creation property list identifier +! Outputs: +! est_num_entries - Estimated number of links to be inserted into group +! est_name_len - Estimated average length of link names +! hdferr - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 21, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE H5Pget_est_link_info_f(gcpl_id, est_num_entries, est_name_len, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pget_est_link_info_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: gcpl_id ! Group creation property list identifier + INTEGER, INTENT(OUT) :: est_num_entries ! Estimated number of links to be inserted into group + INTEGER, INTENT(OUT) :: est_name_len ! Estimated average length of link names + INTEGER, INTENT(OUT) :: hdferr ! Error code + +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION H5Pget_est_link_info_c(gcpl_id, est_num_entries, est_name_len) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PGET_EST_LINK_INFO_C'::h5pget_est_link_info_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: gcpl_id + INTEGER, INTENT(OUT) :: est_num_entries + INTEGER, INTENT(OUT) :: est_name_len + END FUNCTION H5Pget_est_link_info_c + END INTERFACE + + hdferr = H5Pget_est_link_info_c(gcpl_id, est_num_entries, est_name_len) + + END SUBROUTINE H5Pget_est_link_info_f + +!---------------------------------------------------------------------- +! Name: H5Pset_local_heap_size_hint_f +! +! Purpose: Sets the local heap size hint for original-style groups. +! +! Inputs: +! gcpl_id - Group creation property list identifier +! size_hint - Hint for size of local heap +! Outputs: +! hdferr - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 21, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE H5Pset_local_heap_size_hint_f(gcpl_id, size_hint, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_local_heap_size_hint_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: gcpl_id ! Group creation property list identifier + INTEGER(SIZE_T), INTENT(IN) :: size_hint ! Hint for size of local heap + INTEGER, INTENT(OUT) :: hdferr ! Error code + +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION H5Pset_local_heap_size_hint_c(gcpl_id, size_hint) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_LOCAL_HEAP_SIZE_HINT_C'::h5pset_local_heap_size_hint_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: gcpl_id + INTEGER(SIZE_T), INTENT(IN) :: size_hint + END FUNCTION H5Pset_local_heap_size_hint_c + END INTERFACE + + hdferr = H5Pset_local_heap_size_hint_c(gcpl_id, size_hint) + + END SUBROUTINE H5Pset_local_heap_size_hint_f + +!---------------------------------------------------------------------- +! Name: H5Pset_est_link_info_f +! +! Purpose: Sets estimated number of links and length of link names in a group. +! +! Inputs: +! gcpl_id - Group creation property list identifier +! est_num_entries - Estimated number of links to be inserted into group +! est_name_len - Estimated average length of link names +! Outputs: +! hdferr - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 21, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE H5Pset_est_link_info_f(gcpl_id, est_num_entries, est_name_len, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_est_link_info_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: gcpl_id ! Group creation property list identifier + INTEGER, INTENT(IN) :: est_num_entries ! Estimated number of links to be inserted into group + INTEGER, INTENT(IN) :: est_name_len ! Estimated average length of link names + INTEGER, INTENT(OUT) :: hdferr ! Error code + +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION H5Pset_est_link_info_c(gcpl_id, est_num_entries, est_name_len) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_EST_LINK_INFO_C'::h5pset_est_link_info_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: gcpl_id + INTEGER, INTENT(IN) :: est_num_entries + INTEGER, INTENT(IN) :: est_name_len + END FUNCTION H5Pset_est_link_info_c + END INTERFACE + + hdferr = H5Pset_est_link_info_c(gcpl_id, est_num_entries, est_name_len) + + END SUBROUTINE H5Pset_est_link_info_f + +!---------------------------------------------------------------------- +! Name: H5Pset_link_phase_change_f +! +! Purpose: Sets the parameters for conversion between compact and dense groups. +! +! Inputs: +! gcpl_id - Group creation property list identifier +! max_compact - Maximum number of attributes to be stored in compact storage +! min_dense - Minimum number of attributes to be stored in dense storage +! Outputs: +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 21, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pset_link_phase_change_f(gcpl_id, max_compact, min_dense, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_link_phase_change_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: gcpl_id ! Group creation property list identifier + INTEGER, INTENT(IN) :: max_compact ! Maximum number of attributes to be stored in compact storage + INTEGER, INTENT(IN) :: min_dense ! Minimum number of attributes to be stored in dense storage + INTEGER, INTENT(OUT) :: hdferr ! Error code +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pset_link_phase_change_c(gcpl_id, max_compact, min_dense) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_LINK_PHASE_CHANGE_C'::h5pset_link_phase_change_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: gcpl_id + INTEGER, INTENT(IN) :: max_compact + INTEGER, INTENT(IN) :: min_dense + + END FUNCTION h5pset_link_phase_change_c + END INTERFACE + + hdferr = h5pset_link_phase_change_c(gcpl_id, max_compact, min_dense) + END SUBROUTINE h5pset_link_phase_change_f + +!---------------------------------------------------------------------- +! Name: H5Pset_fapl_direct_f +! +! Purpose: Sets up use of the direct I/O driver. +! +! Inputs: +! fapl_id - File access property list identifier +! alignment - Required memory alignment boundary +! block_size - File system block size +! cbuf_size - Copy buffer size +! Outputs: +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 21, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE H5Pset_fapl_direct_f(fapl_id, alignment, block_size, cbuf_size, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_fapl_direct_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: fapl_id ! File access property list identifier + INTEGER(SIZE_T), INTENT(IN) :: alignment ! Required memory alignment boundary! + INTEGER(SIZE_T), INTENT(IN) :: block_size ! File system block size + INTEGER(SIZE_T), INTENT(IN) :: cbuf_size ! Copy buffer size + INTEGER, INTENT(OUT) :: hdferr ! Error code +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION H5Pset_fapl_direct_c(fapl_id, alignment, block_size, cbuf_size) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_FAPL_DIRECT_C'::h5pset_fapl_direct_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: fapl_id + INTEGER(SIZE_T), INTENT(IN) :: alignment + INTEGER(SIZE_T), INTENT(IN) :: block_size + INTEGER(SIZE_T), INTENT(IN) :: cbuf_size + END FUNCTION H5Pset_fapl_direct_c + END INTERFACE + + hdferr = H5Pset_fapl_direct_c(fapl_id, alignment, block_size, cbuf_size) + END SUBROUTINE H5Pset_fapl_direct_f + +!---------------------------------------------------------------------- +! Name: H5Pget_fapl_direct_f +! +! Purpose: Gets up use of the direct I/O driver. +! +! Inputs: +! fapl_id - File access property list identifier +! Outputs: +! alignment - Required memory alignment boundary +! block_size - File system block size +! cbuf_size - Copy buffer size +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 21, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE H5Pget_fapl_direct_f(fapl_id, alignment, block_size, cbuf_size, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pget_fapl_direct_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: fapl_id ! File access property list identifier + INTEGER(SIZE_T), INTENT(OUT) :: alignment ! Required memory alignment boundary! + INTEGER(SIZE_T), INTENT(OUT) :: block_size ! File system block size + INTEGER(SIZE_T), INTENT(OUT) :: cbuf_size ! Copy buffer size + INTEGER, INTENT(OUT) :: hdferr ! Error code +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION H5Pget_fapl_direct_c(fapl_id, alignment, block_size, cbuf_size) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PGET_FAPL_DIRECT_C'::h5pget_fapl_direct_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: fapl_id + INTEGER(SIZE_T), INTENT(OUT) :: alignment + INTEGER(SIZE_T), INTENT(OUT) :: block_size + INTEGER(SIZE_T), INTENT(OUT) :: cbuf_size + END FUNCTION H5Pget_fapl_direct_c + END INTERFACE + + hdferr = H5Pget_fapl_direct_c(fapl_id, alignment, block_size, cbuf_size) + END SUBROUTINE H5Pget_fapl_direct_f + +!---------------------------------------------------------------------- +! Name: H5Pset_attr_phase_change_f +! +! Purpose: Sets attribute storage phase change thresholds. +! +! Inputs: +! ocpl_id - Object (dataset or group) creation property list identifier +! Outputs: +! max_compact - Maximum number of attributes to be stored in compact storage +! (Default: 8) +! min_dense - Minimum number of attributes to be stored in dense storage +! (Default: 6) +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! January, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pset_attr_phase_change_f(ocpl_id, max_compact, min_dense, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_attr_phase_change_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: ocpl_id ! Object (dataset or group) creation property list identifier + INTEGER, INTENT(IN) :: max_compact ! Maximum number of attributes to be stored in compact storage + !(Default: 8) + INTEGER, INTENT(IN) :: min_dense ! Minimum number of attributes to be stored in dense storage + ! (Default: 6) + INTEGER, INTENT(OUT) :: hdferr ! Error code +! +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pset_attr_phase_change_c(ocpl_id, max_compact, min_dense) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_ATTR_PHASE_CHANGE_C'::h5pset_attr_phase_change_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: ocpl_id + INTEGER, INTENT(IN) :: max_compact + INTEGER, INTENT(IN) :: min_dense + + END FUNCTION h5pset_attr_phase_change_c + END INTERFACE + + hdferr = h5pset_attr_phase_change_c(ocpl_id, max_compact, min_dense) + + + END SUBROUTINE h5pset_attr_phase_change_f + +!---------------------------------------------------------------------- +! Name: H5Pset_nbit_f +! +! Purpose: Sets up the use of the N-Bit filter. +! +! Inputs: +! plist_id - Dataset creation property list identifier. +! Outputs: +! hdferr - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 21, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE H5Pset_nbit_f(plist_id, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_nbit_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset creation property list identifier + INTEGER, INTENT(OUT) :: hdferr ! Error code + +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION H5Pset_nbit_c(plist_id) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_NBIT_C'::h5pset_nbit_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: plist_id + END FUNCTION H5Pset_nbit_c + END INTERFACE + + hdferr = H5Pset_nbit_c(plist_id) + + END SUBROUTINE H5Pset_nbit_f + +!---------------------------------------------------------------------- +! Name: H5Pset_scaleoffset_f +! +! Purpose: Sets up the use of the Scale-Offset filter. +! +! Inputs: +! plist_id - Dataset creation property list identifier. +! scale_type - Flag indicating compression method. +! scale_factor - Parameter related to scale. +! Outputs: +! hdferr - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 21, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE H5Pset_scaleoffset_f(plist_id, scale_type, scale_factor, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_scaleoffset_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset creation property list identifier + INTEGER, INTENT(IN) :: scale_type ! Flag indicating compression method. + INTEGER, INTENT(IN) :: scale_factor ! parameter related to scale. + INTEGER, INTENT(OUT) :: hdferr ! Error code + +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION H5Pset_scaleoffset_c(plist_id, scale_type, scale_factor) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_SCALEOFFSET_C'::h5pset_scaleoffset_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: plist_id + INTEGER, INTENT(IN) :: scale_type + INTEGER, INTENT(IN) :: scale_factor + END FUNCTION H5Pset_scaleoffset_c + END INTERFACE + + hdferr = H5Pset_scaleoffset_c(plist_id, scale_type, scale_factor) + + END SUBROUTINE H5Pset_scaleoffset_f + +!---------------------------------------------------------------------- +! Name: h5pset_nlinks_f +! +! Purpose: Sets maximum number of soft or user-defined link traversals. +! +! Inputs: +! lapl_id - File access property list identifier +! nlinks - Maximum number of links to traverse +! +! Outputs: +! hdferr - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 24, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pset_nlinks_f(lapl_id, nlinks, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pset_nlinks_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: lapl_id ! File access property list identifier + INTEGER(SIZE_T), INTENT(IN) :: nlinks ! Maximum number of links to traverse + INTEGER, INTENT(OUT) :: hdferr ! Error code + +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pset_nlinks_c(lapl_id, nlinks) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PSET_NLINKS_C'::h5pset_nlinks_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: lapl_id + INTEGER(SIZE_T), INTENT(IN) :: nlinks + END FUNCTION h5pset_nlinks_c + END INTERFACE + + hdferr = h5pset_nlinks_c(lapl_id, nlinks) + + END SUBROUTINE h5pset_nlinks_f + +!---------------------------------------------------------------------- +! Name: h5pget_nlinks_f +! +! Purpose: Gets maximum number of soft or user-defined link traversals. +! +! Inputs: +! lapl_id - File access property list identifier +! nlinks - Maximum number of links to traverse +! +! Outputs: +! hdferr - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! March 24, 2008 +! +! Modifications: +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5pget_nlinks_f(lapl_id, nlinks, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pget_nlinks_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: lapl_id ! File access property list identifier + INTEGER(SIZE_T), INTENT(OUT) :: nlinks ! Maximum number of links to traverse + INTEGER, INTENT(OUT) :: hdferr ! Error code + +! MS FORTRAN needs explicit interface for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5pget_nlinks_c(lapl_id, nlinks) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PGET_NLINKS_C'::h5pget_nlinks_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: lapl_id + INTEGER(SIZE_T), INTENT(OUT) :: nlinks + END FUNCTION h5pget_nlinks_c + END INTERFACE + + hdferr = h5pget_nlinks_c(lapl_id, nlinks) + + END SUBROUTINE h5pget_nlinks_f + +!---------------------------------------------------------------------- +! Name: H5Pget_create_inter_group_f +! +! Purpose: Determines whether property is set to enable creating missing intermediate groups. +! +! Inputs: +! lcpl_id - Link creation property list identifier +! crt_intermed_group - Specifying whether to create intermediate groups upon +! the creation of an object +! Outputs: +! hdferr: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: M.S. Breitenfeld +! April 4, 2008 +! +! Modifications: +! +! Comment: The long subroutine name (>31) on older f90 compilers causes problems +! so had to shorten the name +!-------------------------------------------------------------------------------------- + + SUBROUTINE h5pget_create_inter_group_f(lcpl_id, crt_intermed_group, hdferr) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5pget_create_inter_group_f +!DEC$endif +! + IMPLICIT NONE + INTEGER(HID_T), INTENT(IN) :: lcpl_id ! Link creation property list identifier + INTEGER, INTENT(IN) :: crt_intermed_group ! Flag specifying whether to create intermediate groups + ! upon creation of an object + INTEGER, INTENT(OUT) :: hdferr ! Error code + + INTERFACE + INTEGER FUNCTION h5pget_create_inter_group_c(lcpl_id, crt_intermed_group) + USE H5GLOBAL + !DEC$ IF DEFINED(HDF5F90_WINDOWS) + !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5PGET_CREATE_INTER_GROUP_C'::h5pget_create_inter_group_c + !DEC$ ENDIF + INTEGER(HID_T), INTENT(IN) :: lcpl_id + INTEGER(HID_T), INTENT(IN) :: crt_intermed_group + END FUNCTION h5pget_create_inter_group_c + END INTERFACE + + hdferr = h5pget_create_inter_group_c(lcpl_id, crt_intermed_group) + + END SUBROUTINE h5pget_create_inter_group_f + + +END MODULE H5P + |