summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Sff.f90
diff options
context:
space:
mode:
authorScott Wegner <swegner@hdfgroup.org>2008-09-03 15:01:28 (GMT)
committerScott Wegner <swegner@hdfgroup.org>2008-09-03 15:01:28 (GMT)
commit442565636a5c638c40f882af087c0e92c52753f3 (patch)
treeaa042e78f22e9df6d266faa05a9e1d1538b62a0d /fortran/src/H5Sff.f90
parent39b9ddf4c8da6d815bd1d81382d480092020b57e (diff)
downloadhdf5-442565636a5c638c40f882af087c0e92c52753f3.zip
hdf5-442565636a5c638c40f882af087c0e92c52753f3.tar.gz
hdf5-442565636a5c638c40f882af087c0e92c52753f3.tar.bz2
[svn-r15583] Purpose: Add Windows Fortran DLL export code to separate DEF file.
Description: In in Fortran source code, there was a great deal of code that was necessary for Windows DLLs, and ignored for others systems. To remove some of the bloat in the source code, we moved these definitions into separate *.def file, which will be used on by the Windows DLL project. Tested: VS2005 on WinXP Note: The Windows project file will still need to be edited-- I will check that in soon.
Diffstat (limited to 'fortran/src/H5Sff.f90')
-rw-r--r--fortran/src/H5Sff.f90124
1 files changed, 0 insertions, 124 deletions
diff --git a/fortran/src/H5Sff.f90 b/fortran/src/H5Sff.f90
index c212d9a..e8c5b21 100644
--- a/fortran/src/H5Sff.f90
+++ b/fortran/src/H5Sff.f90
@@ -50,10 +50,6 @@
SUBROUTINE h5screate_simple_f(rank, dims, space_id, hdferr, maxdims)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5screate_simple_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER, INTENT(IN) :: rank ! Number of dataspace dimensions
@@ -125,10 +121,6 @@
SUBROUTINE h5sclose_f(space_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sclose_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -179,10 +171,6 @@
SUBROUTINE h5screate_f(classtype, space_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5screate_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER, INTENT(IN) :: classtype ! The type of the dataspace
@@ -240,10 +228,6 @@
SUBROUTINE h5scopy_f(space_id, new_space_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5scopy_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -297,10 +281,6 @@
SUBROUTINE h5sget_select_hyper_nblocks_f(space_id, num_blocks, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sget_select_hyper_nblocks_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -359,10 +339,6 @@
num_blocks, buf, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sget_select_hyper_blocklist_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -430,10 +406,6 @@
SUBROUTINE h5sget_select_bounds_f(space_id, start, end, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sget_select_bounds_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -492,10 +464,6 @@
SUBROUTINE h5sget_select_elem_npoints_f(space_id, num_points, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sget_select_elem_npoints_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -554,10 +522,6 @@
num_points, buf, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sget_select_elem_pointlist_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
INTEGER(HSIZE_T), INTENT(IN) :: startpoint
@@ -624,10 +588,6 @@
num_elements, coord, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sselect_elements_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
INTEGER, INTENT(IN) :: operator ! Flag, valid values are:
@@ -704,10 +664,6 @@
SUBROUTINE h5sselect_all_f(space_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sselect_all_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
INTEGER, INTENT(OUT) :: hdferr ! Error code
@@ -757,10 +713,6 @@
SUBROUTINE h5sselect_none_f(space_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sselect_none_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -811,10 +763,6 @@
SUBROUTINE h5sselect_valid_f(space_id, status, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sselect_valid_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -872,10 +820,6 @@
SUBROUTINE h5sget_simple_extent_npoints_f(space_id, npoints, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sget_simple_extent_npoints_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -929,10 +873,6 @@
SUBROUTINE h5sget_select_npoints_f(space_id, npoints, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sget_select_npoints_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -986,10 +926,6 @@
SUBROUTINE h5sget_simple_extent_ndims_f(space_id, rank, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sget_simple_extent_ndims_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -1044,10 +980,6 @@
SUBROUTINE h5sget_simple_extent_dims_f(space_id, dims, maxdims, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sget_simple_extent_dims_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -1111,10 +1043,6 @@
SUBROUTINE h5sget_simple_extent_type_f(space_id, classtype, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sget_simple_extent_type_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -1176,10 +1104,6 @@
maximum_size, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sset_extent_simple_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -1244,10 +1168,6 @@
SUBROUTINE h5sis_simple_f(space_id, status, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sis_simple_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -1305,10 +1225,6 @@
SUBROUTINE h5soffset_simple_f(space_id, offset, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5soffset_simple_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -1365,10 +1281,6 @@
SUBROUTINE h5sextent_copy_f(dest_space_id, source_space_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sextent_copy_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dest_space_id ! Identifier of destination
@@ -1421,10 +1333,6 @@
SUBROUTINE h5sset_extent_none_f(space_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sset_extent_none_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
@@ -1483,10 +1391,6 @@
hdferr, stride, block)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sselect_hyperslab_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
INTEGER, INTENT(IN) :: operator ! Flag, valid values are:
@@ -1622,10 +1526,6 @@
! hyper_id, hdferr, stride, block)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5scombine_hyperslab_f
-!DEC$endif
-!
! IMPLICIT NONE
! INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier
! INTEGER, INTENT(IN) :: operator ! Flag, valid values are:
@@ -1764,10 +1664,6 @@
! ds_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5scombine_select_f
-!DEC$endif
-!
! IMPLICIT NONE
! INTEGER(HID_T), INTENT(IN) :: space1_id ! First dataspace identifier
! INTEGER(HID_T), INTENT(IN) :: space2_id ! Second dataspace identifier
@@ -1843,10 +1739,6 @@
! hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sselect_select_f
-!DEC$endif
-!
! IMPLICIT NONE
! INTEGER(HID_T), INTENT(INOUT) :: space1_id ! Dataspace identifier to
! modify
@@ -1912,10 +1804,6 @@
SUBROUTINE h5sget_select_type_f(space_id, type, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sget_select_type_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(INOUT) :: space_id ! Dataspace identifier to
INTEGER, INTENT(OUT) :: type ! Selection type
@@ -1968,10 +1856,6 @@
SUBROUTINE h5sdecode_f(buf, obj_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sdecode_f
-!DEC$endif
-!
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
@@ -2020,10 +1904,6 @@
SUBROUTINE h5sencode_f(obj_id, buf, nalloc, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sencode_f
-!DEC$endif
-!
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.
@@ -2075,10 +1955,6 @@
SUBROUTINE h5sextent_equal_f(space1_id, space2_id, equal, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5sextent_equal_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: space1_id ! First dataspace identifier.
INTEGER(HID_T), INTENT(IN) :: space2_id ! Second dataspace identifier.