summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Sff.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/src/H5Sff.f90')
-rw-r--r--fortran/src/H5Sff.f90168
1 files changed, 167 insertions, 1 deletions
diff --git a/fortran/src/H5Sff.f90 b/fortran/src/H5Sff.f90
index a4780c1..9e1367d 100644
--- a/fortran/src/H5Sff.f90
+++ b/fortran/src/H5Sff.f90
@@ -1942,4 +1942,170 @@
END SUBROUTINE h5sget_select_type_f
- END MODULE H5S
+!----------------------------------------------------------------------
+! Name: H5Sdecode_f
+!
+! Purpose: Decode a binary object description of data space and return a new object handle.
+!
+! Inputs:
+! buf - Buffer for the data space object to be decoded.
+! obj_id - Object ID
+! Outputs:
+! hdferr: - error code
+! Success: 0
+! Failure: -1
+!
+! Optional parameters: - NONE
+!
+! Programmer: M.S. Breitenfeld
+! March 26, 2008
+!
+! Modifications:
+!
+! 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
+!
+ IMPLICIT NONE
+ CHARACTER(LEN=*), INTENT(IN) :: buf ! Buffer for the data space object to be decoded.
+ INTEGER, INTENT(OUT) :: obj_id ! Object ID
+ INTEGER, INTENT(OUT) :: hdferr ! Error code
+
+ INTERFACE
+ INTEGER FUNCTION h5sdecode_c(buf, obj_id)
+ USE H5GLOBAL
+ !DEC$ IF DEFINED(HDF5F90_WINDOWS)
+ !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SDECODE_C'::h5sdecode_c
+ !DEC$ ENDIF
+ CHARACTER(LEN=*), INTENT(IN) :: buf
+ INTEGER, INTENT(OUT) :: obj_id ! Object ID
+ END FUNCTION h5sdecode_c
+ END INTERFACE
+
+ hdferr = h5sdecode_c(buf, obj_id)
+
+ END SUBROUTINE h5sdecode_f
+
+!----------------------------------------------------------------------
+! Name: H5Sencode_f
+!
+! Purpose: Encode a data space object description into a binary buffer.
+!
+! Inputs:
+! obj_id - Identifier of the object to be encoded.
+! buf - Buffer for the object to be encoded into.
+! nalloc - The size of the allocated buffer.
+! Outputs:
+! nalloc - The size of the buffer needed.
+! hdferr: - error code
+! Success: 0
+! Failure: -1
+!
+! Optional parameters: - NONE
+!
+! Programmer: M.S. Breitenfeld
+! March 26, 2008
+!
+! Modifications:
+!
+! 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
+!
+ 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.
+ INTEGER(SIZE_T), INTENT(INOUT) :: nalloc ! The size of the allocated buffer.
+ INTEGER, INTENT(OUT) :: hdferr ! Error code
+
+
+ INTERFACE
+ INTEGER FUNCTION h5sencode_c(buf, obj_id, nalloc)
+ USE H5GLOBAL
+ !DEC$ IF DEFINED(HDF5F90_WINDOWS)
+ !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SENCODE_C'::h5sencode_c
+ !DEC$ ENDIF
+ INTEGER(HID_T), INTENT(IN) :: obj_id
+ CHARACTER(LEN=*), INTENT(OUT) :: buf
+ INTEGER(SIZE_T), INTENT(INOUT) :: nalloc
+ END FUNCTION h5sencode_c
+ END INTERFACE
+
+ hdferr = h5sencode_c(buf, obj_id, nalloc)
+
+ END SUBROUTINE h5sencode_f
+
+
+!----------------------------------------------------------------------
+! Name: h5sextent_equal_f
+!
+! Purpose: Determines whether two dataspace extents are equal.
+!
+! Inputs:
+! space1_id - First dataspace identifier.
+! space2_id - Second dataspace identifier.
+! Outputs:
+! Equal - .TRUE. if equal, .FALSE. if unequal.
+! hdferr: - error code
+! Success: 0
+! Failure: -1
+! Optional parameters:
+! NONE
+!
+! Programmer: M.S. Breitenfeld
+! April 2, 2008
+!
+! Modifications:
+!
+! Comment:
+!----------------------------------------------------------------------
+
+ 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.
+ LOGICAL, INTENT(OUT) :: Equal ! .TRUE. if equal, .FALSE. if unequal.
+ INTEGER, INTENT(OUT) :: hdferr ! Error code
+
+ INTEGER(HID_T) :: c_equal
+
+ INTERFACE
+ INTEGER FUNCTION h5sextent_equal_c(space1_id, space2_id, c_equal)
+ USE H5GLOBAL
+ !DEC$ IF DEFINED(HDF5F90_WINDOWS)
+ !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5SEXTENT_EQUAL_C'::h5sextent_equal_c
+ !DEC$ ENDIF
+ INTEGER(HID_T), INTENT(IN) :: space1_id
+ INTEGER(HID_T), INTENT(IN) :: space2_id
+ INTEGER(HID_T) :: c_equal
+ END FUNCTION h5sextent_equal_c
+ END INTERFACE
+
+ hdferr = h5sextent_equal_c(space1_id, space2_id, c_equal)
+
+
+ equal = .FALSE.
+ IF(c_equal.GT.0) equal = .TRUE.
+
+
+ END SUBROUTINE h5sextent_equal_f
+
+END MODULE H5S