diff options
Diffstat (limited to 'fortran/src/H5Tff.f90')
-rw-r--r-- | fortran/src/H5Tff.f90 | 484 |
1 files changed, 60 insertions, 424 deletions
diff --git a/fortran/src/H5Tff.f90 b/fortran/src/H5Tff.f90 index 7a812ab..eb4ff30 100644 --- a/fortran/src/H5Tff.f90 +++ b/fortran/src/H5Tff.f90 @@ -52,12 +52,6 @@ CONTAINS !---------------------------------------------------------------------- SUBROUTINE h5topen_f(loc_id, name, type_id, hdferr, tapl_id) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5topen_f -!DEC$endif -! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier CHARACTER(LEN=*), INTENT(IN) :: name ! Datatype name within file or group @@ -129,13 +123,7 @@ CONTAINS !---------------------------------------------------------------------- SUBROUTINE h5tcommit_f(loc_id, name, type_id, hdferr, & - lcpl_id, tcpl_id, tapl_id ) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tcommit_f -!DEC$endif -! + lcpl_id, tcpl_id, tapl_id ) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier CHARACTER(LEN=*), INTENT(IN) :: name @@ -214,13 +202,7 @@ CONTAINS !---------------------------------------------------------------------- - SUBROUTINE h5tcopy_f(type_id, new_type_id, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tcopy_f -!DEC$endif -! + SUBROUTINE h5tcopy_f(type_id, new_type_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER(HID_T), INTENT(OUT) :: new_type_id @@ -272,13 +254,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tequal_f(type1_id, type2_id, flag, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tequal_f -!DEC$endif -! + SUBROUTINE h5tequal_f(type1_id, type2_id, flag, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type1_id ! Datatype identifier INTEGER(HID_T), INTENT(IN) :: type2_id ! Datatype identifier @@ -331,13 +307,7 @@ CONTAINS !---------------------------------------------------------------------- - SUBROUTINE h5tclose_f(type_id, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tclose_f -!DEC$endif -! + SUBROUTINE h5tclose_f(type_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(OUT) :: hdferr ! Error code @@ -394,13 +364,7 @@ CONTAINS !---------------------------------------------------------------------- - SUBROUTINE h5tget_class_f(type_id, class, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_class_f -!DEC$endif -! + SUBROUTINE h5tget_class_f(type_id, class, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(OUT) :: class @@ -460,13 +424,7 @@ CONTAINS !---------------------------------------------------------------------- - SUBROUTINE h5tget_size_f(type_id, size, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_size_f -!DEC$endif -! + SUBROUTINE h5tget_size_f(type_id, size, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER(SIZE_T), INTENT(OUT) :: size ! Datatype size @@ -515,13 +473,7 @@ CONTAINS !---------------------------------------------------------------------- - SUBROUTINE h5tset_size_f(type_id, size, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tset_size_f -!DEC$endif -! + SUBROUTINE h5tset_size_f(type_id, size, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER(SIZE_T), INTENT(IN) :: size ! Datatype size @@ -574,13 +526,7 @@ CONTAINS !---------------------------------------------------------------------- - SUBROUTINE h5tget_order_f(type_id, order, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_order_f -!DEC$endif -! + SUBROUTINE h5tget_order_f(type_id, order, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(OUT) :: order @@ -637,13 +583,7 @@ CONTAINS !---------------------------------------------------------------------- - SUBROUTINE h5tset_order_f(type_id, order, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tset_order_f -!DEC$endif -! + SUBROUTINE h5tset_order_f(type_id, order, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(IN) :: order ! Datatype byte order, bossible values @@ -696,13 +636,7 @@ CONTAINS !---------------------------------------------------------------------- - SUBROUTINE h5tget_precision_f(type_id, precision, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_precision_f -!DEC$endif -! + SUBROUTINE h5tget_precision_f(type_id, precision, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER(SIZE_T), INTENT(OUT) :: precision ! Datatype precision @@ -750,13 +684,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tset_precision_f(type_id, precision, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tset_precision_f -!DEC$endif -! + SUBROUTINE h5tset_precision_f(type_id, precision, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER(SIZE_T), INTENT(IN) :: precision ! Datatype precision @@ -804,13 +732,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_offset_f(type_id, offset, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_offset_f -!DEC$endif -! + SUBROUTINE h5tget_offset_f(type_id, offset, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER(SIZE_T), INTENT(OUT) :: offset ! Datatype bit offset of the @@ -859,13 +781,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tset_offset_f(type_id, offset, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tset_offset_f -!DEC$endif -! + SUBROUTINE h5tset_offset_f(type_id, offset, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER(SIZE_T), INTENT(IN) :: offset ! Datatype bit offset of the @@ -922,13 +838,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_pad_f(type_id, lsbpad, msbpad, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_pad_f -!DEC$endif -! + SUBROUTINE h5tget_pad_f(type_id, lsbpad, msbpad, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(OUT) :: lsbpad ! padding type of the @@ -994,13 +904,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tset_pad_f(type_id, lsbpad, msbpad, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tset_pad_f -!DEC$endif -! + SUBROUTINE h5tset_pad_f(type_id, lsbpad, msbpad, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(IN) :: lsbpad ! padding type of the @@ -1063,13 +967,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_sign_f(type_id, sign, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_sign_f -!DEC$endif -! + SUBROUTINE h5tget_sign_f(type_id, sign, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(OUT) :: sign ! sign type for an integer type @@ -1127,13 +1025,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tset_sign_f(type_id, sign, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tset_sign_f -!DEC$endif -! + SUBROUTINE h5tset_sign_f(type_id, sign, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(IN) :: sign !sign type for an integer type @@ -1190,13 +1082,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_fields_f(type_id, spos, epos, esize, mpos, msize, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_fields_f -!DEC$endif -! + SUBROUTINE h5tget_fields_f(type_id, spos, epos, esize, mpos, msize, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER(SIZE_T), INTENT(OUT) :: spos ! sign bit-position @@ -1257,13 +1143,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tset_fields_f(type_id, spos, epos, esize, mpos, msize, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tset_fields_f -!DEC$endif -! + SUBROUTINE h5tset_fields_f(type_id, spos, epos, esize, mpos, msize, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER(SIZE_T), INTENT(IN) :: spos ! sign bit-position @@ -1319,13 +1199,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_ebias_f(type_id, ebias, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_ebias_f -!DEC$endif -! + SUBROUTINE h5tget_ebias_f(type_id, ebias, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER(SIZE_T), INTENT(OUT) :: ebias ! Datatype exponent bias of a floating-point type @@ -1374,13 +1248,7 @@ CONTAINS !---------------------------------------------------------------------- - SUBROUTINE h5tset_ebias_f(type_id, ebias, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tset_ebias_f -!DEC$endif -! + SUBROUTINE h5tset_ebias_f(type_id, ebias, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER(SIZE_T), INTENT(IN) :: ebias !Datatype exponent bias of a floating-point type @@ -1432,13 +1300,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_norm_f(type_id, norm, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_norm_f -!DEC$endif -! + SUBROUTINE h5tget_norm_f(type_id, norm, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(OUT) :: norm !mantissa normalization of a floating-point datatype @@ -1495,13 +1357,7 @@ CONTAINS !---------------------------------------------------------------------- - SUBROUTINE h5tset_norm_f(type_id, norm, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tset_norm_f -!DEC$endif -! + SUBROUTINE h5tset_norm_f(type_id, norm, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(IN) :: norm !mantissa normalization of a floating-point datatype @@ -1559,13 +1415,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_inpad_f(type_id, padtype, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_inpad_f -!DEC$endif -! + SUBROUTINE h5tget_inpad_f(type_id, padtype, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(OUT) :: padtype ! padding type for unused bits @@ -1623,13 +1473,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tset_inpad_f(type_id, padtype, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tset_inpad_f -!DEC$endif -! + SUBROUTINE h5tset_inpad_f(type_id, padtype, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(IN) :: padtype ! padding type for unused bits @@ -1684,13 +1528,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_cset_f(type_id, cset, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_cset_f -!DEC$endif -! + SUBROUTINE h5tget_cset_f(type_id, cset, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(OUT) :: cset ! character set type of a string datatype @@ -1742,13 +1580,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tset_cset_f(type_id, cset, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tset_cset_f -!DEC$endif -! + SUBROUTINE h5tset_cset_f(type_id, cset, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(IN) :: cset !character set type of a string datatype @@ -1803,13 +1635,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_strpad_f(type_id, strpad, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_strpad_f -!DEC$endif -! + SUBROUTINE h5tget_strpad_f(type_id, strpad, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(OUT) :: strpad @@ -1862,13 +1688,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tset_strpad_f(type_id, strpad, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tset_strpad_f -!DEC$endif -! + SUBROUTINE h5tset_strpad_f(type_id, strpad, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(IN) :: strpad ! string padding method for a string datatype @@ -1917,13 +1737,7 @@ CONTAINS !---------------------------------------------------------------------- - SUBROUTINE h5tget_nmembers_f(type_id, num_members, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_nmembers_f -!DEC$endif -! + SUBROUTINE h5tget_nmembers_f(type_id, num_members, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(OUT) :: num_members !number of fields in a compound datatype @@ -1973,13 +1787,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_member_name_f(type_id, index, member_name, namelen, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_member_name_f -!DEC$endif -! + SUBROUTINE h5tget_member_name_f(type_id, index, member_name, namelen, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(IN) :: index !Field index (0-based) of the field name to retrieve @@ -2034,13 +1842,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_member_offset_f(type_id, member_no, offset, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_member_offset_f -!DEC$endif -! + SUBROUTINE h5tget_member_offset_f(type_id, member_no, offset, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(IN) :: member_no !Number of the field @@ -2090,13 +1892,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_member_index_f(type_id, name, index, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_member_index_f -!DEC$endif -! + SUBROUTINE h5tget_member_index_f(type_id, name, index, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier CHARACTER(LEN=*), INTENT(IN) :: name ! Field or member name @@ -2146,12 +1942,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- -! SUBROUTINE h5tget_member_dims_f(type_id, field_idx,dims, field_dims, perm, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_member_dims_f -!DEC$endif +! SUBROUTINE h5tget_member_dims_f(type_id, field_idx,dims, field_dims, perm, hdferr) ! ! IMPLICIT NONE ! INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier @@ -2195,14 +1986,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_array_dims_f(type_id, dims, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_array_dims_f -!DEC$endif -! - + SUBROUTINE h5tget_array_dims_f(type_id, dims, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Array datatype identifier INTEGER(HSIZE_T),DIMENSION(*), INTENT(OUT) :: dims !buffer to store array datatype @@ -2252,14 +2036,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_array_ndims_f(type_id, ndims, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_array_ndims_f -!DEC$endif -! - + SUBROUTINE h5tget_array_ndims_f(type_id, ndims, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Array datatype identifier INTEGER, INTENT(OUT) :: ndims ! number of array dimensions @@ -2308,14 +2085,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_super_f(type_id, base_type_id, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_super_f -!DEC$endif -! - + SUBROUTINE h5tget_super_f(type_id, base_type_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! datatype identifier INTEGER(HID_T), INTENT(OUT) :: base_type_id ! identifier of the datatype @@ -2367,13 +2137,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_member_type_f(type_id, field_idx, datatype, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_member_type_f -!DEC$endif -! + SUBROUTINE h5tget_member_type_f(type_id, field_idx, datatype, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(IN) :: field_idx !Field index (0-based) of the field type to retrieve @@ -2429,13 +2193,7 @@ CONTAINS !---------------------------------------------------------------------- - SUBROUTINE h5tcreate_f(class, size, type_id, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tcreate_f -!DEC$endif -! + SUBROUTINE h5tcreate_f(class, size, type_id, hdferr) IMPLICIT NONE INTEGER, INTENT(IN) :: class ! Datatype class can be one of ! H5T_COMPOUND_F @@ -2491,13 +2249,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tinsert_f(type_id, name, offset, field_id, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tinsert_f -!DEC$endif -! + SUBROUTINE h5tinsert_f(type_id, name, offset, field_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier CHARACTER(LEN=*), INTENT(IN) :: name !Name of the field to insert @@ -2554,13 +2306,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tpack_f(type_id, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tpack_f -!DEC$endif -! + SUBROUTINE h5tpack_f(type_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(OUT) :: hdferr ! Error code @@ -2604,13 +2350,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- -! SUBROUTINE h5tinsert_array_f(parent_id,name,offset, ndims, dims, member_id, hdferr, perm) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tinsert_array_f -!DEC$endif -! +! SUBROUTINE h5tinsert_array_f(parent_id,name,offset, ndims, dims, member_id, hdferr, perm) ! IMPLICIT NONE ! INTEGER(HID_T), INTENT(IN) :: parent_id ! identifier of the parent compound datatype ! CHARACTER(LEN=*), INTENT(IN) :: name !Name of the new member @@ -2664,13 +2404,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tarray_create_f(base_id, rank, dims, type_id, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tarray_create_f -!DEC$endif -! + SUBROUTINE h5tarray_create_f(base_id, rank, dims, type_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: base_id ! identifier of array base datatype INTEGER, INTENT(IN) :: rank ! Rank of the array @@ -2725,13 +2459,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tenum_create_f(parent_id, new_type_id, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tenum_create_f -!DEC$endif -! + SUBROUTINE h5tenum_create_f(parent_id, new_type_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: parent_id ! Datatype identifier for ! the base datatype @@ -2781,13 +2509,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tenum_insert_f(type_id, name, value, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tenum_insert_f -!DEC$endif -! + SUBROUTINE h5tenum_insert_f(type_id, name, value, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier CHARACTER(LEN=*), INTENT(IN) :: name !Name of the new member @@ -2844,13 +2566,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tenum_nameof_f(type_id, value, namelen, name, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tenum_nameof_f -!DEC$endif -! + SUBROUTINE h5tenum_nameof_f(type_id, value, namelen, name, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier CHARACTER(LEN=*), INTENT(OUT) :: name !Name of the enumeration datatype. @@ -2905,13 +2621,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tenum_valueof_f(type_id, name, value, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tenum_valueof_f -!DEC$endif -! + SUBROUTINE h5tenum_valueof_f(type_id, name, value, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier CHARACTER(LEN=*), INTENT(IN) :: name !Name of the enumeration datatype. @@ -2966,13 +2676,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_member_value_f(type_id, member_no, value, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_member_value_f -!DEC$endif -! + SUBROUTINE h5tget_member_value_f(type_id, member_no, value, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(IN) :: member_no !Number of the enumeration datatype member @@ -3023,13 +2727,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tset_tag_f(type_id, tag, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tset_tag_f -!DEC$endif -! + SUBROUTINE h5tset_tag_f(type_id, tag, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier CHARACTER(LEN=*), INTENT(IN) :: tag !Unique ASCII string with which @@ -3083,13 +2781,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_tag_f(type_id, tag,taglen, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_tag_f -!DEC$endif -! + SUBROUTINE h5tget_tag_f(type_id, tag,taglen, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier CHARACTER(LEN=*), INTENT(OUT) :: tag !Unique ASCII string with which @@ -3139,13 +2831,7 @@ CONTAINS ! Comment: Only basic Fortran base datatypes are supported !---------------------------------------------------------------------- - SUBROUTINE h5tvlen_create_f(type_id, vltype_id, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tvlen_create_f -!DEC$endif -! + SUBROUTINE h5tvlen_create_f(type_id, vltype_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER(HID_T), INTENT(OUT) :: vltype_id ! VL datatype identifier @@ -3189,14 +2875,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tis_variable_str_f(type_id, status, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tis_variable_str_f -!DEC$endif -! - + SUBROUTINE h5tis_variable_str_f(type_id, status, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier LOGICAL, INTENT(OUT) :: status ! Flag, idicates if datatype @@ -3262,14 +2941,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tget_member_class_f(type_id, member_no, class, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_member_class_f -!DEC$endif -! - + SUBROUTINE h5tget_member_class_f(type_id, member_no, class, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier INTEGER, INTENT(IN) :: member_no ! Member number @@ -3324,13 +2996,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tcommit_anon_f(loc_id, dtype_id, hdferr, tcpl_id, tapl_id) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tcommit_anon_f -!DEC$endif -! + SUBROUTINE h5tcommit_anon_f(loc_id, dtype_id, hdferr, tcpl_id, tapl_id) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: loc_id ! A file or group identifier specifying ! the file in which the new named datatype @@ -3396,13 +3062,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tcommitted_f(dtype_id, committed, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tcommitted_f -!DEC$endif -! + SUBROUTINE h5tcommitted_f(dtype_id, committed, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: dtype_id ! A datatype identifier LOGICAL, INTENT(OUT) :: committed ! .TRUE., if the datatype has been committed @@ -3460,13 +3120,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tdecode_f(buf, obj_id, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tdecode_f -!DEC$endif -! + SUBROUTINE h5tdecode_f(buf, obj_id, hdferr) IMPLICIT NONE CHARACTER(LEN=*), INTENT(IN) :: buf ! Buffer for the data space object to be decoded. INTEGER(HID_T), INTENT(OUT) :: obj_id ! Object ID @@ -3512,13 +3166,7 @@ CONTAINS ! Comment: !---------------------------------------------------------------------- - SUBROUTINE h5tencode_f(obj_id, buf, nalloc, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tencode_f -!DEC$endif -! + SUBROUTINE h5tencode_f(obj_id, buf, nalloc, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: obj_id ! Identifier of the object to be encoded. CHARACTER(LEN=*), INTENT(OUT) :: buf ! Buffer for the object to be encoded into. @@ -3564,11 +3212,7 @@ CONTAINS ! !---------------------------------------------------------------------- - SUBROUTINE h5tget_create_plist_f(dtype_id, dtpl_id, hdferr) -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_create_plist_f -!DEC$endif + SUBROUTINE h5tget_create_plist_f(dtype_id, dtpl_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: dtype_id ! Datatype identifier INTEGER(HID_T), INTENT(OUT) :: dtpl_id ! Datatype property list identifier. @@ -3614,11 +3258,7 @@ CONTAINS ! !---------------------------------------------------------------------- - SUBROUTINE h5tcompiler_conv_f( src_id, dst_id, flag, hdferr) -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tcompiler_conv_f -!DEC$endif + SUBROUTINE h5tcompiler_conv_f( src_id, dst_id, flag, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: src_id ! Identifier for the source datatype. INTEGER(HID_T), INTENT(IN) :: dst_id ! Identifier for the destination datatype. @@ -3675,11 +3315,7 @@ CONTAINS ! !---------------------------------------------------------------------- - SUBROUTINE h5tget_native_type_f(dtype_id, direction, native_dtype_id, hdferr) -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5tget_native_type_f -!DEC$endif + SUBROUTINE h5tget_native_type_f(dtype_id, direction, native_dtype_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: dtype_id ! Datatype identifier INTEGER, INTENT(IN) :: direction ! Direction of search: |