summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Off.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/H5Off.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/H5Off.f90')
-rw-r--r--fortran/src/H5Off.f9012
1 files changed, 2 insertions, 10 deletions
diff --git a/fortran/src/H5Off.f90 b/fortran/src/H5Off.f90
index c64b82d..b79dbf2 100644
--- a/fortran/src/H5Off.f90
+++ b/fortran/src/H5Off.f90
@@ -46,11 +46,7 @@ CONTAINS
!
!----------------------------------------------------------------------
- SUBROUTINE h5olink_f(object_id, new_loc_id, new_link_name, hdferr, lcpl_id, lapl_id)
-!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5olink_f
-!DEC$endif
+ SUBROUTINE h5olink_f(object_id, new_loc_id, new_link_name, hdferr, lcpl_id, lapl_id)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: object_id ! Object to be linked
INTEGER(HID_T), INTENT(IN) :: new_loc_id ! File or group identifier specifying
@@ -117,11 +113,7 @@ CONTAINS
!
!----------------------------------------------------------------------
- SUBROUTINE h5oopen_f(loc_id, name, obj_id, hdferr, lapl_id)
-!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5oopen_f
-!DEC$endif
+ SUBROUTINE h5oopen_f(loc_id, name, obj_id, hdferr, lapl_id)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
CHARACTER(LEN=*), INTENT(IN) :: name ! Path to the object, relative to loc_id