summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Rff.f90
diff options
context:
space:
mode:
authorScot Breitenfeld <brtnfld@hdfgroup.org>2008-09-08 15:02:44 (GMT)
committerScot Breitenfeld <brtnfld@hdfgroup.org>2008-09-08 15:02:44 (GMT)
commit077b6446063d54ab7ebd4bfa15f952404adfcc05 (patch)
tree9882a9f68a1413236ccdd7bad94f92a410561551 /fortran/src/H5Rff.f90
parente43736b22b2a68268b134a042cf193b56834a4b5 (diff)
downloadhdf5-077b6446063d54ab7ebd4bfa15f952404adfcc05.zip
hdf5-077b6446063d54ab7ebd4bfa15f952404adfcc05.tar.gz
hdf5-077b6446063d54ab7ebd4bfa15f952404adfcc05.tar.bz2
[svn-r15598] Description:
Moved all the windows DLL function declarations to one file (hdf5_fortrandll.def).
Diffstat (limited to 'fortran/src/H5Rff.f90')
-rw-r--r--fortran/src/H5Rff.f9064
1 files changed, 8 insertions, 56 deletions
diff --git a/fortran/src/H5Rff.f90 b/fortran/src/H5Rff.f90
index a4f4a65..de4f5f0 100644
--- a/fortran/src/H5Rff.f90
+++ b/fortran/src/H5Rff.f90
@@ -94,13 +94,7 @@
! subroutine.
!----------------------------------------------------------------------
- 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
-!
+ SUBROUTINE h5rcreate_object_f(loc_id, name, ref, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Location identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of the object at location specified
@@ -163,13 +157,7 @@
! subroutine.
!----------------------------------------------------------------------
- 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
-!
+ SUBROUTINE h5rcreate_region_f(loc_id, name, space_id, ref, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Location identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of the dataset at location specified
@@ -236,13 +224,7 @@
!----------------------------------------------------------------------
- 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
-!
+ SUBROUTINE h5rdereference_object_f(dset_id, ref, obj_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dset_id ! Dataset identifier
TYPE(hobj_ref_t_f), INTENT(IN) :: ref ! Object reference
@@ -301,13 +283,7 @@
!----------------------------------------------------------------------
- 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
-!
+ SUBROUTINE h5rdereference_region_f(dset_id, ref, obj_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dset_id ! Dataset identifier
TYPE(hdset_reg_ref_t_f), INTENT(IN) :: ref ! Object reference
@@ -367,13 +343,7 @@
- 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
-!
+ SUBROUTINE h5rget_region_region_f(dset_id, ref, space_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dset_id ! Dataset identifier
TYPE(hdset_reg_ref_t_f), INTENT(IN) :: ref ! Dataset region reference
@@ -437,13 +407,7 @@
!----------------------------------------------------------------------
- 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
-!
+ SUBROUTINE h5rget_object_type_obj_f(dset_id, ref, obj_type, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dset_id ! Dataset identifier
TYPE(hobj_ref_t_f), INTENT(IN) :: ref ! Object reference
@@ -505,13 +469,7 @@
!----------------------------------------------------------------------
- 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
-!
+ SUBROUTINE h5rget_name_object_f(loc_id, ref, name, hdferr, size)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Identifier for the dataset containing the reference
! or for the group that dataset is in.
@@ -576,13 +534,7 @@
!----------------------------------------------------------------------
- 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
-!
+ SUBROUTINE h5rget_name_region_f(loc_id, ref, name, hdferr, size)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Identifier for the dataset containing the reference
! or for the group that dataset is in.