summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Rff.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/H5Rff.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/H5Rff.f90')
-rw-r--r--fortran/src/H5Rff.f9032
1 files changed, 0 insertions, 32 deletions
diff --git a/fortran/src/H5Rff.f90 b/fortran/src/H5Rff.f90
index a4f4a65..7da8d20 100644
--- a/fortran/src/H5Rff.f90
+++ b/fortran/src/H5Rff.f90
@@ -97,10 +97,6 @@
SUBROUTINE h5rcreate_object_f(loc_id, name, ref, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5rcreate_object_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Location identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of the object at location specified
@@ -166,10 +162,6 @@
SUBROUTINE h5rcreate_region_f(loc_id, name, space_id, ref, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5rcreate_region_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Location identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of the dataset at location specified
@@ -239,10 +231,6 @@
SUBROUTINE h5rdereference_object_f(dset_id, ref, obj_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5rdereference_object_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dset_id ! Dataset identifier
TYPE(hobj_ref_t_f), INTENT(IN) :: ref ! Object reference
@@ -304,10 +292,6 @@
SUBROUTINE h5rdereference_region_f(dset_id, ref, obj_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5rdereference_region_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dset_id ! Dataset identifier
TYPE(hdset_reg_ref_t_f), INTENT(IN) :: ref ! Object reference
@@ -370,10 +354,6 @@
SUBROUTINE h5rget_region_region_f(dset_id, ref, space_id, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5rget_region_region_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dset_id ! Dataset identifier
TYPE(hdset_reg_ref_t_f), INTENT(IN) :: ref ! Dataset region reference
@@ -440,10 +420,6 @@
SUBROUTINE h5rget_object_type_obj_f(dset_id, ref, obj_type, hdferr)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5rget_object_type_obj_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dset_id ! Dataset identifier
TYPE(hobj_ref_t_f), INTENT(IN) :: ref ! Object reference
@@ -508,10 +484,6 @@
SUBROUTINE h5rget_name_object_f(loc_id, ref, name, hdferr, size)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5rget_name_object_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Identifier for the dataset containing the reference
! or for the group that dataset is in.
@@ -579,10 +551,6 @@
SUBROUTINE h5rget_name_region_f(loc_id, ref, name, hdferr, size)
!
!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5rget_name_region_f
-!DEC$endif
-!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Identifier for the dataset containing the reference
! or for the group that dataset is in.