[svn-r27580] Fix for:

HDFFV-9283
Add H5Dget_offset fortran wrapper

tested: h5committest
This commit is contained in:
Scot Breitenfeld 2015-08-25 16:49:36 -05:00
parent 8aef26f785
commit 4939ee2419
7 changed files with 155 additions and 17 deletions

View File

@ -1094,8 +1094,7 @@ CONTAINS
offset = h5dget_offset(dset_id)
hdferr = 0
IF(offset .LT. 0) hdferr = -1
hdferr = 0 ! never returns a function error because C API never returns a function error.
END SUBROUTINE h5dget_offset_f

View File

@ -436,11 +436,12 @@ h5close_types_c( hid_t_f * types, int_f *lentypes,
*/
int_f
h5init_flags_c( int_f *h5d_flags, size_t_f *h5d_size_flags,
int_f *h5e_flags, hid_t_f *h5e_hid_flags, int_f *h5f_flags,
int_f *h5fd_flags, hid_t_f *h5fd_hid_flags,
int_f *h5g_flags, int_f *h5i_flags, int_f *h5l_flags, int_f *h5o_flags,
hid_t_f *h5p_flags, int_f *h5p_flags_int, int_f *h5r_flags, int_f *h5s_flags,
hsize_t_f *h5s_hsize_flags, int_f *h5t_flags, int_f *h5z_flags, int_f *h5_generic_flags)
int_f *h5e_flags, hid_t_f *h5e_hid_flags, int_f *h5f_flags,
int_f *h5fd_flags, hid_t_f *h5fd_hid_flags,
int_f *h5g_flags, int_f *h5i_flags, int_f *h5l_flags, int_f *h5o_flags,
hid_t_f *h5p_flags, int_f *h5p_flags_int, int_f *h5r_flags, int_f *h5s_flags,
hsize_t_f *h5s_hsize_flags, int_f *h5t_flags, int_f *h5z_flags, int_f *h5_generic_flags,
haddr_t_f *h5_haddr_generic_flags)
/******/
{
int ret_value = -1;
@ -773,7 +774,9 @@ h5init_flags_c( int_f *h5d_flags, size_t_f *h5d_size_flags,
h5_generic_flags[5] = (int_f)H5_ITER_INC; /* Increasing order */
h5_generic_flags[6] = (int_f)H5_ITER_DEC; /* Decreasing order */
h5_generic_flags[7] = (int_f)H5_ITER_NATIVE; /* No particular order, whatever is fastest */
h5_generic_flags[8] = (int_f)H5_ITER_N; /* Number of iteration orders */
h5_generic_flags[8] = (int_f)H5_ITER_N; /* Number of iteration orders */
h5_haddr_generic_flags[0] = (haddr_t_f)HADDR_UNDEF; /* undefined address */
ret_value = 0;
return ret_value;

View File

@ -105,16 +105,17 @@ CONTAINS
i_H5S_hsize_flags, &
i_H5T_flags, &
i_H5Z_flags, &
i_H5generic_flags) &
i_H5generic_flags, &
i_H5generic_haddr_flags) &
BIND(C,NAME='h5init_flags_c')
IMPORT :: HID_T, SIZE_T, HSIZE_T
IMPORT :: HID_T, SIZE_T, HSIZE_T, HADDR_T
IMPORT :: H5D_FLAGS_LEN, H5D_SIZE_FLAGS_LEN, &
H5E_FLAGS_LEN, H5E_HID_FLAGS_LEN, &
H5F_FLAGS_LEN, H5G_FLAGS_LEN, H5FD_FLAGS_LEN, &
H5FD_HID_FLAGS_LEN, H5I_FLAGS_LEN, H5L_FLAGS_LEN, &
H5O_FLAGS_LEN, H5P_FLAGS_LEN, H5P_FLAGS_INT_LEN, &
H5R_FLAGS_LEN, H5S_FLAGS_LEN, H5S_HSIZE_FLAGS_LEN, &
H5T_FLAGS_LEN, H5Z_FLAGS_LEN, H5generic_FLAGS_LEN
H5T_FLAGS_LEN, H5Z_FLAGS_LEN, H5generic_FLAGS_LEN, H5generic_haddr_FLAGS_LEN
IMPLICIT NONE
INTEGER i_H5D_flags(H5D_FLAGS_LEN)
INTEGER(SIZE_T) i_H5D_size_flags(H5D_SIZE_FLAGS_LEN)
@ -135,6 +136,7 @@ CONTAINS
INTEGER i_H5T_flags(H5T_FLAGS_LEN)
INTEGER i_H5Z_flags(H5Z_FLAGS_LEN)
INTEGER i_H5generic_flags(H5generic_FLAGS_LEN)
INTEGER(HADDR_T) i_H5generic_haddr_flags(H5generic_haddr_FLAGS_LEN)
END FUNCTION h5init_flags_c
END INTERFACE
INTERFACE
@ -164,7 +166,8 @@ CONTAINS
H5S_hsize_flags, &
H5T_flags, &
H5Z_flags, &
H5generic_flags)
H5generic_flags,&
H5generic_haddr_flags)
error_3 = h5init1_flags_c(H5LIB_flags )
error = error_1 + error_2 + error_3
END SUBROUTINE h5open_f

View File

@ -316,6 +316,18 @@ MODULE H5GLOBAL
EQUIVALENCE(H5generic_flags(7), H5_ITER_DEC_F)
EQUIVALENCE(H5generic_flags(8), H5_ITER_NATIVE_F)
EQUIVALENCE(H5generic_flags(9), H5_ITER_N_F)
INTEGER, PARAMETER :: H5generic_haddr_FLAGS_LEN = 1
INTEGER(HADDR_T) :: H5generic_haddr_flags(H5generic_haddr_FLAGS_LEN)
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$ATTRIBUTES DLLEXPORT :: /H5generic_haddr_FLAGS/
!DEC$endif
COMMON /H5generic_haddr_FLAGS/ H5generic_haddr_flags
INTEGER(HADDR_T) :: HADDR_UNDEF_F
EQUIVALENCE(H5generic_haddr_flags(1), HADDR_UNDEF_F)
!
! H5G flags declaration
!

View File

@ -524,10 +524,11 @@ H5_FCDLL int_f h5close_c(void);
H5_FCDLL int_f h5init_types_c(hid_t_f *types, hid_t_f *floatingtypes, hid_t_f *integertypes);
H5_FCDLL int_f h5close_types_c(hid_t_f *types, int_f *lentypes, hid_t_f *floatingtypes, int_f *floatinglen, hid_t_f *integertypes, int_f *integerlen);
H5_FCDLL int_f h5init_flags_c(int_f *h5d_flags, size_t_f *h5d_size_flags, int_f *h5e_flags, hid_t_f *h5e_hid_flags, int_f *h5f_flags,
int_f *h5fd_flags, hid_t_f *h5fd_hid_flags,
int_f *h5g_flags, int_f *h5i_flags, int_f *h5l_flags, int_f *h5o_flags,
hid_t_f *h5p_flags, int_f *h5p_flags_int, int_f *h5r_flags, int_f *h5s_flags,
hsize_t_f *h5s_hsize_flags, int_f *h5t_flags, int_f *h5z_flags, int_f *h5_generic_flags);
int_f *h5fd_flags, hid_t_f *h5fd_hid_flags,
int_f *h5g_flags, int_f *h5i_flags, int_f *h5l_flags, int_f *h5o_flags,
hid_t_f *h5p_flags, int_f *h5p_flags_int, int_f *h5r_flags, int_f *h5s_flags,
hsize_t_f *h5s_hsize_flags, int_f *h5t_flags, int_f *h5z_flags, int_f *h5_generic_flags,
haddr_t_f *h5_haddr_generic_flags);
H5_FCDLL int_f h5init1_flags_c(int_f *h5lib_flags);
H5_FCDLL int_f h5get_libversion_c(int_f *majnum, int_f *minnum, int_f *relnum);
H5_FCDLL int_f h5check_version_c(int_f *majnum, int_f *minnum, int_f *relnum);

View File

@ -93,6 +93,8 @@ PROGRAM fortranlibtest
ret_total_error = 0
CALL extenddsettest(cleanup, ret_total_error)
CALL write_test_status(ret_total_error, ' Extendible dataset test', total_error)
CALL test_userblock_offset(cleanup, ret_total_error)
CALL write_test_status(ret_total_error, ' Dataset offset with user block', total_error)
! write(*,*)
! write(*,*) '========================================='

View File

@ -343,7 +343,7 @@ CONTAINS
!Modify dataset creation properties, i.e. enable chunking
!
CALL h5pcreate_f(H5P_DATASET_CREATE_F, crp_list, error)
CALL check("h5pcreat_f",error,total_error)
CALL check("h5pcreate_f",error,total_error)
CALL h5pset_chunk_f(crp_list, RANK, dims1, error)
CALL check("h5pset_chunk_f",error,total_error)
@ -508,5 +508,123 @@ CONTAINS
RETURN
END SUBROUTINE extenddsettest
!
! The following subroutine tests h5dget_offset_f functionality
!
SUBROUTINE test_userblock_offset(cleanup, total_error)
USE ISO_C_BINDING
IMPLICIT NONE
LOGICAL, INTENT(IN) :: cleanup
INTEGER, INTENT(OUT) :: total_error
!
!the dataset is stored in file "offset.h5"
!
INTEGER, PARAMETER :: dset_dim1=2, dset_dim2=10
CHARACTER(LEN=6), PARAMETER :: filename = "offset"
CHARACTER(LEN=80) :: fix_filename
INTEGER(hid_t) :: file, fcpl, dataset, space
INTEGER :: i, j, n, ios
INTEGER(hsize_t), DIMENSION(1:2) :: dims
INTEGER :: f
INTEGER(haddr_t) :: offset
INTEGER, DIMENSION(1:dset_dim1,1:dset_dim2), TARGET :: rdata, data_in
INTEGER :: error
TYPE(C_PTR) :: f_ptr
!
!Create a new file using default properties.
!
CALL h5_fixname_f(filename, fix_filename, H5P_DEFAULT_F, error)
IF (error .NE. 0) THEN
WRITE(*,*) "Cannot modify filename"
STOP
ENDIF
CALL h5pcreate_f(H5P_FILE_CREATE_F, fcpl, error)
CALL check("h5pcreate_f",error,total_error)
! Initialize the dataset
n = 0
DO i = 1, dset_dim1
DO j = 1, dset_dim2
n = n + 1
data_in(i,j) = n
END DO
END DO
CALL h5fcreate_f(fix_filename, H5F_ACC_TRUNC_F, file, error, fcpl)
CALL check("h5fcreate_f",error,total_error)
! Create the data space
dims(1:2) = (/dset_dim1,dset_dim2/)
CALL h5screate_simple_f(2, dims, space, error)
CALL check("h5screate_simple_f",error,total_error)
! Create the dataset
CALL h5dcreate_f(file, "dset1", H5T_NATIVE_INTEGER, space, dataset, error)
CALL check("h5dcreate_f", error, total_error)
! Test dataset address. Should be undefined.
CALL h5dget_offset_f(dataset, offset, error)
CALL VERIFY("h5dget_offset_f",offset, HADDR_UNDEF_F, total_error)
! Write the data to the dataset
f_ptr = C_LOC(data_in(1,1))
CALL h5dwrite_f(dataset, H5T_NATIVE_INTEGER, f_ptr, error)
CALL check("h5dwrite_f", error, total_error)
! Test dataset address in file. Open the same file as a C file, seek
! the data position as H5Dget_offset points to, read the dataset, and
! compare it with the data written in.
CALL h5dget_offset_f(dataset, offset, error)
CALL check("h5dget_offset_f", error, total_error)
IF(offset.EQ.HADDR_UNDEF_F)THEN
total_error = total_error + 1
ENDIF
CALL h5dclose_f(dataset, error)
CALL check("h5dclose_f", error, total_error)
CALL h5fclose_f(file, error)
CALL check("h5fclose_f", error, total_error)
IF(total_error.NE.0) RETURN
OPEN(10,FILE=fix_filename, ACCESS="STREAM", IOSTAT=ios)
IF(ios.NE.0)THEN
WRITE(*,'(A)') "Failed to open file "//TRIM(fix_filename)
total_error = total_error + 1
RETURN
ENDIF
! The pos= specifier illustrates that positions are in bytes,
! starting from byte 1 (as opposed to C, where they start from byte 0)
READ(10, POS=offset+1, IOSTAT=ios) rdata
IF(ios.NE.0)THEN
WRITE(*,'(A)') "Failed to read data from stream I/O "
total_error = total_error + 1
CLOSE(10)
RETURN
ENDIF
! Check that the values read are the same as the values written
DO i = 1, dset_dim1
DO j = 1, dset_dim2
CALL VERIFY("h5dget_offset_f",rdata(i,j), data_in(i,j), total_error)
IF(total_error.NE.0)THEN
WRITE(*,'(A)') " Read different values than written."
WRITE(*,'(2(A,I0))') " At index ",i,",",j
CLOSE(10)
RETURN
ENDIF
END DO
END DO
CLOSE(10)
END SUBROUTINE test_userblock_offset
END MODULE TH5D