summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Pff.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/src/H5Pff.f90')
-rw-r--r--fortran/src/H5Pff.f90560
1 files changed, 0 insertions, 560 deletions
diff --git a/fortran/src/H5Pff.f90 b/fortran/src/H5Pff.f90
index 98fdc81..a7dae95 100644
--- a/fortran/src/H5Pff.f90
+++ b/fortran/src/H5Pff.f90
@@ -116,10 +116,6 @@
SUBROUTINE h5pcreate_f(class, prp_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pcreate_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: class ! The type of the property list
! to be created. Possible values
@@ -183,10 +179,6 @@
SUBROUTINE h5pset_preserve_f(prp_id, flag, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_preserve_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
LOGICAL, INTENT(IN) :: flag ! TRUE/FALSE flag to set the dataset
@@ -244,10 +236,6 @@
SUBROUTINE h5pget_preserve_f(prp_id, flag, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_preserve_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
LOGICAL, INTENT(OUT) :: flag ! TRUE/FALSE flag. Shows status of the dataset's
@@ -310,10 +298,6 @@
SUBROUTINE h5pget_class_f(prp_id, classtype, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_class_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: classtype ! The type of the property list
@@ -374,10 +358,6 @@
SUBROUTINE h5pcopy_f(prp_id, new_prp_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pcopy_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(OUT) :: new_prp_id
@@ -431,10 +411,6 @@
SUBROUTINE h5pclose_f(prp_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pclose_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -486,10 +462,6 @@
SUBROUTINE h5pset_chunk_f(prp_id, ndims, dims, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_chunk_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: ndims ! Number of chunk dimensions
@@ -547,10 +519,6 @@
SUBROUTINE h5pget_chunk_f(prp_id, ndims, dims, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_chunk_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: ndims ! Number of chunk dimensions to
@@ -609,10 +577,6 @@
SUBROUTINE h5pset_deflate_f(prp_id, level, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_deflate_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: level ! Compression level
@@ -669,10 +633,6 @@
hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_fill_value_integer
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier of
@@ -704,10 +664,6 @@
hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_fill_value_integer
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier of
@@ -739,10 +695,6 @@
hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_fill_value_real
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier of
@@ -774,10 +726,6 @@
hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_fill_value_real
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier of
@@ -809,10 +757,6 @@
hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_fill_value_double
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier of
@@ -844,10 +788,6 @@
hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_fill_value_double
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier of
@@ -878,10 +818,6 @@
hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_fill_value_char
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier of
@@ -913,10 +849,6 @@
hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_fill_value_char
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(IN) :: type_id ! Datatype identifier of
@@ -977,10 +909,6 @@
stab, shhdr, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_version_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
@@ -1043,10 +971,6 @@
SUBROUTINE h5pset_userblock_f (prp_id, size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_userblock_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: size !Size of the user-block in bytes
@@ -1098,10 +1022,6 @@
SUBROUTINE h5pget_userblock_f(prp_id, block_size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_userblock_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: block_size !Size of the
@@ -1154,10 +1074,6 @@
SUBROUTINE h5pset_sizes_f (prp_id, sizeof_addr, sizeof_size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_sizes_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(SIZE_T), INTENT(IN) :: sizeof_addr !Size of an object
@@ -1215,10 +1131,6 @@
SUBROUTINE h5pget_sizes_f(prp_id, sizeof_addr, sizeof_size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_sizes_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(SIZE_T), INTENT(OUT) :: sizeof_addr !Size of an object
@@ -1276,10 +1188,6 @@
SUBROUTINE h5pset_sym_k_f (prp_id, ik, lk, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_sym_k_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: ik ! Symbol table tree rank
@@ -1336,10 +1244,6 @@
SUBROUTINE h5pget_sym_k_f(prp_id, ik, lk, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_sym_k_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: ik !Symbol table tree rank
@@ -1393,10 +1297,6 @@
SUBROUTINE h5pset_istore_k_f (prp_id, ik, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_istore_k_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: ik ! 1/2 rank of chunked storage B-tree
@@ -1449,10 +1349,6 @@
SUBROUTINE h5pget_istore_k_f(prp_id, ik, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_istore_k_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: ik !1/2 rank of chunked storage B-tree
@@ -1504,10 +1400,6 @@
SUBROUTINE h5pget_driver_f(prp_id, driver, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_driver_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(OUT) :: driver !low-level file driver identifier
@@ -1557,10 +1449,6 @@
SUBROUTINE h5pset_fapl_stdio_f (prp_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_fapl_stdio_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -1607,10 +1495,6 @@
! SUBROUTINE h5pget_stdio_f (prp_id, io, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_stdio_f
-!DEC$endif
-!
! IMPLICIT NONE
! INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
! INTEGER, INTENT(OUT) :: io ! value indicates that the file
@@ -1648,10 +1532,6 @@
SUBROUTINE h5pset_fapl_sec2_f (prp_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_fapl_sec2_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -1735,10 +1615,6 @@
SUBROUTINE h5pset_alignment_f(prp_id, threshold, alignment, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_alignment_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: threshold ! Threshold value
@@ -1793,10 +1669,6 @@
SUBROUTINE h5pget_alignment_f(prp_id, threshold, alignment, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_alignment_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: threshold ! Threshold value
@@ -1851,10 +1723,6 @@
SUBROUTINE h5pset_fapl_core_f(prp_id, increment, backing_store, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_fapl_core_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(SIZE_T), INTENT(IN) :: increment ! File block size in bytes.
@@ -1913,10 +1781,6 @@
SUBROUTINE h5pget_fapl_core_f(prp_id, increment, backing_store, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_fapl_core_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(SIZE_T), INTENT(OUT) :: increment ! File block size in bytes.
@@ -1976,10 +1840,6 @@
SUBROUTINE h5pset_fapl_family_f(prp_id, memb_size, memb_plist , hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_fapl_family_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: memb_size ! Logical size, in bytes,
@@ -2038,10 +1898,6 @@
SUBROUTINE h5pget_fapl_family_f(prp_id, memb_size, memb_plist , hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_fapl_family_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: memb_size ! Logical size, in bytes,
@@ -2103,10 +1959,6 @@
SUBROUTINE h5pset_cache_f(prp_id, mdc_nelmts,rdcc_nelmts, rdcc_nbytes, rdcc_w0, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_cache_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: mdc_nelmts !Number of elements (objects)
@@ -2175,10 +2027,6 @@
SUBROUTINE h5pget_cache_f(prp_id, mdc_nelmts, rdcc_nelmts, rdcc_nbytes, rdcc_w0, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_cache_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: mdc_nelmts !Number of elements (objects)
@@ -2244,10 +2092,6 @@
SUBROUTINE h5pset_fapl_split_f(prp_id, meta_ext, meta_plist, raw_ext, raw_plist, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_fapl_split_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: meta_ext !Name of the extension for
@@ -2363,10 +2207,6 @@
SUBROUTINE h5pset_gc_references_f (prp_id, gc_reference, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_gc_references_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: gc_reference !the flag for garbage collecting
@@ -2419,10 +2259,6 @@
SUBROUTINE h5pget_gc_references_f (prp_id, gc_reference, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_gc_references_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: gc_reference !the flag for garbage collecting
@@ -2479,10 +2315,6 @@
SUBROUTINE h5pset_layout_f (prp_id, layout, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_layout_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: layout !Type of storage layout for raw data
@@ -2541,10 +2373,6 @@
SUBROUTINE h5pget_layout_f (prp_id, layout, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_layout_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: layout !Type of storage layout for raw data
@@ -2602,10 +2430,6 @@
SUBROUTINE h5pset_filter_f(prp_id, filter, flags, cd_nelmts, cd_values, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_filter_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: filter !Filter to be added to the pipeline.
@@ -2665,10 +2489,6 @@
SUBROUTINE h5pget_nfilters_f (prp_id, nfilters, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_nfilters_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: nfilters !the number of filters in the pipeline
@@ -2727,10 +2547,6 @@
SUBROUTINE h5pget_filter_f(prp_id, filter_number, flags, cd_nelmts, cd_values, namelen, name, filter_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_filter_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: filter_number !Sequence number within the filter
@@ -2805,10 +2621,6 @@
SUBROUTINE h5pset_external_f(prp_id, name, offset,bytes, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_external_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name !Name of an external file
@@ -2872,10 +2684,6 @@
SUBROUTINE h5pget_external_count_f (prp_id, count, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_external_count_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: count !number of external files for the
@@ -2934,10 +2742,6 @@
SUBROUTINE h5pget_external_f(prp_id, idx, name_size, name, offset,bytes, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_external_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: idx !External file index.
@@ -3004,10 +2808,6 @@
SUBROUTINE h5pset_btree_ratios_f(prp_id, left, middle, right, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_btree_ratios_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
REAL, INTENT(IN) :: left !The B-tree split ratio for left-most nodes.
@@ -3067,10 +2867,6 @@
SUBROUTINE h5pget_btree_ratios_f(prp_id, left, middle, right, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_btree_ratios_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
REAL, INTENT(OUT) :: left !The B-tree split ratio for left-most nodes.
@@ -3131,10 +2927,6 @@
SUBROUTINE h5pget_fclose_degree_f(fapl_id, degree, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_fclose_degree_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: fapl_id ! File Access Property list identifier
INTEGER, INTENT(OUT) :: degree ! Possible values
@@ -3194,10 +2986,6 @@
SUBROUTINE h5pset_fclose_degree_f(fapl_id, degree, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_fclose_degree_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: fapl_id ! File Access Property list identifier
INTEGER, INTENT(IN) :: degree ! Possible values
@@ -3251,10 +3039,6 @@
SUBROUTINE h5pequal_f(plist1_id, plist2_id, flag, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pequal_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist1_id ! Property list identifier
INTEGER(HID_T), INTENT(IN) :: plist2_id ! Property list identifier
@@ -3305,10 +3089,6 @@
SUBROUTINE h5pset_buffer_f(plist_id, size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_buffer_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Data transfer property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: size ! Buffer size in bytes;
@@ -3356,10 +3136,6 @@
SUBROUTINE h5pget_buffer_f(plist_id, size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_buffer_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Data transfer property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: size ! Buffer size in bytes;
@@ -3412,10 +3188,6 @@
SUBROUTINE h5pfill_value_defined_f(plist_id, flag, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pfill_value_defined_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id
INTEGER, INTENT(OUT) :: flag
@@ -3467,10 +3239,6 @@
SUBROUTINE h5pset_alloc_time_f(plist_id, flag, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_alloc_time_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id
INTEGER, INTENT(IN) :: flag
@@ -3522,10 +3290,6 @@
SUBROUTINE h5pget_alloc_time_f(plist_id, flag, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_alloc_time_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id
INTEGER, INTENT(OUT) :: flag
@@ -3575,10 +3339,6 @@
SUBROUTINE h5pset_fill_time_f(plist_id, flag, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_fill_time_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id
INTEGER, INTENT(IN) :: flag
@@ -3628,10 +3388,6 @@
SUBROUTINE h5pget_fill_time_f(plist_id, flag, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_fill_time_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id
INTEGER, INTENT(OUT) :: flag
@@ -3677,10 +3433,6 @@
SUBROUTINE h5pset_meta_block_size_f(plist_id, size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_meta_block_size_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: size ! Block size in bytes;
@@ -3726,10 +3478,6 @@
SUBROUTINE h5pget_meta_block_size_f(plist_id, size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_meta_block_size_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: size ! Block size in bytes;
@@ -3775,10 +3523,6 @@
SUBROUTINE h5pset_sieve_buf_size_f(plist_id, size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_sieve_buf_size_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
INTEGER(SIZE_T), INTENT(IN) :: size ! Buffer size in bytes;
@@ -3824,10 +3568,6 @@
SUBROUTINE h5pget_sieve_buf_size_f(plist_id, size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_sieve_buf_size_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
INTEGER(SIZE_T), INTENT(OUT) :: size ! Buffer size in bytes
@@ -3873,10 +3613,6 @@
SUBROUTINE h5pset_small_data_block_size_f(plist_id, size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_small_data_block_size_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: size ! Small raw data block size
@@ -3922,10 +3658,6 @@
SUBROUTINE h5pget_small_data_block_size_f(plist_id, size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_small_data_block_size_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! File access property list identifier
INTEGER(HSIZE_T), INTENT(OUT) :: size ! Small raw data block size
@@ -3971,10 +3703,6 @@
SUBROUTINE h5pset_hyper_vector_size_f(plist_id, size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_hyper_vector_size_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset transfer property list identifier
INTEGER(SIZE_T), INTENT(IN) :: size ! Vector size
@@ -4020,10 +3748,6 @@
SUBROUTINE h5pget_hyper_vector_size_f(plist_id, size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_hyper_vector_size_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Dataset transfer property list identifier
INTEGER(SIZE_T), INTENT(OUT) :: size ! Vector size
@@ -4070,10 +3794,6 @@
SUBROUTINE h5pset_integer(prp_id, name, value, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_integer
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
@@ -4126,10 +3846,6 @@
SUBROUTINE h5pset_real(prp_id, name, value, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_real
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
@@ -4182,10 +3898,6 @@
SUBROUTINE h5pset_double(prp_id, name, value, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_double
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
@@ -4238,10 +3950,6 @@
SUBROUTINE h5pset_char(prp_id, name, value, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_char
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
@@ -4298,10 +4006,6 @@
SUBROUTINE h5pget_integer(prp_id, name, value, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_integer
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
@@ -4354,10 +4058,6 @@
SUBROUTINE h5pget_real(prp_id, name, value, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_real
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
@@ -4410,10 +4110,6 @@
SUBROUTINE h5pget_double(prp_id, name, value, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_double
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
@@ -4466,10 +4162,6 @@
SUBROUTINE h5pget_char(prp_id, name, value, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_char
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
@@ -4526,10 +4218,6 @@
SUBROUTINE h5pexist_f(prp_id, name, flag, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pexist_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to modify
@@ -4586,10 +4274,6 @@
SUBROUTINE h5pget_size_f(prp_id, name, size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_size_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to query
@@ -4640,10 +4324,6 @@
SUBROUTINE h5pget_nprops_f(prp_id, nprops, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_nprops_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(SIZE_T), INTENT(OUT) :: nprops ! iNumber of properties
@@ -4692,10 +4372,6 @@
SUBROUTINE h5pget_class_name_f(prp_id, name, size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_class_name_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
CHARACTER(LEN=*), INTENT(OUT) :: name ! Buffer to retireve class name
@@ -4752,10 +4428,6 @@
SUBROUTINE h5pget_class_parent_f(prp_id, parent_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_class_parent_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HID_T), INTENT(OUT) :: parent_id ! Parent class property list
@@ -4803,10 +4475,6 @@
SUBROUTINE h5pisa_class_f(plist, pclass, flag, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pisa_class_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist ! Property list identifier
INTEGER(HID_T), INTENT(IN) :: pclass ! Class identifier
@@ -4859,10 +4527,6 @@
SUBROUTINE h5pcopy_prop_f(dst_id, src_id, name, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pcopy_prop_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dst_id ! Destination property list
! identifier
@@ -4916,10 +4580,6 @@
SUBROUTINE h5premove_f(plid, name, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5premove_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plid ! property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! name of property to remove
@@ -4970,10 +4630,6 @@
SUBROUTINE h5punregister_f(class, name, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5punregister_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: class ! property list class identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! name of property to remove
@@ -5023,10 +4679,6 @@
SUBROUTINE h5pclose_class_f(class, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pclose_class_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: class ! property list class identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -5079,10 +4731,6 @@
SUBROUTINE h5pcreate_class_f(parent, name, class, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pcreate_class_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: parent ! parent property list class
! identifier
@@ -5140,10 +4788,6 @@
SUBROUTINE h5pregister_integer(class, name, size, value, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pregister_integer
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: class ! Property list class identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to register
@@ -5201,10 +4845,6 @@
SUBROUTINE h5pregister_real(class, name, size, value, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pregister_real
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: class ! Property list class identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to register
@@ -5262,10 +4902,6 @@
SUBROUTINE h5pregister_double(class, name, size, value, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pregister_double
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: class ! Property list class identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to register
@@ -5323,10 +4959,6 @@
SUBROUTINE h5pregister_char(class, name, size, value, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pregister_char
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: class ! Property list class identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to register
@@ -5387,10 +5019,6 @@
SUBROUTINE h5pinsert_integer(plist, name, size, value, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pinsert_integer
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to insert
@@ -5447,10 +5075,6 @@
SUBROUTINE h5pinsert_real(plist, name, size, value, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pinsert_real
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to insert
@@ -5507,10 +5131,6 @@
SUBROUTINE h5pinsert_double(plist, name, size, value, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pinsert_double
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to insert
@@ -5567,10 +5187,6 @@
SUBROUTINE h5pinsert_char(plist, name, size, value, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pinsert_char
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist ! Property list identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of property to insert
@@ -5628,10 +5244,6 @@
SUBROUTINE h5pset_shuffle_f(prp_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_shuffle_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -5681,10 +5293,6 @@
SUBROUTINE h5pset_edc_check_f(prp_id, flag, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_edc_check_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: flag ! Checksum filter flag
@@ -5733,10 +5341,6 @@
SUBROUTINE h5pget_edc_check_f(prp_id, flag, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_edc_check_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset transfer property list identifier
INTEGER, INTENT(OUT) :: flag ! Checksum filter flag
@@ -5790,10 +5394,6 @@
SUBROUTINE h5pset_fletcher32_f(prp_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_fletcher32_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -5841,10 +5441,6 @@
SUBROUTINE h5pset_family_offset_f(prp_id, offset, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_family_offset_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER(HSIZE_T), INTENT(IN) :: offset ! Offset in bytes
@@ -5897,10 +5493,6 @@
SUBROUTINE h5pset_fapl_multi_l(prp_id, memb_map, memb_fapl, memb_name, memb_addr, relax, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_fapl_multi_l
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
INTEGER, DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(IN) :: memb_map
@@ -5973,10 +5565,6 @@
SUBROUTINE h5pset_fapl_multi_s(prp_id, relax, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_fapl_multi_s
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
LOGICAL, INTENT(IN) :: relax
@@ -6031,10 +5619,6 @@
SUBROUTINE h5pget_fapl_multi_f(prp_id, memb_map, memb_fapl, memb_name, memb_addr, relax, hdferr, maxlen_out)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_fapl_multi_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! File creation property list identifier
INTEGER, DIMENSION(0:H5FD_MEM_NTYPES_F-1), INTENT(OUT) :: memb_map
@@ -6110,10 +5694,6 @@
SUBROUTINE h5pset_szip_f(prp_id, options_mask, pixels_per_block, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pset_szip_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset creation property
! list identifier
@@ -6168,10 +5748,6 @@
SUBROUTINE h5pall_filters_avail_f(prp_id, flag, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pall_filters_avail_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset creation property
! list identifier
@@ -6231,10 +5807,6 @@
SUBROUTINE h5pget_filter_by_id_f(prp_id, filter_id, flags, cd_nelmts, cd_values, namelen, name, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pget_filter_by_id_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
@@ -6305,10 +5877,6 @@
SUBROUTINE h5pmodify_filter_f(prp_id, filter, flags, cd_nelmts, cd_values, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5pmodify_filter_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
INTEGER, INTENT(IN) :: filter !Filter to be modified
@@ -6366,10 +5934,6 @@
SUBROUTINE h5premove_filter_f(prp_id, filter, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5premove_filter_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Dataset creation property list
! identifier
@@ -6422,10 +5986,6 @@
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
@@ -6478,10 +6038,6 @@
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
@@ -6532,10 +6088,6 @@
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
@@ -6590,10 +6142,6 @@
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.
@@ -6650,10 +6198,6 @@
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
@@ -6706,10 +6250,6 @@
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, INTENT(IN) :: low ! The earliest version of the library that will be used for writing objects.
@@ -6768,10 +6308,6 @@
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_link_creation_order_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: gcpl_id ! File access property list identifier
INTEGER, INTENT(IN) :: crt_order_flags ! Creation order flag(s)
@@ -6823,10 +6359,6 @@
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
@@ -6878,10 +6410,6 @@
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
@@ -6948,10 +6476,6 @@
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
@@ -7008,10 +6532,6 @@
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
@@ -7062,10 +6582,6 @@
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)
@@ -7119,10 +6635,6 @@
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_char_encoding_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: plist_id ! Property list identifier
@@ -7179,10 +6691,6 @@
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
@@ -7236,10 +6744,6 @@
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:
@@ -7292,10 +6796,6 @@
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:
@@ -7351,10 +6851,6 @@
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
@@ -7416,10 +6912,6 @@
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
@@ -7471,10 +6963,6 @@
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
@@ -7524,10 +7012,6 @@
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
@@ -7578,10 +7062,6 @@
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
@@ -7631,10 +7111,6 @@
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
@@ -7686,10 +7162,6 @@
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
@@ -7742,10 +7214,6 @@
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!
@@ -7799,10 +7267,6 @@
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!
@@ -7857,10 +7321,6 @@
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
@@ -7914,10 +7374,6 @@
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
@@ -7965,10 +7421,6 @@
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.
@@ -8020,10 +7472,6 @@
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
@@ -8073,10 +7521,6 @@
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
@@ -8127,10 +7571,6 @@
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