summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Tff.f90
diff options
context:
space:
mode:
authorScot Breitenfeld <brtnfld@hdfgroup.org>2008-09-30 16:42:10 (GMT)
committerScot Breitenfeld <brtnfld@hdfgroup.org>2008-09-30 16:42:10 (GMT)
commitfe1ca64d1672af7859c38c143b77533a14c518ec (patch)
treebbee085742020b59a4b6136f277c6dd4a0bc8de0 /fortran/src/H5Tff.f90
parentf361635ae5f344bc80aade6432e80bcf1647522b (diff)
downloadhdf5-fe1ca64d1672af7859c38c143b77533a14c518ec.zip
hdf5-fe1ca64d1672af7859c38c143b77533a14c518ec.tar.gz
hdf5-fe1ca64d1672af7859c38c143b77533a14c518ec.tar.bz2
[svn-r15727]
Maintenance: Merged new Fortran Features and tests from trunk into hdf5_1_8 branch (used svn merge -r 14941:14525 http://svn.hdfgroup.uiuc.edu/hdf5/trunk/fortran command).
Diffstat (limited to 'fortran/src/H5Tff.f90')
-rw-r--r--fortran/src/H5Tff.f90248
1 files changed, 63 insertions, 185 deletions
diff --git a/fortran/src/H5Tff.f90 b/fortran/src/H5Tff.f90
index 0db4843..eb4ff30 100644
--- a/fortran/src/H5Tff.f90
+++ b/fortran/src/H5Tff.f90
@@ -52,8 +52,6 @@ CONTAINS
!----------------------------------------------------------------------
SUBROUTINE h5topen_f(loc_id, name, type_id, hdferr, tapl_id)
-!
-!This definition is needed for Windows DLLs
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Datatype name within file or group
@@ -125,9 +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
+ lcpl_id, tcpl_id, tapl_id )
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
CHARACTER(LEN=*), INTENT(IN) :: name
@@ -206,9 +202,7 @@ CONTAINS
!----------------------------------------------------------------------
- SUBROUTINE h5tcopy_f(type_id, new_type_id, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -260,9 +254,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tequal_f(type1_id, type2_id, flag, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -315,9 +307,7 @@ CONTAINS
!----------------------------------------------------------------------
- SUBROUTINE h5tclose_f(type_id, hdferr)
-!
-!This definition is needed for Windows DLLs
+ SUBROUTINE h5tclose_f(type_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -374,9 +364,7 @@ CONTAINS
!----------------------------------------------------------------------
- SUBROUTINE h5tget_class_f(type_id, class, hdferr)
-!
-!This definition is needed for Windows DLLs
+ SUBROUTINE h5tget_class_f(type_id, class, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier
INTEGER, INTENT(OUT) :: class
@@ -436,9 +424,7 @@ CONTAINS
!----------------------------------------------------------------------
- SUBROUTINE h5tget_size_f(type_id, size, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -487,9 +473,7 @@ CONTAINS
!----------------------------------------------------------------------
- SUBROUTINE h5tset_size_f(type_id, size, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -542,9 +526,7 @@ CONTAINS
!----------------------------------------------------------------------
- SUBROUTINE h5tget_order_f(type_id, order, hdferr)
-!
-!This definition is needed for Windows DLLs
+ SUBROUTINE h5tget_order_f(type_id, order, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier
INTEGER, INTENT(OUT) :: order
@@ -601,9 +583,7 @@ CONTAINS
!----------------------------------------------------------------------
- SUBROUTINE h5tset_order_f(type_id, order, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -656,9 +636,7 @@ CONTAINS
!----------------------------------------------------------------------
- SUBROUTINE h5tget_precision_f(type_id, precision, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -706,9 +684,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tset_precision_f(type_id, precision, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -756,9 +732,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_offset_f(type_id, offset, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -807,9 +781,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tset_offset_f(type_id, offset, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -866,9 +838,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_pad_f(type_id, lsbpad, msbpad, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -934,9 +904,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tset_pad_f(type_id, lsbpad, msbpad, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -999,9 +967,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_sign_f(type_id, sign, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -1059,9 +1025,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tset_sign_f(type_id, sign, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -1118,9 +1082,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_fields_f(type_id, spos, epos, esize, mpos, msize, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -1128,7 +1090,7 @@ CONTAINS
INTEGER(SIZE_T), INTENT(OUT) :: esize ! size of exponent in bits
INTEGER(SIZE_T), INTENT(OUT) :: mpos ! mantissa bit-position
INTEGER(SIZE_T), INTENT(OUT) :: msize ! size of mantissa in bits
- INTEGER, INTENT(OUT) :: hdferr ! Error code
+ INTEGER, INTENT(OUT) :: hdferr ! Error code
! INTEGER, EXTERNAL :: h5tget_fields_c
! MS FORTRAN needs explicit interface for C functions called here.
@@ -1181,9 +1143,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tset_fields_f(type_id, spos, epos, esize, mpos, msize, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -1239,9 +1199,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_ebias_f(type_id, ebias, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -1290,9 +1248,7 @@ CONTAINS
!----------------------------------------------------------------------
- SUBROUTINE h5tset_ebias_f(type_id, ebias, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -1344,9 +1300,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_norm_f(type_id, norm, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -1403,9 +1357,7 @@ CONTAINS
!----------------------------------------------------------------------
- SUBROUTINE h5tset_norm_f(type_id, norm, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -1463,9 +1415,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_inpad_f(type_id, padtype, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -1523,9 +1473,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tset_inpad_f(type_id, padtype, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -1580,9 +1528,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_cset_f(type_id, cset, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -1634,9 +1580,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tset_cset_f(type_id, cset, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -1691,9 +1635,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_strpad_f(type_id, strpad, hdferr)
-!
-!This definition is needed for Windows DLLs
+ SUBROUTINE h5tget_strpad_f(type_id, strpad, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier
INTEGER, INTENT(OUT) :: strpad
@@ -1746,9 +1688,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tset_strpad_f(type_id, strpad, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -1797,9 +1737,7 @@ CONTAINS
!----------------------------------------------------------------------
- SUBROUTINE h5tget_nmembers_f(type_id, num_members, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -1849,9 +1787,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_member_name_f(type_id, index, member_name, namelen, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -1906,9 +1842,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_member_offset_f(type_id, member_no, offset, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -1958,9 +1892,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_member_index_f(type_id, name, index, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -2010,9 +1942,8 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
-! SUBROUTINE h5tget_member_dims_f(type_id, field_idx,dims, field_dims, perm, hdferr)
+! SUBROUTINE h5tget_member_dims_f(type_id, field_idx,dims, field_dims, perm, hdferr)
!
-!This definition is needed for Windows DLLs
! IMPLICIT NONE
! INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier
! INTEGER, INTENT(IN) :: field_idx !Field index (0-based) of
@@ -2055,10 +1986,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_array_dims_f(type_id, dims, hdferr)
-!
-!This definition is needed for Windows DLLs
-
+ 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
@@ -2108,10 +2036,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_array_ndims_f(type_id, ndims, hdferr)
-!
-!This definition is needed for Windows DLLs
-
+ 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
@@ -2160,10 +2085,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_super_f(type_id, base_type_id, hdferr)
-!
-!This definition is needed for Windows DLLs
-
+ 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
@@ -2215,9 +2137,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_member_type_f(type_id, field_idx, datatype, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -2273,9 +2193,7 @@ CONTAINS
!----------------------------------------------------------------------
- SUBROUTINE h5tcreate_f(class, size, type_id, hdferr)
-!
-!This definition is needed for Windows DLLs
+ SUBROUTINE h5tcreate_f(class, size, type_id, hdferr)
IMPLICIT NONE
INTEGER, INTENT(IN) :: class ! Datatype class can be one of
! H5T_COMPOUND_F
@@ -2331,9 +2249,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tinsert_f(type_id, name, offset, field_id, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -2390,9 +2306,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tpack_f(type_id, hdferr)
-!
-!This definition is needed for Windows DLLs
+ SUBROUTINE h5tpack_f(type_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -2436,9 +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
+! 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
@@ -2492,9 +2404,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tarray_create_f(base_id, rank, dims, type_id, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -2549,9 +2459,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tenum_create_f(parent_id, new_type_id, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -2601,9 +2509,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tenum_insert_f(type_id, name, value, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -2660,9 +2566,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tenum_nameof_f(type_id, value, namelen, name, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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.
@@ -2717,9 +2621,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tenum_valueof_f(type_id, name, value, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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.
@@ -2774,9 +2676,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_member_value_f(type_id, member_no, value, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -2827,9 +2727,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tset_tag_f(type_id, tag, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -2841,7 +2739,7 @@ CONTAINS
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
- INTEGER FUNCTION h5tset_tag_c(type_id, tag, namelen)
+ INTEGER FUNCTION h5tset_tag_c(type_id, tag, taglen)
USE H5GLOBAL
!DEC$ IF DEFINED(HDF5F90_WINDOWS)
!DEC$ ATTRIBUTES C,reference,decorate,alias:'H5TSET_TAG_C'::h5tset_tag_c
@@ -2883,9 +2781,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_tag_f(type_id, tag,taglen, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -2935,9 +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
+ 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
@@ -2981,10 +2875,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tis_variable_str_f(type_id, status, hdferr)
-!
-!This definition is needed for Windows DLLs
-
+ 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
@@ -3050,10 +2941,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tget_member_class_f(type_id, member_no, class, hdferr)
-!
-!This definition is needed for Windows DLLs
-
+ 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
@@ -3108,9 +2996,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tcommit_anon_f(loc_id, dtype_id, hdferr, tcpl_id, tapl_id)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -3176,9 +3062,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tcommitted_f(dtype_id, committed, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -3236,9 +3120,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tdecode_f(buf, obj_id, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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
@@ -3284,9 +3166,7 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
- SUBROUTINE h5tencode_f(obj_id, buf, nalloc, hdferr)
-!
-!This definition is needed for Windows DLLs
+ 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.
@@ -3332,8 +3212,7 @@ CONTAINS
!
!----------------------------------------------------------------------
- SUBROUTINE h5tget_create_plist_f(dtype_id, dtpl_id, hdferr)
-!This definition is needed for Windows DLLs
+ 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.
@@ -3379,8 +3258,7 @@ CONTAINS
!
!----------------------------------------------------------------------
- SUBROUTINE h5tcompiler_conv_f( src_id, dst_id, flag, hdferr)
-!This definition is needed for Windows DLLs
+ 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.
@@ -3437,8 +3315,7 @@ CONTAINS
!
!----------------------------------------------------------------------
- SUBROUTINE h5tget_native_type_f(dtype_id, direction, native_dtype_id, hdferr)
-!This definition is needed for Windows DLLs
+ 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:
@@ -3462,4 +3339,5 @@ CONTAINS
hdferr = h5tget_native_type_c(dtype_id, direction, native_dtype_id)
END SUBROUTINE h5tget_native_type_f
+
END MODULE H5T