diff options
Diffstat (limited to 'fortran/src/H5Sff.f90')
-rw-r--r-- | fortran/src/H5Sff.f90 | 148 |
1 files changed, 146 insertions, 2 deletions
diff --git a/fortran/src/H5Sff.f90 b/fortran/src/H5Sff.f90 index 881f5da..4ff5bb2 100644 --- a/fortran/src/H5Sff.f90 +++ b/fortran/src/H5Sff.f90 @@ -33,6 +33,12 @@ ! 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 +! IMPLICIT NONE INTEGER, INTENT(IN) :: rank ! Number of dataspace dimensions @@ -100,6 +106,12 @@ !---------------------------------------------------------------------- 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 @@ -146,6 +158,12 @@ !---------------------------------------------------------------------- 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 +! IMPLICIT NONE INTEGER, INTENT(IN) :: classtype ! The type of the dataspace @@ -198,6 +216,12 @@ !---------------------------------------------------------------------- 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier @@ -247,6 +271,12 @@ ! 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier @@ -301,6 +331,12 @@ 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier @@ -325,7 +361,7 @@ !MS$ATTRIBUTES C,reference,alias:'_H5SGET_SELECT_HYPER_BLOCKLIST_C'::h5sget_select_hyper_blocklist_c INTEGER(HID_T), INTENT(IN) :: space_id INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: startblock - INTEGER(HSSIZE_T), INTENT(OUT) :: num_blocks + INTEGER(HSSIZE_T), INTENT(IN) :: num_blocks INTEGER(HSIZE_T), DIMENSION(*), INTENT(OUT) :: buf END FUNCTION h5sget_select_hyper_blocklist_c END INTERFACE @@ -364,6 +400,12 @@ !---------------------------------------------------------------------- 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 @@ -418,6 +460,12 @@ ! 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier @@ -472,6 +520,12 @@ 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER(HSIZE_T),DIMENSION(*), INTENT(IN) :: startpoint @@ -534,6 +588,12 @@ !---------------------------------------------------------------------- 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER, INTENT(IN) :: operator ! Flag, valid values are: @@ -561,7 +621,7 @@ !MS$ATTRIBUTES C,reference,alias:'_H5SSELECT_ELEMENTS_C'::h5sselect_elements_c INTEGER(HID_T), INTENT(IN) :: space_id INTEGER, INTENT(IN) :: operator - INTEGER, INTENT(IN) :: num_elements + INTEGER(SIZE_T), INTENT(IN) :: num_elements INTEGER(HSSIZE_T),DIMENSION(*) :: c_c_coord END FUNCTION h5sselect_elements_c END INTERFACE @@ -606,6 +666,12 @@ !---------------------------------------------------------------------- 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER, INTENT(OUT) :: hdferr ! Error code @@ -651,6 +717,12 @@ !---------------------------------------------------------------------- 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier @@ -697,6 +769,12 @@ ! 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier @@ -750,6 +828,12 @@ !---------------------------------------------------------------------- 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier @@ -799,6 +883,12 @@ !---------------------------------------------------------------------- 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier @@ -848,6 +938,12 @@ !---------------------------------------------------------------------- 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier @@ -898,6 +994,12 @@ !---------------------------------------------------------------------- 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier @@ -956,6 +1058,12 @@ !---------------------------------------------------------------------- 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier @@ -1012,6 +1120,12 @@ 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 @@ -1072,6 +1186,12 @@ !---------------------------------------------------------------------- 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier @@ -1125,6 +1245,12 @@ ! 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier @@ -1177,6 +1303,12 @@ !---------------------------------------------------------------------- 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: dest_space_id ! Identifier of destination @@ -1225,6 +1357,12 @@ ! 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier @@ -1279,6 +1417,12 @@ 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 +! IMPLICIT NONE INTEGER(HID_T), INTENT(IN) :: space_id ! Dataspace identifier INTEGER, INTENT(IN) :: operator ! Flag, valid values are: |