summaryrefslogtreecommitdiffstats
path: root/fortran/test/tH5T.f90
diff options
context:
space:
mode:
authorElena Pourmal <epourmal@hdfgroup.org>2008-05-03 23:39:37 (GMT)
committerElena Pourmal <epourmal@hdfgroup.org>2008-05-03 23:39:37 (GMT)
commitdcad778b42d371c5429b913c65ec5c32f658d94e (patch)
tree3aa9f6ad4ef79064db548aa0ff692d2d1c6bbb51 /fortran/test/tH5T.f90
parent8090e1c6035e784402f8185434f291b63fe1d7c2 (diff)
downloadhdf5-dcad778b42d371c5429b913c65ec5c32f658d94e.zip
hdf5-dcad778b42d371c5429b913c65ec5c32f658d94e.tar.gz
hdf5-dcad778b42d371c5429b913c65ec5c32f658d94e.tar.bz2
[svn-r14923] Maintenance: This check-in merges changes from the fortran_1_8 branch back into the trunk (up to revision 14921)
Platforms tested: kagiso with g95 and Intel compilers; more testing will be done after checking in a fresh copy from the trunk. New code itself was tested with all Fortran compilers available at THG
Diffstat (limited to 'fortran/test/tH5T.f90')
-rw-r--r--fortran/test/tH5T.f9065
1 files changed, 63 insertions, 2 deletions
diff --git a/fortran/test/tH5T.f90 b/fortran/test/tH5T.f90
index 3bbb974..4857a2b 100644
--- a/fortran/test/tH5T.f90
+++ b/fortran/test/tH5T.f90
@@ -27,7 +27,7 @@
! The following H5T interface functions are tested:
! h5tcopy_f, h5tset(get)_size_f, h5tcreate_f, h5tinsert_f, h5tclose_f,
! h5tget_class_f, h5tget_member_name_f, h5tget_member_offset_f, h5tget_member_type_f,
-! h5tequal_f, h5tinsert_array_f, h5tcommit_f
+! h5tequal_f, h5tinsert_array_f, h5tcommit_f, h5tencode_f, h5tdecode_f
USE HDF5 ! This module contains all necessary modules
@@ -88,6 +88,12 @@
INTEGER(SIZE_T) :: sizechar
INTEGER(HSIZE_T), DIMENSION(1) :: data_dims
LOGICAL :: flag = .TRUE.
+
+ CHARACTER(LEN=1024) :: cmpd_buf
+ INTEGER(size_t) :: cmpd_buf_size=0
+ INTEGER(hid_t) :: decoded_sid1
+ INTEGER :: decoded_tid1
+
data_dims(1) = dimsize
!
! Initialize data buffer.
@@ -176,7 +182,36 @@
!
offset = offset + type_sized ! Offset of the last member is 14
CALL h5tinsert_f(dtype_id, "real_field", offset, H5T_NATIVE_REAL, error)
- CALL check("h5tinsert_f", error, total_error)
+ CALL check("h5tinsert_f", error, total_error)
+
+!!$ !/*-----------------------------------------------------------------------
+!!$ ! * Test encoding and decoding compound datatypes
+!!$ ! *-----------------------------------------------------------------------
+!!$ !*/
+!!$ ! /* Encode compound type in a buffer */
+!!$
+!!$ ! First find the buffer size
+!!$
+!!$ CALL H5Tencode_f(dtype_id, cmpd_buf, cmpd_buf_size, error)
+!!$ CALL check("H5Tencode_f", error, total_error)
+!!$
+!!$ ! /* Try decoding bogus buffer */
+!!$
+!!$ CALL H5Tdecode_f(cmpd_buf, decoded_tid1, error)
+!!$ CALL VERIFY("H5Tdecode_f", error, -1, total_error)
+!!$
+!!$ CALL H5Tencode_f(dtype_id, cmpd_buf, cmpd_buf_size, error)
+!!$ CALL check("H5Tencode_f", error, total_error)
+!!$
+!!$ ! /* Decode from the compound buffer and return an object handle */
+!!$ CALL H5Tdecode_f(cmpd_buf, decoded_tid1, error)
+!!$ CALL check("H5Tdecode_f", error, total_error)
+!!$
+!!$ ! /* Verify that the datatype was copied exactly */
+!!$
+!!$ CALL H5Tequal_f(decoded_tid1, dtype_id, flag, error)
+!!$ CALL check("H5Tequal_f", error, total_error)
+!!$ CALL VerifyLogical("H5Tequal_f", flag, .TRUE., total_error)
!
! Create the dataset with compound datatype.
@@ -485,7 +520,33 @@
endif
enddo
!
+ ! *-----------------------------------------------------------------------
+ ! * Test encoding and decoding compound datatypes
+ ! *-----------------------------------------------------------------------
+ !
+ ! /* Encode compound type in a buffer */
+ ! -- First find the buffer size
+
+ CALL H5Tencode_f(dtype_id, cmpd_buf, cmpd_buf_size, error)
+ CALL check("H5Tencode_f", error, total_error)
+ ! /* Try decoding bogus buffer */
+
+ CALL H5Tdecode_f(cmpd_buf, decoded_tid1, error)
+ CALL VERIFY("H5Tdecode_f", error, -1, total_error)
+
+ CALL H5Tencode_f(dtype_id, cmpd_buf, cmpd_buf_size, error)
+ CALL check("H5Tencode_f", error, total_error)
+
+ ! /* Decode from the compound buffer and return an object handle */
+ CALL H5Tdecode_f(cmpd_buf, decoded_tid1, error)
+ CALL check("H5Tdecode_f", error, total_error)
+
+ ! /* Verify that the datatype was copied exactly */
+
+ CALL H5Tequal_f(decoded_tid1, dtype_id, flag, error)
+ CALL check("H5Tequal_f", error, total_error)
+ CALL VerifyLogical("H5Tequal_f", flag, .TRUE., total_error)
!
! Close all open objects.
!