summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Fff.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/src/H5Fff.f90')
-rw-r--r--fortran/src/H5Fff.f9058
1 files changed, 0 insertions, 58 deletions
diff --git a/fortran/src/H5Fff.f90 b/fortran/src/H5Fff.f90
index 6cf6c05..9da5f4a 100644
--- a/fortran/src/H5Fff.f90
+++ b/fortran/src/H5Fff.f90
@@ -53,10 +53,6 @@
creation_prp, access_prp)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5fcreate_f
-!DEC$endif
-!
IMPLICIT NONE
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of the file
@@ -136,10 +132,6 @@
SUBROUTINE h5fflush_f(object_id, scope, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5fflush_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: object_id !identifier for any object
@@ -209,10 +201,6 @@
SUBROUTINE h5fmount_f(loc_id, name, child_id, hdferr, access_prp)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5fmount_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Identifier for file or group
@@ -283,10 +271,6 @@
SUBROUTINE h5funmount_f(loc_id, name, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5funmount_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Identifier for file or group
@@ -348,10 +332,6 @@
access_prp)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5fopen_f
-!DEC$endif
-!
IMPLICIT NONE
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of the file
@@ -420,10 +400,6 @@
SUBROUTINE h5freopen_f(file_id, ret_file_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5freopen_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: file_id ! File identifier
@@ -477,10 +453,6 @@
SUBROUTINE h5fget_create_plist_f(file_id, prop_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5fget_create_plist_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: file_id ! File identifier
@@ -535,10 +507,6 @@
SUBROUTINE h5fget_access_plist_f(file_id, access_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5fget_access_plist_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: file_id ! File identifier
@@ -593,10 +561,6 @@
SUBROUTINE h5fis_hdf5_f(name, status, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5fis_hdf5_f
-!DEC$endif
-!
IMPLICIT NONE
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of the file
@@ -657,10 +621,6 @@
SUBROUTINE h5fclose_f(file_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5fclose_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: file_id ! File identifier
@@ -715,10 +675,6 @@
SUBROUTINE h5fget_obj_count_f(file_id, obj_type, obj_count, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5fget_obj_count_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: file_id ! File identifier
@@ -774,10 +730,6 @@
SUBROUTINE h5fget_obj_ids_f(file_id, obj_type, max_objs, obj_ids, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5fget_obj_ids_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: file_id ! File identifier
@@ -830,10 +782,6 @@
SUBROUTINE h5fget_freespace_f(file_id, free_space, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5fget_freespace_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: file_id ! File identifier
@@ -880,9 +828,6 @@
SUBROUTINE h5fget_name_f(obj_id, buf, size, hdferr)
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5fget_name_f
-!DEC$endif
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: obj_id ! Object identifier
CHARACTER(LEN=*), INTENT(INOUT) :: buf
@@ -933,9 +878,6 @@
SUBROUTINE h5fget_filesize_f(file_id, size, hdferr)
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5fget_filesize_f
-!DEC$endif
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: file_id ! file identifier
INTEGER(HSIZE_T), INTENT(OUT) :: size ! Size of the file