summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Gff.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/src/H5Gff.f90')
-rw-r--r--fortran/src/H5Gff.f9058
1 files changed, 4 insertions, 54 deletions
diff --git a/fortran/src/H5Gff.f90 b/fortran/src/H5Gff.f90
index fa3dfea..5852e4a 100644
--- a/fortran/src/H5Gff.f90
+++ b/fortran/src/H5Gff.f90
@@ -63,8 +63,6 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5gcreate_f(loc_id, name, grp_id, hdferr, size_hint, lcpl_id, gcpl_id, gapl_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 ! Name of the group
@@ -156,13 +154,7 @@ CONTAINS
!!$!----------------------------------------------------------------------
!!$
!!$ SUBROUTINE h5gcreate2_f(name, loc_id, grp_id, hdferr, &
-!!$ lcpl_id, gcpl_id, gapl_id)
-!!$!
-!!$!This definition is needed for Windows DLLs
-!!$!DEC$if defined(BUILD_HDF5_DLL)
-!!$!DEC$attributes dllexport :: h5gcreate_f
-!!$!DEC$endif
-!!$!
+!!$ lcpl_id, gcpl_id, gapl_id)
!!$ IMPLICIT NONE
!!$ CHARACTER(LEN=*), INTENT(IN) :: name ! Name of the group
!!$ INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
@@ -247,8 +239,6 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5gopen_f(loc_id, name, grp_id, hdferr, gapl_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 ! Name of the group
@@ -309,9 +299,6 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5gclose_f(grp_id, hdferr)
-!
-!This definition is needed for Windows DLLs
-
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: grp_id ! Group identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -364,9 +351,6 @@ CONTAINS
!----------------------------------------------------------------------
SUBROUTINE h5gget_obj_info_idx_f(loc_id, name, idx, &
obj_name, obj_type, hdferr)
-!
-!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 ! Name of the group
@@ -435,9 +419,6 @@ CONTAINS
!----------------------------------------------------------------------
SUBROUTINE h5gn_members_f(loc_id, name, nmembers, hdferr)
-!
-!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 ! Name of the group
@@ -503,9 +484,6 @@ CONTAINS
SUBROUTINE h5glink_f(loc_id, link_type, current_name, &
new_name, hdferr)
-!
-!This definition is needed for Windows DLLs
-
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
INTEGER, INTENT(IN) :: link_type ! link type
@@ -581,9 +559,6 @@ CONTAINS
SUBROUTINE h5glink2_f(cur_loc_id, cur_name, link_type, new_loc_id, &
new_name, hdferr)
-!
-!This definition is needed for Windows DLLs
-
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: cur_loc_id ! File or group identifier
CHARACTER(LEN=*), INTENT(IN) :: cur_name
@@ -655,9 +630,6 @@ CONTAINS
!----------------------------------------------------------------------
SUBROUTINE h5gunlink_f(loc_id, name, hdferr)
-!
-!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 ! Name of an object
@@ -713,9 +685,6 @@ CONTAINS
SUBROUTINE h5gmove_f(loc_id, name, new_name, hdferr)
-!
-!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 ! Current name of an object
@@ -774,9 +743,6 @@ CONTAINS
SUBROUTINE h5gmove2_f(src_loc_id, src_name, dst_loc_id, dst_name, hdferr)
-!
-!This definition is needed for Windows DLLs
-
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: src_loc_id ! File or group identifier
CHARACTER(LEN=*), INTENT(IN) :: src_name ! Original name of an object
@@ -845,9 +811,6 @@ CONTAINS
!----------------------------------------------------------------------
SUBROUTINE h5gget_linkval_f(loc_id, name, size, buffer, hdferr)
-!
-!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 ! Current name of an object
@@ -910,9 +873,6 @@ CONTAINS
!----------------------------------------------------------------------
SUBROUTINE h5gset_comment_f(loc_id, name, comment, hdferr)
-!
-!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 ! Current name of an object
@@ -975,9 +935,6 @@ CONTAINS
!----------------------------------------------------------------------
SUBROUTINE h5gget_comment_f(loc_id, name, size, buffer, hdferr)
-!
-!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 ! Current name of an object
@@ -1036,8 +993,6 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5Gcreate_anon_f(loc_id, grp_id, hdferr, gcpl_id, gapl_id)
-!
-!This definition is needed for Windows DLLs
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
INTEGER(HID_T), INTENT(OUT) :: grp_id ! Group identifier
@@ -1093,8 +1048,6 @@ CONTAINS
! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5gget_create_plist_f(grp_id, gcpl_id, hdferr)
-!
-!This definition is needed for Windows DLLs
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: grp_id ! Group identifier
INTEGER(HID_T), INTENT(OUT) :: gcpl_id ! Property list for group creation
@@ -1149,8 +1102,7 @@ CONTAINS
!
!----------------------------------------------------------------------
- SUBROUTINE h5gget_info_f(group_id, storage_type, nlinks, max_corder, hdferr, mounted)
-!This definition is needed for Windows DLLs
+ SUBROUTINE h5gget_info_f(group_id, storage_type, nlinks, max_corder, hdferr, mounted)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: group_id ! Group identifier
@@ -1232,8 +1184,7 @@ CONTAINS
!----------------------------------------------------------------------
SUBROUTINE h5gget_info_by_idx_f(loc_id, group_name, index_type, order, n, &
- storage_type, nlinks, max_corder, hdferr, lapl_id, mounted)
-!This definition is needed for Windows DLLs
+ storage_type, nlinks, max_corder, hdferr, lapl_id, mounted)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
CHARACTER(LEN=*), INTENT(IN) :: group_name ! Name of group containing group for which information is to be retrieved
@@ -1334,8 +1285,7 @@ CONTAINS
!----------------------------------------------------------------------
SUBROUTINE h5gget_info_by_name_f(loc_id, group_name, &
- storage_type, nlinks, max_corder, hdferr, lapl_id, mounted)
-!This definition is needed for Windows DLLs
+ storage_type, nlinks, max_corder, hdferr, lapl_id, mounted)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
CHARACTER(LEN=*), INTENT(IN) :: group_name ! Name of group containing group for which information is to be retrieved