summaryrefslogtreecommitdiffstats
path: root/fortran/test/tH5T_F03.f90
diff options
context:
space:
mode:
authorDana Robinson <derobins@hdfgroup.org>2015-02-22 12:16:30 (GMT)
committerDana Robinson <derobins@hdfgroup.org>2015-02-22 12:16:30 (GMT)
commitc07d8036591313caf15cf626122bd7ce4e61be49 (patch)
treede3cfcb2639a3c84254d536d2f4a1ec9239af019 /fortran/test/tH5T_F03.f90
parent179f3b7879e28165869034255b5852b551700ad6 (diff)
parentf634105bdb7c494a5ab39291d64c00676c11b476 (diff)
downloadhdf5-c07d8036591313caf15cf626122bd7ce4e61be49.zip
hdf5-c07d8036591313caf15cf626122bd7ce4e61be49.tar.gz
hdf5-c07d8036591313caf15cf626122bd7ce4e61be49.tar.bz2
[svn-r26274] Merge of r26096 to r26271 from trunk.
Tested on: jam - serial: C++/Fortran parallel: Fortran
Diffstat (limited to 'fortran/test/tH5T_F03.f90')
-rw-r--r--fortran/test/tH5T_F03.f9020
1 files changed, 12 insertions, 8 deletions
diff --git a/fortran/test/tH5T_F03.f90 b/fortran/test/tH5T_F03.f90
index f15424d..e019d0f 100644
--- a/fortran/test/tH5T_F03.f90
+++ b/fortran/test/tH5T_F03.f90
@@ -1419,7 +1419,7 @@ SUBROUTINE t_enum(total_error)
! Insert enumerated value for memtype.
!
val(1) = i
- CALL H5Tenum_insert_f(memtype, TRIM(names(i+1)), val(1), error)
+ CALL H5Tenum_insert_f(memtype, TRIM(names(i+1)), C_LOC(val(1)), error)
CALL check("H5Tenum_insert_f", error, total_error)
!
! Insert enumerated value for filetype. We must first convert
@@ -1428,7 +1428,11 @@ SUBROUTINE t_enum(total_error)
f_ptr = C_LOC(val(1))
CALL H5Tconvert_f(M_BASET, F_BASET, INT(1,SIZE_T), f_ptr, error)
CALL check("H5Tconvert_f",error, total_error)
- CALL H5Tenum_insert_f(filetype, TRIM(names(i+1)), val(1), error)
+ IF(i.GE.1)THEN ! test both F90 and F03 APIs
+ CALL H5Tenum_insert_f(filetype, TRIM(names(i+1)), f_ptr, error)
+ ELSE
+ CALL H5Tenum_insert_f(filetype, TRIM(names(i+1)), val(1), error)
+ ENDIF
CALL check("H5Tenum_insert_f",error, total_error)
ENDDO
!
@@ -3134,7 +3138,7 @@ SUBROUTINE t_enum_conv(total_error)
ENUMERATOR :: E1_RED, E1_GREEN, E1_BLUE, E1_WHITE, E1_BLACK
END ENUM
- INTEGER :: val
+ INTEGER(KIND(E1_RED)), TARGET :: val
! Enumerated data array
! Some values are out of range for testing. The library should accept them
@@ -3185,19 +3189,19 @@ SUBROUTINE t_enum_conv(total_error)
! Initialize enum data.
!
val = E1_RED
- CALL H5Tenum_insert_f(dtype, "RED", val, error)
+ CALL H5Tenum_insert_f(dtype, "RED", C_LOC(val), error)
CALL check("h5tenum_insert_f",error, total_error)
val = E1_GREEN
- CALL H5Tenum_insert_f(dtype, "GREEN", val, error)
+ CALL H5Tenum_insert_f(dtype, "GREEN", C_LOC(val), error)
CALL check("h5tenum_insert_f",error, total_error)
val = E1_BLUE
- CALL H5Tenum_insert_f(dtype, "BLUE", val, error)
+ CALL H5Tenum_insert_f(dtype, "BLUE", C_LOC(val), error)
CALL check("h5tenum_insert_f",error, total_error)
val = E1_WHITE
- CALL H5Tenum_insert_f(dtype, "WHITE", val, error)
+ CALL H5Tenum_insert_f(dtype, "WHITE", C_LOC(val), error)
CALL check("h5tenum_insert_f",error, total_error)
val = E1_BLACK
- CALL H5Tenum_insert_f(dtype, "BLACK", val, error)
+ CALL H5Tenum_insert_f(dtype, "BLACK", C_LOC(val), error)
CALL check("h5tenum_insert_f",error, total_error)
!
! Create dataspace. Setting maximum size to be the current size.