summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Gff.f90
diff options
context:
space:
mode:
authorElena Pourmal <epourmal@hdfgroup.org>2001-04-27 03:47:27 (GMT)
committerElena Pourmal <epourmal@hdfgroup.org>2001-04-27 03:47:27 (GMT)
commit6182da802691e5702681faf509ac151fe652dd51 (patch)
treeec6a41f8882327da936a0a1709458dba606ef35b /fortran/src/H5Gff.f90
parentc048eed3be375907a030a7f27cb958fcbc95a3ef (diff)
downloadhdf5-6182da802691e5702681faf509ac151fe652dd51.zip
hdf5-6182da802691e5702681faf509ac151fe652dd51.tar.gz
hdf5-6182da802691e5702681faf509ac151fe652dd51.tar.bz2
[svn-r3860]
Purpose: Windows port Description: Multiple changes: * Windows platforms require special compiler directives in order to create DLLs. * In read/write subroutines data arrays were passed by descriptor. This worked on UNIX but did not work on Windows. Solution: * added compiler directives. * read/write APIs have been changed. There is an additional parameter (array that contains the sizes of data buffer dimensions) and regular arrays are used instead of assumed-shaped arrays. Platforms tested: * Currently this feature does not work. Common blocks are not exported correctly from one F90 module to another. I am checking this in so I can ask DEC for help. * For static library tests passed on Windows 98 ( except flush2_fortran) All tests passed on Linux, Solaris 2.7, O2K and T3E
Diffstat (limited to 'fortran/src/H5Gff.f90')
-rw-r--r--fortran/src/H5Gff.f9066
1 files changed, 66 insertions, 0 deletions
diff --git a/fortran/src/H5Gff.f90 b/fortran/src/H5Gff.f90
index c4e83c2..1547d25 100644
--- a/fortran/src/H5Gff.f90
+++ b/fortran/src/H5Gff.f90
@@ -34,6 +34,12 @@
! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5gcreate_f(loc_id, name, grp_id, hdferr, size_hint)
+!
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: h5gcreate_f
+!DEC$endif
+!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
@@ -100,6 +106,12 @@
! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5gopen_f(loc_id, name, grp_id, hdferr)
+!
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: h5gopen_f
+!DEC$endif
+!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
@@ -153,6 +165,12 @@
! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5gclose_f(grp_id, hdferr)
+!
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: h5gclose_f
+!DEC$endif
+!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: grp_id ! Group identifier
@@ -204,6 +222,12 @@
!----------------------------------------------------------------------
SUBROUTINE h5gget_obj_info_idx_f(loc_id, name, idx, &
obj_name, obj_type, hdferr)
+!
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: h5gget_obj_info_idx_f
+!DEC$endif
+!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
@@ -271,6 +295,12 @@
!----------------------------------------------------------------------
SUBROUTINE h5gn_members_f(loc_id, name, nmembers, hdferr)
+!
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: h5gn_members_f
+!DEC$endif
+!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
@@ -335,6 +365,12 @@
SUBROUTINE h5glink_f(loc_id, link_type, current_name, &
new_name, hdferr)
+!
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: h5glink_f
+!DEC$endif
+!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
@@ -405,6 +441,12 @@
!----------------------------------------------------------------------
SUBROUTINE h5gunlink_f(loc_id, name, hdferr)
+!
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: h5gunlink_f
+!DEC$endif
+!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
@@ -459,6 +501,12 @@
SUBROUTINE h5gmove_f(loc_id, name, new_name, hdferr)
+!
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: h5gmove_f
+!DEC$endif
+!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
@@ -522,6 +570,12 @@
!----------------------------------------------------------------------
SUBROUTINE h5gget_linkval_f(loc_id, name, size, buffer, hdferr)
+!
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: h5gget_linkval_f
+!DEC$endif
+!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
@@ -583,6 +637,12 @@
!----------------------------------------------------------------------
SUBROUTINE h5gset_comment_f(loc_id, name, comment, hdferr)
+!
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: h5gset_comment_f
+!DEC$endif
+!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier
@@ -644,6 +704,12 @@
!----------------------------------------------------------------------
SUBROUTINE h5gget_comment_f(loc_id, name, size, buffer, hdferr)
+!
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: h5gget_comment_f
+!DEC$endif
+!
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier