diff options
author | Scot Breitenfeld <brtnfld@hdfgroup.org> | 2008-09-08 15:02:44 (GMT) |
---|---|---|
committer | Scot Breitenfeld <brtnfld@hdfgroup.org> | 2008-09-08 15:02:44 (GMT) |
commit | 077b6446063d54ab7ebd4bfa15f952404adfcc05 (patch) | |
tree | 9882a9f68a1413236ccdd7bad94f92a410561551 /fortran/src/H5Sff.f90 | |
parent | e43736b22b2a68268b134a042cf193b56834a4b5 (diff) | |
download | hdf5-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/H5Sff.f90')
-rw-r--r-- | fortran/src/H5Sff.f90 | 259 |
1 files changed, 27 insertions, 232 deletions
diff --git a/fortran/src/H5Sff.f90 b/fortran/src/H5Sff.f90 index c212d9a..d21b9e1 100644 --- a/fortran/src/H5Sff.f90 +++ b/fortran/src/H5Sff.f90 @@ -47,13 +47,7 @@ ! ! Comment: !---------------------------------------------------------------------- - 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 -! + SUBROUTINE h5screate_simple_f(rank, dims, space_id, hdferr, maxdims) IMPLICIT NONE INTEGER, INTENT(IN) :: rank ! Number of dataspace dimensions @@ -123,13 +117,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 INTEGER, INTENT(OUT) :: hdferr ! Error code @@ -176,14 +163,7 @@ ! Comment: !---------------------------------------------------------------------- - 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 -! - + SUBROUTINE h5screate_f(classtype, space_id, hdferr) IMPLICIT NONE INTEGER, INTENT(IN) :: classtype ! The type of the dataspace ! to be created. @@ -237,14 +217,7 @@ ! Comment: !---------------------------------------------------------------------- - 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 -! - + SUBROUTINE h5scopy_f(space_id, new_space_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER(HID_T), INTENT(OUT) :: new_space_id @@ -294,14 +267,7 @@ ! ! Comment: !---------------------------------------------------------------------- - 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 -! - + SUBROUTINE h5sget_select_hyper_nblocks_f(space_id, num_blocks, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER(HSSIZE_T), INTENT(OUT) :: num_blocks @@ -356,14 +322,7 @@ !---------------------------------------------------------------------- SUBROUTINE h5sget_select_hyper_blocklist_f(space_id, startblock, & - 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 -! - + num_blocks, buf, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER(HSIZE_T), INTENT(IN) :: startblock @@ -428,13 +387,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 INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: start @@ -489,14 +441,7 @@ ! ! Comment: !---------------------------------------------------------------------- - 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 -! - + SUBROUTINE h5sget_select_elem_npoints_f(space_id, num_points, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER(HSSIZE_T), INTENT(OUT) :: num_points @@ -551,13 +496,7 @@ !---------------------------------------------------------------------- SUBROUTINE h5sget_select_elem_pointlist_f(space_id, startpoint, & - 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 -! + num_points, buf, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER(HSIZE_T), INTENT(IN) :: startpoint @@ -621,13 +560,7 @@ ! Comment: !---------------------------------------------------------------------- SUBROUTINE h5sselect_elements_f(space_id, operator, rank, & - 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 -! + num_elements, coord, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER, INTENT(IN) :: operator ! Flag, valid values are: @@ -701,13 +634,7 @@ ! Comment: !---------------------------------------------------------------------- - 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 -! + SUBROUTINE h5sselect_all_f(space_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER, INTENT(OUT) :: hdferr ! Error code @@ -754,14 +681,7 @@ ! Comment: !---------------------------------------------------------------------- - 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 -! - + SUBROUTINE h5sselect_none_f(space_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER, INTENT(OUT) :: hdferr ! Error code @@ -808,14 +728,7 @@ ! ! Comment: !---------------------------------------------------------------------- - 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 -! - + SUBROUTINE h5sselect_valid_f(space_id, status, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier LOGICAL, INTENT(OUT) :: status ! TRUE if the selection is @@ -869,14 +782,7 @@ ! Comment: !---------------------------------------------------------------------- - 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 -! - + SUBROUTINE h5sget_simple_extent_npoints_f(space_id, npoints, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER(HSIZE_T), INTENT(OUT) :: npoints ! Number of elements in @@ -926,14 +832,7 @@ ! Comment: !---------------------------------------------------------------------- - 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 -! - + SUBROUTINE h5sget_select_npoints_f(space_id, npoints, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER(HSSIZE_T), INTENT(OUT) :: npoints ! Number of elements in the @@ -983,14 +882,7 @@ ! Comment: !---------------------------------------------------------------------- - 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 -! - + SUBROUTINE h5sget_simple_extent_ndims_f(space_id, rank, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER, INTENT(OUT) :: rank ! Number of dimensions @@ -1041,14 +933,7 @@ ! Comment: !---------------------------------------------------------------------- - 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 -! - + SUBROUTINE h5sget_simple_extent_dims_f(space_id, dims, maxdims, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: dims @@ -1108,14 +993,7 @@ ! Comment: !---------------------------------------------------------------------- - 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 -! - + SUBROUTINE h5sget_simple_extent_type_f(space_id, classtype, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER, INTENT(OUT) :: classtype ! Class type , possible values @@ -1174,13 +1052,6 @@ SUBROUTINE h5sset_extent_simple_f(space_id, rank, current_size, & 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 INTEGER, INTENT(IN) :: rank ! Dataspace rank @@ -1241,14 +1112,7 @@ ! Comment: !---------------------------------------------------------------------- - 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 -! - + SUBROUTINE h5sis_simple_f(space_id, status, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier LOGICAL, INTENT(OUT) :: status ! Flag, idicates if dataspace @@ -1302,14 +1166,7 @@ ! ! Comment: !---------------------------------------------------------------------- - 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 -! - + SUBROUTINE h5soffset_simple_f(space_id, offset, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER(HSSIZE_T), DIMENSION(*), INTENT(IN) :: offset @@ -1362,14 +1219,7 @@ ! Comment: !---------------------------------------------------------------------- - 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 -! - + SUBROUTINE h5sextent_copy_f(dest_space_id, source_space_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: dest_space_id ! Identifier of destination ! dataspace @@ -1418,14 +1268,7 @@ ! ! Comment: !---------------------------------------------------------------------- - 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 -! - + SUBROUTINE h5sset_extent_none_f(space_id, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER, INTENT(OUT) :: hdferr ! Error code @@ -1480,13 +1323,7 @@ !---------------------------------------------------------------------- SUBROUTINE h5sselect_hyperslab_f(space_id, operator, start, count, & - hdferr, stride, block) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5sselect_hyperslab_f -!DEC$endif -! + hdferr, stride, block) IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER, INTENT(IN) :: operator ! Flag, valid values are: @@ -1619,13 +1456,7 @@ !---------------------------------------------------------------------- ! SUBROUTINE h5scombine_hyperslab_f(space_id, operator, start, count, & -! 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 -! +! hyper_id, hdferr, stride, block) ! IMPLICIT NONE ! INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier ! INTEGER, INTENT(IN) :: operator ! Flag, valid values are: @@ -1761,13 +1592,7 @@ !---------------------------------------------------------------------- ! SUBROUTINE h5scombine_select_f(space1_id, operator, space2_id, & -! ds_id, hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5scombine_select_f -!DEC$endif -! +! ds_id, hdferr) ! IMPLICIT NONE ! INTEGER(HID_T), INTENT(IN) :: space1_id ! First dataspace identifier ! INTEGER(HID_T), INTENT(IN) :: space2_id ! Second dataspace identifier @@ -1840,13 +1665,7 @@ !---------------------------------------------------------------------- ! SUBROUTINE h5sselect_select_f(space1_id, operator, space2_id, & -! hdferr) -! -!This definition is needed for Windows DLLs -!DEC$if defined(BUILD_HDF5_DLL) -!DEC$attributes dllexport :: h5sselect_select_f -!DEC$endif -! +! hdferr) ! IMPLICIT NONE ! INTEGER(HID_T), INTENT(INOUT) :: space1_id ! Dataspace identifier to ! modify @@ -1909,13 +1728,7 @@ ! Comment: !---------------------------------------------------------------------- - 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 -! + SUBROUTINE h5sget_select_type_f(space_id, type, hdferr) IMPLICIT NONE INTEGER(HID_T), INTENT(INOUT) :: space_id ! Dataspace identifier to INTEGER, INTENT(OUT) :: type ! Selection type @@ -1965,13 +1778,7 @@ ! Comment: !---------------------------------------------------------------------- - 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 -! + SUBROUTINE h5sdecode_f(buf, obj_id, hdferr) 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 @@ -2017,13 +1824,7 @@ ! Comment: !---------------------------------------------------------------------- - 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 -! + SUBROUTINE h5sencode_f(obj_id, buf, nalloc, hdferr) 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. @@ -2073,12 +1874,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. |