mirror of
https://github.com/HDFGroup/hdf5.git
synced 2025-03-31 17:10:47 +08:00
[svn-r25304] Fixes latest check-in errors for:
HDFFV-8653 replace non-standard sizeof in the fortran tests with c_sizeof (1) Removed the overloaded h5_sizeof functions for characters and integer arrays since Sun compilers don't allow them to be passed into a function that uses sizeof. (2) Requested min. precision for reals to avoid duplicate interfaces when the flag -r8 (or equiv.) is set. tested: *jam: intel, -i8 -r8 --enable-fortran2003 *jam: pgi, --enable-fortran2003 *emu: sun, --enable-fortran2003
This commit is contained in:
parent
0b75068901
commit
bfb60a0cc1
@ -385,6 +385,8 @@ SUBROUTINE test_h5p_file_image(total_error)
|
||||
TYPE(C_PTR), DIMENSION(1:count) :: f_ptr1
|
||||
TYPE(C_PTR), DIMENSION(1:1) :: f_ptr2
|
||||
|
||||
INTEGER(HSIZE_T) :: sizeof_buffer
|
||||
|
||||
! Initialize file image buffer
|
||||
DO i = 1, count
|
||||
buffer(i) = i*10
|
||||
@ -403,7 +405,8 @@ SUBROUTINE test_h5p_file_image(total_error)
|
||||
|
||||
! Set file image
|
||||
f_ptr = C_LOC(buffer(1))
|
||||
size = H5_SIZEOF(buffer)
|
||||
size = H5_SIZEOF(buffer(1))*count
|
||||
|
||||
CALL h5pset_file_image_f(fapl_1, f_ptr, size, error)
|
||||
CALL check("h5pset_file_image_f", error, total_error)
|
||||
|
||||
@ -456,8 +459,8 @@ SUBROUTINE external_test_offset(cleanup,total_error)
|
||||
INTEGER(hid_t) :: dset=-1 ! dataset
|
||||
INTEGER(hid_t) :: grp=-1 ! group to emit diagnostics
|
||||
INTEGER(size_t) :: i, j ! miscellaneous counters
|
||||
CHARACTER(LEN=180) :: filename ! file names
|
||||
INTEGER, DIMENSION(1:25) :: part ! raw data buffers
|
||||
CHARACTER(LEN=180) :: filename ! file names
|
||||
INTEGER, DIMENSION(1:25) :: part
|
||||
INTEGER, DIMENSION(1:100), TARGET :: whole ! raw data buffers
|
||||
INTEGER(hsize_t), DIMENSION(1:1) :: cur_size ! current data space size
|
||||
INTEGER(hid_t) :: hs_space ! hyperslab data space
|
||||
@ -466,6 +469,7 @@ SUBROUTINE external_test_offset(cleanup,total_error)
|
||||
CHARACTER(LEN=1) :: ichr1 ! character conversion holder
|
||||
INTEGER :: error ! error status
|
||||
TYPE(C_PTR) :: f_ptr ! fortran pointer
|
||||
INTEGER(HSIZE_T) :: sizeof_part
|
||||
|
||||
CHARACTER(LEN=1,KIND=C_CHAR), DIMENSION(1:30) :: temparray
|
||||
|
||||
@ -494,15 +498,18 @@ SUBROUTINE external_test_offset(cleanup,total_error)
|
||||
CALL check("h5gcreate_f",error, total_error)
|
||||
|
||||
! Create the dataset
|
||||
|
||||
sizeof_part = INT(H5_SIZEOF(part(1))*25, hsize_t)
|
||||
|
||||
CALL h5pcreate_f(H5P_DATASET_CREATE_F, dcpl, error)
|
||||
CALL check("h5pcreate_f", error, total_error)
|
||||
CALL h5pset_external_f(dcpl, "extern_1a.raw", INT(0,off_t), INT(H5_SIZEOF(part), hsize_t), error)
|
||||
CALL h5pset_external_f(dcpl, "extern_1a.raw", INT(0,off_t), sizeof_part, error)
|
||||
CALL check("h5pset_external_f",error,total_error)
|
||||
CALL h5pset_external_f(dcpl, "extern_2a.raw", INT(10,off_t), INT(H5_SIZEOF(part), hsize_t), error)
|
||||
CALL h5pset_external_f(dcpl, "extern_2a.raw", INT(10,off_t), sizeof_part, error)
|
||||
CALL check("h5pset_external_f",error,total_error)
|
||||
CALL h5pset_external_f(dcpl, "extern_3a.raw", INT(20,off_t), INT(H5_SIZEOF(part), hsize_t), error)
|
||||
CALL h5pset_external_f(dcpl, "extern_3a.raw", INT(20,off_t), sizeof_part, error)
|
||||
CALL check("h5pset_external_f",error,total_error)
|
||||
CALL h5pset_external_f(dcpl, "extern_4a.raw", INT(30,off_t), INT(H5_SIZEOF(part), hsize_t), error)
|
||||
CALL h5pset_external_f(dcpl, "extern_4a.raw", INT(30,off_t), sizeof_part, error)
|
||||
CALL check("h5pset_external_f",error,total_error)
|
||||
|
||||
cur_size(1) = 100
|
||||
|
@ -1,11 +1,11 @@
|
||||
!****h* root/fortran/test/tf_F08.f90
|
||||
!****h* root/fortran/test/tf_F03.f90
|
||||
!
|
||||
! NAME
|
||||
! tf_F08.f90
|
||||
! tf_F03.f90
|
||||
!
|
||||
! FUNCTION
|
||||
! Contains Functions that are part of the F2008 standard and needed by
|
||||
! the hdf5 fortran tests.
|
||||
! Contains functions that are part of the F2003 standard, and are not F2008 compliant.
|
||||
! Needed by the hdf5 fortran tests.
|
||||
!
|
||||
! COPYRIGHT
|
||||
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
|
||||
@ -26,12 +26,27 @@
|
||||
! CONTAINS SUBROUTINES
|
||||
! H5_SIZEOF
|
||||
!
|
||||
! NOTES
|
||||
! The Sun/Oracle compiler has the following restrictions on the SIZEOF intrinsic function:
|
||||
!
|
||||
! "The SIZEOF intrinsic cannot be applied to arrays of an assumed size, characters of a
|
||||
! length that is passed, or subroutine calls or names. SIZEOF returns default INTEGER*4 data.
|
||||
! If compiling for a 64-bit environment, the compiler will issue a warning if the result overflows
|
||||
! the INTEGER*4 data range. To use SIZEOF in a 64-bit environment with arrays larger
|
||||
! than the INTEGER*4 limit (2 Gbytes), the SIZEOF function and
|
||||
! the variables receiving the result must be declared INTEGER*8."
|
||||
!
|
||||
! Thus, we can not overload the H5_SIZEOF function to handle arrays (as used in tH5P_F03.f90), or
|
||||
! characters that do not have a set length (as used in tH5P_F03.f90), sigh...
|
||||
!
|
||||
!*****
|
||||
MODULE TH5_MISC_PROVISIONAL
|
||||
|
||||
USE ISO_C_BINDING
|
||||
IMPLICIT NONE
|
||||
|
||||
INTEGER, PARAMETER :: sp = KIND(0.0)
|
||||
INTEGER, PARAMETER :: dp = KIND(0.D0)
|
||||
INTEGER, PARAMETER :: sp = SELECTED_REAL_KIND(5) ! This should map to REAL*4 on most modern processors
|
||||
INTEGER, PARAMETER :: dp = SELECTED_REAL_KIND(10) ! This should map to REAL*8 on most modern processors
|
||||
|
||||
! generic compound datatype
|
||||
TYPE, BIND(C) :: comp_datatype
|
||||
@ -40,12 +55,11 @@ MODULE TH5_MISC_PROVISIONAL
|
||||
DOUBLE PRECISION :: y
|
||||
CHARACTER(LEN=1) :: z
|
||||
END TYPE comp_datatype
|
||||
|
||||
|
||||
PUBLIC :: H5_SIZEOF
|
||||
INTERFACE H5_SIZEOF
|
||||
MODULE PROCEDURE H5_SIZEOF_CMPD
|
||||
MODULE PROCEDURE H5_SIZEOF_CHR
|
||||
MODULE PROCEDURE H5_SIZEOF_I, H5_SIZEOF_IV
|
||||
MODULE PROCEDURE H5_SIZEOF_I, H5_SIZEOF_CHR
|
||||
MODULE PROCEDURE H5_SIZEOF_SP,H5_SIZEOF_DP
|
||||
END INTERFACE
|
||||
|
||||
@ -54,7 +68,7 @@ CONTAINS
|
||||
!This definition is needed for Windows DLLs
|
||||
!DEC$if defined(BUILD_HDF5_DLL)
|
||||
!DEC$attributes dllexport :: h5_sizeof_cmpd
|
||||
!DEC$endif
|
||||
!DEC$endif
|
||||
INTEGER(C_SIZE_T) FUNCTION H5_SIZEOF_CMPD(a)
|
||||
IMPLICIT NONE
|
||||
TYPE(comp_datatype), INTENT(in) :: a
|
||||
@ -69,7 +83,7 @@ CONTAINS
|
||||
!DEC$endif
|
||||
INTEGER(C_SIZE_T) FUNCTION H5_SIZEOF_CHR(a)
|
||||
IMPLICIT NONE
|
||||
CHARACTER(LEN=*), INTENT(in):: a
|
||||
CHARACTER(LEN=1), INTENT(in):: a
|
||||
|
||||
H5_SIZEOF_CHR = SIZEOF(a)
|
||||
|
||||
@ -87,18 +101,6 @@ CONTAINS
|
||||
|
||||
END FUNCTION H5_SIZEOF_I
|
||||
|
||||
!This definition is needed for Windows DLLs
|
||||
!DEC$if defined(BUILD_HDF5_DLL)
|
||||
!DEC$attributes dllexport :: h5_sizeof_iv
|
||||
!DEC$endif
|
||||
INTEGER(C_SIZE_T) FUNCTION H5_SIZEOF_IV(a)
|
||||
IMPLICIT NONE
|
||||
INTEGER, DIMENSION(:), INTENT(in):: a
|
||||
|
||||
H5_SIZEOF_IV = SIZEOF(a)
|
||||
|
||||
END FUNCTION H5_SIZEOF_IV
|
||||
|
||||
!This definition is needed for Windows DLLs
|
||||
!DEC$if defined(BUILD_HDF5_DLL)
|
||||
!DEC$attributes dllexport :: h5_sizeof_sp
|
||||
|
@ -43,8 +43,8 @@ MODULE TH5_MISC_PROVISIONAL
|
||||
USE ISO_C_BINDING
|
||||
IMPLICIT NONE
|
||||
|
||||
INTEGER, PARAMETER :: sp = KIND(0.0)
|
||||
INTEGER, PARAMETER :: dp = KIND(0.D0)
|
||||
INTEGER, PARAMETER :: sp = SELECTED_REAL_KIND(5) ! This should map to REAL*4 on most modern processors
|
||||
INTEGER, PARAMETER :: dp = SELECTED_REAL_KIND(10) ! This should map to REAL*8 on most modern processors
|
||||
|
||||
! generic compound datatype
|
||||
TYPE, BIND(C) :: comp_datatype
|
||||
@ -58,7 +58,7 @@ MODULE TH5_MISC_PROVISIONAL
|
||||
INTERFACE H5_SIZEOF
|
||||
MODULE PROCEDURE H5_SIZEOF_CMPD
|
||||
MODULE PROCEDURE H5_SIZEOF_CHR
|
||||
MODULE PROCEDURE H5_SIZEOF_I, H5_SIZEOF_IV
|
||||
MODULE PROCEDURE H5_SIZEOF_I
|
||||
MODULE PROCEDURE H5_SIZEOF_SP,H5_SIZEOF_DP
|
||||
END INTERFACE
|
||||
|
||||
@ -100,17 +100,6 @@ CONTAINS
|
||||
|
||||
END FUNCTION H5_SIZEOF_I
|
||||
|
||||
!This definition is needed for Windows DLLs
|
||||
!DEC$if defined(BUILD_HDF5_DLL)
|
||||
!DEC$attributes dllexport :: h5_sizeof_iv
|
||||
!DEC$endif
|
||||
INTEGER(C_SIZE_T) FUNCTION H5_SIZEOF_IV(a)
|
||||
IMPLICIT NONE
|
||||
INTEGER, DIMENSION(:), INTENT(in):: a
|
||||
|
||||
H5_SIZEOF_IV = SIZE(a)*storage_size(a(1), c_size_t)/storage_size(c_char_'a',c_size_t)
|
||||
|
||||
END FUNCTION H5_SIZEOF_IV
|
||||
|
||||
!This definition is needed for Windows DLLs
|
||||
!DEC$if defined(BUILD_HDF5_DLL)
|
||||
|
Loading…
x
Reference in New Issue
Block a user