From 8ca794438092595180b66bf06087e942e0a40bb7 Mon Sep 17 00:00:00 2001 From: Scot Breitenfeld Date: Wed, 29 Jun 2016 14:21:19 -0500 Subject: [svn-r30120] Fixed compilation failure on emu due to moving testing subroutines into a module. Tested: emu and jelly (gnu) --- hl/fortran/test/tstlite.F90 | 3665 +++++++++++++++++++++---------------------- 1 file changed, 1822 insertions(+), 1843 deletions(-) diff --git a/hl/fortran/test/tstlite.F90 b/hl/fortran/test/tstlite.F90 index 9d47c59..42e2bcc 100644 --- a/hl/fortran/test/tstlite.F90 +++ b/hl/fortran/test/tstlite.F90 @@ -20,1900 +20,1880 @@ MODULE TSTLITE -CONTAINS - -!------------------------------------------------------------------------- -! test_begin -!------------------------------------------------------------------------- - -SUBROUTINE test_begin(string) - CHARACTER(LEN=*), INTENT(IN) :: string - WRITE(*, fmt = '(14a)', advance = 'no') string - WRITE(*, fmt = '(40x,a)', advance = 'no') ' ' -END SUBROUTINE test_begin - -!------------------------------------------------------------------------- -! passed -!------------------------------------------------------------------------- - -SUBROUTINE passed() - WRITE(*, fmt = '(6a)') 'PASSED' -END SUBROUTINE passed - -END MODULE TSTLITE - -MODULE TSTLITE_TESTS + IMPLICIT NONE CONTAINS - -!------------------------------------------------------------------------- -! test_dataset1D -!------------------------------------------------------------------------- - -SUBROUTINE test_dataset1D() - - USE, INTRINSIC :: ISO_C_BINDING - USE H5LT ! module of H5LT - USE HDF5 ! module of HDF5 library - USE TSTLITE ! module for testing lite support routines - - IMPLICIT NONE - - INTEGER, PARAMETER :: DIM1 = 4 ! Dimension of array - CHARACTER(len=9), PARAMETER :: filename = "dsetf1.h5"! File name - CHARACTER(LEN=5), PARAMETER :: dsetname1 = "dset1" ! Dataset name - CHARACTER(LEN=5), PARAMETER :: dsetname2 = "dset2" ! Dataset name - CHARACTER(LEN=5), PARAMETER :: dsetname3 = "dset3" ! Dataset name - INTEGER(HID_T) :: file_id ! File identifier - INTEGER(HSIZE_T), DIMENSION(1) :: dims = (/DIM1/) ! Dataset dimensions - INTEGER :: rank = 1 ! Dataset rank - INTEGER, DIMENSION(DIM1) :: buf1 ! Data buffer - INTEGER, DIMENSION(DIM1) :: bufr1 ! Data buffer - REAL, DIMENSION(DIM1) :: buf2 ! Data buffer - REAL, DIMENSION(DIM1) :: bufr2 ! Data buffer - DOUBLE PRECISION, DIMENSION(DIM1), TARGET :: buf3 ! Data buffer - DOUBLE PRECISION, DIMENSION(DIM1), TARGET :: bufr3 ! Data buffer - INTEGER :: errcode ! Error flag - INTEGER :: i ! general purpose integer - TYPE(C_PTR) :: f_ptr - integer(HID_T) :: mytype - - CALL test_begin(' Make/Read datasets (1D) ') - - ! - ! Initialize the data array. - ! - DO i = 1, DIM1 - buf1(i) = i - buf2(i) = i - buf3(i) = i - END DO - - ! - ! Initialize FORTRAN predefined datatypes. - ! - CALL h5open_f(errcode) - - ! - ! Create a new file using default properties. - ! - CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, errcode) - !------------------------------------------------------------------------- - ! H5T_NATIVE_INTEGER + ! test_begin !------------------------------------------------------------------------- - ! - ! write dataset. - ! - CALL h5ltmake_dataset_f(file_id, dsetname1, rank, dims, H5T_NATIVE_INTEGER, buf1, errcode) - ! - ! read dataset. - ! - CALL h5ltread_dataset_f(file_id, dsetname1, H5T_NATIVE_INTEGER, bufr1, dims, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, DIM1 - IF ( buf1(i) .NE. bufr1(i) ) THEN - PRINT *, 'read buffer differs from write buffer (I)' - PRINT *, bufr1(i), ' and ', buf1(i) - STOP - ENDIF - END DO + SUBROUTINE test_begin(string) + IMPLICIT NONE + CHARACTER(LEN=*), INTENT(IN) :: string + WRITE(*, fmt = '(14a)', advance = 'no') string + WRITE(*, fmt = '(40x,a)', advance = 'no') ' ' + END SUBROUTINE test_begin !------------------------------------------------------------------------- - ! H5T_NATIVE_REAL + ! passed !------------------------------------------------------------------------- - ! - ! write dataset. - ! - CALL h5ltmake_dataset_f(file_id, dsetname2, rank, dims, H5T_NATIVE_REAL, buf2, errcode) - - ! - ! read dataset. - ! - CALL h5ltread_dataset_f(file_id, dsetname2, H5T_NATIVE_REAL, bufr2, dims, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, DIM1 - IF ( buf2(i) .NE. bufr2(i) ) THEN - PRINT *, 'read buffer differs from write buffer (R)' - PRINT *, bufr2(i), ' and ', buf2(i) - STOP - ENDIF - END DO + SUBROUTINE passed() + IMPLICIT NONE + WRITE(*, fmt = '(6a)') 'PASSED' + END SUBROUTINE passed - !------------------------------------------------------------------------- - ! H5T_NATIVE_DOUBLE - !------------------------------------------------------------------------- +END MODULE TSTLITE - ! - ! write dataset. - ! - f_ptr = C_LOC(buf3(1)) - mytype = h5kind_to_type(KIND(buf3(1)), H5_REAL_KIND) - CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims, & - mytype, f_ptr, errcode) - !CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims, H5T_NATIVE_DOUBLE, buf3, errcode) - ! h5kind_to_type(KIND(buf3(1)), H5_REAL_KIND) - ! - ! read dataset. - ! - f_ptr = C_LOC(bufr3(1)) - CALL h5ltread_dataset_f(file_id, dsetname3, & - h5kind_to_type(KIND(bufr3(1)), H5_REAL_KIND), f_ptr, errcode) - !CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_DOUBLE, bufr3, dims, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, DIM1 - IF ( buf3(i) .NE. bufr3(i) ) THEN - PRINT *, 'read buffer differs from write buffer (D)' - PRINT *, bufr3(i), ' and ', buf3(i) - STOP - ENDIF - END DO - - ! - ! Close the file. - ! - CALL h5fclose_f(file_id, errcode) - - ! - ! Close FORTRAN predefined datatypes. - ! - CALL h5close_f(errcode) - - CALL passed() - ! - ! end function. - ! -END SUBROUTINE test_dataset1D - -!------------------------------------------------------------------------- -! test_dataset2D -!------------------------------------------------------------------------- - -SUBROUTINE test_dataset2D() +MODULE TSTLITE_TESTS USE, INTRINSIC :: ISO_C_BINDING - USE H5LT ! module of H5LT - USE HDF5 ! module of HDF5 library + USE H5LT ! module of H5LT + USE HDF5 ! module of HDF5 library USE TSTLITE ! module for testing lite support routines - IMPLICIT NONE +CONTAINS - INTEGER(HSIZE_T), PARAMETER :: DIM1 = 4 ! columns - INTEGER(HSIZE_T), PARAMETER :: DIM2 = 6 ! rows - CHARACTER(len=9), PARAMETER :: filename = "dsetf2.h5"! File name - CHARACTER(LEN=5), PARAMETER :: dsetname1 = "dset1" ! Dataset name - CHARACTER(LEN=5), PARAMETER :: dsetname2 = "dset2" ! Dataset name - CHARACTER(LEN=5), PARAMETER :: dsetname3 = "dset3" ! Dataset name - CHARACTER(LEN=5), PARAMETER :: dsetname4 = "dset4" ! Dataset name - INTEGER(HID_T) :: file_id ! File identifier - INTEGER(HSIZE_T), DIMENSION(2) :: dims = (/4,6/) ! Dataset dimensions - INTEGER :: rank = 2 ! Dataset rank - INTEGER, DIMENSION(DIM1*DIM2) :: buf ! Data buffer - INTEGER, DIMENSION(DIM1*DIM2) :: bufr ! Data buffer - INTEGER, DIMENSION(DIM1,DIM2) :: buf2 ! Data buffer - INTEGER, DIMENSION(DIM1,DIM2) :: buf2r ! Data buffer - REAL, DIMENSION(DIM1,DIM2), TARGET :: buf3 ! Data buffer - REAL, DIMENSION(DIM1,DIM2), TARGET :: buf3r ! Data buffer - DOUBLE PRECISION, DIMENSION(DIM1,DIM2), TARGET :: buf4 ! Data buffer - DOUBLE PRECISION, DIMENSION(DIM1,DIM2), TARGET :: buf4r ! Data buffer - INTEGER :: errcode ! Error flag - INTEGER(HSIZE_T) :: i, j, n ! general purpose integers - TYPE(C_PTR) :: f_ptr - - CALL test_begin(' Make/Read datasets (2D) ') - - - ! - ! Initialize the data arrays. - ! - n=1 - DO i = 1, DIM1*DIM2 - buf(i) = INT(n) - n = n + 1 - END DO - - DO i = 1, dims(1) - DO j = 1, dims(2) - buf2(i,j) = INT((i-1)*dims(2) + j) - buf3(i,j) = INT((i-1)*dims(2) + j) - buf4(i,j) = INT((i-1)*dims(2) + j) - END DO - END DO - - ! - ! Initialize FORTRAN predefined datatypes. - ! - CALL h5open_f(errcode) - - ! - ! Create a new file using default properties. - ! - CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, errcode) !------------------------------------------------------------------------- - ! H5T_NATIVE_INT 1D buffer + ! test_dataset1D !------------------------------------------------------------------------- - ! - ! write dataset. - ! - CALL h5ltmake_dataset_f(file_id, dsetname1, rank, dims, H5T_NATIVE_INTEGER, buf, errcode) - - ! - ! read dataset. - ! - CALL h5ltread_dataset_f(file_id, dsetname1, H5T_NATIVE_INTEGER, bufr, dims, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, DIM1*DIM2 - IF ( buf(i) .NE. bufr(i) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, bufr(i), ' and ', buf(i) - STOP - ENDIF - END DO + SUBROUTINE test_dataset1D() + + IMPLICIT NONE + + INTEGER, PARAMETER :: DIM1 = 4 ! Dimension of array + CHARACTER(len=9), PARAMETER :: filename = "dsetf1.h5"! File name + CHARACTER(LEN=5), PARAMETER :: dsetname1 = "dset1" ! Dataset name + CHARACTER(LEN=5), PARAMETER :: dsetname2 = "dset2" ! Dataset name + CHARACTER(LEN=5), PARAMETER :: dsetname3 = "dset3" ! Dataset name + INTEGER(HID_T) :: file_id ! File identifier + INTEGER(HSIZE_T), DIMENSION(1) :: dims = (/DIM1/) ! Dataset dimensions + INTEGER :: rank = 1 ! Dataset rank + INTEGER, DIMENSION(DIM1) :: buf1 ! Data buffer + INTEGER, DIMENSION(DIM1) :: bufr1 ! Data buffer + REAL, DIMENSION(DIM1) :: buf2 ! Data buffer + REAL, DIMENSION(DIM1) :: bufr2 ! Data buffer + DOUBLE PRECISION, DIMENSION(DIM1), TARGET :: buf3 ! Data buffer + DOUBLE PRECISION, DIMENSION(DIM1), TARGET :: bufr3 ! Data buffer + INTEGER :: errcode ! Error flag + INTEGER :: i ! general purpose integer + TYPE(C_PTR) :: f_ptr + integer(HID_T) :: mytype + + CALL test_begin(' Make/Read datasets (1D) ') + + ! + ! Initialize the data array. + ! + DO i = 1, DIM1 + buf1(i) = i + buf2(i) = i + buf3(i) = i + END DO + + ! + ! Initialize FORTRAN predefined datatypes. + ! + CALL h5open_f(errcode) + + ! + ! Create a new file using default properties. + ! + CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, errcode) + + !------------------------------------------------------------------------- + ! H5T_NATIVE_INTEGER + !------------------------------------------------------------------------- + + ! + ! write dataset. + ! + CALL h5ltmake_dataset_f(file_id, dsetname1, rank, dims, H5T_NATIVE_INTEGER, buf1, errcode) + ! + ! read dataset. + ! + CALL h5ltread_dataset_f(file_id, dsetname1, H5T_NATIVE_INTEGER, bufr1, dims, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, DIM1 + IF ( buf1(i) .NE. bufr1(i) ) THEN + PRINT *, 'read buffer differs from write buffer (I)' + PRINT *, bufr1(i), ' and ', buf1(i) + STOP + ENDIF + END DO + + !------------------------------------------------------------------------- + ! H5T_NATIVE_REAL + !------------------------------------------------------------------------- + + ! + ! write dataset. + ! + CALL h5ltmake_dataset_f(file_id, dsetname2, rank, dims, H5T_NATIVE_REAL, buf2, errcode) + + ! + ! read dataset. + ! + CALL h5ltread_dataset_f(file_id, dsetname2, H5T_NATIVE_REAL, bufr2, dims, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, DIM1 + IF ( buf2(i) .NE. bufr2(i) ) THEN + PRINT *, 'read buffer differs from write buffer (R)' + PRINT *, bufr2(i), ' and ', buf2(i) + STOP + ENDIF + END DO + + !------------------------------------------------------------------------- + ! H5T_NATIVE_DOUBLE + !------------------------------------------------------------------------- + + ! + ! write dataset. + ! + f_ptr = C_LOC(buf3(1)) + mytype = h5kind_to_type(KIND(buf3(1)), H5_REAL_KIND) + CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims, & + mytype, f_ptr, errcode) + !CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims, H5T_NATIVE_DOUBLE, buf3, errcode) + ! h5kind_to_type(KIND(buf3(1)), H5_REAL_KIND) + ! + ! read dataset. + ! + f_ptr = C_LOC(bufr3(1)) + CALL h5ltread_dataset_f(file_id, dsetname3, & + h5kind_to_type(KIND(bufr3(1)), H5_REAL_KIND), f_ptr, errcode) + !CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_DOUBLE, bufr3, dims, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, DIM1 + IF ( buf3(i) .NE. bufr3(i) ) THEN + PRINT *, 'read buffer differs from write buffer (D)' + PRINT *, bufr3(i), ' and ', buf3(i) + STOP + ENDIF + END DO + + ! + ! Close the file. + ! + CALL h5fclose_f(file_id, errcode) + + ! + ! Close FORTRAN predefined datatypes. + ! + CALL h5close_f(errcode) + + CALL passed() + ! + ! end function. + ! + END SUBROUTINE test_dataset1D !------------------------------------------------------------------------- - ! H5T_NATIVE_INT 2D buffer + ! test_dataset2D !------------------------------------------------------------------------- - ! - ! write dataset. - ! - CALL h5ltmake_dataset_f(file_id, dsetname2, rank, dims, H5T_NATIVE_INTEGER, buf2, errcode) - - ! - ! read dataset. - ! - CALL h5ltread_dataset_f(file_id, dsetname2, H5T_NATIVE_INTEGER, buf2r, dims, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, dims(1) - DO j = 1, dims(2) - IF ( buf2(i,j) .NE. buf2r(i,j) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, buf2r(i,j), ' and ', buf2(i,j) - STOP - ENDIF - END DO - END DO - - !------------------------------------------------------------------------- - ! H5T_NATIVE_REAL - !------------------------------------------------------------------------- + SUBROUTINE test_dataset2D() + + IMPLICIT NONE + + INTEGER(HSIZE_T), PARAMETER :: DIM1 = 4 ! columns + INTEGER(HSIZE_T), PARAMETER :: DIM2 = 6 ! rows + CHARACTER(len=9), PARAMETER :: filename = "dsetf2.h5"! File name + CHARACTER(LEN=5), PARAMETER :: dsetname1 = "dset1" ! Dataset name + CHARACTER(LEN=5), PARAMETER :: dsetname2 = "dset2" ! Dataset name + CHARACTER(LEN=5), PARAMETER :: dsetname3 = "dset3" ! Dataset name + CHARACTER(LEN=5), PARAMETER :: dsetname4 = "dset4" ! Dataset name + INTEGER(HID_T) :: file_id ! File identifier + INTEGER(HSIZE_T), DIMENSION(2) :: dims = (/4,6/) ! Dataset dimensions + INTEGER :: rank = 2 ! Dataset rank + INTEGER, DIMENSION(DIM1*DIM2) :: buf ! Data buffer + INTEGER, DIMENSION(DIM1*DIM2) :: bufr ! Data buffer + INTEGER, DIMENSION(DIM1,DIM2) :: buf2 ! Data buffer + INTEGER, DIMENSION(DIM1,DIM2) :: buf2r ! Data buffer + REAL, DIMENSION(DIM1,DIM2), TARGET :: buf3 ! Data buffer + REAL, DIMENSION(DIM1,DIM2), TARGET :: buf3r ! Data buffer + DOUBLE PRECISION, DIMENSION(DIM1,DIM2), TARGET :: buf4 ! Data buffer + DOUBLE PRECISION, DIMENSION(DIM1,DIM2), TARGET :: buf4r ! Data buffer + INTEGER :: errcode ! Error flag + INTEGER(HSIZE_T) :: i, j, n ! general purpose integers + TYPE(C_PTR) :: f_ptr + + CALL test_begin(' Make/Read datasets (2D) ') + + + ! + ! Initialize the data arrays. + ! + n=1 + DO i = 1, DIM1*DIM2 + buf(i) = INT(n) + n = n + 1 + END DO + + DO i = 1, dims(1) + DO j = 1, dims(2) + buf2(i,j) = INT((i-1)*dims(2) + j) + buf3(i,j) = INT((i-1)*dims(2) + j) + buf4(i,j) = INT((i-1)*dims(2) + j) + END DO + END DO + + ! + ! Initialize FORTRAN predefined datatypes. + ! + CALL h5open_f(errcode) + + ! + ! Create a new file using default properties. + ! + CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, errcode) + + !------------------------------------------------------------------------- + ! H5T_NATIVE_INT 1D buffer + !------------------------------------------------------------------------- + + ! + ! write dataset. + ! + CALL h5ltmake_dataset_f(file_id, dsetname1, rank, dims, H5T_NATIVE_INTEGER, buf, errcode) + + ! + ! read dataset. + ! + CALL h5ltread_dataset_f(file_id, dsetname1, H5T_NATIVE_INTEGER, bufr, dims, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, DIM1*DIM2 + IF ( buf(i) .NE. bufr(i) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, bufr(i), ' and ', buf(i) + STOP + ENDIF + END DO + + !------------------------------------------------------------------------- + ! H5T_NATIVE_INT 2D buffer + !------------------------------------------------------------------------- + + ! + ! write dataset. + ! + CALL h5ltmake_dataset_f(file_id, dsetname2, rank, dims, H5T_NATIVE_INTEGER, buf2, errcode) + + ! + ! read dataset. + ! + CALL h5ltread_dataset_f(file_id, dsetname2, H5T_NATIVE_INTEGER, buf2r, dims, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, dims(1) + DO j = 1, dims(2) + IF ( buf2(i,j) .NE. buf2r(i,j) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, buf2r(i,j), ' and ', buf2(i,j) + STOP + ENDIF + END DO + END DO + + !------------------------------------------------------------------------- + ! H5T_NATIVE_REAL + !------------------------------------------------------------------------- + + ! + ! write dataset. + ! + f_ptr = C_LOC(buf3(1,1)) + CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims, H5T_NATIVE_REAL, f_ptr, errcode) + !CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims, H5T_NATIVE_REAL, buf3, errcode) + + ! + ! read dataset. + ! + f_ptr = C_LOC(buf3r(1,1)) + CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, f_ptr, errcode) + !CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, buf3r, dims, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, dims(1) + DO j = 1, dims(2) + IF ( buf3(i,j) .NE. buf3r(i,j) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, buf3r(i,j), ' and ', buf3(i,j) + STOP + ENDIF + END DO + END DO + + !------------------------------------------------------------------------- + ! H5T_NATIVE_DOUBLE + !------------------------------------------------------------------------- + + ! + ! write dataset. + ! + f_ptr = C_LOC(buf4(1,1)) + CALL h5ltmake_dataset_f(file_id, dsetname4, rank, dims, H5T_NATIVE_DOUBLE, f_ptr, errcode) + !CALL h5ltmake_dataset_f(file_id, dsetname4, rank, dims, H5T_NATIVE_DOUBLE, buf4, errcode) + + ! + ! read dataset. + f_ptr = C_LOC(buf4r(1,1)) + CALL h5ltread_dataset_f(file_id, dsetname4, H5T_NATIVE_DOUBLE, f_ptr, errcode) + + !CALL h5ltread_dataset_f(file_id, dsetname4, H5T_NATIVE_DOUBLE, buf4r, dims, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, dims(1) + DO j = 1, dims(2) + IF ( buf4(i,j) .NE. buf4r(i,j) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, buf4r(i,j), ' and ', buf4(i,j) + STOP + ENDIF + END DO + END DO + + ! + ! Close the file. + ! + CALL h5fclose_f(file_id, errcode) + + ! + ! Close FORTRAN predefined datatypes. + ! + CALL h5close_f(errcode) + + CALL passed() + ! + ! end function. + ! + END SUBROUTINE test_dataset2D - ! - ! write dataset. - ! - f_ptr = C_LOC(buf3(1,1)) - CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims, H5T_NATIVE_REAL, f_ptr, errcode) - !CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims, H5T_NATIVE_REAL, buf3, errcode) - - ! - ! read dataset. - ! - f_ptr = C_LOC(buf3r(1,1)) - CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, f_ptr, errcode) - !CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, buf3r, dims, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, dims(1) - DO j = 1, dims(2) - IF ( buf3(i,j) .NE. buf3r(i,j) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, buf3r(i,j), ' and ', buf3(i,j) - STOP - ENDIF - END DO - END DO !------------------------------------------------------------------------- - ! H5T_NATIVE_DOUBLE + ! test_dataset3D !------------------------------------------------------------------------- - ! - ! write dataset. - ! - f_ptr = C_LOC(buf4(1,1)) - CALL h5ltmake_dataset_f(file_id, dsetname4, rank, dims, H5T_NATIVE_DOUBLE, f_ptr, errcode) - !CALL h5ltmake_dataset_f(file_id, dsetname4, rank, dims, H5T_NATIVE_DOUBLE, buf4, errcode) - - ! - ! read dataset. - f_ptr = C_LOC(buf4r(1,1)) - CALL h5ltread_dataset_f(file_id, dsetname4, H5T_NATIVE_DOUBLE, f_ptr, errcode) - - !CALL h5ltread_dataset_f(file_id, dsetname4, H5T_NATIVE_DOUBLE, buf4r, dims, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, dims(1) - DO j = 1, dims(2) - IF ( buf4(i,j) .NE. buf4r(i,j) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, buf4r(i,j), ' and ', buf4(i,j) - STOP - ENDIF - END DO - END DO - - ! - ! Close the file. - ! - CALL h5fclose_f(file_id, errcode) - - ! - ! Close FORTRAN predefined datatypes. - ! - CALL h5close_f(errcode) - - CALL passed() - ! - ! end function. - ! -END SUBROUTINE test_dataset2D - - -!------------------------------------------------------------------------- -! test_dataset3D -!------------------------------------------------------------------------- - - -SUBROUTINE test_dataset3D() - USE, INTRINSIC :: ISO_C_BINDING - USE H5LT ! module of H5LT - USE HDF5 ! module of HDF5 library - USE TSTLITE ! module for testing lite support routines - IMPLICIT NONE - - INTEGER, PARAMETER :: DIM1 = 6 ! columns - INTEGER, PARAMETER :: DIM2 = 4 ! rows - INTEGER, PARAMETER :: DIM3 = 2 ! layers - CHARACTER(len=9), PARAMETER :: filename = "dsetf3.h5" ! File name - CHARACTER(LEN=5), PARAMETER :: dsetname1 = "dset1" ! Dataset name - CHARACTER(LEN=5), PARAMETER :: dsetname2 = "dset2" ! Dataset name - CHARACTER(LEN=5), PARAMETER :: dsetname3 = "dset3" ! Dataset name - CHARACTER(LEN=5), PARAMETER :: dsetname4 = "dset4" ! Dataset name - INTEGER(HID_T) :: file_id ! File identifier - INTEGER(HSIZE_T), DIMENSION(3) :: dims = (/DIM1,DIM2,DIM3/) ! Dataset dimensions - INTEGER(HSIZE_T), DIMENSION(3) :: dimsr ! Dataset dimensions - INTEGER, DIMENSION(DIM1*DIM2*DIM3) :: buf ! Data buffer - INTEGER, DIMENSION(DIM1*DIM2*DIM3) :: bufr ! Data buffer - INTEGER, DIMENSION(DIM1,DIM2,DIM3) :: buf2 ! Data buffer - INTEGER, DIMENSION(DIM1,DIM2,DIM3) :: buf2r ! Data buffer - REAL, DIMENSION(DIM1,DIM2,DIM3), TARGET :: buf3 ! Data buffer - REAL, DIMENSION(DIM1,DIM2,DIM3), TARGET :: buf3r ! Data buffer - DOUBLE PRECISION, DIMENSION(DIM1,DIM2,DIM3), TARGET :: buf4 ! Data buffer - DOUBLE PRECISION, DIMENSION(DIM1,DIM2,DIM3), TARGET :: buf4r ! Data buffer - INTEGER :: rank = 3 ! Dataset rank - INTEGER :: errcode ! Error flag - INTEGER(HSIZE_T) :: i, j, k, n ! general purpose integers - INTEGER :: type_class - INTEGER(SIZE_T) :: type_size - TYPE(C_PTR) :: f_ptr + SUBROUTINE test_dataset3D() + + IMPLICIT NONE + + INTEGER, PARAMETER :: DIM1 = 6 ! columns + INTEGER, PARAMETER :: DIM2 = 4 ! rows + INTEGER, PARAMETER :: DIM3 = 2 ! layers + CHARACTER(len=9), PARAMETER :: filename = "dsetf3.h5" ! File name + CHARACTER(LEN=5), PARAMETER :: dsetname1 = "dset1" ! Dataset name + CHARACTER(LEN=5), PARAMETER :: dsetname2 = "dset2" ! Dataset name + CHARACTER(LEN=5), PARAMETER :: dsetname3 = "dset3" ! Dataset name + CHARACTER(LEN=5), PARAMETER :: dsetname4 = "dset4" ! Dataset name + INTEGER(HID_T) :: file_id ! File identifier + INTEGER(HSIZE_T), DIMENSION(3) :: dims = (/DIM1,DIM2,DIM3/) ! Dataset dimensions + INTEGER(HSIZE_T), DIMENSION(3) :: dimsr ! Dataset dimensions + INTEGER, DIMENSION(DIM1*DIM2*DIM3) :: buf ! Data buffer + INTEGER, DIMENSION(DIM1*DIM2*DIM3) :: bufr ! Data buffer + INTEGER, DIMENSION(DIM1,DIM2,DIM3) :: buf2 ! Data buffer + INTEGER, DIMENSION(DIM1,DIM2,DIM3) :: buf2r ! Data buffer + REAL, DIMENSION(DIM1,DIM2,DIM3), TARGET :: buf3 ! Data buffer + REAL, DIMENSION(DIM1,DIM2,DIM3), TARGET :: buf3r ! Data buffer + DOUBLE PRECISION, DIMENSION(DIM1,DIM2,DIM3), TARGET :: buf4 ! Data buffer + DOUBLE PRECISION, DIMENSION(DIM1,DIM2,DIM3), TARGET :: buf4r ! Data buffer + INTEGER :: rank = 3 ! Dataset rank + INTEGER :: errcode ! Error flag + INTEGER(HSIZE_T) :: i, j, k, n ! general purpose integers + INTEGER :: type_class + INTEGER(SIZE_T) :: type_size + TYPE(C_PTR) :: f_ptr #if H5_HAVE_Fortran_INTEGER_SIZEOF_16!=0 - INTEGER, PARAMETER :: int_kind_32 = SELECTED_INT_KIND(36) !should map to INTEGER*16 on most modern processors - INTEGER(int_kind_32), DIMENSION(DIM1,DIM2,DIM3), TARGET :: dset_data_i32, data_out_i32 - CHARACTER(LEN=7), PARAMETER :: dsetname16a = "dset16a" ! Dataset name - CHARACTER(LEN=7), PARAMETER :: dsetname16b = "dset16b" ! Dataset name - CHARACTER(LEN=7), PARAMETER :: dsetname16c = "dset16c" ! Dataset name - INTEGER(HID_T) :: type_id + INTEGER, PARAMETER :: int_kind_32 = SELECTED_INT_KIND(36) !should map to INTEGER*16 on most modern processors + INTEGER(int_kind_32), DIMENSION(DIM1,DIM2,DIM3), TARGET :: dset_data_i32, data_out_i32 + CHARACTER(LEN=7), PARAMETER :: dsetname16a = "dset16a" ! Dataset name + CHARACTER(LEN=7), PARAMETER :: dsetname16b = "dset16b" ! Dataset name + CHARACTER(LEN=7), PARAMETER :: dsetname16c = "dset16c" ! Dataset name + INTEGER(HID_T) :: type_id #endif - CALL test_begin(' Make/Read datasets (3D) ') - - - ! - ! Initialize the data array. - ! - n=1 - DO i = 1, DIM1*DIM2*DIM3 - buf(i) = INT(n) - n = n + 1 - END DO - - n = 1 - DO i = 1, dims(1) - DO j = 1, dims(2) - DO k = 1, dims(3) - buf2(i,j,k) = INT(n) - buf3(i,j,k) = INT(n) - buf4(i,j,k) = INT(n) + CALL test_begin(' Make/Read datasets (3D) ') + + + ! + ! Initialize the data array. + ! + n=1 + DO i = 1, DIM1*DIM2*DIM3 + buf(i) = INT(n) + n = n + 1 + END DO + + n = 1 + DO i = 1, dims(1) + DO j = 1, dims(2) + DO k = 1, dims(3) + buf2(i,j,k) = INT(n) + buf3(i,j,k) = INT(n) + buf4(i,j,k) = INT(n) #if H5_HAVE_Fortran_INTEGER_SIZEOF_16!=0 - dset_data_i32(i,j,k) = HUGE(1_int_kind_32)-INT(n,int_kind_32) + dset_data_i32(i,j,k) = HUGE(1_int_kind_32)-INT(n,int_kind_32) #endif - n = n + 1 - END DO - END DO - END DO - - ! - ! Initialize FORTRAN predefined datatypes. - ! - CALL h5open_f(errcode) - - ! - ! Create a new file using default properties. - ! - CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, errcode) - - !------------------------------------------------------------------------- - ! H5T_NATIVE_INT 1D buffer - !------------------------------------------------------------------------- - - ! - ! write dataset. - ! - CALL h5ltmake_dataset_f(file_id, dsetname1, rank, dims, H5T_NATIVE_INTEGER, buf, errcode) - - ! - ! read dataset. - ! - CALL h5ltread_dataset_f(file_id, dsetname1, H5T_NATIVE_INTEGER, bufr, dims, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, DIM1*DIM2*DIM3 - IF ( buf(i) .NE. bufr(i) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, bufr(i), ' and ', buf(i) - STOP - ENDIF - END DO - - !------------------------------------------------------------------------- - ! H5T_NATIVE_INT 3D buffer - !------------------------------------------------------------------------- - - ! - ! write dataset. - ! - CALL h5ltmake_dataset_f(file_id, dsetname2, rank, dims, H5T_NATIVE_INTEGER, buf2, errcode) - - ! - ! read dataset. - ! - CALL h5ltread_dataset_f(file_id, dsetname2, H5T_NATIVE_INTEGER, buf2r, dims, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, dims(1) - DO j = 1, dims(2) - DO k = 1, dims(3) - IF ( buf2(i,j,k) .NE. buf2r(i,j,k) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, buf2r(i,j,k), ' and ', buf2(i,j,k) - STOP - ENDIF - END DO - END DO - END DO - - !------------------------------------------------------------------------- - ! H5T_NATIVE_REAL - !------------------------------------------------------------------------- - - ! - ! write dataset. - ! - f_ptr = C_LOC(buf3(1,1,1)) - CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims, H5T_NATIVE_REAL, f_ptr, errcode) - !CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims, H5T_NATIVE_REAL, buf3, errcode) - - ! - ! read dataset. - ! - f_ptr = C_LOC(buf3r(1,1,1)) - CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, f_ptr, errcode) - !CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, buf3r, dims, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, dims(1) - DO j = 1, dims(2) - DO k = 1, dims(3) - IF ( buf3(i,j,k) .NE. buf3r(i,j,k) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, buf3r(i,j,k), ' and ', buf3(i,j,k) - STOP - ENDIF - END DO - END DO - END DO - - !------------------------------------------------------------------------- - ! H5T_NATIVE_DOUBLE - !------------------------------------------------------------------------- - - ! - ! write dataset. - ! - f_ptr = C_LOC(buf4(1,1,1)) - CALL h5ltmake_dataset_f(file_id, dsetname4, rank, dims, H5T_NATIVE_DOUBLE, f_ptr, errcode) - - ! - ! read dataset. - ! - f_ptr = C_LOC(buf4r(1,1,1)) - CALL h5ltread_dataset_f(file_id, dsetname4, H5T_NATIVE_DOUBLE, f_ptr, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, dims(1) - DO j = 1, dims(2) - DO k = 1, dims(3) - IF ( buf4(i,j,k) .NE. buf4r(i,j,k) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, buf4r(i,j,k), ' and ', buf4(i,j,k) - STOP - ENDIF - END DO - END DO - END DO - - CALL h5ltget_dataset_info_f(file_id,dsetname4,dimsr,type_class,type_size,errcode ) - - ! - ! compare dimensions - ! - DO i = 1, rank - IF ( dimsr(i) .NE. dims(i) ) THEN - PRINT *, 'dimensions differ ' - STOP - ENDIF - END DO - - !------------------------------------------------------------------------- - ! CHECKING NON-NATIVE INTEGER TYPES - !------------------------------------------------------------------------- + n = n + 1 + END DO + END DO + END DO + + ! + ! Initialize FORTRAN predefined datatypes. + ! + CALL h5open_f(errcode) + + ! + ! Create a new file using default properties. + ! + CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, errcode) + + !------------------------------------------------------------------------- + ! H5T_NATIVE_INT 1D buffer + !------------------------------------------------------------------------- + + ! + ! write dataset. + ! + CALL h5ltmake_dataset_f(file_id, dsetname1, rank, dims, H5T_NATIVE_INTEGER, buf, errcode) + + ! + ! read dataset. + ! + CALL h5ltread_dataset_f(file_id, dsetname1, H5T_NATIVE_INTEGER, bufr, dims, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, DIM1*DIM2*DIM3 + IF ( buf(i) .NE. bufr(i) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, bufr(i), ' and ', buf(i) + STOP + ENDIF + END DO + + !------------------------------------------------------------------------- + ! H5T_NATIVE_INT 3D buffer + !------------------------------------------------------------------------- + + ! + ! write dataset. + ! + CALL h5ltmake_dataset_f(file_id, dsetname2, rank, dims, H5T_NATIVE_INTEGER, buf2, errcode) + + ! + ! read dataset. + ! + CALL h5ltread_dataset_f(file_id, dsetname2, H5T_NATIVE_INTEGER, buf2r, dims, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, dims(1) + DO j = 1, dims(2) + DO k = 1, dims(3) + IF ( buf2(i,j,k) .NE. buf2r(i,j,k) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, buf2r(i,j,k), ' and ', buf2(i,j,k) + STOP + ENDIF + END DO + END DO + END DO + + !------------------------------------------------------------------------- + ! H5T_NATIVE_REAL + !------------------------------------------------------------------------- + + ! + ! write dataset. + ! + f_ptr = C_LOC(buf3(1,1,1)) + CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims, H5T_NATIVE_REAL, f_ptr, errcode) + !CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims, H5T_NATIVE_REAL, buf3, errcode) + + ! + ! read dataset. + ! + f_ptr = C_LOC(buf3r(1,1,1)) + CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, f_ptr, errcode) + !CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, buf3r, dims, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, dims(1) + DO j = 1, dims(2) + DO k = 1, dims(3) + IF ( buf3(i,j,k) .NE. buf3r(i,j,k) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, buf3r(i,j,k), ' and ', buf3(i,j,k) + STOP + ENDIF + END DO + END DO + END DO + + !------------------------------------------------------------------------- + ! H5T_NATIVE_DOUBLE + !------------------------------------------------------------------------- + + ! + ! write dataset. + ! + f_ptr = C_LOC(buf4(1,1,1)) + CALL h5ltmake_dataset_f(file_id, dsetname4, rank, dims, H5T_NATIVE_DOUBLE, f_ptr, errcode) + + ! + ! read dataset. + ! + f_ptr = C_LOC(buf4r(1,1,1)) + CALL h5ltread_dataset_f(file_id, dsetname4, H5T_NATIVE_DOUBLE, f_ptr, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, dims(1) + DO j = 1, dims(2) + DO k = 1, dims(3) + IF ( buf4(i,j,k) .NE. buf4r(i,j,k) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, buf4r(i,j,k), ' and ', buf4(i,j,k) + STOP + ENDIF + END DO + END DO + END DO + + CALL h5ltget_dataset_info_f(file_id,dsetname4,dimsr,type_class,type_size,errcode ) + + ! + ! compare dimensions + ! + DO i = 1, rank + IF ( dimsr(i) .NE. dims(i) ) THEN + PRINT *, 'dimensions differ ' + STOP + ENDIF + END DO + + !------------------------------------------------------------------------- + ! CHECKING NON-NATIVE INTEGER TYPES + !------------------------------------------------------------------------- #if H5_HAVE_Fortran_INTEGER_SIZEOF_16!=0 - ! (A) CHECKING INTEGER*16 - ! - ! (i.a) write dataset using F2003 interface - ! - type_id = H5kind_to_type(KIND(dset_data_i32(1,1,1)), H5_INTEGER_KIND) - f_ptr = C_LOC(dset_data_i32(1,1,1)) - CALL h5ltmake_dataset_f(file_id, dsetname16a, rank, dims, type_id, f_ptr, errcode) - ! - ! (i.b) read dataset using F2003 interface - ! - f_ptr = C_LOC(data_out_i32(1,1,1)) - CALL h5ltread_dataset_f(file_id, dsetname16a, type_id, f_ptr, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, dims(1) - DO j = 1, dims(2) - DO k = 1, dims(3) - IF ( dset_data_i32(i,j,k) .NE. data_out_i32(i,j,k) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k) - STOP - ENDIF - END DO - END DO - ENDDO - - ! - ! (ii.a) write dataset using F90 interface - ! - type_id = H5kind_to_type(KIND(dset_data_i32(1,1,1)), H5_INTEGER_KIND) - CALL h5ltmake_dataset_f(file_id, dsetname16b, rank, dims, type_id, dset_data_i32, errcode) - ! - ! (ii.b) read dataset using F90 interface - ! - CALL h5ltread_dataset_f(file_id, dsetname16b, type_id, data_out_i32, dims, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, dims(1) - DO j = 1, dims(2) - DO k = 1, dims(3) - IF ( dset_data_i32(i,j,k) .NE. data_out_i32(i,j,k) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k) - STOP - ENDIF - END DO - END DO - ENDDO - - ! - ! (iii.a) write dataset using F90 H5LTmake_dataset_int_f interface - ! - CALL h5ltmake_dataset_int_f(file_id, dsetname16c, rank, dims, dset_data_i32, errcode) - - ! - ! (iii.b) read dataset using F90 H5LTmake_dataset_int_f interface - ! - CALL h5ltread_dataset_int_f(file_id, dsetname16c, data_out_i32, dims, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, dims(1) - DO j = 1, dims(2) - DO k = 1, dims(3) - IF ( dset_data_i32(i,j,k) .NE. data_out_i32(i,j,k) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k) - STOP - ENDIF - END DO - END DO - ENDDO + ! (A) CHECKING INTEGER*16 + ! + ! (i.a) write dataset using F2003 interface + ! + type_id = H5kind_to_type(KIND(dset_data_i32(1,1,1)), H5_INTEGER_KIND) + f_ptr = C_LOC(dset_data_i32(1,1,1)) + CALL h5ltmake_dataset_f(file_id, dsetname16a, rank, dims, type_id, f_ptr, errcode) + ! + ! (i.b) read dataset using F2003 interface + ! + f_ptr = C_LOC(data_out_i32(1,1,1)) + CALL h5ltread_dataset_f(file_id, dsetname16a, type_id, f_ptr, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, dims(1) + DO j = 1, dims(2) + DO k = 1, dims(3) + IF ( dset_data_i32(i,j,k) .NE. data_out_i32(i,j,k) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k) + STOP + ENDIF + END DO + END DO + ENDDO + + ! + ! (ii.a) write dataset using F90 interface + ! + type_id = H5kind_to_type(KIND(dset_data_i32(1,1,1)), H5_INTEGER_KIND) + CALL h5ltmake_dataset_f(file_id, dsetname16b, rank, dims, type_id, dset_data_i32, errcode) + ! + ! (ii.b) read dataset using F90 interface + ! + CALL h5ltread_dataset_f(file_id, dsetname16b, type_id, data_out_i32, dims, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, dims(1) + DO j = 1, dims(2) + DO k = 1, dims(3) + IF ( dset_data_i32(i,j,k) .NE. data_out_i32(i,j,k) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k) + STOP + ENDIF + END DO + END DO + ENDDO + + ! + ! (iii.a) write dataset using F90 H5LTmake_dataset_int_f interface + ! + CALL h5ltmake_dataset_int_f(file_id, dsetname16c, rank, dims, dset_data_i32, errcode) + + ! + ! (iii.b) read dataset using F90 H5LTmake_dataset_int_f interface + ! + CALL h5ltread_dataset_int_f(file_id, dsetname16c, data_out_i32, dims, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, dims(1) + DO j = 1, dims(2) + DO k = 1, dims(3) + IF ( dset_data_i32(i,j,k) .NE. data_out_i32(i,j,k) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k) + STOP + ENDIF + END DO + END DO + ENDDO #endif - ! - ! Close the file. - ! - CALL h5fclose_f(file_id, errcode) - - ! - ! Close FORTRAN predefined datatypes. - ! - CALL h5close_f(errcode) - - CALL passed() - ! - ! end function. - ! -END SUBROUTINE test_dataset3D - -!------------------------------------------------------------------------- -! test_datasetND -!------------------------------------------------------------------------- - - -SUBROUTINE test_datasetND(rank) - - USE, INTRINSIC :: ISO_C_BINDING - USE H5LT ! module of H5LT - USE HDF5 ! module of HDF5 library - USE TSTLITE ! module for testing lite support routines - - IMPLICIT NONE - - INTEGER :: rank ! Dataset rank - - INTEGER, PARAMETER :: DIM1 = 2 ! columns - INTEGER, PARAMETER :: DIM2 = 4 ! rows - INTEGER, PARAMETER :: DIM3 = 2 ! layers - INTEGER, PARAMETER :: DIM4 = 5 ! columns - INTEGER, PARAMETER :: DIM5 = 4 ! rows - INTEGER, PARAMETER :: DIM6 = 3 ! layers - INTEGER, PARAMETER :: DIM7 = 2 ! layers - CHARACTER(len=9), PARAMETER :: filename = "dsetf3.h5" ! File name - CHARACTER(LEN=5), PARAMETER :: dsetname2 = "dset2" ! Dataset name - CHARACTER(LEN=5), PARAMETER :: dsetname3 = "dset3" ! Dataset name - CHARACTER(LEN=5), PARAMETER :: dsetname4 = "dset4" ! Dataset name - CHARACTER(LEN=5), PARAMETER :: dsetname5 = "dset5" ! Dataset name - INTEGER(HID_T) :: file_id ! File identifier - INTEGER(HSIZE_T), DIMENSION(7) :: dims - INTEGER(HSIZE_T), DIMENSION(7) :: dimsr ! Dataset dimensions - INTEGER, ALLOCATABLE, DIMENSION(:,:,:,:) :: ibuf_4 ! Data buffer - INTEGER, ALLOCATABLE, DIMENSION(:,:,:,:) :: ibufr_4 ! Data buffer - INTEGER, ALLOCATABLE, DIMENSION(:,:,:,:,:), TARGET :: ibuf_5 ! Data buffer - INTEGER, ALLOCATABLE, DIMENSION(:,:,:,:,:), TARGET :: ibufr_5 ! Data buffer - INTEGER, ALLOCATABLE, DIMENSION(:,:,:,:,:,:) :: ibuf_6 ! Data buffer - INTEGER, ALLOCATABLE, DIMENSION(:,:,:,:,:,:) :: ibufr_6 ! Data buffer - INTEGER, ALLOCATABLE, DIMENSION(:,:,:,:,:,:,:) :: ibuf_7 ! Data buffer - INTEGER, ALLOCATABLE, DIMENSION(:,:,:,:,:,:,:) :: ibufr_7 ! Data buffer - REAL, ALLOCATABLE, DIMENSION(:,:,:,:), TARGET :: rbuf_4 ! Data buffer - REAL, ALLOCATABLE, DIMENSION(:,:,:,:), TARGET :: rbufr_4 ! Data buffer - REAL, ALLOCATABLE, DIMENSION(:,:,:,:,:), TARGET :: rbuf_5 ! Data buffer - REAL, ALLOCATABLE, DIMENSION(:,:,:,:,:), TARGET :: rbufr_5 ! Data buffer - REAL, ALLOCATABLE, DIMENSION(:,:,:,:,:,:), TARGET :: rbuf_6 ! Data buffer - REAL, ALLOCATABLE, DIMENSION(:,:,:,:,:,:), TARGET :: rbufr_6 ! Data buffer - REAL, ALLOCATABLE, DIMENSION(:,:,:,:,:,:,:), TARGET :: rbuf_7 ! Data buffer - REAL, ALLOCATABLE, DIMENSION(:,:,:,:,:,:,:), TARGET :: rbufr_7 ! Data buffer - DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:,:,:), TARGET :: dbuf_4 ! Data buffer - DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:,:,:), TARGET :: dbufr_4 ! Data buffer - DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:,:,:,:), TARGET :: dbuf_5 ! Data buffer - DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:,:,:,:), TARGET :: dbufr_5 ! Data buffer - DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:,:,:,:,:), TARGET :: dbuf_6 ! Data buffer - DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:,:,:,:,:), TARGET :: dbufr_6 ! Data buffer - DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:,:,:,:,:,:), TARGET :: dbuf_7 ! Data buffer - DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:,:,:,:,:,:), TARGET :: dbufr_7 ! Data buffer - CHARACTER(LEN=5), ALLOCATABLE, DIMENSION(:,:,:,:), TARGET :: cbuf_4 ! Data buffer - CHARACTER(LEN=5), ALLOCATABLE, DIMENSION(:,:,:,:), TARGET :: cbufr_4 ! Data buffer - CHARACTER(LEN=5), ALLOCATABLE, DIMENSION(:,:,:,:,:), TARGET :: cbuf_5 ! Data buffer - CHARACTER(LEN=5), ALLOCATABLE, DIMENSION(:,:,:,:,:), TARGET :: cbufr_5 ! Data buffer - CHARACTER(LEN=5), ALLOCATABLE, DIMENSION(:,:,:,:,:,:), TARGET :: cbuf_6 ! Data buffer - CHARACTER(LEN=5), ALLOCATABLE, DIMENSION(:,:,:,:,:,:), TARGET :: cbufr_6 ! Data buffer - CHARACTER(LEN=5), ALLOCATABLE, DIMENSION(:,:,:,:,:,:,:), TARGET :: cbuf_7 ! Data buffer - CHARACTER(LEN=5), ALLOCATABLE, DIMENSION(:,:,:,:,:,:,:), TARGET :: cbufr_7 ! Data buffer - INTEGER :: errcode ! Error flag - INTEGER(HSIZE_T) :: i, j, k, l, m, n, o, nn ! general purpose integers - INTEGER :: type_class - INTEGER(SIZE_T) :: type_size - CHARACTER(LEN=1) :: ichr1 - TYPE(C_PTR) :: f_ptr - INTEGER(HID_T) :: type_id - - WRITE(ichr1,'(I1.1)') rank - CALL test_begin(' Make/Read datasets ('//ichr1//'D) ') - ! - ! Initialize the data array. - ! - IF(rank.EQ.4)THEN - - ALLOCATE(ibuf_4 (1:DIM1,1:DIM2,1:DIM3,1:DIM4)) - ALLOCATE(ibufr_4(1:DIM1,1:DIM2,1:DIM3,1:DIM4)) - ALLOCATE(rbuf_4 (1:DIM1,1:DIM2,1:DIM3,1:DIM4)) - ALLOCATE(rbufr_4(1:DIM1,1:DIM2,1:DIM3,1:DIM4)) - ALLOCATE(dbuf_4 (1:DIM1,1:DIM2,1:DIM3,1:DIM4)) - ALLOCATE(dbufr_4(1:DIM1,1:DIM2,1:DIM3,1:DIM4)) - ALLOCATE(cbuf_4 (1:DIM1,1:DIM2,1:DIM3,1:DIM4)) - ALLOCATE(cbufr_4(1:DIM1,1:DIM2,1:DIM3,1:DIM4)) - - dims(1:7) = (/DIM1,DIM2,DIM3,DIM4,0,0,0/) - - nn = 1 - DO i = 1, DIM1 - DO j = 1, DIM2 - DO k = 1, DIM3 - DO l = 1, DIM4 - ibuf_4(i,j,k,l) = INT(nn) - rbuf_4(i,j,k,l) = INT(nn) - dbuf_4(i,j,k,l) = INT(nn) - WRITE(cbuf_4(i,j,k,l),'(I5.5)') nn - nn = nn + 1 - END DO - END DO - END DO - - ENDDO - - ELSE IF(rank.EQ.5)THEN - - ALLOCATE(ibuf_5 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5)) - ALLOCATE(ibufr_5(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5)) - ALLOCATE(rbuf_5 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5)) - ALLOCATE(rbufr_5(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5)) - ALLOCATE(dbuf_5 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5)) - ALLOCATE(dbufr_5(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5)) - ALLOCATE(cbuf_5 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5)) - ALLOCATE(cbufr_5(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5)) - - dims(1:7) = (/DIM1,DIM2,DIM3,DIM4,DIM5,0,0/) - - nn = 1 - DO i = 1, DIM1 - DO j = 1, DIM2 - DO k = 1, DIM3 - DO l = 1, DIM4 - DO m = 1, DIM5 - ibuf_5(i,j,k,l,m) = INT(nn) - rbuf_5(i,j,k,l,m) = INT(nn) - dbuf_5(i,j,k,l,m) = INT(nn) - WRITE(cbuf_5(i,j,k,l,m),'(I5.5)') nn - nn = nn + 1 - END DO - END DO - END DO - ENDDO - ENDDO - - ELSE IF(rank.EQ.6)THEN - - ALLOCATE(ibuf_6 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6)) - ALLOCATE(ibufr_6(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6)) - ALLOCATE(rbuf_6 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6)) - ALLOCATE(rbufr_6(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6)) - ALLOCATE(dbuf_6 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6)) - ALLOCATE(dbufr_6(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6)) - ALLOCATE(cbuf_6 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6)) - ALLOCATE(cbufr_6(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6)) - - dims(1:7) = (/DIM1,DIM2,DIM3,DIM4,DIM5,DIM6,0/) - - nn = 1 - DO i = 1, DIM1 - DO j = 1, DIM2 - DO k = 1, DIM3 - DO l = 1, DIM4 - DO m = 1, DIM5 - DO n = 1, DIM6 - ibuf_6(i,j,k,l,m,n) = INT(nn) - rbuf_6(i,j,k,l,m,n) = INT(nn) - dbuf_6(i,j,k,l,m,n) = INT(nn) - WRITE(cbuf_6(i,j,k,l,m,n),'(I5.5)') nn - nn = nn + 1 - END DO - END DO - END DO - ENDDO - ENDDO - ENDDO - - ELSE IF(rank.EQ.7)THEN - - ALLOCATE(ibuf_7 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6,1:DIM7)) - ALLOCATE(ibufr_7(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6,1:DIM7)) - ALLOCATE(rbuf_7 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6,1:DIM7)) - ALLOCATE(rbufr_7(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6,1:DIM7)) - ALLOCATE(dbuf_7 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6,1:DIM7)) - ALLOCATE(dbufr_7(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6,1:DIM7)) - ALLOCATE(cbuf_7 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6,1:DIM7)) - ALLOCATE(cbufr_7(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6,1:DIM7)) - - dims(1:7) = (/DIM1,DIM2,DIM3,DIM4,DIM5,DIM6,DIM7/) - - nn = 1 - DO i = 1, DIM1 - DO j = 1, DIM2 - DO k = 1, DIM3 - DO l = 1, DIM4 - DO m = 1, DIM5 - DO n = 1, DIM6 - DO o = 1, DIM7 - ibuf_7(i,j,k,l,m,n,o) = INT(nn) - rbuf_7(i,j,k,l,m,n,o) = INT(nn) - dbuf_7(i,j,k,l,m,n,o) = INT(nn) - WRITE(cbuf_7(i,j,k,l,m,n,o),'(I5.5)') nn - nn = nn + 1 - END DO - END DO - END DO - ENDDO - ENDDO - ENDDO - ENDDO - - ENDIF - - ! - ! Initialize FORTRAN predefined datatypes. - ! - CALL h5open_f(errcode) - - ! - ! Create a new file using default properties. - ! - CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, errcode) - - !------------------------------------------------------------------------- - ! H5T_NATIVE_INT ND buffer - !------------------------------------------------------------------------- - - ! - ! write dataset. - ! - IF(rank.EQ.4)THEN - CALL h5ltmake_dataset_f(file_id, dsetname2, rank, dims(1:rank), H5T_NATIVE_INTEGER, ibuf_4, errcode) - ELSE IF(rank.EQ.5)THEN - f_ptr = C_LOC(ibuf_5(1,1,1,1,1)) - CALL h5ltmake_dataset_f(file_id, dsetname2, rank, dims(1:rank), H5T_NATIVE_INTEGER, f_ptr, errcode) - ELSE IF(rank.EQ.6)THEN - CALL h5ltmake_dataset_f(file_id, dsetname2, rank, dims(1:rank), H5T_NATIVE_INTEGER, ibuf_6, errcode) - ELSE IF(rank.EQ.7)THEN - CALL h5ltmake_dataset_f(file_id, dsetname2, rank, dims(1:rank), H5T_NATIVE_INTEGER, ibuf_7, errcode) - ENDIF - - - ! - ! read dataset. - ! - IF(rank.EQ.4)THEN - CALL h5ltread_dataset_f(file_id, dsetname2, H5T_NATIVE_INTEGER, ibufr_4, dims(1:rank), errcode) - ELSE IF(rank.EQ.5)THEN - f_ptr = C_LOC(ibufr_5(1,1,1,1,1)) - CALL h5ltread_dataset_f(file_id, dsetname2, H5T_NATIVE_INTEGER, f_ptr, errcode) - ELSE IF(rank.EQ.6)THEN - CALL h5ltread_dataset_f(file_id, dsetname2, H5T_NATIVE_INTEGER, ibufr_6, dims(1:rank), errcode) - ELSE IF(rank.EQ.7)THEN - CALL h5ltread_dataset_f(file_id, dsetname2, H5T_NATIVE_INTEGER, ibufr_7, dims(1:rank), errcode) - ENDIF - - ! - ! compare read and write buffers. - ! - DO i = 1, dims(1) - DO j = 1, dims(2) - DO k = 1, dims(3) - DO l = 1, dims(4) - IF(rank.EQ.4)THEN - IF ( ibuf_4(i,j,k,l) .NE. ibufr_4(i,j,k,l) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, ibuf_4(i,j,k,l), ' and ', ibufr_4(i,j,k,l) - STOP - ENDIF - ENDIF - DO m = 1, dims(5) - IF(rank.EQ.5)THEN - IF ( ibuf_5(i,j,k,l,m) .NE. ibufr_5(i,j,k,l,m) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, ibuf_5(i,j,k,l,m), ' and ', ibufr_5(i,j,k,l,m) - STOP - ENDIF - ENDIF - DO n = 1, dims(6) - IF(rank.EQ.6)THEN - IF ( ibuf_6(i,j,k,l,m,n) .NE. ibufr_6(i,j,k,l,m,n) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, ibuf_6(i,j,k,l,m,n), ' and ', ibufr_6(i,j,k,l,m,n) - STOP - ENDIF - ENDIF - DO o = 1, dims(7) - IF(rank.EQ.7)THEN - IF ( ibuf_7(i,j,k,l,m,n,o) .NE. ibufr_7(i,j,k,l,m,n,o) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, ibuf_7(i,j,k,l,m,n,o), ' and ', ibufr_7(i,j,k,l,m,n,o) - STOP - ENDIF - ENDIF - ENDDO - ENDDO - ENDDO - ENDDO - ENDDO - ENDDO - ENDDO - !------------------------------------------------------------------------- - ! H5T_NATIVE_REAL - !------------------------------------------------------------------------- - - ! - ! write dataset. - ! - IF(rank.EQ.4)THEN - f_ptr = C_LOC(rbuf_4(1,1,1,1)) - CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims(1:rank), H5T_NATIVE_REAL, f_ptr, errcode) - ! CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims(1:rank), H5T_NATIVE_REAL, rbuf_4, errcode) - ELSE IF(rank.EQ.5)THEN - f_ptr = C_LOC(rbuf_5(1,1,1,1,1)) - CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims(1:rank), H5T_NATIVE_REAL, f_ptr, errcode) - ELSE IF(rank.EQ.6)THEN - f_ptr = C_LOC(rbuf_6(1,1,1,1,1,1)) - CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims(1:rank), H5T_NATIVE_REAL, f_ptr, errcode) - !CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims(1:rank), H5T_NATIVE_REAL, rbuf_6, errcode) - ELSE IF(rank.EQ.7)THEN - f_ptr = C_LOC(rbuf_7(1,1,1,1,1,1,1)) - CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims(1:rank), H5T_NATIVE_REAL, f_ptr, errcode) - !CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims(1:rank), H5T_NATIVE_REAL, rbuf_7, errcode) - ENDIF - - - ! - ! read dataset. - ! - IF(rank.EQ.4)THEN - f_ptr = C_LOC(rbufr_4(1,1,1,1)) - CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, f_ptr, errcode) - ELSE IF(rank.EQ.5)THEN - f_ptr = C_LOC(rbufr_5(1,1,1,1,1)) - CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, f_ptr, errcode) - ELSE IF(rank.EQ.6)THEN - f_ptr = C_LOC(rbufr_6(1,1,1,1,1,1)) - CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, f_ptr, errcode) - ELSE IF(rank.EQ.7)THEN - f_ptr = C_LOC(rbufr_7(1,1,1,1,1,1,1)) - CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, f_ptr, errcode) - ENDIF - - ! - ! compare read and write buffers. - ! - DO i = 1, dims(1) - DO j = 1, dims(2) - DO k = 1, dims(3) - DO l = 1, dims(4) - IF(rank.EQ.4)THEN - IF ( rbuf_4(i,j,k,l) .NE. rbufr_4(i,j,k,l) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, rbuf_4(i,j,k,l), ' and ', rbufr_4(i,j,k,l) - STOP - ENDIF - ENDIF - DO m = 1, dims(5) - IF(rank.EQ.5)THEN - IF ( rbuf_5(i,j,k,l,m) .NE. rbufr_5(i,j,k,l,m) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, rbuf_5(i,j,k,l,m), ' and ', rbufr_5(i,j,k,l,m) - STOP - ENDIF - ENDIF - DO n = 1, dims(6) - IF(rank.EQ.6)THEN - IF ( rbuf_6(i,j,k,l,m,n) .NE. rbufr_6(i,j,k,l,m,n) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, rbuf_6(i,j,k,l,m,n), ' and ', rbufr_6(i,j,k,l,m,n) - STOP - ENDIF - ENDIF - DO o = 1, dims(7) - IF(rank.EQ.7)THEN - IF ( rbuf_7(i,j,k,l,m,n,o) .NE. rbufr_7(i,j,k,l,m,n,o) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, rbuf_7(i,j,k,l,m,n,o), ' and ', rbufr_7(i,j,k,l,m,n,o) - STOP - ENDIF - ENDIF - ENDDO - ENDDO - ENDDO - ENDDO - ENDDO - ENDDO - ENDDO - - !------------------------------------------------------------------------- - ! H5T_NATIVE_DOUBLE - !------------------------------------------------------------------------- - - ! - ! write dataset. - ! - IF(rank.EQ.4)THEN - f_ptr = C_LOC(dbuf_4(1,1,1,1)) - CALL h5ltmake_dataset_f(file_id, dsetname4, rank, dims(1:rank), H5T_NATIVE_DOUBLE, f_ptr, errcode) - ELSE IF(rank.EQ.5)THEN - f_ptr = C_LOC(dbuf_5(1,1,1,1,1)) - CALL h5ltmake_dataset_f(file_id, dsetname4, rank, dims(1:rank), H5T_NATIVE_DOUBLE, f_ptr, errcode) - ELSE IF(rank.EQ.6)THEN - f_ptr = C_LOC(dbuf_6(1,1,1,1,1,1)) - CALL h5ltmake_dataset_f(file_id, dsetname4, rank, dims(1:rank), H5T_NATIVE_DOUBLE, f_ptr, errcode) - ELSE IF(rank.EQ.7)THEN - f_ptr = C_LOC(dbuf_7(1,1,1,1,1,1,1)) - CALL h5ltmake_dataset_f(file_id, dsetname4, rank, dims(1:rank), H5T_NATIVE_DOUBLE, f_ptr, errcode) - ENDIF - - ! - ! read dataset. - ! - IF(rank.EQ.4)THEN - f_ptr = C_LOC(dbufr_4(1,1,1,1)) - CALL h5ltread_dataset_f(file_id, dsetname4, H5T_NATIVE_DOUBLE, f_ptr, errcode) - ELSE IF(rank.EQ.5)THEN - f_ptr = C_LOC(dbufr_5(1,1,1,1,1)) - CALL h5ltread_dataset_f(file_id, dsetname4, H5T_NATIVE_DOUBLE, f_ptr, errcode) - ELSE IF(rank.EQ.6)THEN - f_ptr = C_LOC(dbufr_6(1,1,1,1,1,1)) - CALL h5ltread_dataset_f(file_id, dsetname4, H5T_NATIVE_DOUBLE, f_ptr, errcode) - ELSE IF(rank.EQ.7)THEN - f_ptr = C_LOC(dbufr_7(1,1,1,1,1,1,1)) - CALL h5ltread_dataset_f(file_id, dsetname4, H5T_NATIVE_DOUBLE, f_ptr, errcode) - ENDIF - - ! - ! compare read and write buffers. - ! - DO i = 1, dims(1) - DO j = 1, dims(2) - DO k = 1, dims(3) - DO l = 1, dims(4) - IF(rank.EQ.4)THEN - IF ( dbuf_4(i,j,k,l) .NE. dbufr_4(i,j,k,l) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, dbuf_4(i,j,k,l), ' and ', dbufr_4(i,j,k,l) - STOP - ENDIF - ENDIF - DO m = 1, dims(5) - IF(rank.EQ.5)THEN - IF ( dbuf_5(i,j,k,l,m) .NE. dbufr_5(i,j,k,l,m) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, dbuf_5(i,j,k,l,m), ' and ', dbufr_5(i,j,k,l,m) - STOP - ENDIF - ENDIF - DO n = 1, dims(6) - IF(rank.EQ.6)THEN - IF ( dbuf_6(i,j,k,l,m,n) .NE. dbufr_6(i,j,k,l,m,n) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, dbuf_6(i,j,k,l,m,n), ' and ', dbufr_6(i,j,k,l,m,n) - STOP - ENDIF - ENDIF - DO o = 1, dims(7) - IF(rank.EQ.7)THEN - IF ( dbuf_7(i,j,k,l,m,n,o) .NE. dbufr_7(i,j,k,l,m,n,o) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, dbuf_7(i,j,k,l,m,n,o), ' and ', dbufr_7(i,j,k,l,m,n,o) - STOP - ENDIF - ENDIF - ENDDO - ENDDO - ENDDO - ENDDO - ENDDO - ENDDO - ENDDO - - !------------------------------------------------------------------------- - ! H5T_NATIVE_CHARACTER ND buffer - !------------------------------------------------------------------------- - - CALL H5Tcopy_f(H5T_FORTRAN_S1, type_id, errcode) - CALL H5Tset_size_f(type_id, 5_SIZE_T, errcode) - ! - ! write dataset. - ! - IF(rank.EQ.4)THEN - f_ptr = C_LOC(cbuf_4(1,1,1,1)(1:1)) - CALL h5ltmake_dataset_f(file_id, dsetname5, rank, dims(1:rank), type_id, f_ptr, errcode) - ELSE IF(rank.EQ.5)THEN - f_ptr = C_LOC(cbuf_5(1,1,1,1,1)(1:1)) - CALL h5ltmake_dataset_f(file_id, dsetname5, rank, dims(1:rank), type_id, f_ptr, errcode) - ELSE IF(rank.EQ.6)THEN - f_ptr = C_LOC(cbuf_6(1,1,1,1,1,1)(1:1)) - CALL h5ltmake_dataset_f(file_id, dsetname5, rank, dims(1:rank), type_id, f_ptr, errcode) - ELSE IF(rank.EQ.7)THEN - f_ptr = C_LOC(cbuf_7(1,1,1,1,1,1,1)(1:1)) - CALL h5ltmake_dataset_f(file_id, dsetname5, rank, dims(1:rank), type_id, f_ptr, errcode) - ENDIF - - ! - ! read dataset. - ! - IF(rank.EQ.4)THEN - f_ptr = C_LOC(cbufr_4(1,1,1,1)(1:1)) - CALL h5ltread_dataset_f(file_id, dsetname5, type_id, f_ptr, errcode) - ELSE IF(rank.EQ.5)THEN - f_ptr = C_LOC(cbufr_5(1,1,1,1,1)(1:1)) - CALL h5ltread_dataset_f(file_id, dsetname5, type_id, f_ptr, errcode) - ELSE IF(rank.EQ.6)THEN - f_ptr = C_LOC(cbufr_6(1,1,1,1,1,1)(1:1)) - CALL h5ltread_dataset_f(file_id, dsetname5, type_id, f_ptr, errcode) - ELSE IF(rank.EQ.7)THEN - f_ptr = C_LOC(cbufr_7(1,1,1,1,1,1,1)(1:1)) - CALL h5ltread_dataset_f(file_id, dsetname5, type_id, f_ptr, errcode) - ENDIF - - - ! - ! compare read and write buffers. - ! - DO i = 1, dims(1) - DO j = 1, dims(2) - DO k = 1, dims(3) - DO l = 1, dims(4) - IF(rank.EQ.4)THEN - IF ( cbuf_4(i,j,k,l) .NE. cbufr_4(i,j,k,l) ) THEN - PRINT *, 'read buffer differs from write buffer (character)' - PRINT *, cbuf_4(i,j,k,l), ' and ', cbufr_4(i,j,k,l) - STOP - ENDIF - ENDIF - DO m = 1, dims(5) - IF(rank.EQ.5)THEN - IF ( cbuf_5(i,j,k,l,m) .NE. cbufr_5(i,j,k,l,m) ) THEN - PRINT *, 'read buffer differs from write buffer (character)' - PRINT *, cbuf_5(i,j,k,l,m), ' and ', cbufr_5(i,j,k,l,m) - STOP - ENDIF - ENDIF - DO n = 1, dims(6) - IF(rank.EQ.6)THEN - IF ( cbuf_6(i,j,k,l,m,n) .NE. cbufr_6(i,j,k,l,m,n) ) THEN - PRINT *, 'read buffer differs from write buffer (character)' - PRINT *, cbuf_6(i,j,k,l,m,n), ' and ', cbufr_6(i,j,k,l,m,n) - STOP - ENDIF - ENDIF - DO o = 1, dims(7) - IF(rank.EQ.7)THEN - IF ( cbuf_7(i,j,k,l,m,n,o) .NE. cbufr_7(i,j,k,l,m,n,o) ) THEN - PRINT *, 'read buffer differs from write buffer (character)' - PRINT *, cbuf_7(i,j,k,l,m,n,o), ' and ', cbufr_7(i,j,k,l,m,n,o) - STOP - ENDIF - ENDIF - ENDDO - ENDDO - ENDDO - ENDDO - ENDDO - ENDDO - ENDDO - - CALL h5ltget_dataset_info_f(file_id,dsetname4,dimsr,type_class,type_size,errcode ) - - CALL h5tclose_f(type_id,errcode) - - ! - ! compare dimensions - ! - DO i = 1, rank - IF ( dimsr(i) .NE. dims(i) ) THEN - PRINT *, 'dimensions differ ' - STOP - ENDIF - END DO - - ! - ! Close the file. - ! - CALL h5fclose_f(file_id, errcode) - - ! - ! Close FORTRAN predefined datatypes. - ! - CALL h5close_f(errcode) - - ! DEALLOCATE RESOURCES - - IF(rank.EQ.4)THEN - DEALLOCATE(ibuf_4, ibufr_4, rbuf_4, rbufr_4, dbuf_4, dbufr_4, cbuf_4, cbufr_4) - ELSE IF(rank.EQ.5)THEN - DEALLOCATE(ibuf_5, ibufr_5, rbuf_5, rbufr_5, dbuf_5, dbufr_5, cbuf_5, cbufr_5) - ELSE IF(rank.EQ.6)THEN - DEALLOCATE(ibuf_6, ibufr_6, rbuf_6, rbufr_6, dbuf_6, dbufr_6, cbuf_6, cbufr_6) - ELSE IF(rank.EQ.7)THEN - DEALLOCATE(ibuf_7, ibufr_7, rbuf_7, rbufr_7, dbuf_7, dbufr_7, cbuf_7, cbufr_7) - ENDIF - - CALL passed() - ! - ! end function. - ! -END SUBROUTINE test_datasetND - - -!------------------------------------------------------------------------- -! test_datasets -!------------------------------------------------------------------------- - -SUBROUTINE test_datasets() - - USE, INTRINSIC :: ISO_C_BINDING - USE H5LT ! module of H5LT - USE HDF5 ! module of HDF5 library - USE TSTLITE ! module for testing lite support routines - - IMPLICIT NONE - - CHARACTER(len=9), PARAMETER :: filename = "dsetf4.h5"! File name - INTEGER(HID_T) :: file_id ! File identifier - INTEGER :: errcode ! Error flag - INTEGER, PARAMETER :: DIM1 = 10 ! Dimension of array - INTEGER, PARAMETER :: LEN0 = 3 - INTEGER, PARAMETER :: LEN1 = 12 - CHARACTER(LEN=5), PARAMETER :: dsetname2 = "dset2" ! Dataset name - CHARACTER(LEN=5), PARAMETER :: dsetname3 = "dset3" ! Dataset name - CHARACTER(LEN=5), PARAMETER :: dsetname4 = "dset4" ! Dataset name - CHARACTER(LEN=5), PARAMETER :: dsetname5 = "dset5" ! Dataset name - CHARACTER(LEN=5), PARAMETER :: dsetname6 = "dset6" ! Dataset name - INTEGER(HSIZE_T), DIMENSION(1) :: dims = (/DIM1/) ! Dataset dimensions - INTEGER(HSIZE_T), DIMENSION(1) :: dimsr ! Dataset dimensions - INTEGER :: rank = 1 ! Dataset rank - INTEGER :: rankr ! Dataset rank - CHARACTER(LEN=8), PARAMETER :: buf1 = "mystring" ! Data buffer - CHARACTER(LEN=8) :: buf1r ! Data buffer - INTEGER, DIMENSION(DIM1) :: buf2 ! Data buffer - INTEGER, DIMENSION(DIM1) :: bufr2 ! Data buffer - REAL, DIMENSION(DIM1), TARGET :: buf3 ! Data buffer - REAL, DIMENSION(DIM1) , TARGET :: bufr3 ! Data buffer - DOUBLE PRECISION, DIMENSION(DIM1), TARGET :: buf4 ! Data buffer - DOUBLE PRECISION, DIMENSION(DIM1), TARGET :: bufr4 ! Data buffer - INTEGER :: i, j, n ! general purpose integer - INTEGER :: has ! general purpose integer - INTEGER :: type_class - INTEGER(SIZE_T) :: type_size - LOGICAL :: path_valid ! status of the path - CHARACTER(LEN=6) :: chr_exact - CHARACTER(LEN=8) :: chr_lg - TYPE(C_PTR) :: f_ptr - - ! vl data - TYPE vl - INTEGER, DIMENSION(:), POINTER :: DATA - END TYPE vl - TYPE(vl), DIMENSION(:), ALLOCATABLE, TARGET :: ptr - TYPE(hvl_t), DIMENSION(1:2), TARGET :: wdata ! Array of vlen structures - TYPE(hvl_t), DIMENSION(1:2), TARGET :: rdata ! Pointer to vlen structures - INTEGER(hsize_t), DIMENSION(1:1) :: dims_vl = (/2/) - INTEGER, DIMENSION(:), POINTER :: ptr_r - INTEGER(HID_T) :: type_id - - ! - ! Initialize FORTRAN predefined datatypes. - ! - CALL h5open_f(errcode) - - ! - ! Create a new file using default properties. - ! - CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, errcode) - - ! - ! Initialize the data array. - ! - n = 1 - DO i = 1, DIM1 - buf2(i) = n - buf3(i) = n - buf4(i) = n - n = n + 1 - END DO - - ! - ! Initialize variable-length data. wdata(1) is a countdown of - ! length LEN0, wdata(2) is a Fibonacci sequence of length LEN1. - ! - wdata(1)%len = LEN0 - wdata(2)%len = LEN1 - - ALLOCATE( ptr(1:2) ) - ALLOCATE( ptr(1)%data(1:wdata(1)%len) ) - ALLOCATE( ptr(2)%data(1:wdata(2)%len) ) - - DO i=1, wdata(1)%len - ptr(1)%data(i) = wdata(1)%len - i + 1 ! 3 2 1 - ENDDO - wdata(1)%p = C_LOC(ptr(1)%data(1)) - - ptr(2)%data(1:2) = 1 - DO i = 3, wdata(2)%len - ptr(2)%data(i) = ptr(2)%data(i-1) + ptr(2)%data(i-2) ! (1 1 2 3 5 8 etc.) - ENDDO - wdata(2)%p = C_LOC(ptr(2)%data(1)) - - !------------------------------------------------------------------------- - ! int - !------------------------------------------------------------------------- - - CALL test_begin(' Make/Read datasets (integer) ') - - ! - ! write dataset. - ! - CALL h5ltmake_dataset_int_f(file_id, dsetname2, rank, dims, buf2, errcode) - - ! - ! read dataset. - ! - CALL h5ltread_dataset_int_f(file_id, dsetname2, bufr2, dims, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, DIM1 - IF ( buf2(i) .NE. bufr2(i) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, bufr2(i), ' and ', buf2(i) - STOP - ENDIF - END DO - - CALL passed() - - - !------------------------------------------------------------------------- - ! real - !------------------------------------------------------------------------- - - CALL test_begin(' Make/Read datasets (float) ') - - - ! - ! write dataset. - ! - f_ptr = C_LOC(buf3(1)) - CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims, H5T_NATIVE_REAL, f_ptr, errcode) - - ! - ! read dataset. - ! - f_ptr = C_LOC(bufr3(1)) - CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, f_ptr, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, DIM1 - IF ( buf3(i) .NE. bufr3(i) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, bufr3(i), ' and ', buf3(i) - STOP - ENDIF - END DO - - CALL passed() + ! + ! Close the file. + ! + CALL h5fclose_f(file_id, errcode) - !------------------------------------------------------------------------- - ! double - !------------------------------------------------------------------------- - - CALL test_begin(' Make/Read datasets (double) ') - - - ! - ! write dataset. - ! - !f_ptr = C_LOC(buf4(1)) - !CALL h5ltmake_dataset_f(file_id, dsetname4, rank, dims, H5T_NATIVE_DOUBLE, f_ptr, errcode) - CALL h5ltmake_dataset_double_f(file_id, dsetname4, rank, dims, buf4, errcode) - - ! - ! read dataset. - ! - !f_ptr = C_LOC(buf4(1)) - !CALL h5ltread_dataset_f(file_id, dsetname4, H5T_NATIVE_DOUBLE, f_ptr, errcode) - CALL h5ltread_dataset_double_f(file_id, dsetname4, bufr4, dims, errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, DIM1 - IF ( buf4(i) .NE. bufr4(i) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, bufr4(i), ' and ', buf4(i) - STOP - ENDIF - END DO - - CALL passed() + ! + ! Close FORTRAN predefined datatypes. + ! + CALL h5close_f(errcode) + CALL passed() + ! + ! end function. + ! + END SUBROUTINE test_dataset3D !------------------------------------------------------------------------- - ! string + ! test_datasetND !------------------------------------------------------------------------- - CALL test_begin(' Make/Read datasets (string) ') - - - ! - ! write dataset. - ! - CALL h5ltmake_dataset_string_f(file_id, dsetname5, buf1, errcode) - ! - ! read dataset. - ! - CALL h5ltread_dataset_string_f(file_id, dsetname5, buf1r, errcode) + SUBROUTINE test_datasetND(rank) + + IMPLICIT NONE + + INTEGER :: rank ! Dataset rank + + INTEGER, PARAMETER :: DIM1 = 2 ! columns + INTEGER, PARAMETER :: DIM2 = 4 ! rows + INTEGER, PARAMETER :: DIM3 = 2 ! layers + INTEGER, PARAMETER :: DIM4 = 5 ! columns + INTEGER, PARAMETER :: DIM5 = 4 ! rows + INTEGER, PARAMETER :: DIM6 = 3 ! layers + INTEGER, PARAMETER :: DIM7 = 2 ! layers + CHARACTER(len=9), PARAMETER :: filename = "dsetf3.h5" ! File name + CHARACTER(LEN=5), PARAMETER :: dsetname2 = "dset2" ! Dataset name + CHARACTER(LEN=5), PARAMETER :: dsetname3 = "dset3" ! Dataset name + CHARACTER(LEN=5), PARAMETER :: dsetname4 = "dset4" ! Dataset name + CHARACTER(LEN=5), PARAMETER :: dsetname5 = "dset5" ! Dataset name + INTEGER(HID_T) :: file_id ! File identifier + INTEGER(HSIZE_T), DIMENSION(7) :: dims + INTEGER(HSIZE_T), DIMENSION(7) :: dimsr ! Dataset dimensions + INTEGER, ALLOCATABLE, DIMENSION(:,:,:,:) :: ibuf_4 ! Data buffer + INTEGER, ALLOCATABLE, DIMENSION(:,:,:,:) :: ibufr_4 ! Data buffer + INTEGER, ALLOCATABLE, DIMENSION(:,:,:,:,:), TARGET :: ibuf_5 ! Data buffer + INTEGER, ALLOCATABLE, DIMENSION(:,:,:,:,:), TARGET :: ibufr_5 ! Data buffer + INTEGER, ALLOCATABLE, DIMENSION(:,:,:,:,:,:) :: ibuf_6 ! Data buffer + INTEGER, ALLOCATABLE, DIMENSION(:,:,:,:,:,:) :: ibufr_6 ! Data buffer + INTEGER, ALLOCATABLE, DIMENSION(:,:,:,:,:,:,:) :: ibuf_7 ! Data buffer + INTEGER, ALLOCATABLE, DIMENSION(:,:,:,:,:,:,:) :: ibufr_7 ! Data buffer + REAL, ALLOCATABLE, DIMENSION(:,:,:,:), TARGET :: rbuf_4 ! Data buffer + REAL, ALLOCATABLE, DIMENSION(:,:,:,:), TARGET :: rbufr_4 ! Data buffer + REAL, ALLOCATABLE, DIMENSION(:,:,:,:,:), TARGET :: rbuf_5 ! Data buffer + REAL, ALLOCATABLE, DIMENSION(:,:,:,:,:), TARGET :: rbufr_5 ! Data buffer + REAL, ALLOCATABLE, DIMENSION(:,:,:,:,:,:), TARGET :: rbuf_6 ! Data buffer + REAL, ALLOCATABLE, DIMENSION(:,:,:,:,:,:), TARGET :: rbufr_6 ! Data buffer + REAL, ALLOCATABLE, DIMENSION(:,:,:,:,:,:,:), TARGET :: rbuf_7 ! Data buffer + REAL, ALLOCATABLE, DIMENSION(:,:,:,:,:,:,:), TARGET :: rbufr_7 ! Data buffer + DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:,:,:), TARGET :: dbuf_4 ! Data buffer + DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:,:,:), TARGET :: dbufr_4 ! Data buffer + DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:,:,:,:), TARGET :: dbuf_5 ! Data buffer + DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:,:,:,:), TARGET :: dbufr_5 ! Data buffer + DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:,:,:,:,:), TARGET :: dbuf_6 ! Data buffer + DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:,:,:,:,:), TARGET :: dbufr_6 ! Data buffer + DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:,:,:,:,:,:), TARGET :: dbuf_7 ! Data buffer + DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:,:,:,:,:,:), TARGET :: dbufr_7 ! Data buffer + CHARACTER(LEN=5), ALLOCATABLE, DIMENSION(:,:,:,:), TARGET :: cbuf_4 ! Data buffer + CHARACTER(LEN=5), ALLOCATABLE, DIMENSION(:,:,:,:), TARGET :: cbufr_4 ! Data buffer + CHARACTER(LEN=5), ALLOCATABLE, DIMENSION(:,:,:,:,:), TARGET :: cbuf_5 ! Data buffer + CHARACTER(LEN=5), ALLOCATABLE, DIMENSION(:,:,:,:,:), TARGET :: cbufr_5 ! Data buffer + CHARACTER(LEN=5), ALLOCATABLE, DIMENSION(:,:,:,:,:,:), TARGET :: cbuf_6 ! Data buffer + CHARACTER(LEN=5), ALLOCATABLE, DIMENSION(:,:,:,:,:,:), TARGET :: cbufr_6 ! Data buffer + CHARACTER(LEN=5), ALLOCATABLE, DIMENSION(:,:,:,:,:,:,:), TARGET :: cbuf_7 ! Data buffer + CHARACTER(LEN=5), ALLOCATABLE, DIMENSION(:,:,:,:,:,:,:), TARGET :: cbufr_7 ! Data buffer + INTEGER :: errcode ! Error flag + INTEGER(HSIZE_T) :: i, j, k, l, m, n, o, nn ! general purpose integers + INTEGER :: type_class + INTEGER(SIZE_T) :: type_size + CHARACTER(LEN=1) :: ichr1 + TYPE(C_PTR) :: f_ptr + INTEGER(HID_T) :: type_id + + WRITE(ichr1,'(I1.1)') rank + CALL test_begin(' Make/Read datasets ('//ichr1//'D) ') + ! + ! Initialize the data array. + ! + IF(rank.EQ.4)THEN + + ALLOCATE(ibuf_4 (1:DIM1,1:DIM2,1:DIM3,1:DIM4)) + ALLOCATE(ibufr_4(1:DIM1,1:DIM2,1:DIM3,1:DIM4)) + ALLOCATE(rbuf_4 (1:DIM1,1:DIM2,1:DIM3,1:DIM4)) + ALLOCATE(rbufr_4(1:DIM1,1:DIM2,1:DIM3,1:DIM4)) + ALLOCATE(dbuf_4 (1:DIM1,1:DIM2,1:DIM3,1:DIM4)) + ALLOCATE(dbufr_4(1:DIM1,1:DIM2,1:DIM3,1:DIM4)) + ALLOCATE(cbuf_4 (1:DIM1,1:DIM2,1:DIM3,1:DIM4)) + ALLOCATE(cbufr_4(1:DIM1,1:DIM2,1:DIM3,1:DIM4)) + + dims(1:7) = (/DIM1,DIM2,DIM3,DIM4,0,0,0/) + + nn = 1 + DO i = 1, DIM1 + DO j = 1, DIM2 + DO k = 1, DIM3 + DO l = 1, DIM4 + ibuf_4(i,j,k,l) = INT(nn) + rbuf_4(i,j,k,l) = INT(nn) + dbuf_4(i,j,k,l) = INT(nn) + WRITE(cbuf_4(i,j,k,l),'(I5.5)') nn + nn = nn + 1 + END DO + END DO + END DO + + ENDDO + + ELSE IF(rank.EQ.5)THEN + + ALLOCATE(ibuf_5 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5)) + ALLOCATE(ibufr_5(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5)) + ALLOCATE(rbuf_5 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5)) + ALLOCATE(rbufr_5(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5)) + ALLOCATE(dbuf_5 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5)) + ALLOCATE(dbufr_5(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5)) + ALLOCATE(cbuf_5 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5)) + ALLOCATE(cbufr_5(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5)) + + dims(1:7) = (/DIM1,DIM2,DIM3,DIM4,DIM5,0,0/) + + nn = 1 + DO i = 1, DIM1 + DO j = 1, DIM2 + DO k = 1, DIM3 + DO l = 1, DIM4 + DO m = 1, DIM5 + ibuf_5(i,j,k,l,m) = INT(nn) + rbuf_5(i,j,k,l,m) = INT(nn) + dbuf_5(i,j,k,l,m) = INT(nn) + WRITE(cbuf_5(i,j,k,l,m),'(I5.5)') nn + nn = nn + 1 + END DO + END DO + END DO + ENDDO + ENDDO + + ELSE IF(rank.EQ.6)THEN + + ALLOCATE(ibuf_6 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6)) + ALLOCATE(ibufr_6(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6)) + ALLOCATE(rbuf_6 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6)) + ALLOCATE(rbufr_6(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6)) + ALLOCATE(dbuf_6 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6)) + ALLOCATE(dbufr_6(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6)) + ALLOCATE(cbuf_6 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6)) + ALLOCATE(cbufr_6(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6)) + + dims(1:7) = (/DIM1,DIM2,DIM3,DIM4,DIM5,DIM6,0/) + + nn = 1 + DO i = 1, DIM1 + DO j = 1, DIM2 + DO k = 1, DIM3 + DO l = 1, DIM4 + DO m = 1, DIM5 + DO n = 1, DIM6 + ibuf_6(i,j,k,l,m,n) = INT(nn) + rbuf_6(i,j,k,l,m,n) = INT(nn) + dbuf_6(i,j,k,l,m,n) = INT(nn) + WRITE(cbuf_6(i,j,k,l,m,n),'(I5.5)') nn + nn = nn + 1 + END DO + END DO + END DO + ENDDO + ENDDO + ENDDO + + ELSE IF(rank.EQ.7)THEN + + ALLOCATE(ibuf_7 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6,1:DIM7)) + ALLOCATE(ibufr_7(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6,1:DIM7)) + ALLOCATE(rbuf_7 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6,1:DIM7)) + ALLOCATE(rbufr_7(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6,1:DIM7)) + ALLOCATE(dbuf_7 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6,1:DIM7)) + ALLOCATE(dbufr_7(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6,1:DIM7)) + ALLOCATE(cbuf_7 (1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6,1:DIM7)) + ALLOCATE(cbufr_7(1:DIM1,1:DIM2,1:DIM3,1:DIM4,1:DIM5,1:DIM6,1:DIM7)) + + dims(1:7) = (/DIM1,DIM2,DIM3,DIM4,DIM5,DIM6,DIM7/) + + nn = 1 + DO i = 1, DIM1 + DO j = 1, DIM2 + DO k = 1, DIM3 + DO l = 1, DIM4 + DO m = 1, DIM5 + DO n = 1, DIM6 + DO o = 1, DIM7 + ibuf_7(i,j,k,l,m,n,o) = INT(nn) + rbuf_7(i,j,k,l,m,n,o) = INT(nn) + dbuf_7(i,j,k,l,m,n,o) = INT(nn) + WRITE(cbuf_7(i,j,k,l,m,n,o),'(I5.5)') nn + nn = nn + 1 + END DO + END DO + END DO + ENDDO + ENDDO + ENDDO + ENDDO + + ENDIF + + ! + ! Initialize FORTRAN predefined datatypes. + ! + CALL h5open_f(errcode) + + ! + ! Create a new file using default properties. + ! + CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, errcode) + + !------------------------------------------------------------------------- + ! H5T_NATIVE_INT ND buffer + !------------------------------------------------------------------------- + + ! + ! write dataset. + ! + IF(rank.EQ.4)THEN + CALL h5ltmake_dataset_f(file_id, dsetname2, rank, dims(1:rank), H5T_NATIVE_INTEGER, ibuf_4, errcode) + ELSE IF(rank.EQ.5)THEN + f_ptr = C_LOC(ibuf_5(1,1,1,1,1)) + CALL h5ltmake_dataset_f(file_id, dsetname2, rank, dims(1:rank), H5T_NATIVE_INTEGER, f_ptr, errcode) + ELSE IF(rank.EQ.6)THEN + CALL h5ltmake_dataset_f(file_id, dsetname2, rank, dims(1:rank), H5T_NATIVE_INTEGER, ibuf_6, errcode) + ELSE IF(rank.EQ.7)THEN + CALL h5ltmake_dataset_f(file_id, dsetname2, rank, dims(1:rank), H5T_NATIVE_INTEGER, ibuf_7, errcode) + ENDIF + + + ! + ! read dataset. + ! + IF(rank.EQ.4)THEN + CALL h5ltread_dataset_f(file_id, dsetname2, H5T_NATIVE_INTEGER, ibufr_4, dims(1:rank), errcode) + ELSE IF(rank.EQ.5)THEN + f_ptr = C_LOC(ibufr_5(1,1,1,1,1)) + CALL h5ltread_dataset_f(file_id, dsetname2, H5T_NATIVE_INTEGER, f_ptr, errcode) + ELSE IF(rank.EQ.6)THEN + CALL h5ltread_dataset_f(file_id, dsetname2, H5T_NATIVE_INTEGER, ibufr_6, dims(1:rank), errcode) + ELSE IF(rank.EQ.7)THEN + CALL h5ltread_dataset_f(file_id, dsetname2, H5T_NATIVE_INTEGER, ibufr_7, dims(1:rank), errcode) + ENDIF + + ! + ! compare read and write buffers. + ! + DO i = 1, dims(1) + DO j = 1, dims(2) + DO k = 1, dims(3) + DO l = 1, dims(4) + IF(rank.EQ.4)THEN + IF ( ibuf_4(i,j,k,l) .NE. ibufr_4(i,j,k,l) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, ibuf_4(i,j,k,l), ' and ', ibufr_4(i,j,k,l) + STOP + ENDIF + ENDIF + DO m = 1, dims(5) + IF(rank.EQ.5)THEN + IF ( ibuf_5(i,j,k,l,m) .NE. ibufr_5(i,j,k,l,m) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, ibuf_5(i,j,k,l,m), ' and ', ibufr_5(i,j,k,l,m) + STOP + ENDIF + ENDIF + DO n = 1, dims(6) + IF(rank.EQ.6)THEN + IF ( ibuf_6(i,j,k,l,m,n) .NE. ibufr_6(i,j,k,l,m,n) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, ibuf_6(i,j,k,l,m,n), ' and ', ibufr_6(i,j,k,l,m,n) + STOP + ENDIF + ENDIF + DO o = 1, dims(7) + IF(rank.EQ.7)THEN + IF ( ibuf_7(i,j,k,l,m,n,o) .NE. ibufr_7(i,j,k,l,m,n,o) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, ibuf_7(i,j,k,l,m,n,o), ' and ', ibufr_7(i,j,k,l,m,n,o) + STOP + ENDIF + ENDIF + ENDDO + ENDDO + ENDDO + ENDDO + ENDDO + ENDDO + ENDDO + !------------------------------------------------------------------------- + ! H5T_NATIVE_REAL + !------------------------------------------------------------------------- + + ! + ! write dataset. + ! + IF(rank.EQ.4)THEN + f_ptr = C_LOC(rbuf_4(1,1,1,1)) + CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims(1:rank), H5T_NATIVE_REAL, f_ptr, errcode) + ! CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims(1:rank), H5T_NATIVE_REAL, rbuf_4, errcode) + ELSE IF(rank.EQ.5)THEN + f_ptr = C_LOC(rbuf_5(1,1,1,1,1)) + CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims(1:rank), H5T_NATIVE_REAL, f_ptr, errcode) + ELSE IF(rank.EQ.6)THEN + f_ptr = C_LOC(rbuf_6(1,1,1,1,1,1)) + CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims(1:rank), H5T_NATIVE_REAL, f_ptr, errcode) + !CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims(1:rank), H5T_NATIVE_REAL, rbuf_6, errcode) + ELSE IF(rank.EQ.7)THEN + f_ptr = C_LOC(rbuf_7(1,1,1,1,1,1,1)) + CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims(1:rank), H5T_NATIVE_REAL, f_ptr, errcode) + !CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims(1:rank), H5T_NATIVE_REAL, rbuf_7, errcode) + ENDIF + + + ! + ! read dataset. + ! + IF(rank.EQ.4)THEN + f_ptr = C_LOC(rbufr_4(1,1,1,1)) + CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, f_ptr, errcode) + ELSE IF(rank.EQ.5)THEN + f_ptr = C_LOC(rbufr_5(1,1,1,1,1)) + CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, f_ptr, errcode) + ELSE IF(rank.EQ.6)THEN + f_ptr = C_LOC(rbufr_6(1,1,1,1,1,1)) + CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, f_ptr, errcode) + ELSE IF(rank.EQ.7)THEN + f_ptr = C_LOC(rbufr_7(1,1,1,1,1,1,1)) + CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, f_ptr, errcode) + ENDIF + + ! + ! compare read and write buffers. + ! + DO i = 1, dims(1) + DO j = 1, dims(2) + DO k = 1, dims(3) + DO l = 1, dims(4) + IF(rank.EQ.4)THEN + IF ( rbuf_4(i,j,k,l) .NE. rbufr_4(i,j,k,l) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, rbuf_4(i,j,k,l), ' and ', rbufr_4(i,j,k,l) + STOP + ENDIF + ENDIF + DO m = 1, dims(5) + IF(rank.EQ.5)THEN + IF ( rbuf_5(i,j,k,l,m) .NE. rbufr_5(i,j,k,l,m) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, rbuf_5(i,j,k,l,m), ' and ', rbufr_5(i,j,k,l,m) + STOP + ENDIF + ENDIF + DO n = 1, dims(6) + IF(rank.EQ.6)THEN + IF ( rbuf_6(i,j,k,l,m,n) .NE. rbufr_6(i,j,k,l,m,n) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, rbuf_6(i,j,k,l,m,n), ' and ', rbufr_6(i,j,k,l,m,n) + STOP + ENDIF + ENDIF + DO o = 1, dims(7) + IF(rank.EQ.7)THEN + IF ( rbuf_7(i,j,k,l,m,n,o) .NE. rbufr_7(i,j,k,l,m,n,o) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, rbuf_7(i,j,k,l,m,n,o), ' and ', rbufr_7(i,j,k,l,m,n,o) + STOP + ENDIF + ENDIF + ENDDO + ENDDO + ENDDO + ENDDO + ENDDO + ENDDO + ENDDO + + !------------------------------------------------------------------------- + ! H5T_NATIVE_DOUBLE + !------------------------------------------------------------------------- + + ! + ! write dataset. + ! + IF(rank.EQ.4)THEN + f_ptr = C_LOC(dbuf_4(1,1,1,1)) + CALL h5ltmake_dataset_f(file_id, dsetname4, rank, dims(1:rank), H5T_NATIVE_DOUBLE, f_ptr, errcode) + ELSE IF(rank.EQ.5)THEN + f_ptr = C_LOC(dbuf_5(1,1,1,1,1)) + CALL h5ltmake_dataset_f(file_id, dsetname4, rank, dims(1:rank), H5T_NATIVE_DOUBLE, f_ptr, errcode) + ELSE IF(rank.EQ.6)THEN + f_ptr = C_LOC(dbuf_6(1,1,1,1,1,1)) + CALL h5ltmake_dataset_f(file_id, dsetname4, rank, dims(1:rank), H5T_NATIVE_DOUBLE, f_ptr, errcode) + ELSE IF(rank.EQ.7)THEN + f_ptr = C_LOC(dbuf_7(1,1,1,1,1,1,1)) + CALL h5ltmake_dataset_f(file_id, dsetname4, rank, dims(1:rank), H5T_NATIVE_DOUBLE, f_ptr, errcode) + ENDIF + + ! + ! read dataset. + ! + IF(rank.EQ.4)THEN + f_ptr = C_LOC(dbufr_4(1,1,1,1)) + CALL h5ltread_dataset_f(file_id, dsetname4, H5T_NATIVE_DOUBLE, f_ptr, errcode) + ELSE IF(rank.EQ.5)THEN + f_ptr = C_LOC(dbufr_5(1,1,1,1,1)) + CALL h5ltread_dataset_f(file_id, dsetname4, H5T_NATIVE_DOUBLE, f_ptr, errcode) + ELSE IF(rank.EQ.6)THEN + f_ptr = C_LOC(dbufr_6(1,1,1,1,1,1)) + CALL h5ltread_dataset_f(file_id, dsetname4, H5T_NATIVE_DOUBLE, f_ptr, errcode) + ELSE IF(rank.EQ.7)THEN + f_ptr = C_LOC(dbufr_7(1,1,1,1,1,1,1)) + CALL h5ltread_dataset_f(file_id, dsetname4, H5T_NATIVE_DOUBLE, f_ptr, errcode) + ENDIF + + ! + ! compare read and write buffers. + ! + DO i = 1, dims(1) + DO j = 1, dims(2) + DO k = 1, dims(3) + DO l = 1, dims(4) + IF(rank.EQ.4)THEN + IF ( dbuf_4(i,j,k,l) .NE. dbufr_4(i,j,k,l) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, dbuf_4(i,j,k,l), ' and ', dbufr_4(i,j,k,l) + STOP + ENDIF + ENDIF + DO m = 1, dims(5) + IF(rank.EQ.5)THEN + IF ( dbuf_5(i,j,k,l,m) .NE. dbufr_5(i,j,k,l,m) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, dbuf_5(i,j,k,l,m), ' and ', dbufr_5(i,j,k,l,m) + STOP + ENDIF + ENDIF + DO n = 1, dims(6) + IF(rank.EQ.6)THEN + IF ( dbuf_6(i,j,k,l,m,n) .NE. dbufr_6(i,j,k,l,m,n) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, dbuf_6(i,j,k,l,m,n), ' and ', dbufr_6(i,j,k,l,m,n) + STOP + ENDIF + ENDIF + DO o = 1, dims(7) + IF(rank.EQ.7)THEN + IF ( dbuf_7(i,j,k,l,m,n,o) .NE. dbufr_7(i,j,k,l,m,n,o) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, dbuf_7(i,j,k,l,m,n,o), ' and ', dbufr_7(i,j,k,l,m,n,o) + STOP + ENDIF + ENDIF + ENDDO + ENDDO + ENDDO + ENDDO + ENDDO + ENDDO + ENDDO + + !------------------------------------------------------------------------- + ! H5T_NATIVE_CHARACTER ND buffer + !------------------------------------------------------------------------- + + CALL H5Tcopy_f(H5T_FORTRAN_S1, type_id, errcode) + CALL H5Tset_size_f(type_id, 5_SIZE_T, errcode) + ! + ! write dataset. + ! + IF(rank.EQ.4)THEN + f_ptr = C_LOC(cbuf_4(1,1,1,1)(1:1)) + CALL h5ltmake_dataset_f(file_id, dsetname5, rank, dims(1:rank), type_id, f_ptr, errcode) + ELSE IF(rank.EQ.5)THEN + f_ptr = C_LOC(cbuf_5(1,1,1,1,1)(1:1)) + CALL h5ltmake_dataset_f(file_id, dsetname5, rank, dims(1:rank), type_id, f_ptr, errcode) + ELSE IF(rank.EQ.6)THEN + f_ptr = C_LOC(cbuf_6(1,1,1,1,1,1)(1:1)) + CALL h5ltmake_dataset_f(file_id, dsetname5, rank, dims(1:rank), type_id, f_ptr, errcode) + ELSE IF(rank.EQ.7)THEN + f_ptr = C_LOC(cbuf_7(1,1,1,1,1,1,1)(1:1)) + CALL h5ltmake_dataset_f(file_id, dsetname5, rank, dims(1:rank), type_id, f_ptr, errcode) + ENDIF + + ! + ! read dataset. + ! + IF(rank.EQ.4)THEN + f_ptr = C_LOC(cbufr_4(1,1,1,1)(1:1)) + CALL h5ltread_dataset_f(file_id, dsetname5, type_id, f_ptr, errcode) + ELSE IF(rank.EQ.5)THEN + f_ptr = C_LOC(cbufr_5(1,1,1,1,1)(1:1)) + CALL h5ltread_dataset_f(file_id, dsetname5, type_id, f_ptr, errcode) + ELSE IF(rank.EQ.6)THEN + f_ptr = C_LOC(cbufr_6(1,1,1,1,1,1)(1:1)) + CALL h5ltread_dataset_f(file_id, dsetname5, type_id, f_ptr, errcode) + ELSE IF(rank.EQ.7)THEN + f_ptr = C_LOC(cbufr_7(1,1,1,1,1,1,1)(1:1)) + CALL h5ltread_dataset_f(file_id, dsetname5, type_id, f_ptr, errcode) + ENDIF + + + ! + ! compare read and write buffers. + ! + DO i = 1, dims(1) + DO j = 1, dims(2) + DO k = 1, dims(3) + DO l = 1, dims(4) + IF(rank.EQ.4)THEN + IF ( cbuf_4(i,j,k,l) .NE. cbufr_4(i,j,k,l) ) THEN + PRINT *, 'read buffer differs from write buffer (character)' + PRINT *, cbuf_4(i,j,k,l), ' and ', cbufr_4(i,j,k,l) + STOP + ENDIF + ENDIF + DO m = 1, dims(5) + IF(rank.EQ.5)THEN + IF ( cbuf_5(i,j,k,l,m) .NE. cbufr_5(i,j,k,l,m) ) THEN + PRINT *, 'read buffer differs from write buffer (character)' + PRINT *, cbuf_5(i,j,k,l,m), ' and ', cbufr_5(i,j,k,l,m) + STOP + ENDIF + ENDIF + DO n = 1, dims(6) + IF(rank.EQ.6)THEN + IF ( cbuf_6(i,j,k,l,m,n) .NE. cbufr_6(i,j,k,l,m,n) ) THEN + PRINT *, 'read buffer differs from write buffer (character)' + PRINT *, cbuf_6(i,j,k,l,m,n), ' and ', cbufr_6(i,j,k,l,m,n) + STOP + ENDIF + ENDIF + DO o = 1, dims(7) + IF(rank.EQ.7)THEN + IF ( cbuf_7(i,j,k,l,m,n,o) .NE. cbufr_7(i,j,k,l,m,n,o) ) THEN + PRINT *, 'read buffer differs from write buffer (character)' + PRINT *, cbuf_7(i,j,k,l,m,n,o), ' and ', cbufr_7(i,j,k,l,m,n,o) + STOP + ENDIF + ENDIF + ENDDO + ENDDO + ENDDO + ENDDO + ENDDO + ENDDO + ENDDO + + CALL h5ltget_dataset_info_f(file_id,dsetname4,dimsr,type_class,type_size,errcode ) + + CALL h5tclose_f(type_id,errcode) + + ! + ! compare dimensions + ! + DO i = 1, rank + IF ( dimsr(i) .NE. dims(i) ) THEN + PRINT *, 'dimensions differ ' + STOP + ENDIF + END DO + + ! + ! Close the file. + ! + CALL h5fclose_f(file_id, errcode) + + ! + ! Close FORTRAN predefined datatypes. + ! + CALL h5close_f(errcode) + + ! DEALLOCATE RESOURCES + + IF(rank.EQ.4)THEN + DEALLOCATE(ibuf_4, ibufr_4, rbuf_4, rbufr_4, dbuf_4, dbufr_4, cbuf_4, cbufr_4) + ELSE IF(rank.EQ.5)THEN + DEALLOCATE(ibuf_5, ibufr_5, rbuf_5, rbufr_5, dbuf_5, dbufr_5, cbuf_5, cbufr_5) + ELSE IF(rank.EQ.6)THEN + DEALLOCATE(ibuf_6, ibufr_6, rbuf_6, rbufr_6, dbuf_6, dbufr_6, cbuf_6, cbufr_6) + ELSE IF(rank.EQ.7)THEN + DEALLOCATE(ibuf_7, ibufr_7, rbuf_7, rbufr_7, dbuf_7, dbufr_7, cbuf_7, cbufr_7) + ENDIF + + CALL passed() + ! + ! end function. + ! + END SUBROUTINE test_datasetND - ! - ! compare read and write buffers. - ! - IF ( buf1 .NE. buf1r ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, buf1, ' and ', buf1r - STOP - ENDIF - - CALL passed() - - - !------------------------------------------------------------------------- - ! variable-length dataset - !------------------------------------------------------------------------- - CALL test_begin(' Make/Read datasets (vl) ') - ! - ! Create variable-length datatype. - ! - CALL H5Tvlen_create_f(H5T_NATIVE_INTEGER, type_id, errcode) - - f_ptr = C_LOC(wdata(1)) - CALL h5ltmake_dataset_f(file_id, dsetname6, 1, dims_vl, type_id, f_ptr, errcode) - - ! Read the variable-length datatype - f_ptr = C_LOC(rdata(1)) - CALL h5ltread_dataset_f(file_id, dsetname6, type_id, f_ptr, errcode) - - DO i = 1, INT(dims_vl(1)) - CALL c_f_pointer(rdata(i)%p, ptr_r, [rdata(i)%len] ) - DO j = 1, rdata(i)%len - IF(ptr_r(j).NE.ptr(i)%data(j))THEN - PRINT *, 'Writing/Reading variable-length dataset failed' - STOP - ENDIF - ENDDO - ENDDO - - CALL H5Tclose_f(type_id, errcode) - DEALLOCATE(ptr) - - CALL passed() - - CALL test_begin(' Test h5ltpath_valid_f ') - ! - ! test function h5ltpath_valid_f - ! - chr_exact = "/"//dsetname2 ! test character buffer the exact size needed - CALL h5ltpath_valid_f(file_id, chr_exact, .TRUE., path_valid, errcode) - IF(errcode.LT.0.OR..NOT.path_valid)THEN - PRINT *, 'error in h5ltpath_valid_f' - STOP - ENDIF - chr_lg = "/"//dsetname2 ! test character buffer larger then needed - CALL h5ltpath_valid_f(file_id, chr_lg, .TRUE., path_valid, errcode) - IF(errcode.LT.0.OR..NOT.path_valid)THEN - PRINT *, 'error in h5ltpath_valid_f' - STOP - ENDIF - - CALL h5ltpath_valid_f(file_id, chr_lg, .FALSE., path_valid, errcode) - IF(errcode.LT.0.OR..NOT.path_valid)THEN - PRINT *, 'error in h5ltpath_valid_f' - STOP - ENDIF - - ! Should fail, dataset does not exist - CALL h5ltpath_valid_f(file_id, "/"//dsetname2//"junk", .TRUE., path_valid, errcode) - IF(errcode.LT.0.OR.path_valid)THEN - PRINT *, 'error in h5ltpath_valid_f' - STOP - ENDIF - - CALL h5ltpath_valid_f(file_id, "/"//dsetname2//"junk", .FALSE., path_valid, errcode) - IF(errcode.LT.0.OR.path_valid)THEN - PRINT *, 'error in h5ltpath_valid_f' - STOP - ENDIF - - ! Create a dangling soft link - CALL h5lcreate_soft_f("/G2", file_id, "/G3", errcode) - - ! Should pass, does not check for dangled link - CALL h5ltpath_valid_f(file_id, "/G3", .FALSE., path_valid, errcode) - IF(.NOT.path_valid)THEN - PRINT *, 'error in h5ltpath_valid_f' - STOP - ENDIF - - ! Should fail, dangled link - CALL h5ltpath_valid_f(file_id, "/G2", .TRUE., path_valid, errcode) - IF(path_valid)THEN - PRINT *, 'error in h5ltpath_valid_f' - STOP - ENDIF - - CALL passed() - - CALL test_begin(' Get dataset dimensions/info ') !------------------------------------------------------------------------- - ! h5ltget_dataset_ndims_f + ! test_datasets !------------------------------------------------------------------------- - CALL h5ltget_dataset_ndims_f(file_id, dsetname4, rankr, errcode) - IF ( rankr .NE. rank ) THEN - PRINT *, 'h5ltget_dataset_ndims_f return error' - STOP - ENDIF - - !------------------------------------------------------------------------- - ! test h5ltfind_dataset_f function - !------------------------------------------------------------------------- + SUBROUTINE test_datasets() + + IMPLICIT NONE + + CHARACTER(len=9), PARAMETER :: filename = "dsetf4.h5"! File name + INTEGER(HID_T) :: file_id ! File identifier + INTEGER :: errcode ! Error flag + INTEGER, PARAMETER :: DIM1 = 10 ! Dimension of array + INTEGER, PARAMETER :: LEN0 = 3 + INTEGER, PARAMETER :: LEN1 = 12 + CHARACTER(LEN=5), PARAMETER :: dsetname2 = "dset2" ! Dataset name + CHARACTER(LEN=5), PARAMETER :: dsetname3 = "dset3" ! Dataset name + CHARACTER(LEN=5), PARAMETER :: dsetname4 = "dset4" ! Dataset name + CHARACTER(LEN=5), PARAMETER :: dsetname5 = "dset5" ! Dataset name + CHARACTER(LEN=5), PARAMETER :: dsetname6 = "dset6" ! Dataset name + INTEGER(HSIZE_T), DIMENSION(1) :: dims = (/DIM1/) ! Dataset dimensions + INTEGER(HSIZE_T), DIMENSION(1) :: dimsr ! Dataset dimensions + INTEGER :: rank = 1 ! Dataset rank + INTEGER :: rankr ! Dataset rank + CHARACTER(LEN=8), PARAMETER :: buf1 = "mystring" ! Data buffer + CHARACTER(LEN=8) :: buf1r ! Data buffer + INTEGER, DIMENSION(DIM1) :: buf2 ! Data buffer + INTEGER, DIMENSION(DIM1) :: bufr2 ! Data buffer + REAL, DIMENSION(DIM1), TARGET :: buf3 ! Data buffer + REAL, DIMENSION(DIM1) , TARGET :: bufr3 ! Data buffer + DOUBLE PRECISION, DIMENSION(DIM1), TARGET :: buf4 ! Data buffer + DOUBLE PRECISION, DIMENSION(DIM1), TARGET :: bufr4 ! Data buffer + INTEGER :: i, j, n ! general purpose integer + INTEGER :: has ! general purpose integer + INTEGER :: type_class + INTEGER(SIZE_T) :: type_size + LOGICAL :: path_valid ! status of the path + CHARACTER(LEN=6) :: chr_exact + CHARACTER(LEN=8) :: chr_lg + TYPE(C_PTR) :: f_ptr + + ! vl data + TYPE vl + INTEGER, DIMENSION(:), POINTER :: DATA + END TYPE vl + TYPE(vl), DIMENSION(:), ALLOCATABLE, TARGET :: ptr + TYPE(hvl_t), DIMENSION(1:2), TARGET :: wdata ! Array of vlen structures + TYPE(hvl_t), DIMENSION(1:2), TARGET :: rdata ! Pointer to vlen structures + INTEGER(hsize_t), DIMENSION(1:1) :: dims_vl = (/2/) + INTEGER, DIMENSION(:), POINTER :: ptr_r + INTEGER(HID_T) :: type_id + + ! + ! Initialize FORTRAN predefined datatypes. + ! + CALL h5open_f(errcode) + + ! + ! Create a new file using default properties. + ! + CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, errcode) + + ! + ! Initialize the data array. + ! + n = 1 + DO i = 1, DIM1 + buf2(i) = n + buf3(i) = n + buf4(i) = n + n = n + 1 + END DO + + ! + ! Initialize variable-length data. wdata(1) is a countdown of + ! length LEN0, wdata(2) is a Fibonacci sequence of length LEN1. + ! + wdata(1)%len = LEN0 + wdata(2)%len = LEN1 + + ALLOCATE( ptr(1:2) ) + ALLOCATE( ptr(1)%data(1:wdata(1)%len) ) + ALLOCATE( ptr(2)%data(1:wdata(2)%len) ) + + DO i=1, wdata(1)%len + ptr(1)%data(i) = wdata(1)%len - i + 1 ! 3 2 1 + ENDDO + wdata(1)%p = C_LOC(ptr(1)%data(1)) + + ptr(2)%data(1:2) = 1 + DO i = 3, wdata(2)%len + ptr(2)%data(i) = ptr(2)%data(i-1) + ptr(2)%data(i-2) ! (1 1 2 3 5 8 etc.) + ENDDO + wdata(2)%p = C_LOC(ptr(2)%data(1)) + + !------------------------------------------------------------------------- + ! int + !------------------------------------------------------------------------- + + CALL test_begin(' Make/Read datasets (integer) ') + + ! + ! write dataset. + ! + CALL h5ltmake_dataset_int_f(file_id, dsetname2, rank, dims, buf2, errcode) + + ! + ! read dataset. + ! + CALL h5ltread_dataset_int_f(file_id, dsetname2, bufr2, dims, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, DIM1 + IF ( buf2(i) .NE. bufr2(i) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, bufr2(i), ' and ', buf2(i) + STOP + ENDIF + END DO + + CALL passed() + + + !------------------------------------------------------------------------- + ! real + !------------------------------------------------------------------------- + + CALL test_begin(' Make/Read datasets (float) ') + + + ! + ! write dataset. + ! + f_ptr = C_LOC(buf3(1)) + CALL h5ltmake_dataset_f(file_id, dsetname3, rank, dims, H5T_NATIVE_REAL, f_ptr, errcode) + + ! + ! read dataset. + ! + f_ptr = C_LOC(bufr3(1)) + CALL h5ltread_dataset_f(file_id, dsetname3, H5T_NATIVE_REAL, f_ptr, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, DIM1 + IF ( buf3(i) .NE. bufr3(i) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, bufr3(i), ' and ', buf3(i) + STOP + ENDIF + END DO + + CALL passed() + + !------------------------------------------------------------------------- + ! double + !------------------------------------------------------------------------- + + CALL test_begin(' Make/Read datasets (double) ') + + + ! + ! write dataset. + ! + !f_ptr = C_LOC(buf4(1)) + !CALL h5ltmake_dataset_f(file_id, dsetname4, rank, dims, H5T_NATIVE_DOUBLE, f_ptr, errcode) + CALL h5ltmake_dataset_double_f(file_id, dsetname4, rank, dims, buf4, errcode) + + ! + ! read dataset. + ! + !f_ptr = C_LOC(buf4(1)) + !CALL h5ltread_dataset_f(file_id, dsetname4, H5T_NATIVE_DOUBLE, f_ptr, errcode) + CALL h5ltread_dataset_double_f(file_id, dsetname4, bufr4, dims, errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, DIM1 + IF ( buf4(i) .NE. bufr4(i) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, bufr4(i), ' and ', buf4(i) + STOP + ENDIF + END DO + + CALL passed() + + + !------------------------------------------------------------------------- + ! string + !------------------------------------------------------------------------- + + CALL test_begin(' Make/Read datasets (string) ') + + + ! + ! write dataset. + ! + CALL h5ltmake_dataset_string_f(file_id, dsetname5, buf1, errcode) + + ! + ! read dataset. + ! + CALL h5ltread_dataset_string_f(file_id, dsetname5, buf1r, errcode) + + ! + ! compare read and write buffers. + ! + IF ( buf1 .NE. buf1r ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, buf1, ' and ', buf1r + STOP + ENDIF + + CALL passed() + + + !------------------------------------------------------------------------- + ! variable-length dataset + !------------------------------------------------------------------------- + CALL test_begin(' Make/Read datasets (vl) ') + ! + ! Create variable-length datatype. + ! + CALL H5Tvlen_create_f(H5T_NATIVE_INTEGER, type_id, errcode) + + f_ptr = C_LOC(wdata(1)) + CALL h5ltmake_dataset_f(file_id, dsetname6, 1, dims_vl, type_id, f_ptr, errcode) + + ! Read the variable-length datatype + f_ptr = C_LOC(rdata(1)) + CALL h5ltread_dataset_f(file_id, dsetname6, type_id, f_ptr, errcode) + + DO i = 1, INT(dims_vl(1)) + CALL c_f_pointer(rdata(i)%p, ptr_r, [rdata(i)%len] ) + DO j = 1, rdata(i)%len + IF(ptr_r(j).NE.ptr(i)%data(j))THEN + PRINT *, 'Writing/Reading variable-length dataset failed' + STOP + ENDIF + ENDDO + ENDDO + + CALL H5Tclose_f(type_id, errcode) + DEALLOCATE(ptr) + + CALL passed() + + CALL test_begin(' Test h5ltpath_valid_f ') + ! + ! test function h5ltpath_valid_f + ! + chr_exact = "/"//dsetname2 ! test character buffer the exact size needed + CALL h5ltpath_valid_f(file_id, chr_exact, .TRUE., path_valid, errcode) + IF(errcode.LT.0.OR..NOT.path_valid)THEN + PRINT *, 'error in h5ltpath_valid_f' + STOP + ENDIF + chr_lg = "/"//dsetname2 ! test character buffer larger then needed + CALL h5ltpath_valid_f(file_id, chr_lg, .TRUE., path_valid, errcode) + IF(errcode.LT.0.OR..NOT.path_valid)THEN + PRINT *, 'error in h5ltpath_valid_f' + STOP + ENDIF + + CALL h5ltpath_valid_f(file_id, chr_lg, .FALSE., path_valid, errcode) + IF(errcode.LT.0.OR..NOT.path_valid)THEN + PRINT *, 'error in h5ltpath_valid_f' + STOP + ENDIF + + ! Should fail, dataset does not exist + CALL h5ltpath_valid_f(file_id, "/"//dsetname2//"junk", .TRUE., path_valid, errcode) + IF(errcode.LT.0.OR.path_valid)THEN + PRINT *, 'error in h5ltpath_valid_f' + STOP + ENDIF + + CALL h5ltpath_valid_f(file_id, "/"//dsetname2//"junk", .FALSE., path_valid, errcode) + IF(errcode.LT.0.OR.path_valid)THEN + PRINT *, 'error in h5ltpath_valid_f' + STOP + ENDIF + + ! Create a dangling soft link + CALL h5lcreate_soft_f("/G2", file_id, "/G3", errcode) + + ! Should pass, does not check for dangled link + CALL h5ltpath_valid_f(file_id, "/G3", .FALSE., path_valid, errcode) + IF(.NOT.path_valid)THEN + PRINT *, 'error in h5ltpath_valid_f' + STOP + ENDIF + + ! Should fail, dangled link + CALL h5ltpath_valid_f(file_id, "/G2", .TRUE., path_valid, errcode) + IF(path_valid)THEN + PRINT *, 'error in h5ltpath_valid_f' + STOP + ENDIF + + CALL passed() + + CALL test_begin(' Get dataset dimensions/info ') + + !------------------------------------------------------------------------- + ! h5ltget_dataset_ndims_f + !------------------------------------------------------------------------- + + CALL h5ltget_dataset_ndims_f(file_id, dsetname4, rankr, errcode) + IF ( rankr .NE. rank ) THEN + PRINT *, 'h5ltget_dataset_ndims_f return error' + STOP + ENDIF + + !------------------------------------------------------------------------- + ! test h5ltfind_dataset_f function + !------------------------------------------------------------------------- + + + has = h5ltfind_dataset_f(file_id,dsetname4) + IF ( has .NE. 1 ) THEN + PRINT *, 'h5ltfind_dataset_f return error' + STOP + ENDIF + + !------------------------------------------------------------------------- + ! test h5ltget_dataset_info_f function + !------------------------------------------------------------------------- + + CALL h5ltget_dataset_info_f(file_id,dsetname4,dimsr,type_class,type_size,errcode ) + + ! + ! compare dimensions + ! + DO i = 1, rank + IF ( dimsr(i) .NE. dims(i) ) THEN + PRINT *, 'dimensions differ ' + STOP + ENDIF + END DO + + IF ( type_class .NE. 1 ) THEN ! H5T_FLOAT + PRINT *, 'wrong type class ' + STOP + ENDIF + + CALL passed() + + ! + ! Close the file. + ! + CALL h5fclose_f(file_id, errcode) + ! + ! Close FORTRAN predefined datatypes. + ! + CALL h5close_f(errcode) + + ! + ! end function. + ! + END SUBROUTINE test_datasets - has = h5ltfind_dataset_f(file_id,dsetname4) - IF ( has .NE. 1 ) THEN - PRINT *, 'h5ltfind_dataset_f return error' - STOP - ENDIF - !------------------------------------------------------------------------- - ! test h5ltget_dataset_info_f function + ! test_attributes !------------------------------------------------------------------------- - CALL h5ltget_dataset_info_f(file_id,dsetname4,dimsr,type_class,type_size,errcode ) - - ! - ! compare dimensions - ! - DO i = 1, rank - IF ( dimsr(i) .NE. dims(i) ) THEN - PRINT *, 'dimensions differ ' - STOP - ENDIF - END DO + SUBROUTINE test_attributes() - IF ( type_class .NE. 1 ) THEN ! H5T_FLOAT - PRINT *, 'wrong type class ' - STOP - ENDIF + IMPLICIT NONE - CALL passed() - - ! - ! Close the file. - ! - CALL h5fclose_f(file_id, errcode) - ! - ! Close FORTRAN predefined datatypes. - ! - CALL h5close_f(errcode) - - ! - ! end function. - ! -END SUBROUTINE test_datasets - - -!------------------------------------------------------------------------- -! test_attributes -!------------------------------------------------------------------------- - -SUBROUTINE test_attributes() - - USE, INTRINSIC :: ISO_C_BINDING - USE H5LT ! module of H5LT - USE HDF5 ! module of HDF5 library - USE TSTLITE ! module for testing lite support routines - - IMPLICIT NONE - - CHARACTER(len=9), PARAMETER :: filename = "dsetf5.h5"! File name + CHARACTER(len=9), PARAMETER :: filename = "dsetf5.h5"! File name !!$ CHARACTER(len=9), PARAMETER :: filename1 ="tattr.h5" ! C written attribute file - INTEGER(HID_T) :: file_id ! File identifier - ! INTEGER(HID_T) :: file_id1 - INTEGER, PARAMETER :: DIM1 = 10 ! Dimension of array - CHARACTER(LEN=5), PARAMETER :: attrname2 = "attr2" ! Attribute name - CHARACTER(LEN=5), PARAMETER :: attrname3 = "attr3" ! Attribute name - CHARACTER(LEN=5), PARAMETER :: attrname4 = "attr4" ! Attribute name - CHARACTER(LEN=5), PARAMETER :: attrname5 = "attr5" ! Attribute name - CHARACTER(LEN=8), PARAMETER :: buf1 = "mystring" ! Data buffer + INTEGER(HID_T) :: file_id ! File identifier + ! INTEGER(HID_T) :: file_id1 + INTEGER, PARAMETER :: DIM1 = 10 ! Dimension of array + CHARACTER(LEN=5), PARAMETER :: attrname2 = "attr2" ! Attribute name + CHARACTER(LEN=5), PARAMETER :: attrname3 = "attr3" ! Attribute name + CHARACTER(LEN=5), PARAMETER :: attrname4 = "attr4" ! Attribute name + CHARACTER(LEN=5), PARAMETER :: attrname5 = "attr5" ! Attribute name + CHARACTER(LEN=8), PARAMETER :: buf1 = "mystring" ! Data buffer !!$ CHARACTER(LEN=16), PARAMETER :: buf_c = "string attribute" - CHARACTER(LEN=8) :: bufr1 ! Data buffer - CHARACTER(LEN=10) :: bufr1_lg ! Data buffer - ! CHARACTER(LEN=16) :: bufr_c ! Data buffer - ! CHARACTER(LEN=18) :: bufr_c_lg ! Data buffer - INTEGER, DIMENSION(DIM1) :: buf2 ! Data buffer - INTEGER, DIMENSION(DIM1) :: bufr2 ! Data buffer - REAL, DIMENSION(DIM1), target :: buf3 ! Data buffer - REAL, DIMENSION(DIM1), target :: bufr3 ! Data buffer - DOUBLE PRECISION, DIMENSION(DIM1), TARGET :: buf4 ! Data buffer - DOUBLE PRECISION, DIMENSION(DIM1), TARGET :: bufr4 ! Data buffer - INTEGER :: errcode ! Error flag - INTEGER :: i, n ! general purpose integer - INTEGER(SIZE_T) size ! size of attribute array - INTEGER :: rankr ! rank - INTEGER(HSIZE_T), DIMENSION(1) :: dimsr ! attribute dimensions - INTEGER :: type_class - INTEGER(SIZE_T) :: type_size - INTEGER(HSIZE_T), DIMENSION(1) :: dims = (/DIM1/) ! Dataset dimensions - INTEGER :: rank = 1 ! Dataset rank - CHARACTER(LEN=5), PARAMETER :: dsetname1 = "dset1" ! Dataset name - INTEGER, DIMENSION(DIM1) :: buf ! Data buffer - INTEGER(SIZE_T) :: SizeOf_buf_type - TYPE(C_PTR) :: f_ptr - - ! - ! Initialize FORTRAN predefined datatypes. - ! - CALL h5open_f(errcode) - ! - ! Create a new file using default properties. - ! - CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, errcode) - ! - ! make a dataset. - ! - CALL h5ltmake_dataset_int_f(file_id, dsetname1, rank, dims, buf, errcode) - - ! - ! Initialize the data array. - ! - size = DIM1 - n = 1 - DO i = 1, DIM1 - buf2(i) = n - buf3(i) = n - buf4(i) = n - n = n + 1 - END DO - - - !------------------------------------------------------------------------- - ! int - !------------------------------------------------------------------------- - - CALL test_begin(' Set/Get attributes int ') - - - ! - ! write attribute. - ! - CALL h5ltset_attribute_int_f(file_id,dsetname1,attrname2,buf2,size,errcode) - - ! - ! read attribute. - ! - CALL h5ltget_attribute_int_f(file_id,dsetname1,attrname2,bufr2,errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, DIM1 - IF ( buf2(i) .NE. bufr2(i) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, bufr2(i), ' and ', buf2(i) - STOP - ENDIF - END DO - - CALL passed() - - !------------------------------------------------------------------------- - ! float - !------------------------------------------------------------------------- - - CALL test_begin(' Set/Get attributes float ') - - - ! - ! write attribute. - ! + CHARACTER(LEN=8) :: bufr1 ! Data buffer + CHARACTER(LEN=10) :: bufr1_lg ! Data buffer + ! CHARACTER(LEN=16) :: bufr_c ! Data buffer + ! CHARACTER(LEN=18) :: bufr_c_lg ! Data buffer + INTEGER, DIMENSION(DIM1) :: buf2 ! Data buffer + INTEGER, DIMENSION(DIM1) :: bufr2 ! Data buffer + REAL, DIMENSION(DIM1), target :: buf3 ! Data buffer + REAL, DIMENSION(DIM1), target :: bufr3 ! Data buffer + DOUBLE PRECISION, DIMENSION(DIM1), TARGET :: buf4 ! Data buffer + DOUBLE PRECISION, DIMENSION(DIM1), TARGET :: bufr4 ! Data buffer + INTEGER :: errcode ! Error flag + INTEGER :: i, n ! general purpose integer + INTEGER(SIZE_T) size ! size of attribute array + INTEGER :: rankr ! rank + INTEGER(HSIZE_T), DIMENSION(1) :: dimsr ! attribute dimensions + INTEGER :: type_class + INTEGER(SIZE_T) :: type_size + INTEGER(HSIZE_T), DIMENSION(1) :: dims = (/DIM1/) ! Dataset dimensions + INTEGER :: rank = 1 ! Dataset rank + CHARACTER(LEN=5), PARAMETER :: dsetname1 = "dset1" ! Dataset name + INTEGER, DIMENSION(DIM1) :: buf ! Data buffer + INTEGER(SIZE_T) :: SizeOf_buf_type + TYPE(C_PTR) :: f_ptr + + ! + ! Initialize FORTRAN predefined datatypes. + ! + CALL h5open_f(errcode) + ! + ! Create a new file using default properties. + ! + CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, errcode) + ! + ! make a dataset. + ! + CALL h5ltmake_dataset_int_f(file_id, dsetname1, rank, dims, buf, errcode) + + ! + ! Initialize the data array. + ! + size = DIM1 + n = 1 + DO i = 1, DIM1 + buf2(i) = n + buf3(i) = n + buf4(i) = n + n = n + 1 + END DO + + + !------------------------------------------------------------------------- + ! int + !------------------------------------------------------------------------- + + CALL test_begin(' Set/Get attributes int ') + + + ! + ! write attribute. + ! + CALL h5ltset_attribute_int_f(file_id,dsetname1,attrname2,buf2,size,errcode) + + ! + ! read attribute. + ! + CALL h5ltget_attribute_int_f(file_id,dsetname1,attrname2,bufr2,errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, DIM1 + IF ( buf2(i) .NE. bufr2(i) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, bufr2(i), ' and ', buf2(i) + STOP + ENDIF + END DO + + CALL passed() + + !------------------------------------------------------------------------- + ! float + !------------------------------------------------------------------------- + + CALL test_begin(' Set/Get attributes float ') + + + ! + ! write attribute. + ! #ifdef H5_FORTRAN_HAVE_STORAGE_SIZE - SizeOf_buf_type = STORAGE_SIZE(buf3(1), c_size_t)/STORAGE_SIZE(c_char_'a',c_size_t) + SizeOf_buf_type = STORAGE_SIZE(buf3(1), c_size_t)/STORAGE_SIZE(c_char_'a',c_size_t) #else - SizeOf_buf_type = SIZEOF(buf3(1)) + SizeOf_buf_type = SIZEOF(buf3(1)) #endif - f_ptr = C_LOC(buf3(1)) - CALL h5ltset_attribute_f(file_id,dsetname1,attrname3,f_ptr,"REAL", SizeOf_buf_type, size,errcode) - !CALL h5ltset_attribute_float_f(file_id,dsetname1,attrname3,buf3,size,errcode) - ! - ! read attribute. - ! + f_ptr = C_LOC(buf3(1)) + CALL h5ltset_attribute_f(file_id,dsetname1,attrname3,f_ptr,"REAL", SizeOf_buf_type, size,errcode) + !CALL h5ltset_attribute_float_f(file_id,dsetname1,attrname3,buf3,size,errcode) + ! + ! read attribute. + ! #ifdef H5_FORTRAN_HAVE_STORAGE_SIZE - SizeOf_buf_type = STORAGE_SIZE(bufr3(1), c_size_t)/STORAGE_SIZE(c_char_'a',c_size_t) + SizeOf_buf_type = STORAGE_SIZE(bufr3(1), c_size_t)/STORAGE_SIZE(c_char_'a',c_size_t) #else - SizeOf_buf_type = SIZEOF(bufr3(1)) + SizeOf_buf_type = SIZEOF(bufr3(1)) #endif - f_ptr = C_LOC(bufr3(1)) - CALL h5ltget_attribute_f(file_id,dsetname1,attrname3,f_ptr,"REAL",SizeOf_buf_type,errcode) - !CALL h5ltget_attribute_float_f(file_id,dsetname1,attrname3,bufr3,errcode) + f_ptr = C_LOC(bufr3(1)) + CALL h5ltget_attribute_f(file_id,dsetname1,attrname3,f_ptr,"REAL",SizeOf_buf_type,errcode) + !CALL h5ltget_attribute_float_f(file_id,dsetname1,attrname3,bufr3,errcode) - ! - ! compare read and write buffers. - ! - DO i = 1, DIM1 - IF ( buf3(i) .NE. bufr3(i) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, bufr3(i), ' and ', buf3(i) - STOP - ENDIF - END DO + ! + ! compare read and write buffers. + ! + DO i = 1, DIM1 + IF ( buf3(i) .NE. bufr3(i) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, bufr3(i), ' and ', buf3(i) + STOP + ENDIF + END DO - CALL passed() + CALL passed() - !------------------------------------------------------------------------- - ! double - !------------------------------------------------------------------------- + !------------------------------------------------------------------------- + ! double + !------------------------------------------------------------------------- #ifdef H5_FORTRAN_HAVE_STORAGE_SIZE - SizeOf_buf_type = STORAGE_SIZE(buf4(1), c_size_t)/STORAGE_SIZE(c_char_'a',c_size_t) + SizeOf_buf_type = STORAGE_SIZE(buf4(1), c_size_t)/STORAGE_SIZE(c_char_'a',c_size_t) #else - SizeOf_buf_type = SIZEOF(buf4(1)) + SizeOf_buf_type = SIZEOF(buf4(1)) #endif - IF(SizeOf_buf_type.LT.16)THEN ! MSB can't handle 16 byte reals + IF(SizeOf_buf_type.LT.16)THEN ! MSB can't handle 16 byte reals - CALL test_begin(' Set/Get attributes double ') + CALL test_begin(' Set/Get attributes double ') - ! - ! write attribute. - ! - f_ptr = C_LOC(buf4(1)) - CALL h5ltset_attribute_f(file_id,dsetname1,attrname4,f_ptr,"real", SizeOf_buf_type, size, errcode) + ! + ! write attribute. + ! + f_ptr = C_LOC(buf4(1)) + CALL h5ltset_attribute_f(file_id,dsetname1,attrname4,f_ptr,"real", SizeOf_buf_type, size, errcode) - ! CALL h5ltset_attribute_double_f(file_id,dsetname1,attrname4,buf4, size, errcode) + ! CALL h5ltset_attribute_double_f(file_id,dsetname1,attrname4,buf4, size, errcode) - ! - ! read attribute. - ! + ! + ! read attribute. + ! #ifdef H5_FORTRAN_HAVE_STORAGE_SIZE - SizeOf_buf_type = STORAGE_SIZE(bufr4(1), c_size_t)/STORAGE_SIZE(c_char_'a',c_size_t) + SizeOf_buf_type = STORAGE_SIZE(bufr4(1), c_size_t)/STORAGE_SIZE(c_char_'a',c_size_t) #else - SizeOf_buf_type = SIZEOF(bufr4(1)) + SizeOf_buf_type = SIZEOF(bufr4(1)) #endif - f_ptr = C_LOC(bufr4(1)) - CALL h5ltget_attribute_f(file_id,dsetname1,attrname4,f_ptr,"REAL",SizeOf_buf_type,errcode) - - ! - ! compare read and write buffers. - ! - DO i = 1, DIM1 - IF ( buf4(i) .NE. bufr4(i) ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, bufr4(i), ' and ', buf4(i) - STOP - ENDIF - END DO - - CALL passed() - - ENDIF - - !------------------------------------------------------------------------- - ! string - !------------------------------------------------------------------------- - - CALL test_begin(' Set/Get attributes string ') - - ! - ! write attribute. - ! - CALL h5ltset_attribute_string_f(file_id,dsetname1,attrname5,buf1,errcode) - - ! - ! read attribute into a fortran character buf that is the same size as buf1. - ! - CALL h5ltget_attribute_string_f(file_id,dsetname1,attrname5,bufr1,errcode) - - ! - ! compare read and write buffers. - ! - IF ( buf1 .NE. bufr1 ) THEN - PRINT *, 'read buffer differs from write buffer' - PRINT *, buf1, ' and ', bufr1 - STOP - ENDIF - - ! - ! read attribute into a fortran character buf that is larger then buf1. - ! - CALL h5ltget_attribute_string_f(file_id,dsetname1,attrname5,bufr1_lg,errcode) - - ! - ! compare read and write buffers, make sure C NULL character was removed. - ! - IF ( buf1(1:8) .NE. bufr1_lg(1:8) .AND. bufr1_lg(9:10) .NE. ' ' ) THEN - PRINT *, 'larger read buffer differs from write buffer' - PRINT *, buf1, ' and ', bufr1_lg - STOP - ENDIF - - ! - ! ** Test reading a string that was created with a C program ** - ! + f_ptr = C_LOC(bufr4(1)) + CALL h5ltget_attribute_f(file_id,dsetname1,attrname4,f_ptr,"REAL",SizeOf_buf_type,errcode) + + ! + ! compare read and write buffers. + ! + DO i = 1, DIM1 + IF ( buf4(i) .NE. bufr4(i) ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, bufr4(i), ' and ', buf4(i) + STOP + ENDIF + END DO + + CALL passed() + + ENDIF + + !------------------------------------------------------------------------- + ! string + !------------------------------------------------------------------------- + + CALL test_begin(' Set/Get attributes string ') + + ! + ! write attribute. + ! + CALL h5ltset_attribute_string_f(file_id,dsetname1,attrname5,buf1,errcode) + + ! + ! read attribute into a fortran character buf that is the same size as buf1. + ! + CALL h5ltget_attribute_string_f(file_id,dsetname1,attrname5,bufr1,errcode) + + ! + ! compare read and write buffers. + ! + IF ( buf1 .NE. bufr1 ) THEN + PRINT *, 'read buffer differs from write buffer' + PRINT *, buf1, ' and ', bufr1 + STOP + ENDIF + + ! + ! read attribute into a fortran character buf that is larger then buf1. + ! + CALL h5ltget_attribute_string_f(file_id,dsetname1,attrname5,bufr1_lg,errcode) + + ! + ! compare read and write buffers, make sure C NULL character was removed. + ! + IF ( buf1(1:8) .NE. bufr1_lg(1:8) .AND. bufr1_lg(9:10) .NE. ' ' ) THEN + PRINT *, 'larger read buffer differs from write buffer' + PRINT *, buf1, ' and ', bufr1_lg + STOP + ENDIF + + ! + ! ** Test reading a string that was created with a C program ** + ! !!$ CALL h5fopen_f(filename1, H5F_ACC_RDONLY_F, file_id1, errcode) !!$ @@ -1942,59 +1922,58 @@ SUBROUTINE test_attributes() !!$ CALL h5fclose_f(file_id1, errcode) - CALL passed() + CALL passed() - !------------------------------------------------------------------------- - ! get attribute rank - !------------------------------------------------------------------------- + !------------------------------------------------------------------------- + ! get attribute rank + !------------------------------------------------------------------------- - CALL test_begin(' Get attribute rank/info ') + CALL test_begin(' Get attribute rank/info ') - CALL h5ltget_attribute_ndims_f(file_id,dsetname1,attrname2,rankr,errcode) + CALL h5ltget_attribute_ndims_f(file_id,dsetname1,attrname2,rankr,errcode) - IF ( rankr .NE. 1 ) THEN - PRINT *, 'h5ltget_attribute_ndims_f return error' - STOP - ENDIF + IF ( rankr .NE. 1 ) THEN + PRINT *, 'h5ltget_attribute_ndims_f return error' + STOP + ENDIF - CALL h5ltget_attribute_info_f(file_id,dsetname1,attrname2,dimsr,type_class,type_size,errcode) + CALL h5ltget_attribute_info_f(file_id,dsetname1,attrname2,dimsr,type_class,type_size,errcode) - ! - ! compare dimensions - ! - DO i = 1, rank - IF ( dimsr(i) .NE. dims(i) ) THEN - PRINT *, 'dimensions differ ' - STOP - ENDIF - END DO + ! + ! compare dimensions + ! + DO i = 1, rank + IF ( dimsr(i) .NE. dims(i) ) THEN + PRINT *, 'dimensions differ ' + STOP + ENDIF + END DO - ! - ! Close the file. - ! - CALL h5fclose_f(file_id, errcode) - ! - ! Close FORTRAN predefined datatypes. - ! - CALL h5close_f(errcode) + ! + ! Close the file. + ! + CALL h5fclose_f(file_id, errcode) + ! + ! Close FORTRAN predefined datatypes. + ! + CALL h5close_f(errcode) - CALL passed() - ! - ! end function. - ! -END SUBROUTINE test_attributes + CALL passed() + ! + ! end function. + ! + END SUBROUTINE test_attributes END MODULE TSTLITE_TESTS PROGRAM lite_test - + USE TSTLITE_TESTS ! module for testing lite routines - IMPLICIT NONE - + CALL test_dataset1D() CALL test_dataset2D() CALL test_dataset3D() -- cgit v0.12 From 1f811eccebeb991faafd9ce21f5960b70cd555eb Mon Sep 17 00:00:00 2001 From: Quincey Koziol Date: Thu, 30 Jun 2016 15:23:42 -0500 Subject: [svn-r30126] Description: Correct build error with non-debug parallel builds Tested on: MacOSX/64 10.11.5 (amazon) w/serial & parallel (h5committest forthcoming) --- src/H5AC.c | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/H5AC.c b/src/H5AC.c index 0c6aac1..77a58fc 100644 --- a/src/H5AC.c +++ b/src/H5AC.c @@ -183,8 +183,10 @@ done: herr_t H5AC__init_package(void) { -#ifdef H5_DEBUG_BUILD +#if defined H5_DEBUG_BUILD | defined H5_HAVE_PARALLEL H5P_genplist_t *xfer_plist; /* Dataset transfer property list object */ +#endif /* defined H5_DEBUG_BUILD | defined H5_HAVE_PARALLEL */ +#ifdef H5_DEBUG_BUILD H5FD_dxpl_type_t dxpl_type; /* Property indicating the type of the internal dxpl */ #endif /* H5_DEBUG_BUILD */ #ifdef H5_HAVE_PARALLEL -- cgit v0.12 From 35e6928220ad9381b480f8e21e54027a9509fa36 Mon Sep 17 00:00:00 2001 From: Quincey Koziol Date: Thu, 30 Jun 2016 15:59:15 -0500 Subject: [svn-r30127] Description: Use internal rounding routine, if the StdC ones aren't available (like on Windows). Tested on: MacOSX/64 10.11.5 (amazon) w/serial & parallel (h5committest forthcoming) --- configure.ac | 1 + src/H5Zscaleoffset.c | 52 ++++++++++++++++++++++++++++++++++++++++++++++++++++ 2 files changed, 53 insertions(+) diff --git a/configure.ac b/configure.ac index b6bb44c..74342eb 100644 --- a/configure.ac +++ b/configure.ac @@ -1848,6 +1848,7 @@ AC_CHECK_FUNCS([lstat rand_r random setsysinfo]) AC_CHECK_FUNCS([signal longjmp setjmp siglongjmp sigsetjmp sigprocmask]) AC_CHECK_FUNCS([snprintf srandom strdup symlink system]) AC_CHECK_FUNCS([tmpfile asprintf vasprintf vsnprintf waitpid]) +AC_CHECK_FUNCS([roundf lroundf llroundf round lround llround]) ## ---------------------------------------------------------------------- ## Check compiler characteristics diff --git a/src/H5Zscaleoffset.c b/src/H5Zscaleoffset.c index 1cca9b1..91a6c00 100644 --- a/src/H5Zscaleoffset.c +++ b/src/H5Zscaleoffset.c @@ -667,6 +667,58 @@ H5Z_class2_t H5Z_SCALEOFFSET[1] = {{ H5Z_scaleoffset_modify_4(i, type, pow_fun, buf, d_nelmts, min, D_val) \ } +/* Include our own rounding routine and alias it to the stdc macros, if they + * aren't available. + */ +#if !(defined(H5_HAVE_LLROUND) && defined(H5_HAVE_LLROUNDF) && defined(H5_HAVE_LROUND) && defined(H5_HAVE_LROUNDF) && defined(H5_HAVE_ROUND) && defined(H5_HAVE_ROUNDF)) +/* Round a floating-point value to the nearest integer value 4/19/05 */ +/* rounding to the bigger absolute value if val is in the middle, + 0.5 -> 1, -0.5 ->-1 +5/9/05, KY */ +static double +H5Z__scaleoffset_rnd(double val) +{ + double u_val, l_val; + + u_val = HDceil(val); + l_val = HDfloor(val); + + if(val > 0) { + if((u_val - val) <= (val - l_val)) + return u_val; + else + return l_val; + } /* end if */ + else { + if((val - l_val) <= (u_val - val)) + return l_val; + else + return u_val; + } +} /* H5Z__scaleoffset_rnd() */ + +/* Alias rounding macros to routine above, if not defined */ +#if !defined(H5_HAVE_LLROUND) +#define llround(x) H5Z__scaleoffset_rnd(x) +#endif /* !defined(H5_HAVE_LLROUND) */ +#if !defined(H5_HAVE_LLROUNDF) +#define llroundf(x) H5Z__scaleoffset_rnd(x) +#endif /* !defined(H5_HAVE_LLROUNDF) */ +#if !defined(H5_HAVE_LROUND) +#define lround(x) H5Z__scaleoffset_rnd(x) +#endif /* !defined(H5_HAVE_LROUND) */ +#if !defined(H5_HAVE_LROUNDF) +#define lroundf(x) H5Z__scaleoffset_rnd(x) +#endif /* !defined(H5_HAVE_LROUNDF) */ +#if !defined(H5_HAVE_ROUND) +#define round(x) H5Z__scaleoffset_rnd(x) +#endif /* !defined(H5_HAVE_ROUND) */ +#if !defined(H5_HAVE_ROUNDF) +#define roundf(x) H5Z__scaleoffset_rnd(x) +#endif /* !defined(H5_HAVE_ROUNDF) */ + +#endif /* !(defined(H5_HAVE_LLROUND) && defined(H5_HAVE_LLROUNDF) && defined(H5_HAVE_LROUND) && defined(H5_HAVE_LROUNDF) && defined(H5_HAVE_ROUND) && defined(H5_HAVE_ROUNDF)) */ + /*------------------------------------------------------------------------- * Function: H5Z_can_apply_scaleoffset -- cgit v0.12 From bfae878d8f2f65bc5f22f0d4bb314f326278ba7b Mon Sep 17 00:00:00 2001 From: Neil Fortner Date: Fri, 1 Jul 2016 10:31:44 -0500 Subject: [svn-r30131] Fix bug reported by Cisco Talos TALOS-CAN-0178. Added check for a message that should not be sharable being marked as sharable on disk, returns failure in this case. Needs testing. Tested: ummon --- release_docs/RELEASE.txt | 5 +++++ src/H5Ocache.c | 4 ++++ src/H5Opkg.h | 1 + 3 files changed, 10 insertions(+) diff --git a/release_docs/RELEASE.txt b/release_docs/RELEASE.txt index bf2504b..052ba31 100644 --- a/release_docs/RELEASE.txt +++ b/release_docs/RELEASE.txt @@ -526,6 +526,11 @@ Bug Fixes since HDF5-1.8.0 release Library ------- + - Fixed a memory bug that could occur when a message was improperly marked + as sharable on disk. + + (NAF, 2016/07/01, HDFFV-9950) + - Incorrect usage of list in CMake COMPILE_DEFINITIONS set_property The CMake command, set_property with COMPILE_DEFINITIONS property diff --git a/src/H5Ocache.c b/src/H5Ocache.c index e085242..fbbbe60 100644 --- a/src/H5Ocache.c +++ b/src/H5Ocache.c @@ -1162,6 +1162,10 @@ H5O__chunk_deserialize(H5O_t *oh, haddr_t addr, size_t len, const uint8_t *image HGOTO_ERROR(H5E_OHDR, H5E_CANTLOAD, FAIL, "bad flag combination for message") if((flags & H5O_MSG_FLAG_WAS_UNKNOWN) && !(flags & H5O_MSG_FLAG_MARK_IF_UNKNOWN)) HGOTO_ERROR(H5E_OHDR, H5E_CANTLOAD, FAIL, "bad flag combination for message") + if((flags & H5O_MSG_FLAG_SHAREABLE) + && H5O_msg_class_g[id] + && !(H5O_msg_class_g[id]->share_flags & H5O_SHARE_IS_SHARABLE)) + HGOTO_ERROR(H5E_OHDR, H5E_CANTLOAD, FAIL, "message of unsharable class flagged as sharable") /* Reserved bytes/creation index */ if(oh->version == H5O_VERSION_1) diff --git a/src/H5Opkg.h b/src/H5Opkg.h index 14bb342..e40d28a 100644 --- a/src/H5Opkg.h +++ b/src/H5Opkg.h @@ -201,6 +201,7 @@ \ /* Set the message's "shared info", if it's shareable */ \ if((MSG)->flags & H5O_MSG_FLAG_SHAREABLE) { \ + HDassert(msg_type->share_flags & H5O_SHARE_IS_SHARABLE); \ H5O_UPDATE_SHARED((H5O_shared_t *)(MSG)->native, H5O_SHARE_TYPE_HERE, (F), msg_type->id, (MSG)->crt_idx, (OH)->chunk[0].addr) \ } /* end if */ \ \ -- cgit v0.12 From b72eff165916e1763a866211928507b36d58f3a5 Mon Sep 17 00:00:00 2001 From: Quincey Koziol Date: Fri, 1 Jul 2016 22:16:20 -0500 Subject: [svn-r30134] Description: Add CMake macros and detections for the "round" family of routines. Tested on: Upcoming Windows daily tests --- config/cmake/H5pubconf.h.in | 18 ++++++++++++++++++ config/cmake_ext_mod/ConfigureChecks.cmake | 6 ++++++ 2 files changed, 24 insertions(+) diff --git a/config/cmake/H5pubconf.h.in b/config/cmake/H5pubconf.h.in index 31c5afb..5dad4f3 100644 --- a/config/cmake/H5pubconf.h.in +++ b/config/cmake/H5pubconf.h.in @@ -199,9 +199,21 @@ /* Define to 1 if you have the `z' library (-lz). */ #cmakedefine H5_HAVE_LIBZ @H5_HAVE_LIBZ@ +/* Define to 1 if you have the `llround' function. */ +#cmakedefine H5_HAVE_LLROUND @H5_HAVE_LLROUND@ + +/* Define to 1 if you have the `llroundf' function. */ +#cmakedefine H5_HAVE_LLROUNDF @H5_HAVE_LLROUNDF@ + /* Define to 1 if you have the `longjmp' function. */ #cmakedefine H5_HAVE_LONGJMP @H5_HAVE_LONGJMP@ +/* Define to 1 if you have the `lround' function. */ +#cmakedefine H5_HAVE_LROUND @H5_HAVE_LROUND@ + +/* Define to 1 if you have the `lroundf' function. */ +#cmakedefine H5_HAVE_LROUNDF @H5_HAVE_LROUNDF@ + /* Define to 1 if you have the `lseek64' function. */ #cmakedefine H5_HAVE_LSEEK64 @H5_HAVE_LSEEK64@ @@ -241,6 +253,12 @@ /* Define to 1 if you have the `rand_r' function. */ #cmakedefine H5_HAVE_RAND_R @H5_HAVE_RAND_R@ +/* Define to 1 if you have the `round' function. */ +#cmakedefine H5_HAVE_ROUNDF @H5_HAVE_ROUNDF@ + +/* Define to 1 if you have the `roundf' function. */ +#cmakedefine H5_HAVE_ROUND @H5_HAVE_ROUND@ + /* Define to 1 if you have the `setjmp' function. */ #cmakedefine H5_HAVE_SETJMP @H5_HAVE_SETJMP@ diff --git a/config/cmake_ext_mod/ConfigureChecks.cmake b/config/cmake_ext_mod/ConfigureChecks.cmake index cfda66b..33bb5b3 100644 --- a/config/cmake_ext_mod/ConfigureChecks.cmake +++ b/config/cmake_ext_mod/ConfigureChecks.cmake @@ -499,10 +499,16 @@ CHECK_FUNCTION_EXISTS (frexpl ${HDF_PREFIX}_HAVE_FREXPL) CHECK_FUNCTION_EXISTS (gethostname ${HDF_PREFIX}_HAVE_GETHOSTNAME) CHECK_FUNCTION_EXISTS (getpwuid ${HDF_PREFIX}_HAVE_GETPWUID) CHECK_FUNCTION_EXISTS (getrusage ${HDF_PREFIX}_HAVE_GETRUSAGE) +CHECK_FUNCTION_EXISTS (llround ${HDF_PREFIX}_HAVE_LLROUND) +CHECK_FUNCTION_EXISTS (llroundf ${HDF_PREFIX}_HAVE_LLROUNDF) +CHECK_FUNCTION_EXISTS (lround ${HDF_PREFIX}_HAVE_LROUND) +CHECK_FUNCTION_EXISTS (lroundf ${HDF_PREFIX}_HAVE_LROUNDF) CHECK_FUNCTION_EXISTS (lstat ${HDF_PREFIX}_HAVE_LSTAT) CHECK_FUNCTION_EXISTS (rand_r ${HDF_PREFIX}_HAVE_RAND_R) CHECK_FUNCTION_EXISTS (random ${HDF_PREFIX}_HAVE_RANDOM) +CHECK_FUNCTION_EXISTS (round ${HDF_PREFIX}_HAVE_ROUND) +CHECK_FUNCTION_EXISTS (roundf ${HDF_PREFIX}_HAVE_ROUNDF) CHECK_FUNCTION_EXISTS (setsysinfo ${HDF_PREFIX}_HAVE_SETSYSINFO) CHECK_FUNCTION_EXISTS (signal ${HDF_PREFIX}_HAVE_SIGNAL) -- cgit v0.12 From 4f967d5029cd8e0080f5637efd403842394f87d0 Mon Sep 17 00:00:00 2001 From: Quincey Koziol Date: Sat, 2 Jul 2016 00:14:06 -0500 Subject: [svn-r30139] Description: Bring over missing flush+refresh routines, to address Java failures. Tested on: MacOSX/64 10.11.5 (amazon) w/serial, parallel & production Linux/64 2.6.18 (jam) w/Java --- src/H5G.c | 68 +++++++++++++++++++++++++++++++++++++++++++++++++++++ src/H5Gpublic.h | 2 ++ src/H5Oflush.c | 33 ++++++++++++++++++++++++++ src/H5Opublic.h | 1 + src/H5T.c | 72 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++ src/H5Tpublic.h | 2 ++ 6 files changed, 178 insertions(+) diff --git a/src/H5G.c b/src/H5G.c index 4dc282d..5d920a4 100644 --- a/src/H5G.c +++ b/src/H5G.c @@ -735,3 +735,71 @@ done: FUNC_LEAVE_API(ret_value) } /* end H5Gclose() */ + +/*------------------------------------------------------------------------- + * Function: H5Gflush + * + * Purpose: Flushes all buffers associated with a group to disk. + * + * Return: Non-negative on success, negative on failure + * + * Programmer: Mike McGreevy + * May 19, 2010 + * + *------------------------------------------------------------------------- + */ +herr_t +H5Gflush(hid_t group_id) +{ + H5G_t *grp; /* Dataset for this operation */ + herr_t ret_value = SUCCEED; /* return value */ + + FUNC_ENTER_API(FAIL) + H5TRACE1("e", "i", group_id); + + /* Check args */ + if(NULL == (grp = (H5G_t *)H5I_object_verify(group_id, H5I_GROUP))) + HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "not a group") + + /* Flush object's metadata to file */ + if(H5O_flush_common(&grp->oloc, group_id, H5AC_ind_read_dxpl_id) < 0) + HGOTO_ERROR(H5E_SYM, H5E_CANTFLUSH, FAIL, "unable to flush group and object flush callback") + +done: + FUNC_LEAVE_API(ret_value) +} /* H5Gflush */ + + +/*------------------------------------------------------------------------- + * Function: H5Grefresh + * + * Purpose: Refreshes all buffers associated with a dataset. + * + * Return: Non-negative on success, negative on failure + * + * Programmer: Mike McGreevy + * July 21, 2010 + * + *------------------------------------------------------------------------- + */ +herr_t +H5Grefresh(hid_t group_id) +{ + H5G_t * grp = NULL; + herr_t ret_value = SUCCEED; /* return value */ + + FUNC_ENTER_API(FAIL) + H5TRACE1("e", "i", group_id); + + /* Check args */ + if(NULL == (grp = (H5G_t *)H5I_object_verify(group_id, H5I_GROUP))) + HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "not a group") + + /* Call private function to refresh group object */ + if ((H5O_refresh_metadata(group_id, grp->oloc, H5AC_ind_read_dxpl_id)) < 0) + HGOTO_ERROR(H5E_SYM, H5E_CANTLOAD, FAIL, "unable to refresh group") + +done: + FUNC_LEAVE_API(ret_value) +} /* H5Grefresh */ + diff --git a/src/H5Gpublic.h b/src/H5Gpublic.h index 5b8b054..9d8ade5 100644 --- a/src/H5Gpublic.h +++ b/src/H5Gpublic.h @@ -84,6 +84,8 @@ H5_DLL herr_t H5Gget_info_by_idx(hid_t loc_id, const char *group_name, H5_index_t idx_type, H5_iter_order_t order, hsize_t n, H5G_info_t *ginfo, hid_t lapl_id); H5_DLL herr_t H5Gclose(hid_t group_id); +H5_DLL herr_t H5Gflush(hid_t group_id); +H5_DLL herr_t H5Grefresh(hid_t group_id); /* Symbols defined for compatibility with previous versions of the HDF5 API. * diff --git a/src/H5Oflush.c b/src/H5Oflush.c index 6484dfd..4fc9c8e 100644 --- a/src/H5Oflush.c +++ b/src/H5Oflush.c @@ -177,6 +177,39 @@ done: FUNC_LEAVE_NOAPI(ret_value) } /* end H5O_oh_tag() */ + +/*------------------------------------------------------------------------- + * Function: H5Orefresh + * + * Purpose: Refreshes all buffers associated with an object. + * + * Return: Non-negative on success, negative on failure + * + * Programmer: Mike McGreevy + * July 28, 2010 + * + *------------------------------------------------------------------------- + */ +herr_t +H5Orefresh(hid_t oid) +{ + H5O_loc_t *oloc; /* object location */ + herr_t ret_value = SUCCEED; /* return value */ + + FUNC_ENTER_API(FAIL) + H5TRACE1("e", "i", oid); + + /* Check args */ + if(NULL == (oloc = H5O_get_loc(oid))) + HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "not an object") + + /* Private function */ + if(H5O_refresh_metadata(oid, *oloc, H5AC_ind_read_dxpl_id) < 0) + HGOTO_ERROR(H5E_OHDR, H5E_CANTLOAD, FAIL, "unable to refresh object") + +done: + FUNC_LEAVE_API(ret_value) +} /* end H5Orefresh() */ /*------------------------------------------------------------------------- diff --git a/src/H5Opublic.h b/src/H5Opublic.h index 1d2ab7b..dec7b5b 100644 --- a/src/H5Opublic.h +++ b/src/H5Opublic.h @@ -183,6 +183,7 @@ H5_DLL herr_t H5Ovisit_by_name(hid_t loc_id, const char *obj_name, void *op_data, hid_t lapl_id); H5_DLL herr_t H5Oclose(hid_t object_id); H5_DLL herr_t H5Oflush(hid_t obj_id); +H5_DLL herr_t H5Orefresh(hid_t oid); H5_DLL herr_t H5Odisable_mdc_flushes(hid_t object_id); H5_DLL herr_t H5Oenable_mdc_flushes(hid_t object_id); H5_DLL herr_t H5Oare_mdc_flushes_disabled(hid_t object_id, hbool_t *are_disabled); diff --git a/src/H5T.c b/src/H5T.c index a8c9903..38cd250 100644 --- a/src/H5T.c +++ b/src/H5T.c @@ -5495,3 +5495,75 @@ H5T_patch_vlen_file(H5T_t *dt, H5F_t *f) FUNC_LEAVE_NOAPI(SUCCEED) } /* end H5T_patch_vlen_file() */ + +/*------------------------------------------------------------------------- + * Function: H5Tflush + * + * Purpose: Flushes all buffers associated with a named datatype to disk. + * + * Return: Non-negative on success, negative on failure + * + * Programmer: Mike McGreevy + * May 19, 2010 + * + *------------------------------------------------------------------------- + */ +herr_t +H5Tflush(hid_t type_id) +{ + H5T_t *dt; /* Datatype for this operation */ + herr_t ret_value = SUCCEED; /* return value */ + + FUNC_ENTER_API(FAIL) + H5TRACE1("e", "i", type_id); + + /* Check args */ + if(NULL == (dt = (H5T_t *)H5I_object_verify(type_id, H5I_DATATYPE))) + HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "not a datatype") + if(!H5T_is_named(dt)) + HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "not a committed datatype") + + /* To flush metadata and invoke flush callback if there is */ + if(H5O_flush_common(&dt->oloc, type_id, H5AC_ind_read_dxpl_id) < 0) + HGOTO_ERROR(H5E_DATATYPE, H5E_CANTFLUSH, FAIL, "unable to flush datatype and object flush callback") + +done: + FUNC_LEAVE_API(ret_value) +} /* H5Tflush */ + + +/*------------------------------------------------------------------------- + * Function: H5Trefresh + * + * Purpose: Refreshes all buffers associated with a named datatype. + * + * Return: Non-negative on success, negative on failure + * + * Programmer: Mike McGreevy + * July 21, 2010 + * + *------------------------------------------------------------------------- + */ +herr_t +H5Trefresh(hid_t type_id) +{ + H5T_t * dt = NULL; + herr_t ret_value = SUCCEED; /* return value */ + + FUNC_ENTER_API(FAIL) + H5TRACE1("e", "i", type_id); + + /* Check args */ + if(NULL == (dt = (H5T_t *)H5I_object_verify(type_id, H5I_DATATYPE))) + HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "not a datatype") + if(!H5T_is_named(dt)) + HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "not a committed datatype") + + /* Call private function to refresh datatype object */ + if ((H5O_refresh_metadata(type_id, dt->oloc, H5AC_ind_read_dxpl_id)) < 0) + HGOTO_ERROR(H5E_DATATYPE, H5E_CANTLOAD, FAIL, "unable to refresh datatype") + +done: + FUNC_LEAVE_API(ret_value) +} /* H5Trefresh */ + diff --git a/src/H5Tpublic.h b/src/H5Tpublic.h index d646ef1..df7ad41 100644 --- a/src/H5Tpublic.h +++ b/src/H5Tpublic.h @@ -511,6 +511,8 @@ H5_DLL hid_t H5Tget_create_plist(hid_t type_id); H5_DLL htri_t H5Tcommitted(hid_t type_id); H5_DLL herr_t H5Tencode(hid_t obj_id, void *buf, size_t *nalloc); H5_DLL hid_t H5Tdecode(const void *buf); +H5_DLL herr_t H5Tflush(hid_t type_id); +H5_DLL herr_t H5Trefresh(hid_t type_id); /* Operations defined on compound datatypes */ H5_DLL herr_t H5Tinsert(hid_t parent_id, const char *name, size_t offset, -- cgit v0.12 From af0829aa171bddb63fa67ee7f7470e661815c24d Mon Sep 17 00:00:00 2001 From: Vailin Choi Date: Sun, 3 Jul 2016 23:06:34 -0500 Subject: [svn-r30143] Fix for HDFFV-9940. Tested on jam, osx1010test, moohan, platypus, emu, kite, kituo, mayll, ostrich, quail. --- src/H5Aint.c | 5 + src/H5Dint.c | 5 + src/H5T.c | 43 +++++++++ src/H5Tprivate.h | 1 + test/links.c | 277 +++++++++++++++++++++++++++++++++++++++++++++++++++++++ 5 files changed, 331 insertions(+) diff --git a/src/H5Aint.c b/src/H5Aint.c index ffb8667..2730b0b 100644 --- a/src/H5Aint.c +++ b/src/H5Aint.c @@ -202,6 +202,11 @@ H5A_create(const H5G_loc_t *loc, const char *name, const H5T_t *type, if(NULL == (attr->shared->dt = H5T_copy(type, H5T_COPY_ALL))) HGOTO_ERROR(H5E_ATTR, H5E_CANTGET, NULL, "can't get shared datatype info") + /* Convert a datatype (if committed) to a transient type if the committed datatype's file + location is different from the file location where the attribute will be created */ + if(H5T_convert_committed_datatype(attr->shared->dt, loc->oloc->file) < 0) + HGOTO_ERROR(H5E_ATTR, H5E_CANTGET, NULL, "can't get shared datatype info") + /* Mark datatype as being on disk now */ if(H5T_set_loc(attr->shared->dt, loc->oloc->file, H5T_LOC_DISK) < 0) HGOTO_ERROR(H5E_DATATYPE, H5E_CANTINIT, NULL, "invalid datatype location") diff --git a/src/H5Dint.c b/src/H5Dint.c index 6f088af..8a00be2 100644 --- a/src/H5Dint.c +++ b/src/H5Dint.c @@ -683,6 +683,11 @@ H5D__init_type(H5F_t *file, const H5D_t *dset, hid_t type_id, const H5T_t *type) if((dset->shared->type = H5T_copy(type, H5T_COPY_ALL)) == NULL) HGOTO_ERROR(H5E_DATASET, H5E_CANTCOPY, FAIL, "can't copy datatype") + /* Convert a datatype (if committed) to a transient type if the committed datatype's file + location is different from the file location where the dataset will be created */ + if(H5T_convert_committed_datatype(dset->shared->type, file) < 0) + HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "can't get shared datatype info") + /* Mark any datatypes as being on disk now */ if(H5T_set_loc(dset->shared->type, file, H5T_LOC_DISK) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "can't set datatype location") diff --git a/src/H5T.c b/src/H5T.c index 38cd250..b2575d5 100644 --- a/src/H5T.c +++ b/src/H5T.c @@ -5003,6 +5003,49 @@ done: FUNC_LEAVE_NOAPI(ret_value) } +/*------------------------------------------------------------------------- + * Function: H5T_convert_committed_datatype + * + * Purpose: To convert the committed datatype "dt" to a transient embedded + * type if the file location associated with the committed datatype is + * different from the parameter "f". + * "f" is the file location where the dataset or attribute will be created. + * + * Notes: See HDFFV-9940 + * + * Return: Success: non-negative + * Failure: negative + * + * Programmer: Vailin Choi; June 2016 + * + *------------------------------------------------------------------------- + */ +herr_t +H5T_convert_committed_datatype(H5T_t *dt, H5F_t *f) +{ + herr_t ret_value = SUCCEED; /* Return value */ + + FUNC_ENTER_NOAPI(FAIL) + + HDassert(dt); + HDassert(f); + + if(H5T_is_named(dt) && (dt->sh_loc.file != f)) { + HDassert(dt->sh_loc.type == H5O_SHARE_TYPE_COMMITTED); + + H5O_msg_reset_share(H5O_DTYPE_ID, dt); + if(H5O_loc_free(&dt->oloc) < 0) + HGOTO_ERROR(H5E_DATATYPE, H5E_CANTRESET, FAIL, "unable to initialize location") + if(H5G_name_free(&dt->path) < 0) + HGOTO_ERROR(H5E_DATATYPE, H5E_CANTOPENOBJ, FAIL, "unable to reset path") + + dt->shared->state = H5T_STATE_TRANSIENT; + } + +done: + FUNC_LEAVE_NOAPI(ret_value) +} /* end H5T_convert_committed_datatype() */ + /*-------------------------------------------------------------------------- NAME diff --git a/src/H5Tprivate.h b/src/H5Tprivate.h index 17826ae..7efcb41 100644 --- a/src/H5Tprivate.h +++ b/src/H5Tprivate.h @@ -120,6 +120,7 @@ H5_DLL struct H5O_loc_t *H5T_oloc(H5T_t *dt); H5_DLL H5G_name_t *H5T_nameof(H5T_t *dt); H5_DLL htri_t H5T_is_immutable(const H5T_t *dt); H5_DLL htri_t H5T_is_named(const H5T_t *dt); +H5_DLL herr_t H5T_convert_committed_datatype(H5T_t *dt, H5F_t *f); H5_DLL htri_t H5T_is_relocatable(const H5T_t *dt); H5_DLL H5T_path_t *H5T_path_find(const H5T_t *src, const H5T_t *dst, const char *name, H5T_conv_t func, hid_t dxpl_id, hbool_t is_api); diff --git a/test/links.c b/test/links.c index 639a2d8..10bec40 100644 --- a/test/links.c +++ b/test/links.c @@ -7303,6 +7303,282 @@ error: /*------------------------------------------------------------------------- + * Function: external_link_with_committed_datatype + * + * Purpose: Test to verify the problem described in HDFFV-9940 is resolved. + * (A) Attach an attribute to an externally linked group in the target file. + * The attribute's datatype is a committed datatype to the root group + * in the main file. + * (B) Create a dataset to an externally group in the target file. + * The dataset's datatype is a committed datatype to the root group + * in the main file. + * + * Return: Success: 0 + * Failure: -1 + * + * Programmer: This is copied and modified from the customer's test program that + * exposed the problem. + * + *------------------------------------------------------------------------- + */ +static int +external_link_with_committed_datatype(hid_t fapl, hbool_t new_format) +{ + hid_t fid1 = -1, fid2 = -1; /* File IDs */ + hid_t gid1 = -1, gid2 = -1; /* Group IDs */ + hid_t tid = -1; /* Datatype ID */ + hid_t sid = -1; /* Dataspace ID */ + hid_t sid2 = -1; /* Dataspace ID */ + hid_t aid = -1; /* Attribute ID */ + hid_t atid = -1; /* Attribute's datatype ID */ + hid_t did = -1; /* Dataset ID */ + hid_t dtid = -1; /* Dataset's datatype ID */ + hid_t dcpl = -1; /* Dataset creation property list */ + int wdata = 99; /* Attribute data written */ + int rdata = 0; /* Attribute data read */ + int wbuf[60]; /* Data buffer for writing */ + int rbuf[60]; /* Data buffer for reading */ + int i; /* Local index variable */ + char filename1[NAME_BUF_SIZE]; /* File name for main file */ + char filename2[NAME_BUF_SIZE]; /* File name for target file */ + hsize_t dims[2] = {5, 12}; /* Dimension sizes */ + hsize_t chunks[2] = {3, 7}; /* Chunk sizes */ + + if(new_format) + TESTING("attach committed datatype to external group's attribute/dataset(w/new group format)") + else + TESTING("attach committed datatype to external group's attribute/dataset") + + /* Set up filenames */ + h5_fixname(FILENAME[0], fapl, filename1, sizeof filename1); + h5_fixname(FILENAME[1], fapl, filename2, sizeof filename2); + + + /* Main file */ + if((fid1 = H5Fcreate(filename1, H5F_ACC_TRUNC, H5P_DEFAULT, fapl)) < 0) + FAIL_STACK_ERROR + + /* Create external link from main file to target file */ + if(H5Lcreate_external(filename2, "target_group", fid1, "link_to_2", H5P_DEFAULT, H5P_DEFAULT) < 0) + FAIL_STACK_ERROR + + + /* Create target file */ + if((fid2 = H5Fcreate(filename2, H5F_ACC_TRUNC, H5P_DEFAULT, fapl)) < 0) + FAIL_STACK_ERROR + /* Create group in target file */ + if((gid2 = H5Gcreate2(fid2, "target_group", H5P_DEFAULT, H5P_DEFAULT, H5P_DEFAULT)) < 0) + FAIL_STACK_ERROR + + /* Close the group */ + if(H5Gclose(gid2) < 0) + FAIL_STACK_ERROR + /* Close the file */ + if(H5Fclose(fid2) < 0) + FAIL_STACK_ERROR + + /* Open the group which is externally linked to target file */ + if((gid1 = H5Gopen(fid1, "link_to_2", H5P_DEFAULT)) < 0) + FAIL_STACK_ERROR + + /* Create a copy of integer datatype */ + if((tid = H5Tcopy(H5T_NATIVE_INT)) < 0) + FAIL_STACK_ERROR + + /* Commit the datatype to the main file root group */ + if(H5Tcommit2(fid1, "myDatatype", tid, H5P_DEFAULT, H5P_DEFAULT, H5P_DEFAULT) < 0) + FAIL_STACK_ERROR + + /* Create dataspace */ + if((sid = H5Screate(H5S_SCALAR)) < 0) + FAIL_STACK_ERROR + + /* Attach an attribute with the committed datatype to the group */ + if((aid = H5Acreate2(gid1, "myAttribute", tid, sid, H5P_DEFAULT, H5P_DEFAULT)) < 0) + FAIL_STACK_ERROR + + /* Write data to the attribute */ + if(H5Awrite(aid, tid, &wdata) < 0) + FAIL_STACK_ERROR + + /* Get the attribute's datatype */ + if((atid = H5Aget_type(aid)) < 0) + FAIL_STACK_ERROR + + /* Verify the datatype is not committed */ + if(H5Tcommitted(atid) == TRUE) + FAIL_STACK_ERROR + + /* Close the attribute */ + if(H5Aclose(aid) < 0) + FAIL_STACK_ERROR + + /* Create a chunked dataset */ + if((sid2 = H5Screate_simple(2, dims, NULL)) < 0) + FAIL_STACK_ERROR + + if((dcpl = H5Pcreate(H5P_DATASET_CREATE)) < 0) + FAIL_STACK_ERROR + if(H5Pset_chunk(dcpl, 2, chunks) < 0) + FAIL_STACK_ERROR + + /* Initialize data buffers */ + for(i = 0; i < 60; i++) { + wbuf[i] = i; + rbuf[i] = 0; + } + + /* Create a dataset with the committed datatype in the group */ + if((did = H5Dcreate2(gid1, "myDataset", tid, sid2, H5P_DEFAULT, dcpl, H5P_DEFAULT)) < 0) + FAIL_STACK_ERROR + + /* Write to the dataset */ + if(H5Dwrite(did, tid, H5S_ALL, H5S_ALL, H5P_DEFAULT, wbuf) < 0) + FAIL_STACK_ERROR + + /* Get the dataset's datatype */ + if((dtid = H5Dget_type(did)) < 0) + FAIL_STACK_ERROR + + /* Verify the datatype is not committed */ + if(H5Tcommitted(dtid) == TRUE) + FAIL_STACK_ERROR + + /* Close the dataset */ + if(H5Dclose(did) < 0) + FAIL_STACK_ERROR + + /* Close the dataset creation property list */ + if(H5Pclose(dcpl) < 0) + FAIL_STACK_ERROR + + /* Close the dataspaces */ + if(H5Sclose(sid) < 0) + FAIL_STACK_ERROR + if(H5Sclose(sid2) < 0) + FAIL_STACK_ERROR + + /* Close the datatypes */ + if(H5Tclose(tid) < 0) + FAIL_STACK_ERROR + if(H5Tclose(atid) < 0) + FAIL_STACK_ERROR + if(H5Tclose(dtid) < 0) + FAIL_STACK_ERROR + + /* Close the group */ + if(H5Gclose(gid1) < 0) + FAIL_STACK_ERROR + + /* Close the file */ + if(H5Fclose(fid1) < 0) + FAIL_STACK_ERROR + + + /* Open the mainfile */ + if((fid1 = H5Fopen(filename1, H5F_ACC_RDWR, fapl)) < 0) + FAIL_STACK_ERROR + + /* Open the committed datatype in the mainfile */ + if((tid = H5Topen(fid1, "myDatatype", H5P_DEFAULT)) < 0) + FAIL_STACK_ERROR + + /* Verify the datatype is committed */ + if(H5Tcommitted(tid) == FALSE) + FAIL_STACK_ERROR + + /* Open the group which is externally linked to target file */ + if((gid1 = H5Gopen(fid1, "link_to_2", H5P_DEFAULT)) < 0) + FAIL_STACK_ERROR + + /* Open the attribute attached to the group */ + if((aid = H5Aopen(gid1, "myAttribute", H5P_DEFAULT)) < 0) + FAIL_STACK_ERROR + + /* Get the attribute's datatype */ + if((atid = H5Aget_type(aid)) < 0) + FAIL_STACK_ERROR + + /* Verify the attribute's datatype is not committed */ + if(H5Tcommitted(atid) == TRUE) + FAIL_STACK_ERROR + + /* Close the attribute */ + if(H5Aclose(aid) < 0) + FAIL_STACK_ERROR + + /* Delete the attribute */ + if(H5Adelete(gid1, "myAttribute") < 0) + FAIL_STACK_ERROR + + /* Open the dataset in the group */ + if((did = H5Dopen2(gid1, "myDataset", H5P_DEFAULT)) < 0) + FAIL_STACK_ERROR + + /* Get the dataset's datatype */ + if((dtid = H5Dget_type(did)) < 0) + FAIL_STACK_ERROR + + /* Verify the dataset's datatype is not committed */ + if(H5Tcommitted(dtid) == TRUE) + FAIL_STACK_ERROR + + /* Read the dataset */ + if(H5Dread(did, H5T_NATIVE_INT, H5S_ALL, H5S_ALL, H5P_DEFAULT, rbuf) < 0) + FAIL_STACK_ERROR + + /* Compare the data read should be the same as wbuf */ + if(HDmemcmp(wbuf, rbuf, sizeof(wbuf)) != 0) + FAIL_STACK_ERROR + + /* Close the dataset */ + if(H5Dclose(did) < 0) + FAIL_STACK_ERROR + + /* Close the group */ + if(H5Gclose(gid1) < 0) + FAIL_STACK_ERROR + + /* Close the datatypes */ + if(H5Tclose(tid) < 0) + FAIL_STACK_ERROR + if(H5Tclose(atid) < 0) + FAIL_STACK_ERROR + if(H5Tclose(dtid) < 0) + FAIL_STACK_ERROR + + /* Close the file */ + if(H5Fclose(fid1) < 0) + FAIL_STACK_ERROR + + PASSED(); + return 0; + +error: + H5E_BEGIN_TRY { + H5Fclose(fid2); + H5Fclose(fid1); + H5Gclose(gid1); + H5Gclose(gid2); + + H5Aclose(aid); + H5Dclose(did); + + H5Sclose(sid); + H5Sclose(sid2); + + H5Tclose(tid); + H5Aclose(atid); + H5Aclose(dtid); + + H5Pclose(dcpl); + } H5E_END_TRY + + return -1; +} /* end external_link_with_committed_datatype() */ + + +/*------------------------------------------------------------------------- * Function: ud_hard_links * * Purpose: Check that the functionality of hard links can be duplicated @@ -14624,6 +14900,7 @@ main(void) nerrors += external_copy_invalid_object(my_fapl, new_format) < 0 ? 1 : 0; nerrors += external_dont_fail_to_source(my_fapl, new_format) < 0 ? 1 : 0; nerrors += external_open_twice(my_fapl, new_format) < 0 ? 1 : 0; + nerrors += external_link_with_committed_datatype(my_fapl, new_format) < 0 ? 1 : 0; } /* end for */ /* These tests assume that external links are a form of UD links, -- cgit v0.12 From 8e9edc8dc1a03d18db17439337e8fcdbc8aefdf5 Mon Sep 17 00:00:00 2001 From: Dana Robinson Date: Tue, 5 Jul 2016 19:58:58 -0500 Subject: [svn-r30147] Removed #ifdef-guarded debug output from core VFD. Tested on: 64-bit Ubuntu Linux w/ gcc 5.3.1 Autotools serial w/ core and core_paged VFDs --- src/H5FDcore.c | 87 ++++++++++------------------------------------------------ 1 file changed, 15 insertions(+), 72 deletions(-) diff --git a/src/H5FDcore.c b/src/H5FDcore.c index 5ce6560..f29e231 100644 --- a/src/H5FDcore.c +++ b/src/H5FDcore.c @@ -203,9 +203,6 @@ H5FD__core_add_dirty_region(H5FD_core_t *file, haddr_t start, haddr_t end) haddr_t a_addr = 0; hbool_t create_new_node = TRUE; herr_t ret_value = SUCCEED; -#ifdef DER - hbool_t was_adjusted = FALSE; -#endif FUNC_ENTER_STATIC @@ -213,34 +210,15 @@ H5FD__core_add_dirty_region(H5FD_core_t *file, haddr_t start, haddr_t end) HDassert(file->dirty_list); HDassert(start <= end); -#ifdef DER -fprintf(stderr, "Add region: (%llu, %llu)\n", start, end); -#endif - /* Adjust the dirty region to the nearest block boundaries */ - if(start % file->bstore_page_size != 0) { + if(start % file->bstore_page_size != 0) start = (start / file->bstore_page_size) * file->bstore_page_size; -#ifdef DER - was_adjusted = TRUE; -#endif - } + if(end % file->bstore_page_size != (file->bstore_page_size - 1)) { end = (((end / file->bstore_page_size) + 1) * file->bstore_page_size) - 1; - if(end > file->eof){ -#ifdef DER -fprintf(stderr, "Adjusted to EOF\n"); -#endif + if(end > file->eof) end = file->eof - 1; - } -#ifdef DER - was_adjusted = TRUE; -#endif - } - -#ifdef DER -if(was_adjusted) - fprintf(stderr, "Adjusted region: (%llu, %llu)\n", start, end); -#endif + } /* end if */ /* Get the regions before and after the intended insertion point */ b_addr = start +1; @@ -249,15 +227,13 @@ if(was_adjusted) a_item = (H5FD_core_region_t *)H5SL_less(file->dirty_list, &a_addr); /* Check to see if we need to extend the upper end of the NEW region */ - if(a_item) { + if(a_item) if(start < a_item->start && end < a_item->end) { - /* Extend the end of the NEW region to match the existing AFTER region */ end = a_item->end; - } - } + } /* end if */ /* Attempt to extend the PREV region */ - if(b_item) { + if(b_item) if(start <= b_item->end + 1) { /* Need to set this for the delete algorithm */ @@ -267,8 +243,7 @@ if(was_adjusted) * just update an existing one instead. */ create_new_node = FALSE; - } - } + } /* end if */ /* Remove any old nodes that are no longer needed */ while(a_item && a_item->start > start) { @@ -286,7 +261,7 @@ if(was_adjusted) /* Set up to check the next node */ if(less) a_item = less; - } + } /* end while */ /* Insert the new node */ if(create_new_node) { @@ -297,17 +272,17 @@ if(was_adjusted) item->end = end; if(H5SL_insert(file->dirty_list, item, &item->start) < 0) HGOTO_ERROR(H5E_SLIST, H5E_CANTINSERT, FAIL, "can't insert new dirty region: (%llu, %llu)\n", (unsigned long long)start, (unsigned long long)end) - } + } /* end if */ else { /* Store the new item endpoint if it's bigger */ item->end = (item->end < end) ? end : item->end; - } - } + } /* end else */ + } /* end if */ else { /* Update the size of the before region */ if(b_item->end < end) b_item->end = end; - } + } /* end else */ done: FUNC_LEAVE_NOAPI(ret_value) @@ -336,20 +311,13 @@ H5FD__core_destroy_dirty_list(H5FD_core_t *file) if(file->dirty_list) { H5FD_core_region_t *region = NULL; -#ifdef DER -{ -size_t count = H5SL_count(file->dirty_list); -if(count != 0) - fprintf(stderr, "LIST NOT EMPTY AT DESTROY\n"); -} -#endif while(NULL != (region = (H5FD_core_region_t *)H5SL_remove_first(file->dirty_list))) region = H5FL_FREE(H5FD_core_region_t, region); if(H5SL_close(file->dirty_list) < 0) HGOTO_ERROR(H5E_SLIST, H5E_CLOSEERROR, FAIL, "can't close core vfd dirty list") file->dirty_list = NULL; - } + } /* end if */ done: FUNC_LEAVE_NOAPI(ret_value) @@ -394,14 +362,8 @@ H5FD__core_write_to_bstore(H5FD_core_t *file, haddr_t addr, size_t size) else bytes_in = (h5_posix_io_t)size; -#ifdef DER -fprintf(stderr, "\nNEW\n"); -#endif do { bytes_wrote = HDwrite(file->fd, ptr, bytes_in); -#ifdef DER -fprintf(stderr, "bytes wrote: %lu\n", bytes_wrote); -#endif } while(-1 == bytes_wrote && EINTR == errno); if(-1 == bytes_wrote) { /* error */ @@ -844,9 +806,6 @@ H5FD__core_open(const char *name, unsigned flags, hid_t fapl_id, haddr_t maxaddr if(use_write_tracking) { if(NULL == (file->dirty_list = H5SL_create(H5SL_TYPE_HADDR, NULL))) HGOTO_ERROR(H5E_SLIST, H5E_CANTCREATE, NULL, "can't create core vfd dirty region list"); -#ifdef DER -fprintf(stderr, "\n"); -#endif } /* end if */ } /* end if */ @@ -1350,9 +1309,6 @@ H5FD__core_flush(H5FD_t *_file, hid_t H5_ATTR_UNUSED dxpl_id, hbool_t H5_ATTR_UN H5FD_core_region_t *item = NULL; size_t size; -#ifdef DER - fprintf(stderr, "FLUSHING. DIRTY LIST:\n"); -#endif while(NULL != (item = (H5FD_core_region_t *)H5SL_remove_first(file->dirty_list))) { /* The file may have been truncated, so check for that @@ -1362,11 +1318,8 @@ H5FD__core_flush(H5FD_t *_file, hid_t H5_ATTR_UNUSED dxpl_id, hbool_t H5_ATTR_UN if(item->end >= file->eof) item->end = file->eof - 1; - size = (size_t)((item->end - item->start) + 1); -#ifdef DER -fprintf(stderr, "(%llu, %llu : %lu)\n", item->start, item->end, size); -#endif + if(H5FD__core_write_to_bstore(file, item->start, size) != SUCCEED) HGOTO_ERROR(H5E_VFL, H5E_WRITEERROR, FAIL, "unable to write to backing store") } /* end if */ @@ -1374,13 +1327,6 @@ fprintf(stderr, "(%llu, %llu : %lu)\n", item->start, item->end, size); item = H5FL_FREE(H5FD_core_region_t, item); } /* end while */ -#ifdef DER -fprintf(stderr, "EOF: %llu\n", file->eof); -fprintf(stderr, "EOA: %llu\n", file->eoa); -if(file->eoa > file->eof) - fprintf(stderr, "*** EOA BADNESS ***\n"); -fprintf(stderr, "\n"); -#endif } /* end if */ /* Otherwise, write the entire file out at once */ else { @@ -1504,9 +1450,6 @@ H5FD__core_truncate(H5FD_t *_file, hid_t H5_ATTR_UNUSED dxpl_id, hbool_t closing HSYS_GOTO_ERROR(H5E_IO, H5E_SEEKERROR, FAIL, "unable to extend file properly") #endif /* H5_HAVE_WIN32_API */ -#ifdef DER -fprintf(stderr, "OLD: Truncated to: %llu\n", file->eoa); -#endif } /* end if */ /* Update the eof value */ -- cgit v0.12 From 130f8135ca40858c4bda81dcd183b0dff4fe63e6 Mon Sep 17 00:00:00 2001 From: Dana Robinson Date: Tue, 5 Jul 2016 20:40:31 -0500 Subject: [svn-r30148] Expanded core VFD test in vfd.c. Minor tidying to sec2 VFD test also. Tested on: 64-bit Ubuntu Linux w/ gcc 5.3.1 Autotools serial --- test/vfd.c | 484 +++++++++++++++++++++++++++++++++++++------------------------ 1 file changed, 295 insertions(+), 189 deletions(-) diff --git a/test/vfd.c b/test/vfd.c index 708474c..596d39a 100644 --- a/test/vfd.c +++ b/test/vfd.c @@ -27,8 +27,13 @@ #define FAMILY_SIZE (1*KB) #define FAMILY_SIZE2 (5*KB) #define MULTI_SIZE 128 + #define CORE_INCREMENT (4*KB) -#define CORE_PAGE_SIZE (1024 * 1024) +#define CORE_PAGE_SIZE (1024*KB) +#define CORE_DSET_NAME "core dset" +#define CORE_DSET_DIM1 1024 +#define CORE_DSET_DIM2 32 + #define DSET1_NAME "dset1" #define DSET1_DIM1 1024 #define DSET1_DIM2 32 @@ -80,68 +85,73 @@ const char *FILENAME[] = { static herr_t test_sec2(void) { - hid_t file = -1; - hid_t fapl = -1; - hid_t access_fapl = -1; - char filename[1024]; - int *fhandle = NULL; - hsize_t file_size = 0; + hid_t fid = -1; /* file ID */ + hid_t fapl_id = -1; /* file access property list ID */ + hid_t fapl_id_out = -1; /* from H5Fget_access_plist */ + char filename[1024]; /* filename */ + void *os_file_handle = NULL; /* OS file handle */ + hsize_t file_size; /* file size */ TESTING("SEC2 file driver"); h5_reset(); /* Set property list and file name for SEC2 driver. */ - fapl = h5_fileaccess(); - if(H5Pset_fapl_sec2(fapl) < 0) - TEST_ERROR; - h5_fixname(FILENAME[0], fapl, filename, sizeof filename); + fapl_id = h5_fileaccess(); + if(H5Pset_fapl_sec2(fapl_id) < 0) + FAIL_STACK_ERROR; + h5_fixname(FILENAME[0], fapl_id, filename, sizeof(filename)); - if((file = H5Fcreate(filename, H5F_ACC_TRUNC, H5P_DEFAULT, fapl)) < 0) - TEST_ERROR; + if((fid = H5Fcreate(filename, H5F_ACC_TRUNC, H5P_DEFAULT, fapl_id)) < 0) + FAIL_STACK_ERROR; /* Retrieve the access property list... */ - if((access_fapl = H5Fget_access_plist(file)) < 0) - TEST_ERROR; + if((fapl_id_out = H5Fget_access_plist(fid)) < 0) + FAIL_STACK_ERROR; /* Check that the driver is correct */ - if(H5FD_SEC2 != H5Pget_driver(access_fapl)) - TEST_ERROR; + if(H5FD_SEC2 != H5Pget_driver(fapl_id_out)) + FAIL_STACK_ERROR; /* ...and close the property list */ - if(H5Pclose(access_fapl) < 0) - TEST_ERROR; + if(H5Pclose(fapl_id_out) < 0) + FAIL_STACK_ERROR; - /* Check file handle API */ - if(H5Fget_vfd_handle(file, H5P_DEFAULT, (void **)&fhandle) < 0) - TEST_ERROR; - if(*fhandle < 0) - TEST_ERROR; + /* Check that we can get an operating-system-specific handle from + * the library. + */ + if(H5Fget_vfd_handle(fid, H5P_DEFAULT, &os_file_handle) < 0) + FAIL_STACK_ERROR; + if(os_file_handle == NULL) + FAIL_PUTS_ERROR("NULL os-specific vfd/file handle was returned from H5Fget_vfd_handle"); - /* Check file size API */ - if(H5Fget_filesize(file, &file_size) < 0) - TEST_ERROR; - /* There is no guarantee the size of metadata in file is constant. - * Just try to check if it's reasonable. It's 2KB right now. + /* There is no garantee the size of metadata in file is constant. + * Just try to check if it's reasonable. + * + * Currently it should be around 2 KB. */ + if(H5Fget_filesize(fid, &file_size) < 0) + FAIL_STACK_ERROR; if(file_size < 1 * KB || file_size > 4 * KB) - TEST_ERROR; + FAIL_PUTS_ERROR("suspicious file size obtained from H5Fget_filesize"); - if(H5Fclose(file) < 0) - TEST_ERROR; + /* Close the file */ + if(H5Fclose(fid) < 0) + FAIL_STACK_ERROR; - h5_cleanup(FILENAME, fapl); + h5_cleanup(FILENAME, fapl_id); PASSED(); return 0; error: H5E_BEGIN_TRY { - H5Pclose(fapl); - H5Fclose(file); + H5Pclose(fapl_id); + H5Pclose(fapl_id_out); + H5Fclose(fid); } H5E_END_TRY; return -1; -} +} /* end test_sec2() */ /*------------------------------------------------------------------------- @@ -160,218 +170,314 @@ error: static herr_t test_core(void) { - hid_t file=(-1), fapl, access_fapl = -1; - char filename[1024]; - void *fhandle=NULL; - hsize_t file_size; - hbool_t use_write_tracking; - size_t write_tracking_page_size; - int *points = NULL, *check = NULL, *p1, *p2; - hid_t dset1=-1, space1=-1; - hsize_t dims1[2]; - int i, j, n; + hid_t fid = -1; /* file ID */ + hid_t fapl_id = -1; /* file access property list ID */ + hid_t fapl_id_out = -1; /* from H5Fget_access_plist */ + hid_t did = -1; /* dataset ID */ + hid_t sid = -1; /* dataspace ID */ + char filename[1024]; /* filename */ + void *os_file_handle = NULL; /* OS file handle */ + hsize_t file_size; /* file size */ + size_t increment; /* core VFD increment */ + hbool_t backing_store; /* use backing store? */ + hbool_t use_write_tracking; /* write tracking flag */ + size_t write_tracking_page_size; /* write tracking page size */ + int *data_w = NULL; /* data written to the dataset */ + int *data_r = NULL; /* data read from the dataset */ + int val; /* data value */ + int *pw = NULL, *pr = NULL; /* pointers for iterating over + data arrays (write & read) */ + hsize_t dims[2]; /* dataspace dimensions */ + int i, j; /* iterators */ + htri_t status; /* return value from H5Lexists */ TESTING("CORE file driver"); h5_reset(); - /* Set property list and file name for CORE driver */ - fapl = h5_fileaccess(); - if(H5Pset_fapl_core(fapl, (size_t)CORE_INCREMENT, TRUE) < 0) - TEST_ERROR; - if(H5Pset_core_write_tracking(fapl, TRUE, CORE_PAGE_SIZE) < 0) - TEST_ERROR; - h5_fixname(FILENAME[1], fapl, filename, sizeof filename); + /* Get a file access property list and fix up the file name */ + fapl_id = h5_fileaccess(); + h5_fixname(FILENAME[1], fapl_id, filename, sizeof(filename)); + + /************************************************************************ + * Check that the backing store flag works by creating a file, close + * it, and ensure that the file does not exist. + ************************************************************************/ + + /* Make sure it's not present at the start of the test */ + if(HDaccess(filename, F_OK) != -1) + if(HDremove(filename) < 0) + FAIL_PUTS_ERROR("unable to remove backing store file"); + /* Create and close file w/ backing store off */ + if(H5Pset_fapl_core(fapl_id, (size_t)CORE_INCREMENT, FALSE) < 0) + FAIL_STACK_ERROR; + if((fid = H5Fcreate(filename, H5F_ACC_TRUNC, H5P_DEFAULT, fapl_id)) < 0) + FAIL_STACK_ERROR; + if(H5Fclose(fid) < 0) + FAIL_STACK_ERROR; + /* Check for the backing store file */ + if(HDaccess(filename, F_OK) != -1) + FAIL_PUTS_ERROR("file created when backing store set to FALSE"); + + + /************************************************************************ + * Check basic core VFD operation and properties. This is done with the + * backing store on so a file will be created for later use. + ************************************************************************/ + + /* Turn the backing store on */ + if(H5Pset_fapl_core(fapl_id, (size_t)CORE_INCREMENT, TRUE) < 0) + FAIL_STACK_ERROR; + + /* Check that write tracking is off by default and that the default + * page size is non-zero. + */ + if(H5Pget_core_write_tracking(fapl_id, &use_write_tracking, &write_tracking_page_size) < 0) + FAIL_STACK_ERROR; + if(FALSE != use_write_tracking) + FAIL_PUTS_ERROR("write tracking should be off by default"); + if(0 == write_tracking_page_size) + FAIL_PUTS_ERROR("write tracking page size should never be zero"); - if((file=H5Fcreate(filename, H5F_ACC_TRUNC, H5P_DEFAULT, fapl)) < 0) - TEST_ERROR; + /* Set core VFD properties */ + if(H5Pset_core_write_tracking(fapl_id, TRUE, CORE_PAGE_SIZE) < 0) + FAIL_STACK_ERROR; + + /* Create the file */ + if((fid = H5Fcreate(filename, H5F_ACC_TRUNC, H5P_DEFAULT, fapl_id)) < 0) + FAIL_STACK_ERROR; /* Retrieve the access property list... */ - if ((access_fapl = H5Fget_access_plist(file)) < 0) - TEST_ERROR; + if((fapl_id_out = H5Fget_access_plist(fid)) < 0) + FAIL_STACK_ERROR; /* Check that the driver is correct */ - if(H5FD_CORE != H5Pget_driver(access_fapl)) - TEST_ERROR; + if(H5FD_CORE != H5Pget_driver(fapl_id_out)) + FAIL_STACK_ERROR; + + /* Get the basic VFD properties from the fapl and ensure that + * they are correct. + */ + if(H5Pget_fapl_core(fapl_id_out, &increment, &backing_store) < 0) + FAIL_STACK_ERROR + if(increment != (size_t)CORE_INCREMENT) + FAIL_PUTS_ERROR("incorrect increment from file fapl"); + if(backing_store != TRUE) + FAIL_PUTS_ERROR("incorrect backing store flag from file fapl"); /* Check that the backing store write tracking info was saved */ - if(H5Pget_core_write_tracking(fapl, &use_write_tracking, &write_tracking_page_size) < 0) - TEST_ERROR; + /* TODO: There is a bug where H5Fget_access_plist() does not return + * the write tracking properties. Until this bug is fixed, just + * test the main fapl_id. + */ + if(H5Pget_core_write_tracking(fapl_id, &use_write_tracking, &write_tracking_page_size) < 0) + FAIL_STACK_ERROR; if(TRUE != use_write_tracking) - TEST_ERROR; + FAIL_PUTS_ERROR("write tracking flag incorrect in fapl obtained from H5Fget_access_plist"); if(CORE_PAGE_SIZE != write_tracking_page_size) - TEST_ERROR; + FAIL_PUTS_ERROR("write tracking page size incorrect in fapl obtained from H5Fget_access_plist"); - /* ...and close the property list */ - if (H5Pclose(access_fapl) < 0) - TEST_ERROR; + /* Close the property list */ + if(H5Pclose(fapl_id_out) < 0) + FAIL_STACK_ERROR; - if(H5Fget_vfd_handle(file, H5P_DEFAULT, &fhandle) < 0) - TEST_ERROR; - if(fhandle==NULL) - { - printf("fhandle==NULL\n"); - TEST_ERROR; - } - - /* Check file size API */ - if(H5Fget_filesize(file, &file_size) < 0) - TEST_ERROR; + /* Check that we can get an operating-system-specific handle from + * the library. + */ + if(H5Fget_vfd_handle(fid, H5P_DEFAULT, &os_file_handle) < 0) + FAIL_STACK_ERROR; + if(os_file_handle == NULL) + FAIL_PUTS_ERROR("NULL os-specific vfd/file handle was returned from H5Fget_vfd_handle"); /* There is no garantee the size of metadata in file is constant. - * Just try to check if it's reasonable. Why is this 4KB? + * Just try to check if it's reasonable. + * + * TODO: Needs justification of why is this is a reasonable size. */ - if(file_size<2*KB || file_size>6*KB) - TEST_ERROR; + if(H5Fget_filesize(fid, &file_size) < 0) + FAIL_STACK_ERROR; + if(file_size < 2 * KB || file_size > 6 * KB) + FAIL_PUTS_ERROR("suspicious file size obtained from H5Fget_filesize"); - if(H5Fclose(file) < 0) - TEST_ERROR; + /* Close the file */ + if(H5Fclose(fid) < 0) + FAIL_STACK_ERROR; - /* Open the file with backing store off for read and write. - * Changes won't be saved in file. */ - if(H5Pset_fapl_core(fapl, (size_t)CORE_INCREMENT, FALSE) < 0) - TEST_ERROR; + /************************************************************************ + * Make changes to the file with the backing store flag OFF to ensure + * that they ARE NOT propagated. + ************************************************************************/ - if((file=H5Fopen(filename, H5F_ACC_RDWR, fapl)) < 0) - TEST_ERROR; + /* Open the file with backing store off for read and write. + * Changes won't be saved in file. + */ + if(H5Pset_fapl_core(fapl_id, (size_t)CORE_INCREMENT, FALSE) < 0) + FAIL_STACK_ERROR; + if((fid = H5Fopen(filename, H5F_ACC_RDWR, fapl_id)) < 0) + FAIL_STACK_ERROR; /* Allocate memory for data set. */ - if(NULL == (points = (int *)HDmalloc(DSET1_DIM1 * DSET1_DIM2 * sizeof(int)))) - TEST_ERROR; - if(NULL == (check = (int *)HDmalloc(DSET1_DIM1 * DSET1_DIM2 * sizeof(int)))) - TEST_ERROR; - - /* Initialize the dset1 */ - p1 = points; - for(i = n = 0; i < DSET1_DIM1; i++) - for(j = 0; j < DSET1_DIM2; j++) - *p1++ = n++; - - /* Create the data space1 */ - dims1[0] = DSET1_DIM1; - dims1[1] = DSET1_DIM2; - if((space1 = H5Screate_simple(2, dims1, NULL)) < 0) - TEST_ERROR; - - /* Create the dset1 */ - if((dset1 = H5Dcreate2(file, DSET1_NAME, H5T_NATIVE_INT, space1, H5P_DEFAULT, H5P_DEFAULT, H5P_DEFAULT)) < 0) - TEST_ERROR; - - /* Write the data to the dset1 */ - if(H5Dwrite(dset1, H5T_NATIVE_INT, H5S_ALL, H5S_ALL, H5P_DEFAULT, points) < 0) - TEST_ERROR; - - if(H5Dclose(dset1) < 0) - TEST_ERROR; - - if((dset1 = H5Dopen2(file, DSET1_NAME, H5P_DEFAULT)) < 0) - TEST_ERROR; + if(NULL == (data_w = (int *)HDmalloc(DSET1_DIM1 * DSET1_DIM2 * sizeof(int)))) + FAIL_PUTS_ERROR("unable to allocate memory for input array"); + if(NULL == (data_r = (int *)HDmalloc(DSET1_DIM1 * DSET1_DIM2 * sizeof(int)))) + FAIL_PUTS_ERROR("unable to allocate memory for output array"); + + /* Initialize the buffers */ + val = 0; + pw = data_w; + for(i = 0; i < CORE_DSET_DIM1; i++) + for(j = 0; j < CORE_DSET_DIM2; j++) + *pw++ = val++; + HDmemset(data_r, 0, DSET1_DIM1 * DSET1_DIM2 * sizeof(int)); + + /* Create the dataspace */ + dims[0] = CORE_DSET_DIM1; + dims[1] = CORE_DSET_DIM2; + if((sid = H5Screate_simple(2, dims, NULL)) < 0) + FAIL_STACK_ERROR; + + /* Create the dataset */ + if((did = H5Dcreate2(fid, CORE_DSET_NAME, H5T_NATIVE_INT, sid, H5P_DEFAULT, H5P_DEFAULT, H5P_DEFAULT)) < 0) + FAIL_STACK_ERROR; + + /* Write the data to the dataset */ + if(H5Dwrite(did, H5T_NATIVE_INT, H5S_ALL, H5S_ALL, H5P_DEFAULT, data_w) < 0) + FAIL_STACK_ERROR; + + /* Close and reopen the dataset */ + if(H5Dclose(did) < 0) + FAIL_STACK_ERROR; + if((did = H5Dopen2(fid, CORE_DSET_NAME, H5P_DEFAULT)) < 0) + FAIL_STACK_ERROR; /* Read the data back from dset1 */ - if(H5Dread(dset1, H5T_NATIVE_INT, H5S_ALL, H5S_ALL, H5P_DEFAULT, check) < 0) - TEST_ERROR; + if(H5Dread(did, H5T_NATIVE_INT, H5S_ALL, H5S_ALL, H5P_DEFAULT, data_r) < 0) + FAIL_STACK_ERROR; /* Check that the values read are the same as the values written */ - p1 = points; - p2 = check; - for(i = 0; i < DSET1_DIM1; i++) - for(j = 0; j < DSET1_DIM2; j++) - if(*p1++ != *p2++) { + pw = data_w; + pr = data_r; + for(i = 0; i < CORE_DSET_DIM1; i++) + for(j = 0; j < CORE_DSET_DIM2; j++) + if(*pr++ != *pw++) { H5_FAILED(); - printf(" Read different values than written in data set 1.\n"); + printf(" Read different values than written in data set.\n"); printf(" At index %d,%d\n", i, j); TEST_ERROR; } /* end if */ - if(H5Dclose(dset1) < 0) - TEST_ERROR; + /* Close everything except the dataspace ID (needed below)*/ + if(H5Dclose(did) < 0) + FAIL_STACK_ERROR; + if(H5Fclose(fid) < 0) + FAIL_STACK_ERROR; - if(H5Fclose(file) < 0) - TEST_ERROR; - - /* Open the file with backing store on for read and write. - * Changes will be saved in file. */ - if(H5Pset_fapl_core(fapl, (size_t)CORE_INCREMENT, TRUE) < 0) - TEST_ERROR; - - if((file = H5Fopen(filename, H5F_ACC_RDWR, fapl)) < 0) - TEST_ERROR; - - /* Create the dset1 */ - if((dset1 = H5Dcreate2(file, DSET1_NAME, H5T_NATIVE_INT, space1, H5P_DEFAULT, H5P_DEFAULT, H5P_DEFAULT)) < 0) - TEST_ERROR; - - /* Write the data to the dset1 */ - if(H5Dwrite(dset1, H5T_NATIVE_INT, H5S_ALL, H5S_ALL, H5P_DEFAULT, points) < 0) - TEST_ERROR; + /* Reopen the file and ensure that the dataset does not exist */ + if((fid = H5Fopen(filename, H5F_ACC_RDWR, fapl_id)) < 0) + FAIL_STACK_ERROR; + status = H5Lexists(fid, CORE_DSET_NAME, H5P_DEFAULT); + if(status < 0) + FAIL_STACK_ERROR; + if(status > 0) + FAIL_PUTS_ERROR("core VFD dataset created in file when backing store disabled"); - if(H5Dclose(dset1) < 0) - TEST_ERROR; + /* Close the file */ + if(H5Fclose(fid) < 0) + FAIL_STACK_ERROR; - if((dset1 = H5Dopen2(file, DSET1_NAME, H5P_DEFAULT)) < 0) - TEST_ERROR; - /* Reallocate memory for reading buffer. */ - HDassert(check); - HDfree(check); - if(NULL == (check = (int *)HDmalloc(DSET1_DIM1 * DSET1_DIM2 * sizeof(int)))) - TEST_ERROR; + /************************************************************************ + * Make changes to the file with the backing store flag ON to ensure + * that they ARE propagated. + ************************************************************************/ - /* Read the data back from dset1 */ - if(H5Dread(dset1, H5T_NATIVE_INT, H5S_ALL, H5S_ALL, H5P_DEFAULT, check) < 0) - TEST_ERROR; + /* Open the file with backing store on for read and write. + * Changes will be saved in file. + */ + if(H5Pset_fapl_core(fapl_id, (size_t)CORE_INCREMENT, TRUE) < 0) + FAIL_STACK_ERROR; + if((fid = H5Fopen(filename, H5F_ACC_RDWR, fapl_id)) < 0) + FAIL_STACK_ERROR; + + /* Create the dataset */ + if((did = H5Dcreate2(fid, CORE_DSET_NAME, H5T_NATIVE_INT, sid, H5P_DEFAULT, H5P_DEFAULT, H5P_DEFAULT)) < 0) + FAIL_STACK_ERROR; + + /* Write the data to the dataset */ + if(H5Dwrite(did, H5T_NATIVE_INT, H5S_ALL, H5S_ALL, H5P_DEFAULT, data_w) < 0) + FAIL_STACK_ERROR; + + /* Close everything and reopen */ + if(H5Dclose(did) < 0) + FAIL_STACK_ERROR; + if(H5Fclose(fid) < 0) + FAIL_STACK_ERROR; + if((fid = H5Fopen(filename, H5F_ACC_RDWR, fapl_id)) < 0) + FAIL_STACK_ERROR; + if((did = H5Dopen2(fid, CORE_DSET_NAME, H5P_DEFAULT)) < 0) + TEST_ERROR; + + /* Read the data back from the dataset */ + HDmemset(data_r, 0, DSET1_DIM1 * DSET1_DIM2 * sizeof(int)); + if(H5Dread(did, H5T_NATIVE_INT, H5S_ALL, H5S_ALL, H5P_DEFAULT, data_r) < 0) + FAIL_STACK_ERROR; /* Check that the values read are the same as the values written */ - p1 = points; - p2 = check; - for(i = 0; i < DSET1_DIM1; i++) - for(j = 0; j < DSET1_DIM2; j++) - if(*p1++ != *p2++) { + pw = data_w; + pr = data_r; + for(i = 0; i < CORE_DSET_DIM1; i++) + for(j = 0; j < CORE_DSET_DIM2; j++) + if(*pw++ != *pr++) { H5_FAILED(); - printf(" Read different values than written in data set 1.\n"); + printf(" Read different values than written in data set.\n"); printf(" At index %d,%d\n", i, j); TEST_ERROR; } /* end if */ - /* Check file size API */ - if(H5Fget_filesize(file, &file_size) < 0) - TEST_ERROR; + /* Check file size API. + * There is no garantee the size of metadata in file is constant. + * Just try to check if it's reasonable. + * + * TODO: Needs justification of why is this is a reasonable size. + */ + if(H5Fget_filesize(fid, &file_size) < 0) + FAIL_STACK_ERROR; + if(file_size < 64 * KB || file_size > 256 * KB) + FAIL_PUTS_ERROR("suspicious file size obtained from H5Fget_filesize"); - /* There is no garantee the size of metadata in file is constant. - * Just try to check if it's reasonable. */ - if(file_size<64*KB || file_size>256*KB) - TEST_ERROR; + /* Close everything */ + if(H5Sclose(sid) < 0) + FAIL_STACK_ERROR; + if(H5Dclose(did) < 0) + FAIL_STACK_ERROR; + if(H5Fclose(fid) < 0) + FAIL_STACK_ERROR; - if(H5Sclose(space1) < 0) - TEST_ERROR; - if(H5Dclose(dset1) < 0) - TEST_ERROR; - if(H5Fclose(file) < 0) - TEST_ERROR; - HDassert(points); - HDfree(points); - HDassert(check); - HDfree(check); + HDfree(data_w); + HDfree(data_r); - h5_cleanup(FILENAME, fapl); + h5_cleanup(FILENAME, fapl_id); PASSED(); return 0; error: H5E_BEGIN_TRY { - H5Pclose(fapl); - H5Fclose(file); + H5Sclose(sid); + H5Dclose(did); + H5Pclose(fapl_id_out); + H5Pclose(fapl_id); + H5Fclose(fid); } H5E_END_TRY; - if(points) - HDfree(points); - if(check) - HDfree(check); + if(data_w) + HDfree(data_w); + if(data_r) + HDfree(data_r); return -1; -} +} /* end test_core() */ /*------------------------------------------------------------------------- -- cgit v0.12 From 88476380be230e68f84cd5ed117af098c4133dd0 Mon Sep 17 00:00:00 2001 From: Vailin Choi Date: Wed, 6 Jul 2016 18:08:42 -0500 Subject: [svn-r30151] Fix daily test failures for checkin #30143 for HDFFV-9940. Tested on osx1010test, moohan, emu, kituo. --- test/links.c | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/test/links.c b/test/links.c index 10bec40..dcea7ce 100644 --- a/test/links.c +++ b/test/links.c @@ -7378,7 +7378,7 @@ external_link_with_committed_datatype(hid_t fapl, hbool_t new_format) FAIL_STACK_ERROR /* Open the group which is externally linked to target file */ - if((gid1 = H5Gopen(fid1, "link_to_2", H5P_DEFAULT)) < 0) + if((gid1 = H5Gopen2(fid1, "link_to_2", H5P_DEFAULT)) < 0) FAIL_STACK_ERROR /* Create a copy of integer datatype */ @@ -7480,7 +7480,7 @@ external_link_with_committed_datatype(hid_t fapl, hbool_t new_format) FAIL_STACK_ERROR /* Open the committed datatype in the mainfile */ - if((tid = H5Topen(fid1, "myDatatype", H5P_DEFAULT)) < 0) + if((tid = H5Topen2(fid1, "myDatatype", H5P_DEFAULT)) < 0) FAIL_STACK_ERROR /* Verify the datatype is committed */ @@ -7488,7 +7488,7 @@ external_link_with_committed_datatype(hid_t fapl, hbool_t new_format) FAIL_STACK_ERROR /* Open the group which is externally linked to target file */ - if((gid1 = H5Gopen(fid1, "link_to_2", H5P_DEFAULT)) < 0) + if((gid1 = H5Gopen2(fid1, "link_to_2", H5P_DEFAULT)) < 0) FAIL_STACK_ERROR /* Open the attribute attached to the group */ -- cgit v0.12 From 3e5a61c9ff7a22589dbb2fc71f95f32f919c8b54 Mon Sep 17 00:00:00 2001 From: Scot Breitenfeld Date: Thu, 7 Jul 2016 08:36:50 -0500 Subject: [svn-r30154] Fixed inequality comparsions for reals in HL fortran tests (HDFFV-9949, MSB, 7/7/16) --- hl/fortran/test/CMakeLists.txt | 8 ++--- hl/fortran/test/Makefile.am | 29 +++++++++++++++-- hl/fortran/test/tstlite.F90 | 74 +++++++++++++++++++++++++++--------------- hl/fortran/test/tsttable.F90 | 52 ++++++++++++++++++----------- 4 files changed, 112 insertions(+), 51 deletions(-) diff --git a/hl/fortran/test/CMakeLists.txt b/hl/fortran/test/CMakeLists.txt index fc703dc..13cb177 100644 --- a/hl/fortran/test/CMakeLists.txt +++ b/hl/fortran/test/CMakeLists.txt @@ -31,7 +31,7 @@ endif (BUILD_SHARED_LIBS AND NOT SKIP_HDF5_FORTRAN_SHARED) add_executable (hl_f90_tstlite tstlite.F90) TARGET_NAMING (hl_f90_tstlite STATIC) TARGET_FORTRAN_PROPERTIES (hl_f90_tstlite STATIC " " " ") -target_link_libraries (hl_f90_tstlite ${HDF5_HL_F90_LIB_TARGET} ${HDF5_F90_LIB_TARGET}) +target_link_libraries (hl_f90_tstlite ${HDF5_HL_F90_LIB_TARGET} ${HDF5_F90_LIB_TARGET} ${HDF5_F90_TEST_LIB_TARGET}) target_include_directories (hl_f90_tstlite PRIVATE ${CMAKE_Fortran_MODULE_DIRECTORY}/static) set_target_properties (hl_f90_tstlite PROPERTIES LINKER_LANGUAGE Fortran) set_target_properties (hl_f90_tstlite PROPERTIES FOLDER test/hl/fortran) @@ -39,7 +39,7 @@ if (BUILD_SHARED_LIBS AND NOT SKIP_HDF5_FORTRAN_SHARED) add_executable (hl_f90_tstlite-shared tstlite.F90) TARGET_NAMING (hl_f90_tstlite-shared SHARED) TARGET_FORTRAN_PROPERTIES (hl_f90_tstlite-shared SHARED " " " ") - target_link_libraries (hl_f90_tstlite-shared ${HDF5_HL_F90_LIBSH_TARGET} ${HDF5_F90_LIBSH_TARGET}) + target_link_libraries (hl_f90_tstlite-shared ${HDF5_HL_F90_LIBSH_TARGET} ${HDF5_F90_LIBSH_TARGET} ${HDF5_F90_TEST_LIBSH_TARGET}) target_include_directories (hl_f90_tstlite-shared PRIVATE ${CMAKE_Fortran_MODULE_DIRECTORY}/shared) set_target_properties (hl_f90_tstlite-shared PROPERTIES LINKER_LANGUAGE Fortran @@ -73,7 +73,7 @@ endif (BUILD_SHARED_LIBS AND NOT SKIP_HDF5_FORTRAN_SHARED) add_executable (hl_f90_tsttable tsttable.F90) TARGET_NAMING (hl_f90_tsttable STATIC) TARGET_FORTRAN_PROPERTIES (hl_f90_tsttable STATIC " " " ") -target_link_libraries (hl_f90_tsttable ${HDF5_HL_F90_LIB_TARGET} ${HDF5_F90_LIB_TARGET}) +target_link_libraries (hl_f90_tsttable ${HDF5_HL_F90_LIB_TARGET} ${HDF5_F90_LIB_TARGET} ${HDF5_F90_TEST_LIB_TARGET}) target_include_directories (hl_f90_tsttable PRIVATE ${CMAKE_Fortran_MODULE_DIRECTORY}/static) set_target_properties (hl_f90_tsttable PROPERTIES LINKER_LANGUAGE Fortran) set_target_properties (hl_f90_tsttable PROPERTIES FOLDER test/hl/fortran) @@ -81,7 +81,7 @@ if (BUILD_SHARED_LIBS AND NOT SKIP_HDF5_FORTRAN_SHARED) add_executable (hl_f90_tsttable-shared tsttable.F90) TARGET_NAMING (hl_f90_tsttable-shared SHARED) TARGET_FORTRAN_PROPERTIES (hl_f90_tsttable-shared SHARED " " " ") - target_link_libraries (hl_f90_tsttable-shared ${HDF5_HL_F90_LIBSH_TARGET} ${HDF5_F90_LIBSH_TARGET}) + target_link_libraries (hl_f90_tsttable-shared ${HDF5_HL_F90_LIBSH_TARGET} ${HDF5_F90_LIBSH_TARGET} ${HDF5_F90_TEST_LIBSH_TARGET}) target_include_directories (hl_f90_tsttable-shared PRIVATE ${CMAKE_Fortran_MODULE_DIRECTORY}/shared) set_target_properties (hl_f90_tsttable-shared PROPERTIES LINKER_LANGUAGE Fortran diff --git a/hl/fortran/test/Makefile.am b/hl/fortran/test/Makefile.am index 32d367c..4013d39 100644 --- a/hl/fortran/test/Makefile.am +++ b/hl/fortran/test/Makefile.am @@ -22,7 +22,7 @@ include $(top_srcdir)/config/commence.am AM_CPPFLAGS+=-I$(top_srcdir)/src -I$(top_builddir)/src -I$(top_srcdir)/hl/src -AM_FCFLAGS+=-I$(top_builddir)/fortran/src -I$(top_builddir)/hl/fortran/src $(F9XMODFLAG)$(top_builddir)/fortran/src $(F9XMODFLAG)$(top_builddir)/hl/fortran/src +AM_FCFLAGS+=-I$(top_builddir)/fortran/src -I$(top_builddir)/hl/fortran/src -I$(top_builddir)/fortran/test $(F9XMODFLAG)$(top_builddir)/fortran/src $(F9XMODFLAG)$(top_builddir)/fortran/test $(F9XMODFLAG)$(top_builddir)/hl/fortran/src # Some Fortran compilers can't build shared libraries, so sometimes we # need to make sure the Fortran programs link against the static version @@ -36,7 +36,9 @@ endif TEST_PROG=tstds tstlite tstimage tsttable check_PROGRAMS=$(TEST_PROG) -LDADD= $(LIBH5F_HL) $(LIBH5F) $(LIBH5_HL) $(LIBHDF5) +LIBOBJS=$(top_builddir)/fortran/test/tf_gen.o + +LDADD=$(LIBOBJS) $(LIBH5F_HL) $(LIBH5F) $(LIBH5_HL) $(LIBHDF5) # Source files for the programs tstds_SOURCES=tstds.F90 @@ -47,6 +49,29 @@ tsttable_SOURCES=tsttable.F90 # Temporary files. CHECK_CLEANFILES+=dsetf[1-5].h5 f1img.h5 f[1-2]tab.h5 tstds.h5 +# Fortran module files can have different extensions and different names +# (e.g., different capitalizations) on different platforms. Write rules +# for them explicitly rather than trying to teach automake about them. +# They should be installed as headers and removed during clean. +maintainer-clean-local: clean-local +distclean-local: clean-local +clean-local: + @if test -n "$(F9XMODEXT)" && test "X$(F9XMODEXT)" != "Xo"; then \ + $(RM) *.$(F9XMODEXT); \ + fi + +install-data-local: + @if test -n "$(F9XMODEXT)" && test "X$(F9XMODEXT)" != "Xo"; then \ + $(CP) $(top_builddir)/$(subdir)/*.$(F9XMODEXT) $(DESTDIR)$(includedir)/. ; \ + fi + +uninstall-local: + @if test -n "$(F9XMODEXT)" -a "X$(F9XMODEXT)" != "Xo"; then \ + if test -f "$(includedir)/hdf5.$(F9XMODEXT)" -o -f "$(DESTDIR)$(includedir)/HDF5.$(F9XMODEXT)"; then \ + set -x; $(RM) $(includedir)/*.$(F9XMODEXT); \ + fi; \ + fi + # Mark this directory as part of the Fortran API (this affects output # from tests in conclude.am) FORTRAN_API=yes diff --git a/hl/fortran/test/tstlite.F90 b/hl/fortran/test/tstlite.F90 index 42e2bcc..b19ca5a 100644 --- a/hl/fortran/test/tstlite.F90 +++ b/hl/fortran/test/tstlite.F90 @@ -20,6 +20,7 @@ MODULE TSTLITE + USE TH5_MISC_GEN IMPLICIT NONE CONTAINS @@ -122,7 +123,8 @@ CONTAINS ! compare read and write buffers. ! DO i = 1, DIM1 - IF ( buf1(i) .NE. bufr1(i) ) THEN + CALL VERIFY("h5ltread_dataset_f",buf1(i), bufr1(i), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer (I)' PRINT *, bufr1(i), ' and ', buf1(i) STOP @@ -147,7 +149,8 @@ CONTAINS ! compare read and write buffers. ! DO i = 1, DIM1 - IF ( buf2(i) .NE. bufr2(i) ) THEN + CALL VERIFY("h5ltread_dataset_f",buf2(i), bufr2(i), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer (R)' PRINT *, bufr2(i), ' and ', buf2(i) STOP @@ -179,7 +182,8 @@ CONTAINS ! compare read and write buffers. ! DO i = 1, DIM1 - IF ( buf3(i) .NE. bufr3(i) ) THEN + CALL VERIFY("h5ltread_dataset_f",buf3(i), bufr3(i), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer (D)' PRINT *, bufr3(i), ' and ', buf3(i) STOP @@ -337,7 +341,8 @@ CONTAINS ! DO i = 1, dims(1) DO j = 1, dims(2) - IF ( buf3(i,j) .NE. buf3r(i,j) ) THEN + CALL VERIFY("h5ltread_dataset_f",buf3(i,j), buf3r(i,j), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, buf3r(i,j), ' and ', buf3(i,j) STOP @@ -368,7 +373,8 @@ CONTAINS ! DO i = 1, dims(1) DO j = 1, dims(2) - IF ( buf4(i,j) .NE. buf4r(i,j) ) THEN + CALL VERIFY("h5ltread_dataset_f", buf4(i,j), buf4r(i,j), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, buf4r(i,j), ' and ', buf4(i,j) STOP @@ -551,7 +557,8 @@ CONTAINS DO i = 1, dims(1) DO j = 1, dims(2) DO k = 1, dims(3) - IF ( buf3(i,j,k) .NE. buf3r(i,j,k) ) THEN + CALL VERIFY("h5ltread_dataset_f",buf3(i,j,k), buf3r(i,j,k), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, buf3r(i,j,k), ' and ', buf3(i,j,k) STOP @@ -582,7 +589,8 @@ CONTAINS DO i = 1, dims(1) DO j = 1, dims(2) DO k = 1, dims(3) - IF ( buf4(i,j,k) .NE. buf4r(i,j,k) ) THEN + CALL VERIFY("h5ltread_dataset_f", buf4(i,j,k), buf4r(i,j,k), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, buf4r(i,j,k), ' and ', buf4(i,j,k) STOP @@ -1040,7 +1048,8 @@ CONTAINS DO k = 1, dims(3) DO l = 1, dims(4) IF(rank.EQ.4)THEN - IF ( rbuf_4(i,j,k,l) .NE. rbufr_4(i,j,k,l) ) THEN + CALL VERIFY("h5ltread_dataset_f",rbuf_4(i,j,k,l), rbufr_4(i,j,k,l), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, rbuf_4(i,j,k,l), ' and ', rbufr_4(i,j,k,l) STOP @@ -1048,7 +1057,8 @@ CONTAINS ENDIF DO m = 1, dims(5) IF(rank.EQ.5)THEN - IF ( rbuf_5(i,j,k,l,m) .NE. rbufr_5(i,j,k,l,m) ) THEN + CALL VERIFY("h5ltread_dataset_f",rbuf_5(i,j,k,l,m), rbufr_5(i,j,k,l,m), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, rbuf_5(i,j,k,l,m), ' and ', rbufr_5(i,j,k,l,m) STOP @@ -1056,7 +1066,8 @@ CONTAINS ENDIF DO n = 1, dims(6) IF(rank.EQ.6)THEN - IF ( rbuf_6(i,j,k,l,m,n) .NE. rbufr_6(i,j,k,l,m,n) ) THEN + CALL VERIFY("h5ltread_dataset_f",rbuf_6(i,j,k,l,m,n), rbufr_6(i,j,k,l,m,n), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, rbuf_6(i,j,k,l,m,n), ' and ', rbufr_6(i,j,k,l,m,n) STOP @@ -1064,7 +1075,8 @@ CONTAINS ENDIF DO o = 1, dims(7) IF(rank.EQ.7)THEN - IF ( rbuf_7(i,j,k,l,m,n,o) .NE. rbufr_7(i,j,k,l,m,n,o) ) THEN + CALL VERIFY("h5ltread_dataset_f",rbuf_7(i,j,k,l,m,n,o), rbufr_7(i,j,k,l,m,n,o), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, rbuf_7(i,j,k,l,m,n,o), ' and ', rbufr_7(i,j,k,l,m,n,o) STOP @@ -1124,7 +1136,8 @@ CONTAINS DO k = 1, dims(3) DO l = 1, dims(4) IF(rank.EQ.4)THEN - IF ( dbuf_4(i,j,k,l) .NE. dbufr_4(i,j,k,l) ) THEN + CALL VERIFY("h5ltread_dataset_f",dbuf_4(i,j,k,l), dbufr_4(i,j,k,l), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, dbuf_4(i,j,k,l), ' and ', dbufr_4(i,j,k,l) STOP @@ -1132,7 +1145,8 @@ CONTAINS ENDIF DO m = 1, dims(5) IF(rank.EQ.5)THEN - IF ( dbuf_5(i,j,k,l,m) .NE. dbufr_5(i,j,k,l,m) ) THEN + CALL VERIFY("h5ltread_dataset_f",dbuf_5(i,j,k,l,m), dbufr_5(i,j,k,l,m), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, dbuf_5(i,j,k,l,m), ' and ', dbufr_5(i,j,k,l,m) STOP @@ -1140,7 +1154,8 @@ CONTAINS ENDIF DO n = 1, dims(6) IF(rank.EQ.6)THEN - IF ( dbuf_6(i,j,k,l,m,n) .NE. dbufr_6(i,j,k,l,m,n) ) THEN + CALL VERIFY("h5ltread_dataset_f",dbuf_6(i,j,k,l,m,n), dbufr_6(i,j,k,l,m,n), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, dbuf_6(i,j,k,l,m,n), ' and ', dbufr_6(i,j,k,l,m,n) STOP @@ -1148,7 +1163,8 @@ CONTAINS ENDIF DO o = 1, dims(7) IF(rank.EQ.7)THEN - IF ( dbuf_7(i,j,k,l,m,n,o) .NE. dbufr_7(i,j,k,l,m,n,o) ) THEN + CALL VERIFY("h5ltread_dataset_f",dbuf_7(i,j,k,l,m,n,o), dbufr_7(i,j,k,l,m,n,o), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, dbuf_7(i,j,k,l,m,n,o), ' and ', dbufr_7(i,j,k,l,m,n,o) STOP @@ -1323,7 +1339,8 @@ CONTAINS REAL, DIMENSION(DIM1) , TARGET :: bufr3 ! Data buffer DOUBLE PRECISION, DIMENSION(DIM1), TARGET :: buf4 ! Data buffer DOUBLE PRECISION, DIMENSION(DIM1), TARGET :: bufr4 ! Data buffer - INTEGER :: i, j, n ! general purpose integer + INTEGER :: i, n ! general purpose integer + INTEGER(SIZE_T) :: i_sz, j_sz ! general purpose integer INTEGER :: has ! general purpose integer INTEGER :: type_class INTEGER(SIZE_T) :: type_size @@ -1375,14 +1392,14 @@ CONTAINS ALLOCATE( ptr(1)%data(1:wdata(1)%len) ) ALLOCATE( ptr(2)%data(1:wdata(2)%len) ) - DO i=1, wdata(1)%len - ptr(1)%data(i) = wdata(1)%len - i + 1 ! 3 2 1 + DO i_sz=1, wdata(1)%len + ptr(1)%data(i_sz) = INT(wdata(1)%len) - INT(i_sz) + 1 ! 3 2 1 ENDDO wdata(1)%p = C_LOC(ptr(1)%data(1)) ptr(2)%data(1:2) = 1 - DO i = 3, wdata(2)%len - ptr(2)%data(i) = ptr(2)%data(i-1) + ptr(2)%data(i-2) ! (1 1 2 3 5 8 etc.) + DO i_sz = 3, wdata(2)%len + ptr(2)%data(i_sz) = ptr(2)%data(i_sz-1_size_t) + ptr(2)%data(i_sz-2_size_t) ! (1 1 2 3 5 8 etc.) ENDDO wdata(2)%p = C_LOC(ptr(2)%data(1)) @@ -1439,7 +1456,8 @@ CONTAINS ! compare read and write buffers. ! DO i = 1, DIM1 - IF ( buf3(i) .NE. bufr3(i) ) THEN + CALL VERIFY("h5ltread_dataset_f", buf3(i), bufr3(i), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, bufr3(i), ' and ', buf3(i) STOP @@ -1473,7 +1491,8 @@ CONTAINS ! compare read and write buffers. ! DO i = 1, DIM1 - IF ( buf4(i) .NE. bufr4(i) ) THEN + CALL VERIFY("h5ltread_dataset_double_f", buf4(i), bufr4(i), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, bufr4(i), ' and ', buf4(i) STOP @@ -1530,8 +1549,9 @@ CONTAINS DO i = 1, INT(dims_vl(1)) CALL c_f_pointer(rdata(i)%p, ptr_r, [rdata(i)%len] ) - DO j = 1, rdata(i)%len - IF(ptr_r(j).NE.ptr(i)%data(j))THEN + DO j_sz = 1, rdata(i)%len + CALL VERIFY("h5ltread_dataset_f", ptr_r(j_sz), ptr(i)%data(j_sz), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'Writing/Reading variable-length dataset failed' STOP ENDIF @@ -1793,7 +1813,8 @@ CONTAINS ! compare read and write buffers. ! DO i = 1, DIM1 - IF ( buf3(i) .NE. bufr3(i) ) THEN + CALL VERIFY("h5ltget_attribute_f",buf3(i), bufr3(i), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, bufr3(i), ' and ', buf3(i) STOP @@ -1841,7 +1862,8 @@ CONTAINS ! compare read and write buffers. ! DO i = 1, DIM1 - IF ( buf4(i) .NE. bufr4(i) ) THEN + CALL VERIFY("h5ltget_attribute_f",buf4(i), bufr4(i), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, bufr4(i), ' and ', buf4(i) STOP diff --git a/hl/fortran/test/tsttable.F90 b/hl/fortran/test/tsttable.F90 index 822f116..62d291f 100644 --- a/hl/fortran/test/tsttable.F90 +++ b/hl/fortran/test/tsttable.F90 @@ -44,6 +44,9 @@ END MODULE TSTTABLE MODULE TSTTABLE_TESTS + USE TH5_MISC_GEN + IMPLICIT NONE + CONTAINS !------------------------------------------------------------------------- @@ -283,7 +286,8 @@ SUBROUTINE test_table1() ! compare read and write buffers. ! DO i = 1, nrecords - IF ( bufrr(i) .NE. bufr(i) ) THEN + CALL VERIFY("h5tbread_field_name_f", bufrr(i), bufr(i), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, bufrr(i), ' and ', bufr(i) STOP @@ -298,7 +302,8 @@ SUBROUTINE test_table1() ! compare read and write buffers. ! DO i = 1, nrecords - IF ( bufdr(i) .NE. bufd(i) ) THEN + CALL VERIFY("h5tbread_field_name_f", bufdr(i), bufd(i), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, bufdr(i), ' and ', bufd(i) STOP @@ -315,7 +320,8 @@ SUBROUTINE test_table1() ! compare read and write buffers. ! DO i = 1, nrecords - IF ( bufrr(i) .NE. bufr(i) ) THEN + CALL VERIFY("h5tbread_field_name_f", bufrr(i), bufr(i), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, bufrr(i), ' and ', bufr(i) STOP @@ -362,7 +368,8 @@ SUBROUTINE test_table1() ! compare read and write buffers. ! DO i = 1, nrecords - IF ( bufsr(i) .NE. bufs(i) ) THEN + CALL VERIFY("h5tbread_field_index_f", bufsr(i), bufs(i), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, bufsr(i), ' and ', bufs(i) STOP @@ -376,7 +383,8 @@ SUBROUTINE test_table1() ! compare read and write buffers. ! DO i = 1, nrecords - IF ( bufir(i) .NE. bufi(i) ) THEN + CALL VERIFY("h5tbread_field_index_f", bufir(i), bufi(i), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, bufir(i), ' and ', bufi(i) STOP @@ -390,7 +398,8 @@ SUBROUTINE test_table1() ! compare read and write buffers. ! DO i = 1, nrecords - IF ( bufrr(i) .NE. bufr(i) ) THEN + CALL VERIFY("h5tbread_field_index_f", bufrr(i), bufr(i), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, bufrr(i), ' and ', bufr(i) STOP @@ -404,7 +413,8 @@ SUBROUTINE test_table1() ! compare read and write buffers. ! DO i = 1, nrecords - IF ( bufdr(i) .NE. bufd(i) ) THEN + CALL VERIFY("h5tbread_field_index_f", bufdr(i), bufd(i), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, bufdr(i), ' and ', bufd(i) STOP @@ -419,7 +429,8 @@ SUBROUTINE test_table1() ! compare read and write buffers. ! DO i = 1, nrecords - IF ( bufrr(i) .NE. bufr(i) ) THEN + CALL VERIFY("h5tbread_field_index_f", bufrr(i), bufr(i), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, bufrr(i), ' and ', bufr(i) STOP @@ -444,7 +455,8 @@ SUBROUTINE test_table1() ! compare read and write buffers. ! DO i = 1, nrecords - IF ( bufrr(i) .NE. bufr(i) ) THEN + CALL VERIFY("h5tbread_field_index_f", bufrr(i), bufr(i), errcode) + IF (errcode .NE.0 ) THEN PRINT *, 'read buffer differs from write buffer' PRINT *, bufrr(i), ' and ', bufr(i) STOP @@ -670,11 +682,12 @@ SUBROUTINE test_table2() CALL h5tbread_table_f(file_id, table_name_fill, nfields, dst_size, dst_offset, dst_sizes, f_ptr3, errcode) DO i = 1, nfields - IF(r_data(i)%name.NE.fill_data(i)%name.OR. & - r_data(i)%lati.NE.fill_data(i)%lati.OR. & - r_data(i)%long.NE.fill_data(i)%long.OR. & - r_data(i)%pressure.NE.fill_data(i)%pressure.OR. & - r_data(i)%temperature.NE.fill_data(i)%temperature)THEN + CALL VERIFY("h5tbread_table_f", r_data(i)%name, fill_data(i)%name, errcode) + CALL VERIFY("h5tbread_table_f", r_data(i)%lati, fill_data(i)%lati, errcode) + CALL VERIFY("h5tbread_table_f", r_data(i)%long, fill_data(i)%long, errcode) + CALL VERIFY("h5tbread_table_f", r_data(i)%pressure, fill_data(i)%pressure, errcode) + CALL VERIFY("h5tbread_table_f", r_data(i)%temperature, fill_data(i)%temperature, errcode) + IF (errcode .NE.0 ) THEN PRINT*,'H5TBmake/read_table_f --filled-- FAILED' STOP ENDIF @@ -693,11 +706,12 @@ SUBROUTINE test_table2() CALL h5tbread_table_f(file_id, table_name, nfields, dst_size, dst_offset, dst_sizes, f_ptr3, errcode) DO i = 1, nfields - IF(r_data(i)%name.NE.p_data(i)%name.OR. & - r_data(i)%lati.NE.p_data(i)%lati.OR. & - r_data(i)%long.NE.p_data(i)%long.OR. & - r_data(i)%pressure.NE.p_data(i)%pressure.OR. & - r_data(i)%temperature.NE.p_data(i)%temperature)THEN + CALL VERIFY("h5tbread_table_f", r_data(i)%name, p_data(i)%name, errcode) + CALL VERIFY("h5tbread_table_f", r_data(i)%lati, p_data(i)%lati, errcode) + CALL VERIFY("h5tbread_table_f", r_data(i)%long, p_data(i)%long, errcode) + CALL VERIFY("h5tbread_table_f", r_data(i)%pressure, p_data(i)%pressure, errcode) + CALL VERIFY("h5tbread_table_f", r_data(i)%temperature, p_data(i)%temperature, errcode) + IF (errcode .NE.0 ) THEN PRINT*,'H5TBmake/read_table_f FAILED' STOP ENDIF -- cgit v0.12 From ec2fbe0883f9e76df60bcfbebbd4b6f62d5a09e6 Mon Sep 17 00:00:00 2001 From: Quincey Koziol Date: Thu, 7 Jul 2016 13:54:11 -0500 Subject: [svn-r30158] Description: More warning cleanups. This brings us down to ~1300 warnings in 167 files Tested on: MacOSX/64 10.11.5 (amazon) w/serial & parallel (h5committest forthcoming) --- hl/test/test_packet_vlen.c | 282 +++++++++++++++++++++++---------------------- src/H5FSstat.c | 2 +- src/H5Oattr.c | 18 ++- test/H5srcdir.h | 42 +++---- test/tsohm.c | 83 +++++++------ 5 files changed, 222 insertions(+), 205 deletions(-) diff --git a/hl/test/test_packet_vlen.c b/hl/test/test_packet_vlen.c index 82c8d1c..f1e4e00 100644 --- a/hl/test/test_packet_vlen.c +++ b/hl/test/test_packet_vlen.c @@ -60,7 +60,7 @@ static int test_VLof_atomic(void) hid_t ptable=H5I_INVALID_HID; /* Packet table identifier */ hid_t vltype=H5I_INVALID_HID; /* Variable length datatype */ hsize_t count; /* Number of records in the table */ - int ii, jj; /* Loop variables */ + unsigned uu, vv; /* Loop variables */ hvl_t writeBuf[NRECORDS]; /* Buffer to hold data to be written */ hvl_t readBuf[NRECORDS]; /* Buffer to hold read data */ char msg[80]; /* For error message */ @@ -69,15 +69,15 @@ static int test_VLof_atomic(void) TESTING3(" with vlen of atomic"); /* Allocate and initialize VL data to write (copied from C test) */ - for (ii=0; iip = HDmalloc((jj+L2_INCM)*sizeof(unsigned int)); + t1->p = HDmalloc((vv + L2_INCM) * sizeof(unsigned int)); if (t1->p == NULL) { - fprintf(stderr, "Cannot allocate memory for VL data! ii=%d\n",ii); + fprintf(stderr, "Cannot allocate memory for VL data! uu=%u\n", uu); goto error; } - t1->len = jj+L2_INCM; - for (kk=0; kkp)[kk] = ii*100 + jj*10 + kk; + t1->len = vv + L2_INCM; + for (ww = 0; ww < vv + L2_INCM; ww++) + ((unsigned int *)t1->p)[ww] = uu * 100 + vv * 10 + ww; } } /* end for */ @@ -377,7 +377,7 @@ static int test_compound_VL_VLtype(void) goto error; /* Insert fields: atomic, atomic, vlen */ - ret = H5Tinsert(comp_vlvl, "i", HOFFSET(compVLVL_t, i), H5T_NATIVE_INT); + ret = H5Tinsert(comp_vlvl, "u", HOFFSET(compVLVL_t, u), H5T_NATIVE_UINT); if (ret < 0) goto error; ret = H5Tinsert(comp_vlvl, "f", HOFFSET(compVLVL_t, f), H5T_NATIVE_FLOAT); @@ -417,29 +417,29 @@ static int test_compound_VL_VLtype(void) goto error; /* Compare data read in */ - for (ii = 0; ii < NRECORDS; ii++) { - if (writeBuf[ii].i != readBuf[ii].i) { - fprintf(stderr, "Integer components don't match!, writeBuf[%d].i=%d, readBuf[%d].i=%d\n",(int)ii,(int)writeBuf[ii].i,(int)ii,(int)readBuf[ii].i); + for (uu = 0; uu < NRECORDS; uu++) { + if (writeBuf[uu].u != readBuf[uu].u) { + fprintf(stderr, "Integer components don't match!, writeBuf[%u].u=%u, readBuf[%u].u=%u\n", uu, writeBuf[uu].u, uu, readBuf[uu].u); continue; } /* end if */ - if (!H5_FLT_ABS_EQUAL(writeBuf[ii].f,readBuf[ii].f)) { - fprintf(stderr, "Float components don't match!, writeBuf[%d].f=%f, readBuf[%d].f=%f\n",(int)ii,(double)writeBuf[ii].f,(int)ii,(double)readBuf[ii].f); + if (!H5_FLT_ABS_EQUAL(writeBuf[uu].f,readBuf[uu].f)) { + fprintf(stderr, "Float components don't match!, writeBuf[%u].f=%f, readBuf[%u].f=%f\n", uu, (double)writeBuf[uu].f, uu, (double)readBuf[uu].f); continue; } /* end if */ - if (writeBuf[ii].v.len != readBuf[ii].v.len) { - fprintf(stderr, "%d: VL data length don't match!, writeBuf[%d].v.len=%d, readBuf[%d].v.len=%d\n",__LINE__,(int)ii,(int)writeBuf[ii].v.len,(int)ii,(int)readBuf[ii].v.len); + if (writeBuf[uu].v.len != readBuf[uu].v.len) { + fprintf(stderr, "%d: VL data length don't match!, writeBuf[%d].v.len=%zu, readBuf[%d].v.len=%zu\n", __LINE__, uu, writeBuf[uu].v.len, uu, readBuf[uu].v.len); continue; } /* end if */ - for (t1=(hvl_t *)(writeBuf[ii].v.p), t2=(hvl_t *)(readBuf[ii].v.p), jj=0; (size_t)jjlen != t2->len) { - fprintf(stderr, "%d: VL data length don't match!, ii=%d, jj=%d, t1->len=%d, t2->len=%d\n",__LINE__,(int)ii,(int)jj,(int)t1->len,(int)t2->len); + fprintf(stderr, "%d: VL data length don't match!, uu=%u, vv=%u, t1->len=%zu, t2->len=%zu\n", __LINE__, uu, vv, t1->len, t2->len); continue; } /* end if */ - for (kk=0; (size_t)kklen; kk++) { - if (((unsigned int *)t1->p)[kk] != ((unsigned int *)t2->p)[kk] ) { - fprintf(stderr, "VL data values don't match!, t1->p[%d]=%d, t2->p[%d]=%d\n",(int)kk, (int)((unsigned int *)t1->p)[kk], (int)kk, (int)((unsigned int *)t2->p)[kk]); + for (ww = 0; (size_t)ww < t2->len; ww++) { + if (((unsigned int *)t1->p)[ww] != ((unsigned int *)t2->p)[ww] ) { + fprintf(stderr, "VL data values don't match!, t1->p[%u]=%u, t2->p[%u]=%u\n", ww, ((unsigned int *)t1->p)[ww], ww, ((unsigned int *)t2->p)[ww]); continue; } /* end if */ } /* end for */ @@ -497,7 +497,7 @@ static int test_VLof_VLtype(void) hid_t vlofvl=H5I_INVALID_HID; /* VL datatype of VL datatypes */ hsize_t count; /* Number of records in the table */ hvl_t *t1; /* pointer to advance */ - int ii, jj, kk; /* Loop variables */ + unsigned uu, vv, ww; /* Loop variables */ hvl_t writeBuf[NRECORDS]; /* Buffer to hold data to be written */ hvl_t readBuf[NRECORDS]; /* Buffer to hold read data */ char msg[80]; /* For error message */ @@ -506,23 +506,23 @@ static int test_VLof_VLtype(void) TESTING3(" with vlen datatype of vlen datatype"); /* Allocate and initialize VL data to write (copied from C test) */ - for (ii=0; ii< NRECORDS; ii++) { - writeBuf[ii].p = HDmalloc((ii+1)*sizeof(hvl_t)); - if (writeBuf[ii].p == NULL) { - fprintf(stderr, "Cannot allocate memory for VL data! ii=%u\n",ii); + for (uu = 0; uu < NRECORDS; uu++) { + writeBuf[uu].p = HDmalloc((uu + 1) * sizeof(hvl_t)); + if (writeBuf[uu].p == NULL) { + fprintf(stderr, "Cannot allocate memory for VL data! uu=%u\n", uu); goto error; } /* end if */ - writeBuf[ii].len = ii+1; - for (t1=(hvl_t *)(writeBuf[ii].p), jj=0; jj<(ii+1); jj++, t1++) + writeBuf[uu].len = uu + 1; + for (t1=(hvl_t *)(writeBuf[uu].p), vv = 0; vv < (uu + 1); vv++, t1++) { - t1->p = HDmalloc((jj+1)*sizeof(unsigned int)); + t1->p = HDmalloc((vv + 1) * sizeof(unsigned int)); if (t1->p == NULL) { - fprintf(stderr, "Cannot allocate memory for VL data! ii=%u\n",ii); + fprintf(stderr, "Cannot allocate memory for VL data! uu=%u\n", uu); goto error; } - t1->len = jj+1; - for (kk=0; kk<(jj+1); kk++) - ((unsigned int *)t1->p)[kk] = ii*100+jj*10+kk; + t1->len = vv * 1; + for (ww = 0; ww < (vv * 1); ww++) + ((unsigned int *)t1->p)[ww] = uu * 100 + vv * 10 + ww; } /* end for */ } /* end for */ @@ -958,6 +958,8 @@ static herr_t verify_accessors(const char *table_name, herr_t expected_value) /* Check if the packet table's name matches its associated dataset's. */ *buf = '\0'; name_size = H5Iget_name(dset_id, (char*)buf, NAME_BUF_SIZE); + if (name_size < 0) + goto error; VERIFY(HDstrcmp(buf, table_name), "Names of dataset and packet table don't match"); /* Get the packet table's datatype ID */ @@ -1059,7 +1061,7 @@ static int testfl_VLof_atomic(void) hid_t ptable=H5I_INVALID_HID; /* Packet table identifier */ hid_t vltype=H5I_INVALID_HID; /* Variable length datatype */ hsize_t count; /* Number of records in the table */ - int ii, jj; /* Loop variables */ + unsigned uu, vv; /* Loop variables */ hvl_t writeBuf[NRECORDS]; /* Buffer to hold data to be written */ hvl_t readBuf[NRECORDS]; /* Buffer to hold read data */ char msg[80]; /* For error message */ @@ -1068,15 +1070,15 @@ static int testfl_VLof_atomic(void) TESTING3(" with vlen of atomic"); /* Allocate and initialize VL data to write (copied from C test) */ - for (ii=0; iip = HDmalloc((jj+L2_INCM)*sizeof(unsigned int)); + t1->p = HDmalloc((vv + L2_INCM) * sizeof(unsigned int)); if (t1->p == NULL) { - fprintf(stderr, "Cannot allocate memory for VL data! ii=%d\n",ii); + fprintf(stderr, "Cannot allocate memory for VL data! uu=%u\n", uu); goto error; } - t1->len = jj+L2_INCM; - for (kk=0; kkp)[kk] = ii*100 + jj*10 + kk; + t1->len = vv + L2_INCM; + for (ww = 0; ww < vv + L2_INCM; ww++) + ((unsigned int*)t1->p)[ww] = uu * 100 + vv * 10 + ww; } } /* end for */ @@ -1376,7 +1378,7 @@ static int testfl_compound_VL_VLtype(void) goto error; /* Insert fields: atomic, atomic, vlen */ - ret = H5Tinsert(comp_vlvl, "i", HOFFSET(compVLVL_t, i), H5T_NATIVE_INT); + ret = H5Tinsert(comp_vlvl, "u", HOFFSET(compVLVL_t, u), H5T_NATIVE_UINT); if (ret < 0) goto error; ret = H5Tinsert(comp_vlvl, "f", HOFFSET(compVLVL_t, f), H5T_NATIVE_FLOAT); @@ -1416,29 +1418,29 @@ static int testfl_compound_VL_VLtype(void) goto error; /* Compare data read in */ - for (ii = 0; ii < NRECORDS; ii++) { - if (writeBuf[ii].i != readBuf[ii].i) { - fprintf(stderr, "Integer components don't match!, writeBuf[%d].i=%d, readBuf[%d].i=%d\n",(int)ii,(int)writeBuf[ii].i,(int)ii,(int)readBuf[ii].i); + for (uu = 0; uu < NRECORDS; uu++) { + if (writeBuf[uu].u != readBuf[uu].u) { + fprintf(stderr, "Integer components don't match!, writeBuf[%u].u=%u, readBuf[%u].u=%u\n", uu, writeBuf[uu].u, uu, readBuf[uu].u); continue; } /* end if */ - if (!H5_FLT_ABS_EQUAL(writeBuf[ii].f,readBuf[ii].f)) { - fprintf(stderr, "Float components don't match!, writeBuf[%d].f=%f, readBuf[%d].f=%f\n",(int)ii,(double)writeBuf[ii].f,(int)ii,(double)readBuf[ii].f); + if (!H5_FLT_ABS_EQUAL(writeBuf[uu].f, readBuf[uu].f)) { + fprintf(stderr, "Float components don't match!, writeBuf[%u].f=%f, readBuf[%u].f=%f\n", uu, (double)writeBuf[uu].f, uu, (double)readBuf[uu].f); continue; } /* end if */ - if (writeBuf[ii].v.len != readBuf[ii].v.len) { - fprintf(stderr, "%d: VL data length don't match!, writeBuf[%d].v.len=%d, readBuf[%d].v.len=%d\n",__LINE__,(int)ii,(int)writeBuf[ii].v.len,(int)ii,(int)readBuf[ii].v.len); + if (writeBuf[uu].v.len != readBuf[uu].v.len) { + fprintf(stderr, "%d: VL data length don't match!, writeBuf[%u].v.len=%zu, readBuf[%u].v.len=%zu\n", __LINE__, uu, writeBuf[uu].v.len, uu, readBuf[uu].v.len); continue; } /* end if */ - for (t1=(hvl_t *)(writeBuf[ii].v.p), t2=(hvl_t *)(readBuf[ii].v.p), jj=0; (size_t)jjlen != t2->len) { - fprintf(stderr, "%d: VL data length don't match!, ii=%d, jj=%d, t1->len=%d, t2->len=%d\n",__LINE__,(int)ii,(int)jj,(int)t1->len,(int)t2->len); + fprintf(stderr, "%d: VL data length don't match!, uu=%u, vv=%u, t1->len=%zu, t2->len=%zu\n", __LINE__, uu, vv, t1->len, t2->len); continue; } /* end if */ - for (kk=0; (size_t)kklen; kk++) { - if (((unsigned int *)t1->p)[kk] != ((unsigned int *)t2->p)[kk] ) { - fprintf(stderr, "VL data values don't match!, t1->p[%d]=%d, t2->p[%d]=%d\n",(int)kk, (int)((unsigned int *)t1->p)[kk], (int)kk, (int)((unsigned int *)t2->p)[kk]); + for (ww = 0; (size_t)ww < t2->len; ww++) { + if (((unsigned int *)t1->p)[ww] != ((unsigned int *)t2->p)[ww] ) { + fprintf(stderr, "VL data values don't match!, t1->p[%u]=%u, t2->p[%u]=%u\n", ww, ((unsigned int *)t1->p)[ww], ww, ((unsigned int *)t2->p)[ww]); continue; } /* end if */ } /* end for */ @@ -1496,7 +1498,7 @@ static int testfl_VLof_VLtype(void) hid_t vlofvl=H5I_INVALID_HID; /* VL datatype of VL datatypes */ hsize_t count; /* Number of records in the table */ hvl_t *t1; /* pointer to advance */ - int ii, jj, kk; /* Loop variables */ + unsigned uu, vv, ww; /* Loop variables */ hvl_t writeBuf[NRECORDS]; /* Buffer to hold data to be written */ hvl_t readBuf[NRECORDS]; /* Buffer to hold read data */ char msg[80]; /* For error message */ @@ -1505,23 +1507,23 @@ static int testfl_VLof_VLtype(void) TESTING3(" with vlen datatype of vlen datatype"); /* Allocate and initialize VL data to write (copied from C test) */ - for (ii=0; ii< NRECORDS; ii++) { - writeBuf[ii].p = HDmalloc((ii+1)*sizeof(hvl_t)); - if (writeBuf[ii].p == NULL) { - fprintf(stderr, "Cannot allocate memory for VL data! ii=%u\n",ii); + for (uu = 0; uu < NRECORDS; uu++) { + writeBuf[uu].p = HDmalloc((uu + 1) * sizeof(hvl_t)); + if (writeBuf[uu].p == NULL) { + fprintf(stderr, "Cannot allocate memory for VL data! uu=%u\n", uu); goto error; } /* end if */ - writeBuf[ii].len = ii+1; - for (t1=(hvl_t *)(writeBuf[ii].p), jj=0; jj<(ii+1); jj++, t1++) + writeBuf[uu].len = uu + 1; + for (t1 = (hvl_t *)(writeBuf[uu].p), vv = 0; vv < (uu + 1); vv++, t1++) { - t1->p = HDmalloc((jj+1)*sizeof(unsigned int)); + t1->p = HDmalloc((vv + 1) * sizeof(unsigned int)); if (t1->p == NULL) { - fprintf(stderr, "Cannot allocate memory for VL data! ii=%u\n",ii); + fprintf(stderr, "Cannot allocate memory for VL data! uu=%u\n", uu); goto error; } - t1->len = jj+1; - for (kk=0; kk<(jj+1); kk++) - ((unsigned int *)t1->p)[kk] = ii*100+jj*10+kk; + t1->len = vv + 1; + for (ww = 0; ww < (vv + 1); ww++) + ((unsigned int *)t1->p)[ww] = uu * 100 + vv * 10 + ww; } /* end for */ } /* end for */ diff --git a/src/H5FSstat.c b/src/H5FSstat.c index d2c0177..3200849 100644 --- a/src/H5FSstat.c +++ b/src/H5FSstat.c @@ -96,7 +96,7 @@ H5FS_stat_info(const H5F_t *f, const H5FS_t *frsp, H5FS_stat_t *stats) stats->serial_sect_count = frsp->serial_sect_count; stats->ghost_sect_count = frsp->ghost_sect_count; stats->addr = frsp->addr; - stats->hdr_size = (size_t)H5FS_HEADER_SIZE(f); + stats->hdr_size = (hsize_t)H5FS_HEADER_SIZE(f); stats->sect_addr = frsp->sect_addr; stats->alloc_sect_size = frsp->alloc_sect_size; stats->sect_size = frsp->sect_size; diff --git a/src/H5Oattr.c b/src/H5Oattr.c index 9cbcdc4..064c4cb 100644 --- a/src/H5Oattr.c +++ b/src/H5Oattr.c @@ -128,6 +128,9 @@ H5O_attr_decode(H5F_t *f, hid_t dxpl_id, H5O_t *open_oh, unsigned H5_ATTR_UNUSED H5A_t *attr = NULL; H5S_extent_t *extent; /*extent dimensionality information */ size_t name_len; /*attribute name length */ + size_t dt_size; /* Datatype size */ + hssize_t sds_size; /* Signed Dataspace size */ + hsize_t ds_size; /* Dataspace size */ unsigned flags = 0; /* Attribute flags */ H5A_t *ret_value = NULL; /* Return value */ @@ -199,7 +202,7 @@ H5O_attr_decode(H5F_t *f, hid_t dxpl_id, H5O_t *open_oh, unsigned H5_ATTR_UNUSED /* Decode attribute's dataspace extent */ if((extent = (H5S_extent_t *)(H5O_MSG_SDSPACE->decode)(f, dxpl_id, open_oh, - ((flags & H5O_ATTR_FLAG_SPACE_SHARED) ? H5O_MSG_FLAG_SHARED : 0), ioflags, p)) == NULL) + ((flags & H5O_ATTR_FLAG_SPACE_SHARED) ? H5O_MSG_FLAG_SHARED : 0), ioflags, p)) == NULL) HGOTO_ERROR(H5E_ATTR, H5E_CANTDECODE, NULL, "can't decode attribute dataspace") /* Copy the extent information to the dataspace */ @@ -217,8 +220,19 @@ H5O_attr_decode(H5F_t *f, hid_t dxpl_id, H5O_t *open_oh, unsigned H5_ATTR_UNUSED else p += attr->shared->ds_size; + /* Get the datatype's size */ + if(0 == (dt_size = H5T_get_size(attr->shared->dt))) + HGOTO_ERROR(H5E_ATTR, H5E_CANTGET, NULL, "unable to get datatype size") + + /* Get the datatype & dataspace sizes */ + if(0 == (dt_size = H5T_get_size(attr->shared->dt))) + HGOTO_ERROR(H5E_ATTR, H5E_CANTGET, NULL, "unable to get datatype size") + if((sds_size = H5S_GET_EXTENT_NPOINTS(attr->shared->ds)) < 0) + HGOTO_ERROR(H5E_ATTR, H5E_CANTGET, NULL, "unable to get dataspace size") + ds_size = (hsize_t)sds_size; + /* Compute the size of the data */ - H5_CHECKED_ASSIGN(attr->shared->data_size, size_t, H5S_GET_EXTENT_NPOINTS(attr->shared->ds) * H5T_get_size(attr->shared->dt), hsize_t); + H5_CHECKED_ASSIGN(attr->shared->data_size, size_t, ds_size * (hsize_t)dt_size, hsize_t); /* Go get the data */ if(attr->shared->data_size) { diff --git a/test/H5srcdir.h b/test/H5srcdir.h index 81624d8..2f04295 100644 --- a/test/H5srcdir.h +++ b/test/H5srcdir.h @@ -31,26 +31,9 @@ static char srcdir_path[1024] = ""; /* Buffer to construct file in and return pointer to */ static char srcdir_testpath[1024] = ""; -/* Append the test file name to the srcdir path and return the whole string */ -static const char *H5_get_srcdir_filename(const char *filename) -{ - const char *srcdir = HDgetenv("srcdir"); - - /* Check for using the srcdir from configure time */ - if(NULL == srcdir) - srcdir = config_srcdir; - - /* Build path to test file */ - if((HDstrlen(srcdir) + HDstrlen(filename) + 2) < sizeof(srcdir_testpath)) { - HDsnprintf(srcdir_testpath, sizeof(srcdir_testpath), "%s/%s", srcdir, filename); - return(srcdir_testpath); - } /* end if */ - else - return(NULL); -} - /* Just return the srcdir path */ -static const char *H5_get_srcdir(void) +static const char * +H5_get_srcdir(void) { const char *srcdir = HDgetenv("srcdir"); @@ -65,6 +48,25 @@ static const char *H5_get_srcdir(void) } /* end if */ else return(NULL); -} +} /* end H5_get_srcdir() */ + +/* Append the test file name to the srcdir path and return the whole string */ +static const char *H5_get_srcdir_filename(const char *filename) +{ + const char *srcdir = H5_get_srcdir(); + + /* Check for error */ + if(NULL == srcdir) + return(NULL); + else { + /* Build path to test file */ + if((HDstrlen(srcdir) + HDstrlen(filename) + 1) < sizeof(srcdir_testpath)) { + HDsnprintf(srcdir_testpath, sizeof(srcdir_testpath), "%s%s", srcdir, filename); + return(srcdir_testpath); + } /* end if */ + else + return(NULL); + } /* end else */ +} /* end H5_get_srcdir_filename() */ #endif /* _H5SRCDIR_H */ diff --git a/test/tsohm.c b/test/tsohm.c index b3ffac7..9d56fcc 100644 --- a/test/tsohm.c +++ b/test/tsohm.c @@ -1681,8 +1681,8 @@ size2_helper(hid_t fcpl_id, int test_file_closing, size2_helper_struct *ret_size for(x = 0; x < NUM_ATTRIBUTES; ++x) { /* Create a unique name and value for each attribute */ - attr_string1[0] = attr_name[0] = (x / 10) + '0'; - attr_string1[1] = attr_name[1] = (x % 10) + '0'; + attr_string1[0] = attr_name[0] = (char)((x / 10) + '0'); + attr_string1[1] = attr_name[1] = (char)((x % 10) + '0'); /* Create an attribute on the group */ attr_id = H5Acreate2(group_id, attr_name, attr_type_id, attr_space_id, H5P_DEFAULT, H5P_DEFAULT); @@ -1721,8 +1721,8 @@ size2_helper(hid_t fcpl_id, int test_file_closing, size2_helper_struct *ret_size for(x=0; x norm_sizes.empty_size * OVERHEAD_ALLOWED) + if(list_index_med.empty_size > (h5_stat_size_t)((float)norm_sizes.empty_size * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); @@ -2258,7 +2258,7 @@ static void test_sohm_size2(int close_reopen) */ if(list_index_med.dsets2 >= btree_index.dsets2) VERIFY(list_index_med.dsets2, 1, "h5_get_file_size"); - if(btree_index.dsets2 > list_index_small.dsets2 * OVERHEAD_ALLOWED) + if(btree_index.dsets2 > (h5_stat_size_t)((float)list_index_small.dsets2 * OVERHEAD_ALLOWED)) VERIFY(btree_index.dsets2, list_index_small.dsets2, "h5_get_file_size"); if(list_index_small.dsets2 >= norm_sizes.dsets2) VERIFY(btree_index.dsets2, 1, "h5_get_file_size"); @@ -2267,7 +2267,7 @@ static void test_sohm_size2(int close_reopen) * It seems that the small lists tends to be pretty big anyway. Allow * for it to have twice as much overhead. */ - if(list_index_small.dsets2 > btree_index.dsets2 * OVERHEAD_ALLOWED * OVERHEAD_ALLOWED) + if(list_index_small.dsets2 > (h5_stat_size_t)((float)btree_index.dsets2 * OVERHEAD_ALLOWED * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); /* The lists should have grown the least since they share messages and * have no extra overhead. The normal file should have grown more than @@ -2291,7 +2291,7 @@ static void test_sohm_size2(int close_reopen) */ if(list_index_med.interleaved >= btree_index.interleaved) VERIFY(0, 1, "h5_get_file_size"); - if(btree_index.interleaved > list_index_small.interleaved * OVERHEAD_ALLOWED) + if(btree_index.interleaved > (h5_stat_size_t)((float)list_index_small.interleaved * OVERHEAD_ALLOWED)) VERIFY(btree_index.interleaved, list_index_small.interleaved, "h5_get_file_size"); if(list_index_small.interleaved >= norm_sizes.interleaved) VERIFY(0, 1, "h5_get_file_size"); @@ -2318,22 +2318,21 @@ static void test_sohm_size2(int close_reopen) * that started as a B-tree. * Add in OVERHEAD_ALLOWED as a fudge factor here, since the allocation * of file space can be hard to predict. - */ - if(btree_index.attrs1 > list_index_small.attrs1 * OVERHEAD_ALLOWED) + if(btree_index.attrs1 > (h5_stat_size_t)((float)list_index_small.attrs1 * OVERHEAD_ALLOWED)) VERIFY(btree_index.attrs1, list_index_small.attrs1, "h5_get_file_size"); - if(btree_index.attrs1 > list_index_med.attrs1 * OVERHEAD_ALLOWED) + if(btree_index.attrs1 > (h5_stat_size_t)((float)list_index_med.attrs1 * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); - if(list_index_med.attrs1 > btree_index.attrs1 * OVERHEAD_ALLOWED) + if(list_index_med.attrs1 > (h5_stat_size_t)((float)btree_index.attrs1 * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); - if(list_index_small.attrs1 > btree_index.attrs1 * OVERHEAD_ALLOWED) + if(list_index_small.attrs1 > (h5_stat_size_t)((float)btree_index.attrs1 * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); /* Neither of the converted lists should be too much bigger than * the index that was originally a B-tree. */ - if(list_index_small.attrs1 > btree_index.attrs1 * OVERHEAD_ALLOWED) + if(list_index_small.attrs1 > (h5_stat_size_t)((float)btree_index.attrs1 * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); - if(list_index_med.attrs1 > btree_index.attrs1 * OVERHEAD_ALLOWED) + if(list_index_med.attrs1 > (h5_stat_size_t)((float)btree_index.attrs1 * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); /* The "normal" file should have had less overhead, so should gain less * size than any of the other indexes since none of these attribute @@ -2349,7 +2348,7 @@ static void test_sohm_size2(int close_reopen) /* Give it some overhead (for checkin to move messages into continuation message) */ if((list_index_small.attrs1 - list_index_small.interleaved) > - ((btree_index.attrs1 - btree_index.interleaved) * OVERHEAD_ALLOWED)) + (h5_stat_size_t)((float)(btree_index.attrs1 - btree_index.interleaved) * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); @@ -2357,13 +2356,13 @@ static void test_sohm_size2(int close_reopen) * of sizes. The big list index is still too big to be smaller than a * normal file. The B-tree indexes should all be about the same size. */ - if(btree_index.attrs2 > list_index_small.attrs2 * OVERHEAD_ALLOWED) + if(btree_index.attrs2 > (h5_stat_size_t)((float)list_index_small.attrs2 * OVERHEAD_ALLOWED)) VERIFY(btree_index.attrs2, list_index_small.attrs2, "h5_get_file_size"); - if(list_index_small.attrs2 > btree_index.attrs2 * OVERHEAD_ALLOWED) + if(list_index_small.attrs2 > (h5_stat_size_t)((float)btree_index.attrs2 * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); - if(btree_index.attrs2 > list_index_med.attrs2 * OVERHEAD_ALLOWED) + if(btree_index.attrs2 > (h5_stat_size_t)((float)list_index_med.attrs2 * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); - if(list_index_med.attrs2 > btree_index.attrs2 * OVERHEAD_ALLOWED) + if(list_index_med.attrs2 > (h5_stat_size_t)((float)btree_index.attrs2 * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); if(list_index_med.attrs2 >= norm_sizes.attrs2) VERIFY(0, 1, "h5_get_file_size"); @@ -2451,17 +2450,17 @@ static void test_sohm_size2(int close_reopen) VERIFY((mult_index_btree.dsets1 - mult_index_btree.second_dset), (btree_index.dsets1 - btree_index.second_dset), "h5_get_file_size"); if((mult_index_med.dsets2 - mult_index_med.dsets1) > - (list_index_med.dsets2 - list_index_med.dsets1) * OVERHEAD_ALLOWED) + (h5_stat_size_t)((float)(list_index_med.dsets2 - list_index_med.dsets1) * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); if((mult_index_btree.dsets2 - mult_index_btree.dsets1) > - (btree_index.dsets2 - btree_index.dsets1) * OVERHEAD_ALLOWED) + (h5_stat_size_t)((float)(btree_index.dsets2 - btree_index.dsets1) * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); if((mult_index_med.interleaved - mult_index_med.dsets2) > - (list_index_med.interleaved - list_index_med.dsets2) * OVERHEAD_ALLOWED) + (h5_stat_size_t)((float)(list_index_med.interleaved - list_index_med.dsets2) * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); if((mult_index_btree.interleaved - mult_index_btree.dsets2) > - (btree_index.interleaved - btree_index.dsets2) * OVERHEAD_ALLOWED) + (h5_stat_size_t)((float)(btree_index.interleaved - btree_index.dsets2) * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); /* When all the attributes are added, only the index holding attributes @@ -2470,10 +2469,10 @@ static void test_sohm_size2(int close_reopen) * will take. */ if((mult_index_med.attrs2 - mult_index_med.attrs1) > - (list_index_med.attrs2 - list_index_med.attrs1) * OVERHEAD_ALLOWED) + (h5_stat_size_t)((float)(list_index_med.attrs2 - list_index_med.attrs1) * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); if((mult_index_btree.attrs2 - mult_index_btree.attrs1) > - (btree_index.attrs2 - btree_index.attrs1) * OVERHEAD_ALLOWED) + (h5_stat_size_t)((float)(btree_index.attrs2 - btree_index.attrs1) * OVERHEAD_ALLOWED)) VERIFY(0, 1, "h5_get_file_size"); /* The final file size for both of the multiple index files should be @@ -2483,9 +2482,9 @@ static void test_sohm_size2(int close_reopen) VERIFY(0, 1, "h5_get_file_size"); if(mult_index_btree.attrs2 >= norm_sizes.attrs2) VERIFY(0, 1, "h5_get_file_size"); - if(mult_index_med.attrs2 * OVERHEAD_ALLOWED < btree_index.attrs2) + if((h5_stat_size_t)((float)mult_index_med.attrs2 * OVERHEAD_ALLOWED) < btree_index.attrs2) VERIFY(0, 1, "h5_get_file_size"); - if(mult_index_btree.attrs2 * OVERHEAD_ALLOWED < btree_index.attrs2) + if((h5_stat_size_t)((float)mult_index_btree.attrs2 * OVERHEAD_ALLOWED) < btree_index.attrs2) VERIFY(0, 1, "h5_get_file_size"); @@ -2554,39 +2553,39 @@ static void test_sohm_size2(int close_reopen) if(share_tiny_index.empty_size != type_space_index.empty_size) VERIFY(share_tiny_index.empty_size, type_space_index.empty_size, "h5_get_file_size"); - if(share_tiny_index.first_dset >= type_space_index.first_dset * OVERHEAD_ALLOWED) + if(share_tiny_index.first_dset >= (h5_stat_size_t)((float)type_space_index.first_dset * OVERHEAD_ALLOWED)) VERIFY(share_tiny_index.first_dset, type_space_index.first_dset, "h5_get_file_size"); if(share_tiny_index.first_dset < type_space_index.first_dset) VERIFY(0, 1, "h5_get_file_size"); if(share_tiny_index.second_dset >= type_space_index.second_dset) VERIFY(share_tiny_index.second_dset, type_space_index.second_dset, "h5_get_file_size"); - if(share_tiny_index.second_dset * OVERHEAD_ALLOWED < type_space_index.second_dset) + if((h5_stat_size_t)((float)share_tiny_index.second_dset * OVERHEAD_ALLOWED) < type_space_index.second_dset) VERIFY(0, 1, "h5_get_file_size"); if(share_tiny_index.dsets1 >= type_space_index.dsets1) VERIFY(0, 1, "h5_get_file_size"); - if(share_tiny_index.dsets1 * OVERHEAD_ALLOWED < type_space_index.dsets1) + if((h5_stat_size_t)((float)share_tiny_index.dsets1 * OVERHEAD_ALLOWED) < type_space_index.dsets1) VERIFY(0, 1, "h5_get_file_size"); if(share_tiny_index.dsets2 >= type_space_index.dsets2) VERIFY(0, 1, "h5_get_file_size"); - if(share_tiny_index.dsets2 * OVERHEAD_ALLOWED < type_space_index.dsets2) + if((h5_stat_size_t)((float)share_tiny_index.dsets2 * OVERHEAD_ALLOWED) < type_space_index.dsets2) VERIFY(0, 1, "h5_get_file_size"); if(share_tiny_index.interleaved >= type_space_index.interleaved) VERIFY(0, 1, "h5_get_file_size"); - if(share_tiny_index.interleaved * OVERHEAD_ALLOWED < type_space_index.interleaved) + if((h5_stat_size_t)((float)share_tiny_index.interleaved * OVERHEAD_ALLOWED) < type_space_index.interleaved) VERIFY(0, 1, "h5_get_file_size"); if(share_tiny_index.attrs1 >= type_space_index.attrs1) VERIFY(0, 1, "h5_get_file_size"); - if(share_tiny_index.attrs1 * OVERHEAD_ALLOWED < type_space_index.attrs1) + if((h5_stat_size_t)((float)share_tiny_index.attrs1 * OVERHEAD_ALLOWED) < type_space_index.attrs1) VERIFY(0, 1, "h5_get_file_size"); if(share_tiny_index.attrs2 >= type_space_index.attrs2) VERIFY(0, 1, "h5_get_file_size"); - if(share_tiny_index.attrs2 * OVERHEAD_ALLOWED < type_space_index.attrs2) + if((h5_stat_size_t)((float)share_tiny_index.attrs2 * OVERHEAD_ALLOWED) < type_space_index.attrs2) VERIFY(0, 1, "h5_get_file_size"); } /* end test_sohm_size2() */ @@ -2616,7 +2615,7 @@ static void delete_helper_write(hid_t file_id, hid_t *dspace_id, hid_t *dcpl_id, CHECK_I(dset_id, "H5Dcreate2"); /* Write data to dataset */ - wdata = x + 'a'; + wdata = (char)(x + 'a'); ret = H5Dwrite(dset_id, H5T_NATIVE_CHAR, dspace_id[x], dspace_id[x], H5P_DEFAULT, &wdata); CHECK_I(ret, "H5Dwrite"); @@ -2764,9 +2763,9 @@ static void delete_helper(hid_t fcpl_id, hid_t *dspace_id, hid_t *dcpl_id) deleted_filesize = h5_get_file_size(FILENAME, H5P_DEFAULT); /* The two filesizes should be almost the same */ - if(norm_filesize > deleted_filesize * OVERHEAD_ALLOWED) + if(norm_filesize > (h5_stat_size_t)((float)deleted_filesize * OVERHEAD_ALLOWED)) VERIFY(norm_filesize, deleted_filesize, "h5_get_file_size"); - if(deleted_filesize > norm_filesize * OVERHEAD_ALLOWED) + if(deleted_filesize > (h5_stat_size_t)((float)norm_filesize * OVERHEAD_ALLOWED)) VERIFY(deleted_filesize, norm_filesize, "h5_get_file_size"); } @@ -3887,8 +3886,8 @@ test_sohm_external_dtype(void) orig = (s1_t*)HDmalloc(NX * NY * sizeof(s1_t)); for(i=0; ia = i*3 + 1; - s_ptr->b = i*3 + 2; + s_ptr->a = (int)(i * 3 + 1); + s_ptr->b = (int)(i * 3 + 2); } /* Write the data to the dataset1 */ -- cgit v0.12 From 267787999532fa12bd36d3eb3ea334a864d4b1a1 Mon Sep 17 00:00:00 2001 From: Quincey Koziol Date: Thu, 7 Jul 2016 16:38:35 -0500 Subject: [svn-r30161] Description: Switch from atoll to strtoull, to make VS2012 happy. Tested on: MacOSX/64 10.11.5 (amazon) w/serial & parallel (h5committest forthcoming) --- tools/h5dump/h5dump.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tools/h5dump/h5dump.c b/tools/h5dump/h5dump.c index 3b46912..562cfd5 100644 --- a/tools/h5dump/h5dump.c +++ b/tools/h5dump/h5dump.c @@ -638,7 +638,7 @@ parse_hsize_list(const char *h_list, subset_d *d) for (ptr = h_list; i < size_count && ptr && *ptr && *ptr != ';' && *ptr != ']'; ptr++) if(HDisdigit(*ptr)) { /* we should have an integer now */ - p_list[i++] = (hsize_t)HDatoll(ptr); + p_list[i++] = (hsize_t)HDstrtoull(ptr, NULL, 0); while (HDisdigit(*ptr)) /* scroll to end of integer */ -- cgit v0.12 From b2c8ac133cba4e9265b4f40c4c2d085f8d72f92e Mon Sep 17 00:00:00 2001 From: Dana Robinson Date: Sat, 9 Jul 2016 01:43:11 -0500 Subject: [svn-r30163] Changed a h5_fileaccess() call to H5Pcreate() in the core VFD test. Since it only tests the core VFD, there's no need to get a VFD-dependent fapl. Tested on: 64-bit Ubuntu Linux w/ gcc 5.3.1 vfd test w/ all VFDs tested by make check-vfd --- test/vfd.c | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/test/vfd.c b/test/vfd.c index 596d39a..c947589 100644 --- a/test/vfd.c +++ b/test/vfd.c @@ -196,7 +196,8 @@ test_core(void) h5_reset(); /* Get a file access property list and fix up the file name */ - fapl_id = h5_fileaccess(); + if((fapl_id = H5Pcreate(H5P_FILE_ACCESS)) < 0) + FAIL_STACK_ERROR; h5_fixname(FILENAME[1], fapl_id, filename, sizeof(filename)); /************************************************************************ -- cgit v0.12 From c8f4641507bf4ca85c70c39c786c07f8ef4a24ed Mon Sep 17 00:00:00 2001 From: Dana Robinson Date: Thu, 14 Jul 2016 08:55:50 -0500 Subject: [svn-r30184] Converted h5_fileaccess() to H5Pcreate() in the sec2 test. Tested on: 64-bit Ubuntu Linux 16.04 LTS w/ gcc 5.4.0 Autotools serial, vfd test only w/ various VFDs --- test/vfd.c | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/test/vfd.c b/test/vfd.c index c947589..daac185 100644 --- a/test/vfd.c +++ b/test/vfd.c @@ -97,7 +97,8 @@ test_sec2(void) h5_reset(); /* Set property list and file name for SEC2 driver. */ - fapl_id = h5_fileaccess(); + if((fapl_id = H5Pcreate(H5P_FILE_ACCESS)) < 0) + FAIL_STACK_ERROR; if(H5Pset_fapl_sec2(fapl_id) < 0) FAIL_STACK_ERROR; h5_fixname(FILENAME[0], fapl_id, filename, sizeof(filename)); -- cgit v0.12 From bb19817c9fd5d46cdc1ab5a396f38f0561dfa167 Mon Sep 17 00:00:00 2001 From: Quincey Koziol Date: Sun, 17 Jul 2016 19:18:42 -0500 Subject: [svn-r30189] Description: Clean up more warnings: drop the warning count from ~1310 down to ~940, with only 31 types of warnings in 148 files (down from 38 types in 167 files). Tested on: MacOSX/64 10.11.5 (amazon) w/serial & parallel (h5committest forthcoming) --- hl/test/test_dset_append.c | 1 - hl/test/test_dset_opt.c | 1 - src/H5Dchunk.c | 19 +- src/H5Dfill.c | 25 +- src/H5Dio.c | 37 +- src/H5Dscatgath.c | 333 ++++++++--------- src/H5Dselect.c | 84 ++--- src/H5FDfamily.c | 44 ++- src/H5FL.c | 18 +- src/H5FLprivate.h | 12 +- src/H5HFcache.c | 4 +- src/H5Oalloc.c | 5 +- src/H5Ocache.c | 4 +- src/H5Pfapl.c | 2 +- src/H5Shyper.c | 60 ++-- src/H5Sselect.c | 111 ++++-- src/H5system.c | 29 +- src/H5timer.c | 38 +- test/cmpd_dset.c | 185 +++++----- test/dsets.c | 659 ++++++++++++++++++++-------------- test/file_image.c | 1 - test/filter_fail.c | 1 - test/freespace.c | 16 +- test/getname.c | 89 ++--- test/links.c | 1 - test/mtime.c | 2 +- test/ohdr.c | 1 - test/set_extent.c | 6 +- test/testframe.c | 4 +- test/tmeta.c | 2 +- test/tvltypes.c | 94 ++--- test/vds.c | 1 - testpar/t_shapesame.c | 16 +- tools/h5copy/h5copy.c | 24 +- tools/h5diff/h5diff_main.c | 5 +- tools/h5diff/h5diffgentest.c | 217 ++++++----- tools/h5format_convert/h5fc_gentest.c | 4 +- tools/h5jam/h5unjam.c | 10 +- tools/h5ls/h5ls.c | 10 +- tools/h5repack/h5repack.c | 5 +- tools/h5repack/h5repack_filters.c | 17 +- tools/lib/h5tools_filters.c | 4 +- tools/lib/h5tools_ref.c | 2 +- tools/perform/sio_engine.c | 32 +- tools/perform/sio_perf.c | 89 ++--- tools/perform/sio_perf.h | 32 +- tools/perform/zip_perf.c | 24 +- 47 files changed, 1316 insertions(+), 1064 deletions(-) diff --git a/hl/test/test_dset_append.c b/hl/test/test_dset_append.c index 0f193d9..57dab81 100644 --- a/hl/test/test_dset_append.c +++ b/hl/test/test_dset_append.c @@ -16,7 +16,6 @@ #include #include #include "h5hltest.h" -#include "H5srcdir.h" #include "H5DOpublic.h" #include diff --git a/hl/test/test_dset_opt.c b/hl/test/test_dset_opt.c index c1e369e..b03ab44 100644 --- a/hl/test/test_dset_opt.c +++ b/hl/test/test_dset_opt.c @@ -16,7 +16,6 @@ #include #include #include "h5hltest.h" -#include "H5srcdir.h" #include "H5DOpublic.h" #include diff --git a/src/H5Dchunk.c b/src/H5Dchunk.c index 8cf86ac..dde83fe 100644 --- a/src/H5Dchunk.c +++ b/src/H5Dchunk.c @@ -364,6 +364,9 @@ H5FL_DEFINE(H5D_chunk_info_t); /* Declare a free list to manage the chunk sequence information */ H5FL_BLK_DEFINE_STATIC(chunk); +/* Declare extern free list to manage the H5S_sel_iter_t struct */ +H5FL_EXTERN(H5S_sel_iter_t); + /*------------------------------------------------------------------------- * Function: H5D__chunk_direct_write @@ -4557,14 +4560,14 @@ H5D__chunk_prune_fill(H5D_chunk_it_ud1_t *udata, hbool_t new_unfilt_chunk) const H5O_layout_t *layout = &(dset->shared->layout); /* Dataset's layout */ unsigned rank = udata->common.layout->ndims - 1; /* Dataset rank */ const hsize_t *scaled = udata->common.scaled; /* Scaled chunk offset */ - H5S_sel_iter_t chunk_iter; /* Memory selection iteration info */ + H5S_sel_iter_t *chunk_iter = NULL; /* Memory selection iteration info */ + hbool_t chunk_iter_init = FALSE; /* Whether the chunk iterator has been initialized */ hssize_t sel_nelmts; /* Number of elements in selection */ hsize_t count[H5O_LAYOUT_NDIMS]; /* Element count of hyperslab */ size_t chunk_size; /*size of a chunk */ void *chunk; /* The file chunk */ H5D_chunk_ud_t chk_udata; /* User data for locking chunk */ uint32_t bytes_accessed; /* Bytes accessed in chunk */ - hbool_t chunk_iter_init = FALSE; /* Whether the chunk iterator has been initialized */ unsigned u; /* Local index variable */ herr_t ret_value = SUCCEED; /* Return value */ @@ -4629,13 +4632,17 @@ H5D__chunk_prune_fill(H5D_chunk_it_ud1_t *udata, hbool_t new_unfilt_chunk) if(H5D__fill_refill_vl(&udata->fb_info, (size_t)sel_nelmts, io_info->md_dxpl_id) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTCONVERT, FAIL, "can't refill fill value buffer") + /* Allocate the chunk selection iterator */ + if(NULL == (chunk_iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate chunk selection iterator") + /* Create a selection iterator for scattering the elements to memory buffer */ - if(H5S_select_iter_init(&chunk_iter, udata->chunk_space, layout->u.chunk.dim[rank]) < 0) + if(H5S_select_iter_init(chunk_iter, udata->chunk_space, layout->u.chunk.dim[rank]) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize chunk selection information") chunk_iter_init = TRUE; /* Scatter the data into memory */ - if(H5D__scatter_mem(udata->fb_info.fill_buf, udata->chunk_space, &chunk_iter, (size_t)sel_nelmts, io_info->dxpl_cache, chunk/*out*/) < 0) + if(H5D__scatter_mem(udata->fb_info.fill_buf, udata->chunk_space, chunk_iter, (size_t)sel_nelmts, io_info->dxpl_cache, chunk/*out*/) < 0) HGOTO_ERROR(H5E_DATASET, H5E_WRITEERROR, FAIL, "scatter failed") @@ -4650,8 +4657,10 @@ H5D__chunk_prune_fill(H5D_chunk_it_ud1_t *udata, hbool_t new_unfilt_chunk) done: /* Release the selection iterator */ - if(chunk_iter_init && H5S_SELECT_ITER_RELEASE(&chunk_iter) < 0) + if(chunk_iter_init && H5S_SELECT_ITER_RELEASE(chunk_iter) < 0) HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") + if(chunk_iter) + chunk_iter = H5FL_FREE(H5S_sel_iter_t, chunk_iter); FUNC_LEAVE_NOAPI(ret_value) } /* H5D__chunk_prune_fill */ diff --git a/src/H5Dfill.c b/src/H5Dfill.c index e5b2161..50c964b 100644 --- a/src/H5Dfill.c +++ b/src/H5Dfill.c @@ -88,6 +88,9 @@ H5FL_BLK_DEFINE_STATIC(non_zero_fill); /* Declare the free list to manage blocks of zero fill-value data */ H5FL_BLK_DEFINE_STATIC(zero_fill); +/* Declare extern free list to manage the H5S_sel_iter_t struct */ +H5FL_EXTERN(H5S_sel_iter_t); + /*-------------------------------------------------------------------------- NAME @@ -174,6 +177,8 @@ herr_t H5D__fill(const void *fill, const H5T_t *fill_type, void *buf, const H5T_t *buf_type, const H5S_t *space, hid_t dxpl_id) { + H5S_sel_iter_t *mem_iter = NULL; /* Memory selection iteration info */ + hbool_t mem_iter_init = FALSE; /* Whether the memory selection iterator has been initialized */ H5WB_t *elem_wb = NULL; /* Wrapped buffer for element data */ uint8_t elem_buf[H5T_ELEM_BUF_SIZE]; /* Buffer for element data */ H5WB_t *bkg_elem_wb = NULL; /* Wrapped buffer for background data */ @@ -246,7 +251,6 @@ H5D__fill(const void *fill, const H5T_t *fill_type, void *buf, if(TRUE == H5T_detect_class(fill_type, H5T_VLEN, FALSE)) { H5D_dxpl_cache_t _dxpl_cache; /* Data transfer property cache buffer */ H5D_dxpl_cache_t *dxpl_cache = &_dxpl_cache; /* Data transfer property cache */ - H5S_sel_iter_t mem_iter; /* Memory selection iteration info */ hssize_t nelmts; /* Number of data elements */ /* Get the number of elements in the selection */ @@ -273,19 +277,18 @@ H5D__fill(const void *fill, const H5T_t *fill_type, void *buf, if(H5D__get_dxpl_cache(dxpl_id, &dxpl_cache) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTGET, FAIL, "can't fill dxpl cache") + /* Allocate the chunk selection iterator */ + if(NULL == (mem_iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate memory selection iterator") + /* Create a selection iterator for scattering the elements to memory buffer */ - if(H5S_select_iter_init(&mem_iter, space, dst_type_size) < 0) + if(H5S_select_iter_init(mem_iter, space, dst_type_size) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize memory selection information") + mem_iter_init = TRUE; /* Scatter the data into memory */ - if(H5D__scatter_mem(tmp_buf, space, &mem_iter, (size_t)nelmts, dxpl_cache, buf/*out*/) < 0) { - H5S_SELECT_ITER_RELEASE(&mem_iter); + if(H5D__scatter_mem(tmp_buf, space, mem_iter, (size_t)nelmts, dxpl_cache, buf/*out*/) < 0) HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "scatter failed") - } /* end if */ - - /* Release the selection iterator */ - if(H5S_SELECT_ITER_RELEASE(&mem_iter) < 0) - HGOTO_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") } /* end if */ else { const uint8_t *fill_buf; /* Buffer to use for writing fill values */ @@ -335,6 +338,10 @@ H5D__fill(const void *fill, const H5T_t *fill_type, void *buf, } /* end else */ done: + if(mem_iter_init && H5S_SELECT_ITER_RELEASE(mem_iter) < 0) + HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") + if(mem_iter) + mem_iter = H5FL_FREE(H5S_sel_iter_t, mem_iter); if(src_id != (-1) && H5I_dec_ref(src_id) < 0) HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't decrement temporary datatype ID") if(dst_id != (-1) && H5I_dec_ref(dst_id) < 0) diff --git a/src/H5Dio.c b/src/H5Dio.c index 5004132..f5087da 100644 --- a/src/H5Dio.c +++ b/src/H5Dio.c @@ -87,6 +87,9 @@ static herr_t H5D__typeinfo_term(const H5D_type_info_t *type_info); /* Declare a free list to manage blocks of type conversion data */ H5FL_BLK_DEFINE(type_conv); +/* Declare a free list to manage the H5D_chunk_map_t struct */ +H5FL_DEFINE(H5D_chunk_map_t); + /*------------------------------------------------------------------------- @@ -366,7 +369,7 @@ herr_t H5D__read(H5D_t *dataset, hid_t mem_type_id, const H5S_t *mem_space, const H5S_t *file_space, hid_t dxpl_id, void *buf/*out*/) { - H5D_chunk_map_t fm; /* Chunk file<->memory mapping */ + H5D_chunk_map_t *fm = NULL; /* Chunk file<->memory mapping */ H5D_io_info_t io_info; /* Dataset I/O info */ H5D_type_info_t type_info; /* Datatype info for operation */ hbool_t type_info_init = FALSE; /* Whether the datatype info has been initialized */ @@ -523,26 +526,31 @@ H5D__read(H5D_t *dataset, hid_t mem_type_id, const H5S_t *mem_space, || dataset->shared->dcpl_cache.efl.nused > 0 || dataset->shared->layout.type == H5D_COMPACT); + /* Allocate the chunk map */ + if(NULL == (fm = H5FL_CALLOC(H5D_chunk_map_t))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate chunk map") + /* Call storage method's I/O initialization routine */ - HDmemset(&fm, 0, sizeof(H5D_chunk_map_t)); - if(io_info.layout_ops.io_init && (*io_info.layout_ops.io_init)(&io_info, &type_info, nelmts, file_space, mem_space, &fm) < 0) + if(io_info.layout_ops.io_init && (*io_info.layout_ops.io_init)(&io_info, &type_info, nelmts, file_space, mem_space, fm) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "can't initialize I/O info") io_op_init = TRUE; #ifdef H5_HAVE_PARALLEL /* Adjust I/O info for any parallel I/O */ - if(H5D__ioinfo_adjust(&io_info, dataset, dxpl_id, file_space, mem_space, &type_info, &fm) < 0) + if(H5D__ioinfo_adjust(&io_info, dataset, dxpl_id, file_space, mem_space, &type_info, fm) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to adjust I/O info for parallel I/O") #endif /*H5_HAVE_PARALLEL*/ /* Invoke correct "high level" I/O routine */ - if((*io_info.io_ops.multi_read)(&io_info, &type_info, nelmts, file_space, mem_space, &fm) < 0) + if((*io_info.io_ops.multi_read)(&io_info, &type_info, nelmts, file_space, mem_space, fm) < 0) HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "can't read data") done: /* Shut down the I/O op information */ - if(io_op_init && io_info.layout_ops.io_term && (*io_info.layout_ops.io_term)(&fm) < 0) + if(io_op_init && io_info.layout_ops.io_term && (*io_info.layout_ops.io_term)(fm) < 0) HDONE_ERROR(H5E_DATASET, H5E_CANTCLOSEOBJ, FAIL, "unable to shut down I/O op info") + if(fm) + fm = H5FL_FREE(H5D_chunk_map_t, fm); if(io_info_init) { #ifdef H5_DEBUG_BUILD @@ -587,7 +595,7 @@ herr_t H5D__write(H5D_t *dataset, hid_t mem_type_id, const H5S_t *mem_space, const H5S_t *file_space, hid_t dxpl_id, const void *buf) { - H5D_chunk_map_t fm; /* Chunk file<->memory mapping */ + H5D_chunk_map_t *fm = NULL; /* Chunk file<->memory mapping */ H5D_io_info_t io_info; /* Dataset I/O info */ H5D_type_info_t type_info; /* Datatype info for operation */ hbool_t type_info_init = FALSE; /* Whether the datatype info has been initialized */ @@ -765,20 +773,23 @@ H5D__write(H5D_t *dataset, hid_t mem_type_id, const H5S_t *mem_space, HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize storage") } /* end if */ + /* Allocate the chunk map */ + if(NULL == (fm = H5FL_CALLOC(H5D_chunk_map_t))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate chunk map") + /* Call storage method's I/O initialization routine */ - HDmemset(&fm, 0, sizeof(H5D_chunk_map_t)); - if(io_info.layout_ops.io_init && (*io_info.layout_ops.io_init)(&io_info, &type_info, nelmts, file_space, mem_space, &fm) < 0) + if(io_info.layout_ops.io_init && (*io_info.layout_ops.io_init)(&io_info, &type_info, nelmts, file_space, mem_space, fm) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "can't initialize I/O info") io_op_init = TRUE; #ifdef H5_HAVE_PARALLEL /* Adjust I/O info for any parallel I/O */ - if(H5D__ioinfo_adjust(&io_info, dataset, dxpl_id, file_space, mem_space, &type_info, &fm) < 0) + if(H5D__ioinfo_adjust(&io_info, dataset, dxpl_id, file_space, mem_space, &type_info, fm) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to adjust I/O info for parallel I/O") #endif /*H5_HAVE_PARALLEL*/ /* Invoke correct "high level" I/O routine */ - if((*io_info.io_ops.multi_write)(&io_info, &type_info, nelmts, file_space, mem_space, &fm) < 0) + if((*io_info.io_ops.multi_write)(&io_info, &type_info, nelmts, file_space, mem_space, fm) < 0) HGOTO_ERROR(H5E_DATASET, H5E_WRITEERROR, FAIL, "can't write data") #ifdef OLD_WAY @@ -801,8 +812,10 @@ H5D__write(H5D_t *dataset, hid_t mem_type_id, const H5S_t *mem_space, done: /* Shut down the I/O op information */ - if(io_op_init && io_info.layout_ops.io_term && (*io_info.layout_ops.io_term)(&fm) < 0) + if(io_op_init && io_info.layout_ops.io_term && (*io_info.layout_ops.io_term)(fm) < 0) HDONE_ERROR(H5E_DATASET, H5E_CANTCLOSEOBJ, FAIL, "unable to shut down I/O op info") + if(fm) + fm = H5FL_FREE(H5D_chunk_map_t, fm); if(io_info_init) { #ifdef H5_DEBUG_BUILD diff --git a/src/H5Dscatgath.c b/src/H5Dscatgath.c index 7c1abca..55111f0 100644 --- a/src/H5Dscatgath.c +++ b/src/H5Dscatgath.c @@ -67,10 +67,13 @@ static herr_t H5D__compound_opt_write(size_t nelmts, const H5D_type_info_t *type /* Local Variables */ /*******************/ -/* Declare a free list to manage sequences of size_t */ +/* Declare extern free list to manage the H5S_sel_iter_t struct */ +H5FL_EXTERN(H5S_sel_iter_t); + +/* Declare extern free list to manage sequences of size_t */ H5FL_SEQ_EXTERN(size_t); -/* Declare a free list to manage sequences of hsize_t */ +/* Declare extern free list to manage sequences of hsize_t */ H5FL_SEQ_EXTERN(hsize_t); @@ -97,17 +100,16 @@ H5D__scatter_file(const H5D_io_info_t *_io_info, const void *_buf) { H5D_io_info_t tmp_io_info; /* Temporary I/O info object */ - hsize_t _off[H5D_IO_VECTOR_SIZE]; /* Array to store sequence offsets */ hsize_t *off = NULL; /* Pointer to sequence offsets */ hsize_t mem_off; /* Offset in memory */ size_t mem_curr_seq; /* "Current sequence" in memory */ size_t dset_curr_seq; /* "Current sequence" in dataset */ - size_t _len[H5D_IO_VECTOR_SIZE]; /* Array to store sequence lengths */ size_t *len = NULL; /* Array to store sequence lengths */ size_t orig_mem_len, mem_len; /* Length of sequence in memory */ - size_t nseq; /* Number of sequences generated */ - size_t nelem; /* Number of elements used in sequences */ - herr_t ret_value = SUCCEED; /* Return value */ + size_t nseq; /* Number of sequences generated */ + size_t nelem; /* Number of elements used in sequences */ + size_t vec_size; /* Vector length */ + herr_t ret_value = SUCCEED; /* Return value */ FUNC_ENTER_STATIC @@ -124,21 +126,19 @@ H5D__scatter_file(const H5D_io_info_t *_io_info, tmp_io_info.u.wbuf = _buf; /* Allocate the vector I/O arrays */ - if(tmp_io_info.dxpl_cache->vec_size > H5D_IO_VECTOR_SIZE) { - if(NULL == (len = H5FL_SEQ_MALLOC(size_t, tmp_io_info.dxpl_cache->vec_size))) - HGOTO_ERROR(H5E_RESOURCE, H5E_NOSPACE, FAIL, "can't allocate I/O length vector array") - if(NULL == (off = H5FL_SEQ_MALLOC(hsize_t, tmp_io_info.dxpl_cache->vec_size))) - HGOTO_ERROR(H5E_RESOURCE, H5E_NOSPACE, FAIL, "can't allocate I/O offset vector array") - } /* end if */ - else { - len = _len; - off = _off; - } /* end else */ + if(tmp_io_info.dxpl_cache->vec_size > H5D_IO_VECTOR_SIZE) + vec_size = tmp_io_info.dxpl_cache->vec_size; + else + vec_size = H5D_IO_VECTOR_SIZE; + if(NULL == (len = H5FL_SEQ_MALLOC(size_t, vec_size))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate I/O length vector array") + if(NULL == (off = H5FL_SEQ_MALLOC(hsize_t, vec_size))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate I/O offset vector array") /* Loop until all elements are written */ while(nelmts > 0) { /* Get list of sequences for selection to write */ - if(H5S_SELECT_GET_SEQ_LIST(space, H5S_GET_SEQ_LIST_SORTED, iter, tmp_io_info.dxpl_cache->vec_size, nelmts, &nseq, &nelem, off, len) < 0) + if(H5S_SELECT_GET_SEQ_LIST(space, H5S_GET_SEQ_LIST_SORTED, iter, vec_size, nelmts, &nseq, &nelem, off, len) < 0) HGOTO_ERROR(H5E_INTERNAL, H5E_UNSUPPORTED, FAIL, "sequence length generation failed") /* Reset the current sequence information */ @@ -160,9 +160,9 @@ H5D__scatter_file(const H5D_io_info_t *_io_info, done: /* Release resources, if allocated */ - if(len && len != _len) + if(len) len = H5FL_SEQ_FREE(size_t, len); - if(off && off != _off) + if(off) off = H5FL_SEQ_FREE(hsize_t, off); FUNC_LEAVE_NOAPI(ret_value) @@ -196,16 +196,15 @@ H5D__gather_file(const H5D_io_info_t *_io_info, void *_buf/*out*/) { H5D_io_info_t tmp_io_info; /* Temporary I/O info object */ - hsize_t _off[H5D_IO_VECTOR_SIZE]; /* Array to store sequence offsets */ hsize_t *off = NULL; /* Pointer to sequence offsets */ hsize_t mem_off; /* Offset in memory */ size_t mem_curr_seq; /* "Current sequence" in memory */ size_t dset_curr_seq; /* "Current sequence" in dataset */ - size_t _len[H5D_IO_VECTOR_SIZE]; /* Array to store sequence lengths */ size_t *len = NULL; /* Pointer to sequence lengths */ size_t orig_mem_len, mem_len; /* Length of sequence in memory */ size_t nseq; /* Number of sequences generated */ size_t nelem; /* Number of elements used in sequences */ + size_t vec_size; /* Vector length */ size_t ret_value = nelmts; /* Return value */ FUNC_ENTER_STATIC @@ -225,21 +224,19 @@ H5D__gather_file(const H5D_io_info_t *_io_info, tmp_io_info.u.rbuf = _buf; /* Allocate the vector I/O arrays */ - if(tmp_io_info.dxpl_cache->vec_size > H5D_IO_VECTOR_SIZE) { - if(NULL == (len = H5FL_SEQ_MALLOC(size_t, tmp_io_info.dxpl_cache->vec_size))) - HGOTO_ERROR(H5E_RESOURCE, H5E_NOSPACE, 0, "can't allocate I/O length vector array") - if(NULL == (off = H5FL_SEQ_MALLOC(hsize_t, tmp_io_info.dxpl_cache->vec_size))) - HGOTO_ERROR(H5E_RESOURCE, H5E_NOSPACE, 0, "can't allocate I/O offset vector array") - } /* end if */ - else { - len = _len; - off = _off; - } /* end else */ + if(tmp_io_info.dxpl_cache->vec_size > H5D_IO_VECTOR_SIZE) + vec_size = tmp_io_info.dxpl_cache->vec_size; + else + vec_size = H5D_IO_VECTOR_SIZE; + if(NULL == (len = H5FL_SEQ_MALLOC(size_t, vec_size))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, 0, "can't allocate I/O length vector array") + if(NULL == (off = H5FL_SEQ_MALLOC(hsize_t, vec_size))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, 0, "can't allocate I/O offset vector array") /* Loop until all elements are read */ while(nelmts > 0) { /* Get list of sequences for selection to read */ - if(H5S_SELECT_GET_SEQ_LIST(space, H5S_GET_SEQ_LIST_SORTED, iter, tmp_io_info.dxpl_cache->vec_size, nelmts, &nseq, &nelem, off, len) < 0) + if(H5S_SELECT_GET_SEQ_LIST(space, H5S_GET_SEQ_LIST_SORTED, iter, vec_size, nelmts, &nseq, &nelem, off, len) < 0) HGOTO_ERROR(H5E_INTERNAL, H5E_UNSUPPORTED, 0, "sequence length generation failed") /* Reset the current sequence information */ @@ -261,9 +258,9 @@ H5D__gather_file(const H5D_io_info_t *_io_info, done: /* Release resources, if allocated */ - if(len && len != _len) + if(len) len = H5FL_SEQ_FREE(size_t, len); - if(off && off != _off) + if(off) off = H5FL_SEQ_FREE(hsize_t, off); FUNC_LEAVE_NOAPI(ret_value) @@ -292,15 +289,14 @@ H5D__scatter_mem (const void *_tscat_buf, const H5S_t *space, { uint8_t *buf = (uint8_t *)_buf; /* Get local copies for address arithmetic */ const uint8_t *tscat_buf = (const uint8_t *)_tscat_buf; - hsize_t _off[H5D_IO_VECTOR_SIZE]; /* Array to store sequence offsets */ - hsize_t *off = NULL; /* Pointer to sequence offsets */ - size_t _len[H5D_IO_VECTOR_SIZE]; /* Array to store sequence lengths */ - size_t *len = NULL; /* Pointer to sequence lengths */ + hsize_t *off = NULL; /* Pointer to sequence offsets */ + size_t *len = NULL; /* Pointer to sequence lengths */ size_t curr_len; /* Length of bytes left to process in sequence */ size_t nseq; /* Number of sequences generated */ size_t curr_seq; /* Current sequence being processed */ size_t nelem; /* Number of elements used in sequences */ - herr_t ret_value = SUCCEED; /* Number of elements scattered */ + size_t vec_size; /* Vector length */ + herr_t ret_value = SUCCEED; /* Number of elements scattered */ FUNC_ENTER_PACKAGE @@ -312,21 +308,19 @@ H5D__scatter_mem (const void *_tscat_buf, const H5S_t *space, HDassert(buf); /* Allocate the vector I/O arrays */ - if(dxpl_cache->vec_size > H5D_IO_VECTOR_SIZE) { - if(NULL == (len = H5FL_SEQ_MALLOC(size_t, dxpl_cache->vec_size))) - HGOTO_ERROR(H5E_RESOURCE, H5E_NOSPACE, FAIL, "can't allocate I/O length vector array") - if(NULL == (off = H5FL_SEQ_MALLOC(hsize_t, dxpl_cache->vec_size))) - HGOTO_ERROR(H5E_RESOURCE, H5E_NOSPACE, FAIL, "can't allocate I/O offset vector array") - } /* end if */ - else { - len = _len; - off = _off; - } /* end else */ + if(dxpl_cache->vec_size > H5D_IO_VECTOR_SIZE) + vec_size = dxpl_cache->vec_size; + else + vec_size = H5D_IO_VECTOR_SIZE; + if(NULL == (len = H5FL_SEQ_MALLOC(size_t, vec_size))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate I/O length vector array") + if(NULL == (off = H5FL_SEQ_MALLOC(hsize_t, vec_size))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate I/O offset vector array") /* Loop until all elements are written */ while(nelmts > 0) { /* Get list of sequences for selection to write */ - if(H5S_SELECT_GET_SEQ_LIST(space, 0, iter, dxpl_cache->vec_size, nelmts, &nseq, &nelem, off, len) < 0) + if(H5S_SELECT_GET_SEQ_LIST(space, 0, iter, vec_size, nelmts, &nseq, &nelem, off, len) < 0) HGOTO_ERROR (H5E_INTERNAL, H5E_UNSUPPORTED, 0, "sequence length generation failed") /* Loop, while sequences left to process */ @@ -346,9 +340,9 @@ H5D__scatter_mem (const void *_tscat_buf, const H5S_t *space, done: /* Release resources, if allocated */ - if(len && len != _len) + if(len) len = H5FL_SEQ_FREE(size_t, len); - if(off && off != _off) + if(off) off = H5FL_SEQ_FREE(hsize_t, off); FUNC_LEAVE_NOAPI(ret_value) @@ -379,15 +373,14 @@ H5D__gather_mem(const void *_buf, const H5S_t *space, { const uint8_t *buf = (const uint8_t *)_buf; /* Get local copies for address arithmetic */ uint8_t *tgath_buf = (uint8_t *)_tgath_buf; - hsize_t _off[H5D_IO_VECTOR_SIZE]; /* Array to store sequence offsets */ hsize_t *off = NULL; /* Pointer to sequence offsets */ - size_t _len[H5D_IO_VECTOR_SIZE]; /* Array to store sequence lengths */ - size_t *len = NULL; /* Pointer to sequence lengths */ + size_t *len = NULL; /* Pointer to sequence lengths */ size_t curr_len; /* Length of bytes left to process in sequence */ size_t nseq; /* Number of sequences generated */ size_t curr_seq; /* Current sequence being processed */ size_t nelem; /* Number of elements used in sequences */ - size_t ret_value = nelmts; /* Number of elements gathered */ + size_t vec_size; /* Vector length */ + size_t ret_value = nelmts; /* Number of elements gathered */ FUNC_ENTER_STATIC @@ -399,21 +392,19 @@ H5D__gather_mem(const void *_buf, const H5S_t *space, HDassert(tgath_buf); /* Allocate the vector I/O arrays */ - if(dxpl_cache->vec_size > H5D_IO_VECTOR_SIZE) { - if(NULL == (len = H5FL_SEQ_MALLOC(size_t, dxpl_cache->vec_size))) - HGOTO_ERROR(H5E_RESOURCE, H5E_NOSPACE, 0, "can't allocate I/O length vector array") - if(NULL == (off = H5FL_SEQ_MALLOC(hsize_t, dxpl_cache->vec_size))) - HGOTO_ERROR(H5E_RESOURCE, H5E_NOSPACE, 0, "can't allocate I/O offset vector array") - } /* end if */ - else { - len = _len; - off = _off; - } /* end else */ + if(dxpl_cache->vec_size > H5D_IO_VECTOR_SIZE) + vec_size = dxpl_cache->vec_size; + else + vec_size = H5D_IO_VECTOR_SIZE; + if(NULL == (len = H5FL_SEQ_MALLOC(size_t, vec_size))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, 0, "can't allocate I/O length vector array") + if(NULL == (off = H5FL_SEQ_MALLOC(hsize_t, vec_size))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, 0, "can't allocate I/O offset vector array") /* Loop until all elements are written */ while(nelmts > 0) { /* Get list of sequences for selection to write */ - if(H5S_SELECT_GET_SEQ_LIST(space, 0, iter, dxpl_cache->vec_size, nelmts, &nseq, &nelem, off, len) < 0) + if(H5S_SELECT_GET_SEQ_LIST(space, 0, iter, vec_size, nelmts, &nseq, &nelem, off, len) < 0) HGOTO_ERROR (H5E_INTERNAL, H5E_UNSUPPORTED, 0, "sequence length generation failed") /* Loop, while sequences left to process */ @@ -433,9 +424,9 @@ H5D__gather_mem(const void *_buf, const H5S_t *space, done: /* Release resources, if allocated */ - if(len && len != _len) + if(len) len = H5FL_SEQ_FREE(size_t, len); - if(off && off != _off) + if(off) off = H5FL_SEQ_FREE(hsize_t, off); FUNC_LEAVE_NOAPI(ret_value) @@ -460,15 +451,15 @@ H5D__scatgath_read(const H5D_io_info_t *io_info, const H5D_type_info_t *type_inf { const H5D_dxpl_cache_t *dxpl_cache = io_info->dxpl_cache; /* Local pointer to dataset transfer info */ void *buf = io_info->u.rbuf; /* Local pointer to application buffer */ - H5S_sel_iter_t mem_iter; /*memory selection iteration info*/ - hbool_t mem_iter_init = FALSE; /*memory selection iteration info has been initialized */ - H5S_sel_iter_t bkg_iter; /*background iteration info*/ - hbool_t bkg_iter_init = FALSE; /*background iteration info has been initialized */ - H5S_sel_iter_t file_iter; /*file selection iteration info*/ - hbool_t file_iter_init = FALSE; /*file selection iteration info has been initialized */ - hsize_t smine_start; /*strip mine start loc */ - size_t smine_nelmts; /*elements per strip */ - herr_t ret_value = SUCCEED; /*return value */ + H5S_sel_iter_t *mem_iter = NULL; /* Memory selection iteration info*/ + hbool_t mem_iter_init = FALSE; /* Memory selection iteration info has been initialized */ + H5S_sel_iter_t *bkg_iter = NULL; /* Background iteration info*/ + hbool_t bkg_iter_init = FALSE; /* Background iteration info has been initialized */ + H5S_sel_iter_t *file_iter = NULL; /* File selection iteration info*/ + hbool_t file_iter_init = FALSE; /* File selection iteration info has been initialized */ + hsize_t smine_start; /* Strip mine start loc */ + size_t smine_nelmts; /* Elements per strip */ + herr_t ret_value = SUCCEED; /* Return value */ FUNC_ENTER_PACKAGE @@ -483,14 +474,22 @@ H5D__scatgath_read(const H5D_io_info_t *io_info, const H5D_type_info_t *type_inf if(nelmts == 0) HGOTO_DONE(SUCCEED) + /* Allocate the iterators */ + if(NULL == (mem_iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate memory iterator") + if(NULL == (bkg_iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate background iterator") + if(NULL == (file_iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate file iterator") + /* Figure out the strip mine size. */ - if(H5S_select_iter_init(&file_iter, file_space, type_info->src_type_size) < 0) + if(H5S_select_iter_init(file_iter, file_space, type_info->src_type_size) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize file selection information") file_iter_init = TRUE; /*file selection iteration info has been initialized */ - if(H5S_select_iter_init(&mem_iter, mem_space, type_info->dst_type_size) < 0) + if(H5S_select_iter_init(mem_iter, mem_space, type_info->dst_type_size) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize memory selection information") mem_iter_init = TRUE; /*file selection iteration info has been initialized */ - if(H5S_select_iter_init(&bkg_iter, mem_space, type_info->dst_type_size) < 0) + if(H5S_select_iter_init(bkg_iter, mem_space, type_info->dst_type_size) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize background selection information") bkg_iter_init = TRUE; /*file selection iteration info has been initialized */ @@ -499,7 +498,7 @@ H5D__scatgath_read(const H5D_io_info_t *io_info, const H5D_type_info_t *type_inf size_t n; /* Elements operated on */ /* Go figure out how many elements to read from the file */ - HDassert(H5S_SELECT_ITER_NELMTS(&file_iter) == (nelmts - smine_start)); + HDassert(H5S_SELECT_ITER_NELMTS(file_iter) == (nelmts - smine_start)); smine_nelmts = (size_t)MIN(type_info->request_nelmts, (nelmts - smine_start)); /* @@ -511,8 +510,7 @@ H5D__scatgath_read(const H5D_io_info_t *io_info, const H5D_type_info_t *type_inf /* * Gather data */ - n = H5D__gather_file(io_info, file_space, &file_iter, smine_nelmts, - type_info->tconv_buf/*out*/); + n = H5D__gather_file(io_info, file_space, file_iter, smine_nelmts, type_info->tconv_buf/*out*/); if(n != smine_nelmts) HGOTO_ERROR(H5E_IO, H5E_READERROR, FAIL, "file gather failed") @@ -521,14 +519,12 @@ H5D__scatgath_read(const H5D_io_info_t *io_info, const H5D_type_info_t *type_inf * bypass the rest of steps. */ if(type_info->cmpd_subset && H5T_SUBSET_FALSE != type_info->cmpd_subset->subset) { - if(H5D__compound_opt_read(smine_nelmts, mem_space, &mem_iter, dxpl_cache, - type_info, buf /*out*/) < 0) + if(H5D__compound_opt_read(smine_nelmts, mem_space, mem_iter, dxpl_cache, type_info, buf /*out*/) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "datatype conversion failed") } /* end if */ else { if(H5T_BKG_YES == type_info->need_bkg) { - n = H5D__gather_mem(buf, mem_space, &bkg_iter, smine_nelmts, - dxpl_cache, type_info->bkg_buf/*out*/); + n = H5D__gather_mem(buf, mem_space, bkg_iter, smine_nelmts, dxpl_cache, type_info->bkg_buf/*out*/); if(n != smine_nelmts) HGOTO_ERROR(H5E_IO, H5E_READERROR, FAIL, "mem gather failed") } /* end if */ @@ -549,26 +545,25 @@ H5D__scatgath_read(const H5D_io_info_t *io_info, const H5D_type_info_t *type_inf /* * Scatter the data into memory. */ - if(H5D__scatter_mem(type_info->tconv_buf, mem_space, &mem_iter, - smine_nelmts, dxpl_cache, buf/*out*/) < 0) + if(H5D__scatter_mem(type_info->tconv_buf, mem_space, mem_iter, smine_nelmts, dxpl_cache, buf/*out*/) < 0) HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "scatter failed") } /* end else */ } /* end for */ done: /* Release selection iterators */ - if(file_iter_init) { - if(H5S_SELECT_ITER_RELEASE(&file_iter) < 0) - HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") - } /* end if */ - if(mem_iter_init) { - if(H5S_SELECT_ITER_RELEASE(&mem_iter) < 0) - HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") - } /* end if */ - if(bkg_iter_init) { - if(H5S_SELECT_ITER_RELEASE(&bkg_iter) < 0) - HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") - } /* end if */ + if(file_iter_init && H5S_SELECT_ITER_RELEASE(file_iter) < 0) + HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") + if(file_iter) + file_iter = H5FL_FREE(H5S_sel_iter_t, file_iter); + if(mem_iter_init && H5S_SELECT_ITER_RELEASE(mem_iter) < 0) + HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") + if(mem_iter) + mem_iter = H5FL_FREE(H5S_sel_iter_t, mem_iter); + if(bkg_iter_init && H5S_SELECT_ITER_RELEASE(bkg_iter) < 0) + HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") + if(bkg_iter) + bkg_iter = H5FL_FREE(H5S_sel_iter_t, bkg_iter); FUNC_LEAVE_NOAPI(ret_value) } /* end H5D__scatgath_read() */ @@ -592,15 +587,15 @@ H5D__scatgath_write(const H5D_io_info_t *io_info, const H5D_type_info_t *type_in { const H5D_dxpl_cache_t *dxpl_cache = io_info->dxpl_cache; /* Local pointer to dataset transfer info */ const void *buf = io_info->u.wbuf; /* Local pointer to application buffer */ - H5S_sel_iter_t mem_iter; /*memory selection iteration info*/ - hbool_t mem_iter_init = FALSE; /*memory selection iteration info has been initialized */ - H5S_sel_iter_t bkg_iter; /*background iteration info*/ - hbool_t bkg_iter_init = FALSE; /*background iteration info has been initialized */ - H5S_sel_iter_t file_iter; /*file selection iteration info*/ - hbool_t file_iter_init = FALSE; /*file selection iteration info has been initialized */ - hsize_t smine_start; /*strip mine start loc */ - size_t smine_nelmts; /*elements per strip */ - herr_t ret_value = SUCCEED; /*return value */ + H5S_sel_iter_t *mem_iter = NULL; /* Memory selection iteration info*/ + hbool_t mem_iter_init = FALSE; /* Memory selection iteration info has been initialized */ + H5S_sel_iter_t *bkg_iter = NULL; /* Background iteration info*/ + hbool_t bkg_iter_init = FALSE; /* Background iteration info has been initialized */ + H5S_sel_iter_t *file_iter = NULL; /* File selection iteration info*/ + hbool_t file_iter_init = FALSE; /* File selection iteration info has been initialized */ + hsize_t smine_start; /* Strip mine start loc */ + size_t smine_nelmts; /* Elements per strip */ + herr_t ret_value = SUCCEED; /* Return value */ FUNC_ENTER_PACKAGE @@ -615,14 +610,22 @@ H5D__scatgath_write(const H5D_io_info_t *io_info, const H5D_type_info_t *type_in if(nelmts == 0) HGOTO_DONE(SUCCEED) + /* Allocate the iterators */ + if(NULL == (mem_iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate memory iterator") + if(NULL == (bkg_iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate background iterator") + if(NULL == (file_iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate file iterator") + /* Figure out the strip mine size. */ - if(H5S_select_iter_init(&file_iter, file_space, type_info->dst_type_size) < 0) + if(H5S_select_iter_init(file_iter, file_space, type_info->dst_type_size) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize file selection information") file_iter_init = TRUE; /*file selection iteration info has been initialized */ - if(H5S_select_iter_init(&mem_iter, mem_space, type_info->src_type_size) < 0) + if(H5S_select_iter_init(mem_iter, mem_space, type_info->src_type_size) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize memory selection information") mem_iter_init = TRUE; /*file selection iteration info has been initialized */ - if(H5S_select_iter_init(&bkg_iter, file_space, type_info->dst_type_size) < 0) + if(H5S_select_iter_init(bkg_iter, file_space, type_info->dst_type_size) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize background selection information") bkg_iter_init = TRUE; /*file selection iteration info has been initialized */ @@ -631,7 +634,7 @@ H5D__scatgath_write(const H5D_io_info_t *io_info, const H5D_type_info_t *type_in size_t n; /* Elements operated on */ /* Go figure out how many elements to read from the file */ - HDassert(H5S_SELECT_ITER_NELMTS(&file_iter) == (nelmts - smine_start)); + HDassert(H5S_SELECT_ITER_NELMTS(file_iter) == (nelmts - smine_start)); smine_nelmts = (size_t)MIN(type_info->request_nelmts, (nelmts - smine_start)); /* @@ -639,8 +642,7 @@ H5D__scatgath_write(const H5D_io_info_t *io_info, const H5D_type_info_t *type_in * buffer. Also gather data from the file into the background buffer * if necessary. */ - n = H5D__gather_mem(buf, mem_space, &mem_iter, smine_nelmts, - dxpl_cache, type_info->tconv_buf/*out*/); + n = H5D__gather_mem(buf, mem_space, mem_iter, smine_nelmts, dxpl_cache, type_info->tconv_buf/*out*/); if(n != smine_nelmts) HGOTO_ERROR(H5E_IO, H5E_WRITEERROR, FAIL, "mem gather failed") @@ -657,8 +659,7 @@ H5D__scatgath_write(const H5D_io_info_t *io_info, const H5D_type_info_t *type_in } /* end if */ else { if(H5T_BKG_YES == type_info->need_bkg) { - n = H5D__gather_file(io_info, file_space, &bkg_iter, smine_nelmts, - type_info->bkg_buf/*out*/); + n = H5D__gather_file(io_info, file_space, bkg_iter, smine_nelmts, type_info->bkg_buf/*out*/); if(n != smine_nelmts) HGOTO_ERROR(H5E_IO, H5E_READERROR, FAIL, "file gather failed") } /* end if */ @@ -681,25 +682,24 @@ H5D__scatgath_write(const H5D_io_info_t *io_info, const H5D_type_info_t *type_in /* * Scatter the data out to the file. */ - if(H5D__scatter_file(io_info, file_space, &file_iter, smine_nelmts, - type_info->tconv_buf) < 0) + if(H5D__scatter_file(io_info, file_space, file_iter, smine_nelmts, type_info->tconv_buf) < 0) HGOTO_ERROR(H5E_DATASET, H5E_WRITEERROR, FAIL, "scatter failed") } /* end for */ done: /* Release selection iterators */ - if(file_iter_init) { - if(H5S_SELECT_ITER_RELEASE(&file_iter) < 0) - HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") - } /* end if */ - if(mem_iter_init) { - if(H5S_SELECT_ITER_RELEASE(&mem_iter) < 0) - HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") - } /* end if */ - if(bkg_iter_init) { - if(H5S_SELECT_ITER_RELEASE(&bkg_iter) < 0) - HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") - } /* end if */ + if(file_iter_init && H5S_SELECT_ITER_RELEASE(file_iter) < 0) + HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") + if(file_iter) + file_iter = H5FL_FREE(H5S_sel_iter_t, file_iter); + if(mem_iter_init && H5S_SELECT_ITER_RELEASE(mem_iter) < 0) + HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") + if(mem_iter) + mem_iter = H5FL_FREE(H5S_sel_iter_t, mem_iter); + if(bkg_iter_init && H5S_SELECT_ITER_RELEASE(bkg_iter) < 0) + HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") + if(bkg_iter) + bkg_iter = H5FL_FREE(H5S_sel_iter_t, bkg_iter); FUNC_LEAVE_NOAPI(ret_value) } /* end H5D__scatgath_write() */ @@ -744,12 +744,11 @@ H5D__compound_opt_read(size_t nelmts, const H5S_t *space, { uint8_t *ubuf = (uint8_t *)user_buf; /* Cast for pointer arithmetic */ uint8_t *xdbuf; /* Pointer into dataset buffer */ - hsize_t _off[H5D_IO_VECTOR_SIZE]; /* Array to store sequence offsets */ hsize_t *off = NULL; /* Pointer to sequence offsets */ - size_t _len[H5D_IO_VECTOR_SIZE]; /* Array to store sequence lengths */ size_t *len = NULL; /* Pointer to sequence lengths */ size_t src_stride, dst_stride, copy_size; - herr_t ret_value = SUCCEED; /*return value */ + size_t vec_size; /* Vector length */ + herr_t ret_value = SUCCEED; /* Return value */ FUNC_ENTER_STATIC @@ -765,16 +764,14 @@ H5D__compound_opt_read(size_t nelmts, const H5S_t *space, HDassert(user_buf); /* Allocate the vector I/O arrays */ - if(dxpl_cache->vec_size > H5D_IO_VECTOR_SIZE) { - if(NULL == (len = H5FL_SEQ_MALLOC(size_t, dxpl_cache->vec_size))) - HGOTO_ERROR(H5E_RESOURCE, H5E_NOSPACE, FAIL, "can't allocate I/O length vector array") - if(NULL == (off = H5FL_SEQ_MALLOC(hsize_t, dxpl_cache->vec_size))) - HGOTO_ERROR(H5E_RESOURCE, H5E_NOSPACE, FAIL, "can't allocate I/O offset vector array") - } /* end if */ - else { - len = _len; - off = _off; - } /* end else */ + if(dxpl_cache->vec_size > H5D_IO_VECTOR_SIZE) + vec_size = dxpl_cache->vec_size; + else + vec_size = H5D_IO_VECTOR_SIZE; + if(NULL == (len = H5FL_SEQ_MALLOC(size_t, vec_size))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate I/O length vector array") + if(NULL == (off = H5FL_SEQ_MALLOC(hsize_t, vec_size))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate I/O offset vector array") /* Get source & destination strides */ src_stride = type_info->src_type_size; @@ -791,7 +788,7 @@ H5D__compound_opt_read(size_t nelmts, const H5S_t *space, size_t elmtno; /* Element counter */ /* Get list of sequences for selection to write */ - if(H5S_SELECT_GET_SEQ_LIST(space, 0, iter, dxpl_cache->vec_size, nelmts, &nseq, &elmtno, off, len) < 0) + if(H5S_SELECT_GET_SEQ_LIST(space, 0, iter, vec_size, nelmts, &nseq, &elmtno, off, len) < 0) HGOTO_ERROR(H5E_INTERNAL, H5E_UNSUPPORTED, 0, "sequence length generation failed") /* Loop, while sequences left to process */ @@ -827,9 +824,9 @@ H5D__compound_opt_read(size_t nelmts, const H5S_t *space, done: /* Release resources, if allocated */ - if(len && len != _len) + if(len) len = H5FL_SEQ_FREE(size_t, len); - if(off && off != _off) + if(off) off = H5FL_SEQ_FREE(hsize_t, off); FUNC_LEAVE_NOAPI(ret_value) @@ -923,7 +920,7 @@ H5Dscatter(H5D_scatter_func_t op, void *op_data, hid_t type_id, { H5T_t *type; /* Datatype */ H5S_t *dst_space; /* Dataspace */ - H5S_sel_iter_t iter; /* Selection iteration info*/ + H5S_sel_iter_t *iter = NULL; /* Selection iteration info*/ hbool_t iter_init = FALSE; /* Selection iteration info has been initialized */ const void *src_buf = NULL; /* Source (contiguous) data buffer */ size_t src_buf_nbytes = 0; /* Size of src_buf */ @@ -959,8 +956,12 @@ H5Dscatter(H5D_scatter_func_t op, void *op_data, hid_t type_id, if((nelmts = (hssize_t)H5S_GET_SELECT_NPOINTS(dst_space)) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTCOUNT, FAIL, "unable to get number of elements in selection") + /* Allocate the selection iterator */ + if(NULL == (iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate selection iterator") + /* Initialize selection iterator */ - if(H5S_select_iter_init(&iter, dst_space, type_size) < 0) + if(H5S_select_iter_init(iter, dst_space, type_size) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize selection iterator information") iter_init = TRUE; @@ -984,7 +985,7 @@ H5Dscatter(H5D_scatter_func_t op, void *op_data, hid_t type_id, HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "callback returned more elements than in selection") /* Scatter data */ - if(H5D__scatter_mem(src_buf, dst_space, &iter, nelmts_scatter, dxpl_cache, dst_buf) < 0) + if(H5D__scatter_mem(src_buf, dst_space, iter, nelmts_scatter, dxpl_cache, dst_buf) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTCOPY, FAIL, "scatter failed") nelmts -= (hssize_t)nelmts_scatter; @@ -992,10 +993,10 @@ H5Dscatter(H5D_scatter_func_t op, void *op_data, hid_t type_id, done: /* Release selection iterator */ - if(iter_init) { - if(H5S_SELECT_ITER_RELEASE(&iter) < 0) - HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") - } /* end if */ + if(iter_init && H5S_SELECT_ITER_RELEASE(iter) < 0) + HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") + if(iter) + iter = H5FL_FREE(H5S_sel_iter_t, iter); FUNC_LEAVE_API(ret_value) } /* H5Dscatter() */ @@ -1023,7 +1024,7 @@ H5Dgather(hid_t src_space_id, const void *src_buf, hid_t type_id, { H5T_t *type; /* Datatype */ H5S_t *src_space; /* Dataspace */ - H5S_sel_iter_t iter; /* Selection iteration info*/ + H5S_sel_iter_t *iter = NULL; /* Selection iteration info*/ hbool_t iter_init = FALSE; /* Selection iteration info has been initialized */ size_t type_size; /* Datatype element size */ hssize_t nelmts; /* Number of remaining elements in selection */ @@ -1071,15 +1072,19 @@ H5Dgather(hid_t src_space_id, const void *src_buf, hid_t type_id, if(((size_t)nelmts > dst_buf_nelmts) && (op == NULL)) HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "no callback supplied and destination buffer too small") + /* Allocate the selection iterator */ + if(NULL == (iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate selection iterator") + /* Initialize selection iterator */ - if(H5S_select_iter_init(&iter, src_space, type_size) < 0) + if(H5S_select_iter_init(iter, src_space, type_size) < 0) HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize selection iterator information") iter_init = TRUE; /* Loop until all data has been scattered */ while(nelmts > 0) { /* Gather data */ - if(0 == (nelmts_gathered = H5D__gather_mem(src_buf, src_space, &iter, MIN(dst_buf_nelmts, (size_t)nelmts), dxpl_cache, dst_buf))) + if(0 == (nelmts_gathered = H5D__gather_mem(src_buf, src_space, iter, MIN(dst_buf_nelmts, (size_t)nelmts), dxpl_cache, dst_buf))) HGOTO_ERROR(H5E_IO, H5E_CANTCOPY, FAIL, "gather failed") HDassert(nelmts_gathered == MIN(dst_buf_nelmts, (size_t)nelmts)); @@ -1093,10 +1098,10 @@ H5Dgather(hid_t src_space_id, const void *src_buf, hid_t type_id, done: /* Release selection iterator */ - if(iter_init) { - if(H5S_SELECT_ITER_RELEASE(&iter) < 0) - HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") - } /* end if */ + if(iter_init && H5S_SELECT_ITER_RELEASE(iter) < 0) + HDONE_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "Can't release selection iterator") + if(iter) + iter = H5FL_FREE(H5S_sel_iter_t, iter); FUNC_LEAVE_API(ret_value) } /* H5Dgather() */ diff --git a/src/H5Dselect.c b/src/H5Dselect.c index 312beba..53829e5 100644 --- a/src/H5Dselect.c +++ b/src/H5Dselect.c @@ -68,6 +68,9 @@ H5FL_SEQ_DEFINE(size_t); /* Declare a free list to manage sequences of hsize_t */ H5FL_SEQ_DEFINE(hsize_t); +/* Declare extern free list to manage the H5S_sel_iter_t struct */ +H5FL_EXTERN(H5S_sel_iter_t); + /*------------------------------------------------------------------------- @@ -86,22 +89,19 @@ static herr_t H5D__select_io(const H5D_io_info_t *io_info, size_t elmt_size, size_t nelmts, const H5S_t *file_space, const H5S_t *mem_space) { - H5S_sel_iter_t mem_iter; /* Memory selection iteration info */ - hbool_t mem_iter_init = 0; /* Memory selection iteration info has been initialized */ - H5S_sel_iter_t file_iter; /* File selection iteration info */ - hbool_t file_iter_init = 0; /* File selection iteration info has been initialized */ - hsize_t _mem_off[H5D_IO_VECTOR_SIZE]; /* Array to store sequence offsets in memory */ + H5S_sel_iter_t *mem_iter = NULL; /* Memory selection iteration info */ + hbool_t mem_iter_init = FALSE; /* Memory selection iteration info has been initialized */ + H5S_sel_iter_t *file_iter = NULL; /* File selection iteration info */ + hbool_t file_iter_init = FALSE; /* File selection iteration info has been initialized */ hsize_t *mem_off = NULL; /* Pointer to sequence offsets in memory */ - hsize_t _file_off[H5D_IO_VECTOR_SIZE]; /* Array to store sequence offsets in the file */ hsize_t *file_off = NULL; /* Pointer to sequence offsets in the file */ - size_t _mem_len[H5D_IO_VECTOR_SIZE]; /* Array to store sequence lengths in memory */ size_t *mem_len = NULL; /* Pointer to sequence lengths in memory */ - size_t _file_len[H5D_IO_VECTOR_SIZE]; /* Array to store sequence lengths in the file */ size_t *file_len = NULL; /* Pointer to sequence lengths in the file */ size_t curr_mem_seq; /* Current memory sequence to operate on */ size_t curr_file_seq; /* Current file sequence to operate on */ size_t mem_nseq; /* Number of sequences generated in the file */ size_t file_nseq; /* Number of sequences generated in memory */ + size_t vec_size; /* Vector length */ ssize_t tmp_file_len; /* Temporary number of bytes in file sequence */ herr_t ret_value = SUCCEED; /* Return value */ @@ -115,22 +115,18 @@ H5D__select_io(const H5D_io_info_t *io_info, size_t elmt_size, HDassert(io_info->u.rbuf); /* Allocate the vector I/O arrays */ - if(io_info->dxpl_cache->vec_size > H5D_IO_VECTOR_SIZE) { - if(NULL == (mem_len = H5FL_SEQ_MALLOC(size_t,io_info->dxpl_cache->vec_size))) - HGOTO_ERROR(H5E_RESOURCE, H5E_NOSPACE, FAIL, "can't allocate I/O length vector array") - if(NULL == (mem_off = H5FL_SEQ_MALLOC(hsize_t,io_info->dxpl_cache->vec_size))) - HGOTO_ERROR(H5E_RESOURCE, H5E_NOSPACE, FAIL, "can't allocate I/O offset vector array") - if(NULL == (file_len = H5FL_SEQ_MALLOC(size_t,io_info->dxpl_cache->vec_size))) - HGOTO_ERROR(H5E_RESOURCE, H5E_NOSPACE, FAIL, "can't allocate I/O length vector array") - if(NULL == (file_off = H5FL_SEQ_MALLOC(hsize_t,io_info->dxpl_cache->vec_size))) - HGOTO_ERROR(H5E_RESOURCE, H5E_NOSPACE, FAIL, "can't allocate I/O offset vector array") - } /* end if */ - else { - mem_len = _mem_len; - mem_off = _mem_off; - file_len = _file_len; - file_off = _file_off; - } /* end else */ + if(io_info->dxpl_cache->vec_size > H5D_IO_VECTOR_SIZE) + vec_size = io_info->dxpl_cache->vec_size; + else + vec_size = H5D_IO_VECTOR_SIZE; + if(NULL == (mem_len = H5FL_SEQ_MALLOC(size_t, vec_size))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate I/O length vector array") + if(NULL == (mem_off = H5FL_SEQ_MALLOC(hsize_t, vec_size))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate I/O offset vector array") + if(NULL == (file_len = H5FL_SEQ_MALLOC(size_t, vec_size))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate I/O length vector array") + if(NULL == (file_off = H5FL_SEQ_MALLOC(hsize_t, vec_size))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate I/O offset vector array") /* Check for only one element in selection */ if(nelmts == 1) { @@ -169,13 +165,19 @@ H5D__select_io(const H5D_io_info_t *io_info, size_t elmt_size, size_t mem_nelem; /* Number of elements used in memory sequences */ size_t file_nelem; /* Number of elements used in file sequences */ + /* Allocate the iterators */ + if(NULL == (mem_iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate memory iterator") + if(NULL == (file_iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate file iterator") + /* Initialize file iterator */ - if(H5S_select_iter_init(&file_iter, file_space, elmt_size) < 0) + if(H5S_select_iter_init(file_iter, file_space, elmt_size) < 0) HGOTO_ERROR(H5E_DATASPACE, H5E_CANTINIT, FAIL, "unable to initialize selection iterator") file_iter_init = 1; /* File selection iteration info has been initialized */ /* Initialize memory iterator */ - if(H5S_select_iter_init(&mem_iter, mem_space, elmt_size) < 0) + if(H5S_select_iter_init(mem_iter, mem_space, elmt_size) < 0) HGOTO_ERROR(H5E_DATASPACE, H5E_CANTINIT, FAIL, "unable to initialize selection iterator") mem_iter_init = 1; /* Memory selection iteration info has been initialized */ @@ -188,7 +190,7 @@ H5D__select_io(const H5D_io_info_t *io_info, size_t elmt_size, /* Check if more file sequences are needed */ if(curr_file_seq >= file_nseq) { /* Get sequences for file selection */ - if(H5S_SELECT_GET_SEQ_LIST(file_space, H5S_GET_SEQ_LIST_SORTED, &file_iter, io_info->dxpl_cache->vec_size, nelmts, &file_nseq, &file_nelem, file_off, file_len) < 0) + if(H5S_SELECT_GET_SEQ_LIST(file_space, H5S_GET_SEQ_LIST_SORTED, file_iter, vec_size, nelmts, &file_nseq, &file_nelem, file_off, file_len) < 0) HGOTO_ERROR(H5E_INTERNAL, H5E_UNSUPPORTED, FAIL, "sequence length generation failed") /* Start at the beginning of the sequences again */ @@ -198,7 +200,7 @@ H5D__select_io(const H5D_io_info_t *io_info, size_t elmt_size, /* Check if more memory sequences are needed */ if(curr_mem_seq >= mem_nseq) { /* Get sequences for memory selection */ - if(H5S_SELECT_GET_SEQ_LIST(mem_space, 0, &mem_iter, io_info->dxpl_cache->vec_size, nelmts, &mem_nseq, &mem_nelem, mem_off, mem_len) < 0) + if(H5S_SELECT_GET_SEQ_LIST(mem_space, 0, mem_iter, vec_size, nelmts, &mem_nseq, &mem_nelem, mem_off, mem_len) < 0) HGOTO_ERROR(H5E_INTERNAL, H5E_UNSUPPORTED, FAIL, "sequence length generation failed") /* Start at the beginning of the sequences again */ @@ -227,24 +229,24 @@ H5D__select_io(const H5D_io_info_t *io_info, size_t elmt_size, } /* end else */ done: - /* Release file selection iterator */ - if(file_iter_init) - if(H5S_SELECT_ITER_RELEASE(&file_iter) < 0) - HDONE_ERROR(H5E_DATASPACE, H5E_CANTRELEASE, FAIL, "unable to release selection iterator") - - /* Release memory selection iterator */ - if(mem_iter_init) - if(H5S_SELECT_ITER_RELEASE(&mem_iter) < 0) - HDONE_ERROR(H5E_DATASPACE, H5E_CANTRELEASE, FAIL, "unable to release selection iterator") + /* Release selection iterators */ + if(file_iter_init && H5S_SELECT_ITER_RELEASE(file_iter) < 0) + HDONE_ERROR(H5E_DATASET, H5E_CANTRELEASE, FAIL, "unable to release selection iterator") + if(file_iter) + file_iter = H5FL_FREE(H5S_sel_iter_t, file_iter); + if(mem_iter_init && H5S_SELECT_ITER_RELEASE(mem_iter) < 0) + HDONE_ERROR(H5E_DATASET, H5E_CANTRELEASE, FAIL, "unable to release selection iterator") + if(mem_iter) + mem_iter = H5FL_FREE(H5S_sel_iter_t, mem_iter); /* Release vector arrays, if allocated */ - if(file_len && file_len != _file_len) + if(file_len) file_len = H5FL_SEQ_FREE(size_t, file_len); - if(file_off && file_off != _file_off) + if(file_off) file_off = H5FL_SEQ_FREE(hsize_t, file_off); - if(mem_len && mem_len != _mem_len) + if(mem_len) mem_len = H5FL_SEQ_FREE(size_t, mem_len); - if(mem_off && mem_off != _mem_off) + if(mem_off) mem_off = H5FL_SEQ_FREE(hsize_t, mem_off); FUNC_LEAVE_NOAPI(ret_value) diff --git a/src/H5FDfamily.c b/src/H5FDfamily.c index 3b38836..7ec8751 100644 --- a/src/H5FDfamily.c +++ b/src/H5FDfamily.c @@ -46,10 +46,8 @@ #include "H5MMprivate.h" /* Memory management */ #include "H5Pprivate.h" /* Property lists */ -#undef MAX -#define MAX(X,Y) ((X)>(Y)?(X):(Y)) -#undef MIN -#define MIN(X,Y) ((X)<(Y)?(X):(Y)) +/* The size of the member name buffers */ +#define H5FD_FAM_MEMB_NAME_BUF_SIZE 4096 /* The driver identification number, initialized at runtime */ static hid_t H5FD_FAMILY_g = 0; @@ -623,11 +621,11 @@ static H5FD_t * H5FD_family_open(const char *name, unsigned flags, hid_t fapl_id, haddr_t maxaddr) { - H5FD_family_t *file=NULL; - H5FD_t *ret_value=NULL; - char memb_name[4096], temp[4096]; - hsize_t eof=HADDR_UNDEF; + H5FD_family_t *file = NULL; + char *memb_name = NULL, *temp = NULL; + hsize_t eof = HADDR_UNDEF; unsigned t_flags = flags & ~H5F_ACC_CREAT; + H5FD_t *ret_value = NULL; FUNC_ENTER_NOAPI_NOINIT @@ -683,15 +681,21 @@ H5FD_family_open(const char *name, unsigned flags, hid_t fapl_id, file->name = H5MM_strdup(name); file->flags = flags; + /* Allocate space for the string buffers */ + if(NULL == (memb_name = (char *)H5MM_malloc(H5FD_FAM_MEMB_NAME_BUF_SIZE))) + HGOTO_ERROR(H5E_FILE, H5E_CANTALLOC, NULL, "unable to allocate member name") + if(NULL == (temp = (char *)H5MM_malloc(H5FD_FAM_MEMB_NAME_BUF_SIZE))) + HGOTO_ERROR(H5E_FILE, H5E_CANTALLOC, NULL, "unable to allocate temporary member name") + /* Check that names are unique */ - HDsnprintf(memb_name, sizeof(memb_name), name, 0); - HDsnprintf(temp, sizeof(temp), name, 1); + HDsnprintf(memb_name, H5FD_FAM_MEMB_NAME_BUF_SIZE, name, 0); + HDsnprintf(temp, H5FD_FAM_MEMB_NAME_BUF_SIZE, name, 1); if(!HDstrcmp(memb_name, temp)) HGOTO_ERROR(H5E_FILE, H5E_FILEEXISTS, NULL, "file names not unique") /* Open all the family members */ while(1) { - HDsnprintf(memb_name, sizeof(memb_name), name, file->nmembs); + HDsnprintf(memb_name, H5FD_FAM_MEMB_NAME_BUF_SIZE, name, file->nmembs); /* Enlarge member array */ if(file->nmembs >= file->amembs) { @@ -732,6 +736,12 @@ H5FD_family_open(const char *name, unsigned flags, hid_t fapl_id, ret_value=(H5FD_t *)file; done: + /* Release resources */ + if(memb_name) + H5MM_xfree(memb_name); + if(temp) + H5MM_xfree(temp); + /* Cleanup and fail */ if(ret_value == NULL && file != NULL) { unsigned nerrors = 0; /* Number of errors closing member files */ @@ -941,12 +951,16 @@ H5FD_family_set_eoa(H5FD_t *_file, H5FD_mem_t type, haddr_t abs_eoa) { H5FD_family_t *file = (H5FD_family_t*)_file; haddr_t addr = abs_eoa; - char memb_name[4096]; + char *memb_name = NULL; unsigned u; /* Local index variable */ herr_t ret_value = SUCCEED; /* Return value */ FUNC_ENTER_NOAPI_NOINIT + /* Allocate space for the member name buffer */ + if(NULL == (memb_name = (char *)H5MM_malloc(H5FD_FAM_MEMB_NAME_BUF_SIZE))) + HGOTO_ERROR(H5E_FILE, H5E_CANTALLOC, FAIL, "unable to allocate member name") + for(u = 0; addr || u < file->nmembs; u++) { /* Enlarge member array */ @@ -964,7 +978,7 @@ H5FD_family_set_eoa(H5FD_t *_file, H5FD_mem_t type, haddr_t abs_eoa) /* Create another file if necessary */ if(u >= file->nmembs || !file->memb[u]) { file->nmembs = MAX(file->nmembs, u+1); - HDsnprintf(memb_name, sizeof(memb_name), file->name, u); + HDsnprintf(memb_name, H5FD_FAM_MEMB_NAME_BUF_SIZE, file->name, u); H5E_BEGIN_TRY { H5_CHECK_OVERFLOW(file->memb_size, hsize_t, haddr_t); file->memb[u] = H5FDopen(memb_name, file->flags | H5F_ACC_CREAT, @@ -992,6 +1006,10 @@ H5FD_family_set_eoa(H5FD_t *_file, H5FD_mem_t type, haddr_t abs_eoa) file->eoa = abs_eoa; done: + /* Release resources */ + if(memb_name) + H5MM_xfree(memb_name); + FUNC_LEAVE_NOAPI(ret_value) } diff --git a/src/H5FL.c b/src/H5FL.c index 00cbf0c..db51809 100644 --- a/src/H5FL.c +++ b/src/H5FL.c @@ -293,7 +293,7 @@ H5FL_reg_init(H5FL_reg_head_t *head) H5FL_reg_gc_head.first=new_node; /* Indicate that the free list is initialized */ - head->init=1; + head->init = TRUE; /* Make certain that the space allocated is large enough to store a free list pointer (eventually) */ if(head->sizename = %s, head->allocated = %d\n", FUNC, H5FL_reg_gc_head.fir /* No allocations left open for list, get rid of it */ else { /* Reset the "initialized" flag, in case we restart this list somehow (I don't know how..) */ - H5FL_reg_gc_head.first->list->init = 0; + H5FL_reg_gc_head.first->list->init = FALSE; /* Free the node from the garbage collection list */ H5MM_xfree(H5FL_reg_gc_head.first); @@ -822,7 +822,7 @@ H5FL_blk_init(H5FL_blk_head_t *head) H5FL_blk_gc_head.first=new_node; /* Indicate that the PQ is initialized */ - head->init=1; + head->init = TRUE; done: FUNC_LEAVE_NOAPI(ret_value) @@ -1326,7 +1326,7 @@ printf("%s: head->name = %s, head->allocated = %d\n", FUNC, H5FL_blk_gc_head.fir /* No allocations left open for list, get rid of it */ else { /* Reset the "initialized" flag, in case we restart this list somehow (I don't know how..) */ - H5FL_blk_gc_head.first->pq->init = 0; + H5FL_blk_gc_head.first->pq->init = FALSE; /* Free the node from the garbage collection list */ H5MM_free(H5FL_blk_gc_head.first); @@ -1379,7 +1379,7 @@ H5FL_arr_init(H5FL_arr_head_t *head) H5FL_arr_gc_head.first=new_node; /* Allocate room for the free lists */ - if(NULL == (head->list_arr = (H5FL_arr_node_t *)H5MM_calloc((size_t)head->maxelem*sizeof(H5FL_arr_node_t)))) + if(NULL == (head->list_arr = (H5FL_arr_node_t *)H5MM_calloc((size_t)head->maxelem * sizeof(H5FL_arr_node_t)))) HGOTO_ERROR(H5E_RESOURCE, H5E_NOSPACE, FAIL, "memory allocation failed") /* Initialize the size of each array */ @@ -1387,7 +1387,7 @@ H5FL_arr_init(H5FL_arr_head_t *head) head->list_arr[u].size = head->base_size + (head->elem_size * u); /* Indicate that the free list is initialized */ - head->init = 1; + head->init = TRUE; done: FUNC_LEAVE_NOAPI(ret_value) @@ -1795,7 +1795,7 @@ printf("%s: head->name = %s, head->allocated = %d\n", FUNC, H5FL_arr_gc_head.fir H5MM_xfree(H5FL_arr_gc_head.first->list->list_arr); /* Reset the "initialized" flag, in case we restart this list somehow (I don't know how..) */ - H5FL_arr_gc_head.first->list->init = 0; + H5FL_arr_gc_head.first->list->init = FALSE; /* Free the node from the garbage collection list */ H5MM_free(H5FL_arr_gc_head.first); @@ -2007,7 +2007,7 @@ H5FL_fac_init(size_t size) #endif /* H5FL_TRACK */ /* Indicate that the free list is initialized */ - factory->init = 1; + factory->init = TRUE; /* Set return value */ ret_value = factory; @@ -2417,7 +2417,7 @@ printf("%s: head->size = %d, head->allocated = %d\n", FUNC, (int)H5FL_fac_gc_hea HDassert(H5FL_fac_gc_head.first->list->allocated == 0); /* Reset the "initialized" flag, in case we restart this list somehow (I don't know how..) */ - H5FL_fac_gc_head.first->list->init = 0; + H5FL_fac_gc_head.first->list->init = FALSE; /* Free the node from the garbage collection list */ H5FL_fac_gc_head.first = H5FL_FREE(H5FL_fac_gc_node_t, H5FL_fac_gc_head.first); diff --git a/src/H5FLprivate.h b/src/H5FLprivate.h index 3cd30a6..f44d359 100644 --- a/src/H5FLprivate.h +++ b/src/H5FLprivate.h @@ -97,7 +97,7 @@ typedef struct H5FL_reg_node_t { /* Data structure for free list of blocks */ typedef struct H5FL_reg_head_t { - unsigned init; /* Whether the free list has been initialized */ + hbool_t init; /* Whether the free list has been initialized */ unsigned allocated; /* Number of blocks allocated */ unsigned onlist; /* Number of blocks on free list */ const char *name; /* Name of the type */ @@ -166,9 +166,9 @@ typedef struct H5FL_blk_node_t { /* Data structure for priority queue of native block free lists */ typedef struct H5FL_blk_head_t { - unsigned init; /* Whether the free list has been initialized */ - unsigned allocated; /* Number of blocks allocated */ - unsigned onlist; /* Number of blocks on free list */ + hbool_t init; /* Whether the free list has been initialized */ + unsigned allocated; /* Number of blocks allocated */ + unsigned onlist; /* Number of blocks on free list */ size_t list_mem; /* Amount of memory in block on free list */ const char *name; /* Name of the type */ H5FL_blk_node_t *head; /* Pointer to first free list in queue */ @@ -237,7 +237,7 @@ typedef struct H5FL_arr_node_t { /* Data structure for free list of array blocks */ typedef struct H5FL_arr_head_t { - unsigned init; /* Whether the free list has been initialized */ + hbool_t init; /* Whether the free list has been initialized */ unsigned allocated; /* Number of blocks allocated */ size_t list_mem; /* Amount of memory in block on free list */ const char *name; /* Name of the type */ @@ -354,7 +354,7 @@ typedef struct H5FL_fac_node_t H5FL_fac_node_t; /* Data structure for free list block factory */ typedef struct H5FL_fac_head_t { - unsigned init; /* Whether the free list has been initialized */ + hbool_t init; /* Whether the free list has been initialized */ unsigned allocated; /* Number of blocks allocated */ unsigned onlist; /* Number of blocks on free list */ size_t size; /* Size of the blocks in the list */ diff --git a/src/H5HFcache.c b/src/H5HFcache.c index 759fff0..31ecc62 100644 --- a/src/H5HFcache.c +++ b/src/H5HFcache.c @@ -618,8 +618,8 @@ H5HF__cache_hdr_image_len(const void *_thing, size_t *image_len, *------------------------------------------------------------------------- */ static herr_t -H5HF__cache_hdr_pre_serialize(const H5F_t *f, hid_t dxpl_id, void *_thing, - haddr_t addr, size_t len, size_t H5_ATTR_UNUSED compressed_len, +H5HF__cache_hdr_pre_serialize(const H5F_t *f, hid_t H5_ATTR_UNUSED dxpl_id, + void *_thing, haddr_t addr, size_t len, size_t H5_ATTR_UNUSED compressed_len, haddr_t H5_ATTR_UNUSED *new_addr, size_t H5_ATTR_UNUSED *new_len, size_t H5_ATTR_UNUSED *new_compressed_len, unsigned *flags) { diff --git a/src/H5Oalloc.c b/src/H5Oalloc.c index 99f1322..69b4b11 100644 --- a/src/H5Oalloc.c +++ b/src/H5Oalloc.c @@ -763,7 +763,7 @@ H5O_alloc_new_chunk(H5F_t *f, hid_t dxpl_id, H5O_t *oh, size_t size, size_t *new size_t idx; /* Message number */ uint8_t *p = NULL; /*ptr into new chunk */ H5O_cont_t *cont = NULL; /*native continuation message */ - size_t chunkno; /* Chunk allocated */ + unsigned chunkno; /* Chunk allocated */ haddr_t new_chunk_addr; unsigned u; /* Local index variable */ herr_t ret_value = SUCCEED; /* Return value */ @@ -921,7 +921,8 @@ H5O_alloc_new_chunk(H5F_t *f, hid_t dxpl_id, H5O_t *oh, size_t size, size_t *new oh->chunk = x; } /* end if */ - chunkno = (unsigned)oh->nchunks++; + H5_CHECKED_ASSIGN(chunkno, unsigned, oh->nchunks, size_t); + oh->nchunks++; oh->chunk[chunkno].addr = new_chunk_addr; oh->chunk[chunkno].size = size; oh->chunk[chunkno].gap = 0; diff --git a/src/H5Ocache.c b/src/H5Ocache.c index fbbbe60..3803978 100644 --- a/src/H5Ocache.c +++ b/src/H5Ocache.c @@ -770,7 +770,7 @@ H5O__cache_chk_deserialize(const void *image, size_t len, void *_udata, /* Set the fields for the chunk proxy */ chk_proxy->oh = udata->oh; - chk_proxy->chunkno = udata->oh->nchunks - 1; + H5_CHECKED_ASSIGN(chk_proxy->chunkno, unsigned, udata->oh->nchunks - 1, size_t); } /* end if */ else { /* Sanity check */ @@ -1324,7 +1324,7 @@ H5O__chunk_deserialize(H5O_t *oh, haddr_t addr, size_t len, const uint8_t *image /* Decode continuation message */ cont = (H5O_cont_t *)(H5O_MSG_CONT->decode)(udata->f, udata->dxpl_id, NULL, 0, &ioflags, oh->mesg[curmesg].raw); - cont->chunkno = udata->cont_msg_info->nmsgs + 1; /*the next continuation message/chunk */ + H5_CHECKED_ASSIGN(cont->chunkno, unsigned, udata->cont_msg_info->nmsgs + 1, size_t); /* the next continuation message/chunk */ /* Save 'native' form of continuation message */ oh->mesg[curmesg].native = cont; diff --git a/src/H5Pfapl.c b/src/H5Pfapl.c index a315f92..96de39c 100644 --- a/src/H5Pfapl.c +++ b/src/H5Pfapl.c @@ -778,7 +778,7 @@ done: const void * H5P_peek_driver_info(H5P_genplist_t *plist) { - void *ret_value = NULL; /* Return value */ + const void *ret_value = NULL; /* Return value */ FUNC_ENTER_NOAPI(NULL) diff --git a/src/H5Shyper.c b/src/H5Shyper.c index fe013a7..5231c6e 100644 --- a/src/H5Shyper.c +++ b/src/H5Shyper.c @@ -145,6 +145,9 @@ H5FL_DEFINE_STATIC(H5S_hyper_span_t); /* Declare a free list to manage the H5S_hyper_span_info_t struct */ H5FL_DEFINE_STATIC(H5S_hyper_span_info_t); +/* Declare extern free list to manage the H5S_sel_iter_t struct */ +H5FL_EXTERN(H5S_sel_iter_t); + /* #define H5S_HYPER_DEBUG */ #ifdef H5S_HYPER_DEBUG static herr_t @@ -9288,7 +9291,7 @@ H5S__hyper_project_intersection(const H5S_t *src_space, const H5S_t *dst_space, size_t ss_nelem; /* Number of elements for src_space */ size_t ss_i = (size_t)0; /* Index into offset/length arrays for src_space */ hbool_t advance_ss = FALSE; /* Whether to advance ss_i on the next iteration */ - H5S_sel_iter_t ss_iter; /* Selection iterator for src_space */ + H5S_sel_iter_t *ss_iter = NULL; /* Selection iterator for src_space */ hbool_t ss_iter_init = FALSE; /* Whether ss_iter is initialized */ hsize_t ss_sel_off = (hsize_t)0; /* Offset within src_space selection */ hsize_t ds_off[H5S_PROJECT_INTERSECT_NSEQS]; /* Offset array for dst_space */ @@ -9296,7 +9299,7 @@ H5S__hyper_project_intersection(const H5S_t *src_space, const H5S_t *dst_space, size_t ds_nseq; /* Number of sequences for dst_space */ size_t ds_nelem; /* Number of elements for dst_space */ size_t ds_i = (size_t)0; /* Index into offset/length arrays for dst_space */ - H5S_sel_iter_t ds_iter; /* Selection iterator for dst_space */ + H5S_sel_iter_t *ds_iter = NULL; /* Selection iterator for dst_space */ hbool_t ds_iter_init = FALSE; /* Whether ds_iter is initialized */ hsize_t ds_sel_off = (hsize_t)0; /* Offset within dst_space selection */ hsize_t sis_off[H5S_PROJECT_INTERSECT_NSEQS]; /* Offset array for src_intersect_space */ @@ -9305,7 +9308,7 @@ H5S__hyper_project_intersection(const H5S_t *src_space, const H5S_t *dst_space, size_t sis_nelem; /* Number of elements for src_intersect_space */ size_t sis_i = (size_t)0; /* Index into offset/length arrays for src_intersect_space */ hbool_t advance_sis = FALSE; /* Whether to advance sis_i on the next iteration */ - H5S_sel_iter_t sis_iter; /* Selection iterator for src_intersect_space */ + H5S_sel_iter_t *sis_iter = NULL; /* Selection iterator for src_intersect_space */ hbool_t sis_iter_init = FALSE; /* Whether sis_iter is initialized */ hsize_t int_sel_off; /* Offset within intersected selections (ss/sis and ds/ps) */ size_t int_len; /* Length of segment in intersected selections */ @@ -9384,35 +9387,47 @@ H5S__hyper_project_intersection(const H5S_t *src_space, const H5S_t *dst_space, /* Set unlim_dim */ proj_space->select.sel_info.hslab->unlim_dim = -1; + /* Allocate the source space iterator */ + if(NULL == (ss_iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASPACE, H5E_CANTALLOC, FAIL, "can't allocate source space iterator") + /* Initialize source space iterator */ - if(H5S_select_iter_init(&ss_iter, src_space, (size_t)1) < 0) + if(H5S_select_iter_init(ss_iter, src_space, (size_t)1) < 0) HGOTO_ERROR(H5E_DATASPACE, H5E_CANTINIT, FAIL, "unable to initialize selection iterator") ss_iter_init = TRUE; /* Get sequence list for source space */ - if(H5S_SELECT_GET_SEQ_LIST(src_space, 0u, &ss_iter, H5S_PROJECT_INTERSECT_NSEQS, ss_nelem, &ss_nseq, &nelem, ss_off, ss_len) < 0) + if(H5S_SELECT_GET_SEQ_LIST(src_space, 0u, ss_iter, H5S_PROJECT_INTERSECT_NSEQS, ss_nelem, &ss_nseq, &nelem, ss_off, ss_len) < 0) HGOTO_ERROR(H5E_INTERNAL, H5E_UNSUPPORTED, FAIL, "sequence length generation failed") ss_nelem -= nelem; HDassert(ss_nseq > 0); + /* Allocate the destination space iterator */ + if(NULL == (ds_iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASPACE, H5E_CANTALLOC, FAIL, "can't allocate destination space iterator") + /* Initialize destination space iterator */ - if(H5S_select_iter_init(&ds_iter, dst_space, (size_t)1) < 0) + if(H5S_select_iter_init(ds_iter, dst_space, (size_t)1) < 0) HGOTO_ERROR(H5E_DATASPACE, H5E_CANTINIT, FAIL, "unable to initialize selection iterator") ds_iter_init = TRUE; /* Get sequence list for destination space */ - if(H5S_SELECT_GET_SEQ_LIST(dst_space, 0u, &ds_iter, H5S_PROJECT_INTERSECT_NSEQS, ds_nelem, &ds_nseq, &nelem, ds_off, ds_len) < 0) + if(H5S_SELECT_GET_SEQ_LIST(dst_space, 0u, ds_iter, H5S_PROJECT_INTERSECT_NSEQS, ds_nelem, &ds_nseq, &nelem, ds_off, ds_len) < 0) HGOTO_ERROR(H5E_DATASPACE, H5E_CANTINIT, FAIL, "unable to initialize selection iterator") ds_nelem -= nelem; HDassert(ds_nseq > 0); + /* Allocate the source intersect space iterator */ + if(NULL == (sis_iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASPACE, H5E_CANTALLOC, FAIL, "can't allocate source intersect space iterator") + /* Initialize source intersect space iterator */ - if(H5S_select_iter_init(&sis_iter, src_intersect_space, (size_t)1) < 0) + if(H5S_select_iter_init(sis_iter, src_intersect_space, (size_t)1) < 0) HGOTO_ERROR(H5E_DATASPACE, H5E_CANTINIT, FAIL, "unable to initialize selection iterator") sis_iter_init = TRUE; /* Get sequence list for source intersect space */ - if(H5S_SELECT_GET_SEQ_LIST(src_intersect_space, 0u, &sis_iter, H5S_PROJECT_INTERSECT_NSEQS, sis_nelem, &sis_nseq, &nelem, sis_off, sis_len) < 0) + if(H5S_SELECT_GET_SEQ_LIST(src_intersect_space, 0u, sis_iter, H5S_PROJECT_INTERSECT_NSEQS, sis_nelem, &sis_nseq, &nelem, sis_off, sis_len) < 0) HGOTO_ERROR(H5E_INTERNAL, H5E_UNSUPPORTED, FAIL, "sequence length generation failed") sis_nelem -= nelem; HDassert(sis_nseq > 0); @@ -9427,7 +9442,7 @@ H5S__hyper_project_intersection(const H5S_t *src_space, const H5S_t *dst_space, if(++ss_i == ss_nseq) { if(ss_nelem > 0) { /* Try to grab more sequences from src_space */ - if(H5S_SELECT_GET_SEQ_LIST(src_space, 0u, &ss_iter, H5S_PROJECT_INTERSECT_NSEQS, ss_nelem, &ss_nseq, &nelem, ss_off, ss_len) < 0) + if(H5S_SELECT_GET_SEQ_LIST(src_space, 0u, ss_iter, H5S_PROJECT_INTERSECT_NSEQS, ss_nelem, &ss_nseq, &nelem, ss_off, ss_len) < 0) HGOTO_ERROR(H5E_INTERNAL, H5E_UNSUPPORTED, FAIL, "sequence length generation failed") HDassert(ss_len[0] > 0); @@ -9459,7 +9474,7 @@ H5S__hyper_project_intersection(const H5S_t *src_space, const H5S_t *dst_space, if(sis_nelem > 0) { /* Try to grab more sequences from src_intersect_space */ - if(H5S_SELECT_GET_SEQ_LIST(src_intersect_space, 0u, &sis_iter, H5S_PROJECT_INTERSECT_NSEQS, sis_nelem, &sis_nseq, &nelem, sis_off, sis_len) < 0) + if(H5S_SELECT_GET_SEQ_LIST(src_intersect_space, 0u, sis_iter, H5S_PROJECT_INTERSECT_NSEQS, sis_nelem, &sis_nseq, &nelem, sis_off, sis_len) < 0) HGOTO_ERROR(H5E_INTERNAL, H5E_UNSUPPORTED, FAIL, "sequence length generation failed") HDassert(sis_len[0] > 0); @@ -9511,7 +9526,7 @@ H5S__hyper_project_intersection(const H5S_t *src_space, const H5S_t *dst_space, HDassert(ds_nelem > 0); /* Try to grab more sequences from dst_space */ - if(H5S_SELECT_GET_SEQ_LIST(dst_space, 0u, &ds_iter, H5S_PROJECT_INTERSECT_NSEQS, ds_nelem, &ds_nseq, &nelem, ds_off, ds_len) < 0) + if(H5S_SELECT_GET_SEQ_LIST(dst_space, 0u, ds_iter, H5S_PROJECT_INTERSECT_NSEQS, ds_nelem, &ds_nseq, &nelem, ds_off, ds_len) < 0) HGOTO_ERROR(H5E_INTERNAL, H5E_UNSUPPORTED, FAIL, "sequence length generation failed") HDassert(ds_len[0] > 0); @@ -9625,19 +9640,22 @@ loop_end: done: /* Release source selection iterator */ - if(ss_iter_init) - if(H5S_SELECT_ITER_RELEASE(&ss_iter) < 0) - HDONE_ERROR(H5E_DATASPACE, H5E_CANTRELEASE, FAIL, "unable to release selection iterator") + if(ss_iter_init && H5S_SELECT_ITER_RELEASE(ss_iter) < 0) + HDONE_ERROR(H5E_DATASPACE, H5E_CANTRELEASE, FAIL, "unable to release selection iterator") + if(ss_iter) + ss_iter = H5FL_FREE(H5S_sel_iter_t, ss_iter); /* Release destination selection iterator */ - if(ds_iter_init) - if(H5S_SELECT_ITER_RELEASE(&ds_iter) < 0) - HDONE_ERROR(H5E_DATASPACE, H5E_CANTRELEASE, FAIL, "unable to release selection iterator") + if(ds_iter_init && H5S_SELECT_ITER_RELEASE(ds_iter) < 0) + HDONE_ERROR(H5E_DATASPACE, H5E_CANTRELEASE, FAIL, "unable to release selection iterator") + if(ds_iter) + ds_iter = H5FL_FREE(H5S_sel_iter_t, ds_iter); /* Release source intersect selection iterator */ - if(sis_iter_init) - if(H5S_SELECT_ITER_RELEASE(&sis_iter) < 0) - HDONE_ERROR(H5E_DATASPACE, H5E_CANTRELEASE, FAIL, "unable to release selection iterator") + if(sis_iter_init && H5S_SELECT_ITER_RELEASE(sis_iter) < 0) + HDONE_ERROR(H5E_DATASPACE, H5E_CANTRELEASE, FAIL, "unable to release selection iterator") + if(sis_iter) + sis_iter = H5FL_FREE(H5S_sel_iter_t, sis_iter); /* Cleanup on error */ if(ret_value < 0) { diff --git a/src/H5Sselect.c b/src/H5Sselect.c index d4a4d69..2968bed 100644 --- a/src/H5Sselect.c +++ b/src/H5Sselect.c @@ -39,6 +39,15 @@ static htri_t H5S_select_iter_has_next_block(const H5S_sel_iter_t *iter); static herr_t H5S_select_iter_next_block(H5S_sel_iter_t *iter); #endif /* LATER */ +/* Declare a free list to manage the H5S_sel_iter_t struct */ +H5FL_DEFINE(H5S_sel_iter_t); + +/* Declare extern free list to manage sequences of size_t */ +H5FL_SEQ_EXTERN(size_t); + +/* Declare extern free list to manage sequences of hsize_t */ +H5FL_SEQ_EXTERN(hsize_t); + /*-------------------------------------------------------------------------- @@ -1364,8 +1373,10 @@ herr_t H5S_select_iterate(void *buf, const H5T_t *type, const H5S_t *space, const H5S_sel_iter_op_t *op, void *op_data) { - H5S_sel_iter_t iter; /* Selection iteration info */ + H5S_sel_iter_t *iter = NULL; /* Selection iteration info */ hbool_t iter_init = FALSE; /* Selection iteration info has been initialized */ + hsize_t *off = NULL; /* Array to store sequence offsets */ + size_t *len = NULL; /* Array to store sequence lengths */ hssize_t nelmts; /* Number of elements in selection */ hsize_t space_size[H5O_LAYOUT_NDIMS]; /* Dataspace size */ size_t max_elem; /* Maximum number of elements allowed in sequences */ @@ -1386,8 +1397,12 @@ H5S_select_iterate(void *buf, const H5T_t *type, const H5S_t *space, if(0 == (elmt_size = H5T_get_size(type))) HGOTO_ERROR(H5E_DATATYPE, H5E_BADSIZE, FAIL, "datatype size invalid") + /* Allocate the selection iterator */ + if(NULL == (iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASPACE, H5E_CANTALLOC, FAIL, "can't allocate selection iterator") + /* Initialize iterator */ - if(H5S_select_iter_init(&iter, space, elmt_size) < 0) + if(H5S_select_iter_init(iter, space, elmt_size) < 0) HGOTO_ERROR(H5E_DATASPACE, H5E_CANTINIT, FAIL, "unable to initialize selection iterator") iter_init = TRUE; /* Selection iteration info has been initialized */ @@ -1408,16 +1423,20 @@ H5S_select_iterate(void *buf, const H5T_t *type, const H5S_t *space, /* Compute the maximum number of bytes required */ H5_CHECKED_ASSIGN(max_elem, size_t, nelmts, hssize_t); + /* Allocate the offset & length arrays */ + if(NULL == (len = H5FL_SEQ_MALLOC(size_t, H5D_IO_VECTOR_SIZE))) + HGOTO_ERROR(H5E_DATASPACE, H5E_CANTALLOC, FAIL, "can't allocate length vector array") + if(NULL == (off = H5FL_SEQ_MALLOC(hsize_t, H5D_IO_VECTOR_SIZE))) + HGOTO_ERROR(H5E_DATASPACE, H5E_CANTALLOC, FAIL, "can't allocate offset vector array") + /* Loop, while elements left in selection */ while(max_elem > 0 && user_ret == 0) { - hsize_t off[H5D_IO_VECTOR_SIZE]; /* Array to store sequence offsets */ - size_t len[H5D_IO_VECTOR_SIZE]; /* Array to store sequence lengths */ size_t nelem; /* Number of elements used in sequences */ size_t nseq; /* Number of sequences generated */ size_t curr_seq; /* Current sequence being worked on */ /* Get the sequences of bytes */ - if(H5S_SELECT_GET_SEQ_LIST(space, 0, &iter, (size_t)H5D_IO_VECTOR_SIZE, max_elem, &nseq, &nelem, off, len) < 0) + if(H5S_SELECT_GET_SEQ_LIST(space, 0, iter, (size_t)H5D_IO_VECTOR_SIZE, max_elem, &nseq, &nelem, off, len) < 0) HGOTO_ERROR(H5E_INTERNAL, H5E_UNSUPPORTED, FAIL, "sequence length generation failed") /* Loop, while sequences left to process */ @@ -1477,9 +1496,17 @@ H5S_select_iterate(void *buf, const H5T_t *type, const H5S_t *space, ret_value = user_ret; done: + /* Release resources, if allocated */ + if(len) + len = H5FL_SEQ_FREE(size_t, len); + if(off) + off = H5FL_SEQ_FREE(hsize_t, off); + /* Release selection iterator */ - if(iter_init && H5S_SELECT_ITER_RELEASE(&iter) < 0) + if(iter_init && H5S_SELECT_ITER_RELEASE(iter) < 0) HDONE_ERROR(H5E_DATASPACE, H5E_CANTRELEASE, FAIL, "unable to release selection iterator") + if(iter) + iter = H5FL_FREE(H5S_sel_iter_t, iter); FUNC_LEAVE_NOAPI(ret_value) } /* end H5S_select_iterate() */ @@ -1583,8 +1610,8 @@ H5S_get_select_type(const H5S_t *space) htri_t H5S_select_shape_same(const H5S_t *space1, const H5S_t *space2) { - H5S_sel_iter_t iter_a; /* Selection a iteration info */ - H5S_sel_iter_t iter_b; /* Selection b iteration info */ + H5S_sel_iter_t *iter_a = NULL; /* Selection a iteration info */ + H5S_sel_iter_t *iter_b = NULL; /* Selection b iteration info */ hbool_t iter_a_init = 0; /* Selection a iteration info has been initialized */ hbool_t iter_b_init = 0; /* Selection b iteration info has been initialized */ htri_t ret_value = TRUE; /* Return value */ @@ -1729,15 +1756,21 @@ H5S_select_shape_same(const H5S_t *space1, const H5S_t *space2) hsize_t off_b[H5O_LAYOUT_NDIMS]; /* Offset of selection b blocks */ hbool_t first_block = TRUE; /* Flag to indicate the first block */ + /* Allocate the selection iterators */ + if(NULL == (iter_a = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASPACE, H5E_CANTALLOC, FAIL, "can't allocate selection iterator") + if(NULL == (iter_b = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASPACE, H5E_CANTALLOC, FAIL, "can't allocate selection iterator") + /* Initialize iterator for each dataspace selection * Use '0' for element size instead of actual element size to indicate * that the selection iterator shouldn't be "flattened", since we * aren't actually going to be doing I/O with the iterators. */ - if(H5S_select_iter_init(&iter_a, space_a, (size_t)0) < 0) + if(H5S_select_iter_init(iter_a, space_a, (size_t)0) < 0) HGOTO_ERROR(H5E_DATASPACE, H5E_CANTINIT, FAIL, "unable to initialize selection iterator a") iter_a_init = 1; - if(H5S_select_iter_init(&iter_b, space_b, (size_t)0) < 0) + if(H5S_select_iter_init(iter_b, space_b, (size_t)0) < 0) HGOTO_ERROR(H5E_DATASPACE, H5E_CANTINIT, FAIL, "unable to initialize selection iterator b") iter_b_init = 1; @@ -1748,9 +1781,9 @@ H5S_select_shape_same(const H5S_t *space1, const H5S_t *space2) htri_t status_a, status_b; /* Status from next block checks */ /* Get the current block for each selection iterator */ - if(H5S_SELECT_ITER_BLOCK(&iter_a, start_a, end_a) < 0) + if(H5S_SELECT_ITER_BLOCK(iter_a, start_a, end_a) < 0) HGOTO_ERROR(H5E_DATASPACE, H5E_CANTGET, FAIL, "unable to get iterator block a") - if(H5S_SELECT_ITER_BLOCK(&iter_b, start_b, end_b) < 0) + if(H5S_SELECT_ITER_BLOCK(iter_b, start_b, end_b) < 0) HGOTO_ERROR(H5E_DATASPACE, H5E_CANTGET, FAIL, "unable to get iterator block b") space_a_dim = (int)space_a_rank - 1; @@ -1821,10 +1854,10 @@ H5S_select_shape_same(const H5S_t *space1, const H5S_t *space2) } /* end else */ /* Check if we are able to advance to the next selection block */ - if((status_a = H5S_SELECT_ITER_HAS_NEXT_BLOCK(&iter_a)) < 0) + if((status_a = H5S_SELECT_ITER_HAS_NEXT_BLOCK(iter_a)) < 0) HGOTO_ERROR(H5E_DATASPACE, H5E_CANTNEXT, FAIL, "unable to check iterator block a") - if((status_b = H5S_SELECT_ITER_HAS_NEXT_BLOCK(&iter_b)) < 0) + if((status_b = H5S_SELECT_ITER_HAS_NEXT_BLOCK(iter_b)) < 0) HGOTO_ERROR(H5E_DATASPACE, H5E_CANTNEXT, FAIL, "unable to check iterator block b") /* Did we run out of blocks at the same time? */ @@ -1834,10 +1867,10 @@ H5S_select_shape_same(const H5S_t *space1, const H5S_t *space2) HGOTO_DONE(FALSE) else { /* Advance to next block in selection iterators */ - if(H5S_SELECT_ITER_NEXT_BLOCK(&iter_a) < 0) + if(H5S_SELECT_ITER_NEXT_BLOCK(iter_a) < 0) HGOTO_ERROR(H5E_DATASPACE, H5E_CANTNEXT, FAIL, "unable to advance to next iterator block a") - if(H5S_SELECT_ITER_NEXT_BLOCK(&iter_b) < 0) + if(H5S_SELECT_ITER_NEXT_BLOCK(iter_b) < 0) HGOTO_ERROR(H5E_DATASPACE, H5E_CANTNEXT, FAIL, "unable to advance to next iterator block b") } /* end else */ } /* end while */ @@ -1845,12 +1878,14 @@ H5S_select_shape_same(const H5S_t *space1, const H5S_t *space2) } /* end else */ done: - if(iter_a_init) - if(H5S_SELECT_ITER_RELEASE(&iter_a) < 0) - HDONE_ERROR(H5E_DATASPACE, H5E_CANTRELEASE, FAIL, "unable to release selection iterator a") - if(iter_b_init) - if(H5S_SELECT_ITER_RELEASE(&iter_b) < 0) - HDONE_ERROR(H5E_DATASPACE, H5E_CANTRELEASE, FAIL, "unable to release selection iterator b") + if(iter_a_init && H5S_SELECT_ITER_RELEASE(iter_a) < 0) + HDONE_ERROR(H5E_DATASPACE, H5E_CANTRELEASE, FAIL, "unable to release selection iterator a") + if(iter_a) + iter_a = H5FL_FREE(H5S_sel_iter_t, iter_a); + if(iter_b_init && H5S_SELECT_ITER_RELEASE(iter_b) < 0) + HDONE_ERROR(H5E_DATASPACE, H5E_CANTRELEASE, FAIL, "unable to release selection iterator b") + if(iter_b) + iter_b = H5FL_FREE(H5S_sel_iter_t, iter_b); FUNC_LEAVE_NOAPI(ret_value) } /* H5S_select_shape_same() */ @@ -2152,8 +2187,10 @@ done: herr_t H5S_select_fill(const void *fill, size_t fill_size, const H5S_t *space, void *_buf) { - H5S_sel_iter_t iter; /* Selection iteration info */ + H5S_sel_iter_t *iter = NULL; /* Selection iteration info */ hbool_t iter_init = 0; /* Selection iteration info has been initialized */ + hsize_t *off = NULL; /* Array to store sequence offsets */ + size_t *len = NULL; /* Array to store sequence lengths */ hssize_t nelmts; /* Number of elements in selection */ size_t max_elem; /* Total number of elements in selection */ herr_t ret_value = SUCCEED; /* Return value */ @@ -2166,8 +2203,12 @@ H5S_select_fill(const void *fill, size_t fill_size, const H5S_t *space, void *_b HDassert(space); HDassert(_buf); + /* Allocate the selection iterator */ + if(NULL == (iter = H5FL_MALLOC(H5S_sel_iter_t))) + HGOTO_ERROR(H5E_DATASPACE, H5E_CANTALLOC, FAIL, "can't allocate selection iterator") + /* Initialize iterator */ - if(H5S_select_iter_init(&iter, space, fill_size) < 0) + if(H5S_select_iter_init(iter, space, fill_size) < 0) HGOTO_ERROR(H5E_DATASPACE, H5E_CANTINIT, FAIL, "unable to initialize selection iterator") iter_init = 1; /* Selection iteration info has been initialized */ @@ -2178,16 +2219,20 @@ H5S_select_fill(const void *fill, size_t fill_size, const H5S_t *space, void *_b /* Compute the number of bytes to process */ H5_CHECKED_ASSIGN(max_elem, size_t, nelmts, hssize_t); + /* Allocate the offset & length arrays */ + if(NULL == (len = H5FL_SEQ_MALLOC(size_t, H5D_IO_VECTOR_SIZE))) + HGOTO_ERROR(H5E_DATASPACE, H5E_CANTALLOC, FAIL, "can't allocate length vector array") + if(NULL == (off = H5FL_SEQ_MALLOC(hsize_t, H5D_IO_VECTOR_SIZE))) + HGOTO_ERROR(H5E_DATASPACE, H5E_CANTALLOC, FAIL, "can't allocate offset vector array") + /* Loop, while elements left in selection */ while(max_elem > 0) { - hsize_t off[H5D_IO_VECTOR_SIZE]; /* Array to store sequence offsets */ - size_t len[H5D_IO_VECTOR_SIZE]; /* Array to store sequence lengths */ size_t nseq; /* Number of sequences generated */ size_t curr_seq; /* Current sequnce being worked on */ size_t nelem; /* Number of elements used in sequences */ /* Get the sequences of bytes */ - if(H5S_SELECT_GET_SEQ_LIST(space, 0, &iter, (size_t)H5D_IO_VECTOR_SIZE, max_elem, &nseq, &nelem, off, len) < 0) + if(H5S_SELECT_GET_SEQ_LIST(space, 0, iter, (size_t)H5D_IO_VECTOR_SIZE, max_elem, &nseq, &nelem, off, len) < 0) HGOTO_ERROR(H5E_INTERNAL, H5E_UNSUPPORTED, FAIL, "sequence length generation failed") /* Loop over sequences */ @@ -2207,9 +2252,17 @@ H5S_select_fill(const void *fill, size_t fill_size, const H5S_t *space, void *_b } /* end while */ done: - /* Release resouces */ - if(iter_init && H5S_SELECT_ITER_RELEASE(&iter) < 0) + /* Release resources, if allocated */ + if(len) + len = H5FL_SEQ_FREE(size_t, len); + if(off) + off = H5FL_SEQ_FREE(hsize_t, off); + + /* Release selection iterator */ + if(iter_init && H5S_SELECT_ITER_RELEASE(iter) < 0) HDONE_ERROR(H5E_DATASPACE, H5E_CANTRELEASE, FAIL, "unable to release selection iterator") + if(iter) + iter = H5FL_FREE(H5S_sel_iter_t, iter); FUNC_LEAVE_NOAPI(ret_value) } /* H5S_select_fill() */ diff --git a/src/H5system.c b/src/H5system.c index e6ca5d4..e17373c 100644 --- a/src/H5system.c +++ b/src/H5system.c @@ -172,7 +172,7 @@ HDfprintf(FILE *stream, const char *fmt, ...) s = rest; } /* end if */ else if ('*'==*s) { - fwidth = va_arg (ap, int); + fwidth = va_arg(ap, int); if(fwidth < 0) { leftjust = 1; fwidth = -fwidth; @@ -269,23 +269,22 @@ HDfprintf(FILE *stream, const char *fmt, ...) len += HDsnprintf(format_templ + len, (sizeof(format_templ) - (size_t)(len + 1)), "%s", modifier); HDsnprintf(format_templ + len, (sizeof(format_templ) - (size_t)(len + 1)), "%c", conv); - /* Conversion */ switch (conv) { case 'd': case 'i': if(!HDstrcmp(modifier, "h")) { - short x = (short)va_arg (ap, int); - n = fprintf (stream, format_templ, x); + short x = (short)va_arg(ap, int); + n = fprintf(stream, format_templ, x); } else if(!*modifier) { - int x = va_arg (ap, int); - n = fprintf (stream, format_templ, x); - } else if(!HDstrcmp (modifier, "l")) { - long x = va_arg (ap, long); - n = fprintf (stream, format_templ, x); + int x = va_arg(ap, int); + n = fprintf(stream, format_templ, x); + } else if(!HDstrcmp(modifier, "l")) { + long x = va_arg(ap, long); + n = fprintf(stream, format_templ, x); } else { int64_t x = va_arg(ap, int64_t); - n = fprintf (stream, format_templ, x); + n = fprintf(stream, format_templ, x); } break; @@ -294,13 +293,13 @@ HDfprintf(FILE *stream, const char *fmt, ...) case 'x': case 'X': if(!HDstrcmp(modifier, "h")) { - unsigned short x = (unsigned short)va_arg (ap, unsigned int); + unsigned short x = (unsigned short)va_arg(ap, unsigned int); n = fprintf(stream, format_templ, x); } else if(!*modifier) { - unsigned int x = va_arg (ap, unsigned int); /*lint !e732 Loss of sign not really occuring */ + unsigned int x = va_arg(ap, unsigned int); /*lint !e732 Loss of sign not really occuring */ n = fprintf(stream, format_templ, x); } else if(!HDstrcmp(modifier, "l")) { - unsigned long x = va_arg (ap, unsigned long); /*lint !e732 Loss of sign not really occuring */ + unsigned long x = va_arg(ap, unsigned long); /*lint !e732 Loss of sign not really occuring */ n = fprintf(stream, format_templ, x); } else { uint64_t x = va_arg(ap, uint64_t); /*lint !e732 Loss of sign not really occuring */ @@ -336,7 +335,7 @@ HDfprintf(FILE *stream, const char *fmt, ...) case 'a': { - haddr_t x = va_arg (ap, haddr_t); /*lint !e732 Loss of sign not really occuring */ + haddr_t x = va_arg(ap, haddr_t); /*lint !e732 Loss of sign not really occuring */ if(H5F_addr_defined(x)) { len = 0; @@ -405,7 +404,7 @@ HDfprintf(FILE *stream, const char *fmt, ...) htri_t tri_var = va_arg(ap, htri_t); if(tri_var > 0) - fprintf (stream, "TRUE"); + fprintf(stream, "TRUE"); else if(!tri_var) fprintf(stream, "FALSE"); else diff --git a/src/H5timer.c b/src/H5timer.c index d9be6bb..f36681e 100644 --- a/src/H5timer.c +++ b/src/H5timer.c @@ -127,16 +127,16 @@ H5_timer_begin (H5_timer_t *timer) #ifdef H5_HAVE_GETRUSAGE HDgetrusage (RUSAGE_SELF, &rusage); timer->utime = (double)rusage.ru_utime.tv_sec + - ((double)rusage.ru_utime.tv_usec / 1e6F); + ((double)rusage.ru_utime.tv_usec / (double)1e6F); timer->stime = (double)rusage.ru_stime.tv_sec + - ((double)rusage.ru_stime.tv_usec / 1e6F); + ((double)rusage.ru_stime.tv_usec / (double)1e6F); #else timer->utime = 0.0F; timer->stime = 0.0F; #endif #ifdef H5_HAVE_GETTIMEOFDAY HDgettimeofday (&etime, NULL); - timer->etime = (double)etime.tv_sec + ((double)etime.tv_usec / 1e6F); + timer->etime = (double)etime.tv_sec + ((double)etime.tv_usec / (double)1e6F); #else timer->etime = 0.0F; #endif @@ -166,9 +166,9 @@ H5_timer_end (H5_timer_t *sum/*in,out*/, H5_timer_t *timer/*in,out*/) HDassert(timer); H5_timer_begin(&now); - timer->utime = MAX(0.0F, now.utime - timer->utime); - timer->stime = MAX(0.0F, now.stime - timer->stime); - timer->etime = MAX(0.0F, now.etime - timer->etime); + timer->utime = MAX((double)0.0F, now.utime - timer->utime); + timer->stime = MAX((double)0.0F, now.stime - timer->stime); + timer->etime = MAX((double)0.0F, now.etime - timer->etime); if (sum) { sum->utime += timer->utime; @@ -208,28 +208,28 @@ H5_bandwidth(char *buf/*out*/, double nbytes, double nseconds) { double bw; - if(nseconds <= 0.0F) + if(nseconds <= (double)0.0F) HDstrcpy(buf, " NaN"); else { bw = nbytes/nseconds; - if(H5_DBL_ABS_EQUAL(bw, 0.0F)) - HDstrcpy(buf, "0.000 B/s"); - else if(bw < 1.0F) + if(H5_DBL_ABS_EQUAL(bw, (double)0.0F)) + HDstrcpy(buf, "0.000 B/s"); + else if(bw < (double)1.0F) sprintf(buf, "%10.4e", bw); - else if(bw < H5_KB) { + else if(bw < (double)H5_KB) { sprintf(buf, "%05.4f", bw); HDstrcpy(buf+5, " B/s"); - } else if(bw < H5_MB) { - sprintf(buf, "%05.4f", bw / H5_KB); + } else if(bw < (double)H5_MB) { + sprintf(buf, "%05.4f", bw / (double)H5_KB); HDstrcpy(buf+5, " kB/s"); - } else if(bw < H5_GB) { - sprintf(buf, "%05.4f", bw / H5_MB); + } else if(bw < (double)H5_GB) { + sprintf(buf, "%05.4f", bw / (double)H5_MB); HDstrcpy(buf+5, " MB/s"); - } else if(bw < H5_TB) { - sprintf(buf, "%05.4f", bw / H5_GB); + } else if(bw < (double)H5_TB) { + sprintf(buf, "%05.4f", bw / (double)H5_GB); HDstrcpy(buf+5, " GB/s"); - } else if(bw < H5_PB) { - sprintf(buf, "%05.4f", bw / H5_TB); + } else if(bw < (double)H5_PB) { + sprintf(buf, "%05.4f", bw / (double)H5_TB); HDstrcpy(buf+5, " TB/s"); } else { sprintf(buf, "%10.4e", bw); diff --git a/test/cmpd_dset.c b/test/cmpd_dset.c index 22bf3a2..311b9bb 100644 --- a/test/cmpd_dset.c +++ b/test/cmpd_dset.c @@ -102,15 +102,18 @@ typedef struct { float f, g, h[16], i, j; double k, l, m, n; } stype1; + typedef struct { int a, b, c[8], d, e; float f, g, h[16], i, j; double k, l, m, n; long o, p, q; } stype2; + typedef struct { int a, b, c[8], d, e; } stype3; + typedef struct { int a, b, c[8], d, e; float f, g, h[16], i, j; @@ -147,7 +150,7 @@ typedef struct { * Moved this part of code from MAIN to TEST_COMPOUND function. *------------------------------------------------------------------------- */ -static int +static unsigned test_compound (char *filename, hid_t fapl) { /* First dataset */ @@ -868,31 +871,31 @@ error: *------------------------------------------------------------------------- */ static void -initialize_stype1(unsigned char *buf, const size_t num) +initialize_stype1(unsigned char *buf, size_t num) { int i, j; stype1 *s_ptr; - for (i=0; i<(int)num; i++) { - s_ptr = (stype1*)buf + i; - s_ptr->a = i*8+0; - s_ptr->b = i*8+1; - for(j=0; j<8; j++) - s_ptr->c[j] = i*8+j; - s_ptr->d = i*8+6; - s_ptr->e = i*8+7; - - s_ptr->f = i*2/3; - s_ptr->g = i*2/3+1; - for(j=0; j<16; j++) - s_ptr->h[j] = i*j/5+j; - s_ptr->i = i*2/3+2; - s_ptr->j = i*2/3+3; - - s_ptr->k = i/7+1; - s_ptr->l = i/7+2; - s_ptr->m = i/7+3; - s_ptr->n = i/7+4; + for(i = 0; i < (int)num; i++) { + s_ptr = (stype1 *)buf + i; + s_ptr->a = i * 8 + 0; + s_ptr->b = i * 8 + 1; + for(j = 0; j < 8; j++) + s_ptr->c[j] = i * 8 + j; + s_ptr->d = i * 8 + 6; + s_ptr->e = i * 8 + 7; + + s_ptr->f = (float)(i * 2 / 3); + s_ptr->g = (float)(i * 2 / 3 + 1); + for(j = 0; j < 16; j++) + s_ptr->h[j] = (float)(i * j / 5 + j); + s_ptr->i = (float)(i * 2 / 3 + 2); + s_ptr->j = (float)(i * 2 / 3 + 3); + + s_ptr->k = i / 7 + 1; + s_ptr->l = i / 7 + 2; + s_ptr->m = i / 7 + 3; + s_ptr->n = i / 7 + 4; } } @@ -911,35 +914,35 @@ initialize_stype1(unsigned char *buf, const size_t num) *------------------------------------------------------------------------- */ static void -initialize_stype2(unsigned char *buf, const size_t num) +initialize_stype2(unsigned char *buf, size_t num) { size_t i, j; stype2 *s_ptr; - for (i=0; ia = i*8+0; - s_ptr->b = i*8+1; - for(j=0; j<8; j++) - s_ptr->c[j] = i*8+j; - s_ptr->d = i*8+6; - s_ptr->e = i*8+7; - - s_ptr->f = i*2/3; - s_ptr->g = i*2/3+1; - for(j=0; j<16; j++) - s_ptr->h[j] = i*j/5+j; - s_ptr->i = i*2/3+2; - s_ptr->j = i*2/3+3; - - s_ptr->k = i/7+1; - s_ptr->l = i/7+2; - s_ptr->m = i/7+3; - s_ptr->n = i/7+4; - - s_ptr->o = i*3+0; - s_ptr->p = i*3+1; - s_ptr->q = i*3+2; + for(i = 0; i < num; i++) { + s_ptr = (stype2 *)buf + i; + s_ptr->a = (int)(i * 8 + 0); + s_ptr->b = (int)(i * 8 + 1); + for(j = 0; j < 8; j++) + s_ptr->c[j] = (int)(i * 8 + j); + s_ptr->d = (int)(i * 8 + 6); + s_ptr->e = (int)(i * 8 + 7); + + s_ptr->f = (float)(i * 2 / 3); + s_ptr->g = (float)(i * 2 / 3 + 1); + for(j = 0; j < 16; j++) + s_ptr->h[j] = (float)(i * j / 5 + j); + s_ptr->i = (float)(i * 2 / 3 + 2); + s_ptr->j = (float)(i * 2 / 3 + 3); + + s_ptr->k = (double)(i / 7 + 1); + s_ptr->l = (double)(i / 7 + 2); + s_ptr->m = (double)(i / 7 + 3); + s_ptr->n = (double)(i / 7 + 4); + + s_ptr->o = (long)(i * 3 + 0); + s_ptr->p = (long)(i * 3 + 1); + s_ptr->q = (long)(i * 3 + 2); } } @@ -958,19 +961,19 @@ initialize_stype2(unsigned char *buf, const size_t num) *------------------------------------------------------------------------- */ static void -initialize_stype3(unsigned char *buf, const size_t num) +initialize_stype3(unsigned char *buf, size_t num) { int i, j; stype3 *s_ptr; - for (i=0; i<(int)num; i++) { - s_ptr = (stype3*)buf + i; - s_ptr->a = i*8+0; - s_ptr->b = i*8+1; - for(j=0; j<8; j++) - s_ptr->c[j] = i*8+j; - s_ptr->d = i*8+6; - s_ptr->e = i*8+7; + for(i = 0; i < (int)num; i++) { + s_ptr = (stype3 *)buf + i; + s_ptr->a = i * 8 + 0; + s_ptr->b = i * 8 + 1; + for(j = 0; j < 8; j++) + s_ptr->c[j] = i * 8 + j; + s_ptr->d = i * 8 + 6; + s_ptr->e = i * 8 + 7; } } @@ -989,39 +992,39 @@ initialize_stype3(unsigned char *buf, const size_t num) *------------------------------------------------------------------------- */ static void -initialize_stype4(unsigned char *buf, const size_t num) +initialize_stype4(unsigned char *buf, size_t num) { size_t i, j; stype4 *s_ptr; - for (i=0; ia = i*8+0; - s_ptr->b = i*8+1; - for(j=0; j<8; j++) - s_ptr->c[j] = i*8+j; - s_ptr->d = i*8+6; - s_ptr->e = i*8+7; - - s_ptr->f = i*2/3; - s_ptr->g = i*2/3+1; - for(j=0; j<16; j++) - s_ptr->h[j] = i*j/5+j; - s_ptr->i = i*2/3+2; - s_ptr->j = i*2/3+3; - - s_ptr->k = i/7+1; - s_ptr->l = i/7+2; - s_ptr->m = i/7+3; - s_ptr->n = i/7+4; - - s_ptr->o = i*3+0; - s_ptr->p = i*3+1; - s_ptr->q = i*3+2; - - s_ptr->r = i*5+1; - s_ptr->s = i*5+2; - s_ptr->t = i*5+3; + for(i = 0; i < num; i++) { + s_ptr = (stype4 *)buf + i; + s_ptr->a = (int)(i * 8 + 0); + s_ptr->b = (int)(i * 8 + 1); + for(j = 0; j < 8; j++) + s_ptr->c[j] = (int)(i * 8 + j); + s_ptr->d = (int)(i * 8 + 6); + s_ptr->e = (int)(i * 8 + 7); + + s_ptr->f = (float)(i * 2 / 3); + s_ptr->g = (float)(i * 2 / 3 + 1); + for(j = 0; j < 16; j++) + s_ptr->h[j] = (float)(i * j / 5 + j); + s_ptr->i = (float)(i * 2 / 3 + 2); + s_ptr->j = (float)(i * 2 / 3 + 3); + + s_ptr->k = (double)(i / 7 + 1); + s_ptr->l = (double)(i / 7 + 2); + s_ptr->m = (double)(i / 7 + 3); + s_ptr->n = (double)(i / 7 + 4); + + s_ptr->o = (long)(i * 3 + 0); + s_ptr->p = (long)(i * 3 + 1); + s_ptr->q = (long)(i * 3 + 2); + + s_ptr->r = (long long)(i * 5 + 1); + s_ptr->s = (long long)(i * 5 + 2); + s_ptr->t = (long long)(i * 5 + 3); } } @@ -1349,7 +1352,7 @@ error: * Modifications: *------------------------------------------------------------------------- */ -static int +static unsigned test_hdf5_src_subset(char *filename, hid_t fapl) { hid_t file; @@ -1554,7 +1557,7 @@ error: * Modifications: *------------------------------------------------------------------------- */ -static int +static unsigned test_hdf5_dst_subset(char *filename, hid_t fapl) { hid_t file; @@ -1763,7 +1766,7 @@ error: * Modifications: *------------------------------------------------------------------------- */ -static int +static unsigned test_pack_ooo(void) { hid_t cmpd, sub_cmpd; /* Datatype IDs */ @@ -1788,7 +1791,7 @@ test_pack_ooo(void) for(i=0; i= size of member datatypes */ - for(i= 0;i< (size_t)size[0]; i++) - for(j = 0; j < (size_t)size[1]; j++) { - power = HDpow(2.0F, (double)(precision[0]-1)); - orig_data[i][j].i = (int)(((long long)HDrandom() % (long long)power) << offset[0]); - power = HDpow(2.0F, (double)(precision[1]-1)); - orig_data[i][j].c = (char)(((long long)HDrandom() % (long long)power) << offset[1]); - power = HDpow(2.0F, (double)(precision[2]-1)); - orig_data[i][j].s = (short)(((long long)HDrandom() % (long long)power) << offset[2]); - orig_data[i][j].f = float_val[i][j]; - - /* some even-numbered integer values are negtive */ - if((i*size[1]+j+1)%2 == 0) { - orig_data[i][j].i = -orig_data[i][j].i; - orig_data[i][j].s = (short)-orig_data[i][j].s; + for(i = 0; i < (size_t)size[0]; i++) + for(j = 0; j < (size_t)size[1]; j++) { + power = HDpow(2.0F, (double)(precision[0]-1)); + orig_data[i][j].i = (int)(((long long)HDrandom() % (long long)power) << offset[0]); + power = HDpow(2.0F, (double)(precision[1]-1)); + orig_data[i][j].c = (char)(((long long)HDrandom() % (long long)power) << offset[1]); + power = HDpow(2.0F, (double)(precision[2]-1)); + orig_data[i][j].s = (short)(((long long)HDrandom() % (long long)power) << offset[2]); + orig_data[i][j].f = float_val[i][j]; + + /* some even-numbered integer values are negtive */ + if((i * size[1] + j + 1) % 2 == 0) { + orig_data[i][j].i = -orig_data[i][j].i; + orig_data[i][j].s = (short)-orig_data[i][j].s; + } } - } PASSED(); @@ -3407,9 +3461,8 @@ test_nbit_compound(hid_t file) */ TESTING(" nbit compound (write)"); - if(H5Dwrite(dataset, mem_cmpd_tid, H5S_ALL, H5S_ALL, H5P_DEFAULT, - orig_data) < 0) - goto error; + if(H5Dwrite(dataset, mem_cmpd_tid, H5S_ALL, H5S_ALL, H5P_DEFAULT, orig_data) < 0) + FAIL_STACK_ERROR PASSED(); /*---------------------------------------------------------------------- @@ -3419,9 +3472,8 @@ test_nbit_compound(hid_t file) TESTING(" nbit compound (read)"); /* Read the dataset back */ - if(H5Dread(dataset, mem_cmpd_tid, H5S_ALL, H5S_ALL, H5P_DEFAULT, - new_data) < 0) - goto error; + if(H5Dread(dataset, mem_cmpd_tid, H5S_ALL, H5S_ALL, H5P_DEFAULT, new_data) < 0) + FAIL_STACK_ERROR /* Check that the values read are the same as the values written * Use mask for checking the significant bits, ignoring the padding bits @@ -3429,12 +3481,12 @@ test_nbit_compound(hid_t file) i_mask = ~((unsigned)~0 << (precision[0] + offset[0])) & ((unsigned)~0 << offset[0]); c_mask = ~((unsigned)~0 << (precision[1] + offset[1])) & ((unsigned)~0 << offset[1]); s_mask = ~((unsigned)~0 << (precision[2] + offset[2])) & ((unsigned)~0 << offset[2]); - for(i=0; i= size of member datatypes */ for(i= 0;i< (size_t)size[0]; i++) - for(j = 0; j < (size_t)size[1]; j++) { - power = HDpow(2.0F, (double)(precision[0]-1)); - orig_data[i][j].a.i = (int)(((long long)HDrandom() % (long long)power) << offset[0]); - power = HDpow(2.0F, (double)(precision[1]-1)); - orig_data[i][j].a.c = (char)(((long long)HDrandom() % (long long)power) << offset[1]); - power = HDpow(2.0F, (double)(precision[2]-1)); - orig_data[i][j].a.s = (short)(-((long long)HDrandom() % (long long)power) << offset[2]); - orig_data[i][j].a.f = float_val[i][j]; - - power = HDpow(2.0F, (double)precision[3]); - orig_data[i][j].v = (unsigned int)(((long long)HDrandom() % (long long)power) << offset[3]); - - for(m = 0; m < (size_t)array_dims[0]; m++) - for(n = 0; n < (size_t)array_dims[1]; n++) { - power = HDpow(2.0F, (double)(precision[4]-1)); - orig_data[i][j].b[m][n] = (char)(((long long)HDrandom() % (long long)power) << offset[4]); - } /* end for */ - - for(m = 0; m < (size_t)array_dims[0]; m++) - for(n = 0; n < (size_t)array_dims[1]; n++) { + for(j = 0; j < (size_t)size[1]; j++) { power = HDpow(2.0F, (double)(precision[0]-1)); - orig_data[i][j].d[m][n].i = (int)(-((long long)HDrandom() % (long long)power) << offset[0]); + orig_data[i][j].a.i = (int)(((long long)HDrandom() % (long long)power) << offset[0]); power = HDpow(2.0F, (double)(precision[1]-1)); - orig_data[i][j].d[m][n].c = (char)(((long long)HDrandom() % (long long)power) << offset[1]); + orig_data[i][j].a.c = (char)(((long long)HDrandom() % (long long)power) << offset[1]); power = HDpow(2.0F, (double)(precision[2]-1)); - orig_data[i][j].d[m][n].s = (short)(((long long)HDrandom() % (long long)power) << offset[2]); - orig_data[i][j].d[m][n].f = float_val[i][j]; - } /* end for */ - } /* end for */ + orig_data[i][j].a.s = (short)(-((long long)HDrandom() % (long long)power) << offset[2]); + orig_data[i][j].a.f = float_val[i][j]; + + power = HDpow(2.0F, (double)precision[3]); + orig_data[i][j].v = (unsigned int)(((long long)HDrandom() % (long long)power) << offset[3]); + + for(m = 0; m < (size_t)array_dims[0]; m++) + for(n = 0; n < (size_t)array_dims[1]; n++) { + power = HDpow(2.0F, (double)(precision[4]-1)); + orig_data[i][j].b[m][n] = (char)(((long long)HDrandom() % (long long)power) << offset[4]); + } /* end for */ + + for(m = 0; m < (size_t)array_dims[0]; m++) + for(n = 0; n < (size_t)array_dims[1]; n++) { + power = HDpow(2.0F, (double)(precision[0]-1)); + orig_data[i][j].d[m][n].i = (int)(-((long long)HDrandom() % (long long)power) << offset[0]); + power = HDpow(2.0F, (double)(precision[1]-1)); + orig_data[i][j].d[m][n].c = (char)(((long long)HDrandom() % (long long)power) << offset[1]); + power = HDpow(2.0F, (double)(precision[2]-1)); + orig_data[i][j].d[m][n].s = (short)(((long long)HDrandom() % (long long)power) << offset[2]); + orig_data[i][j].d[m][n].f = float_val[i][j]; + } /* end for */ + } /* end for */ PASSED(); @@ -3648,9 +3759,8 @@ test_nbit_compound_2(hid_t file) */ TESTING(" nbit compound complex (write)"); - if(H5Dwrite(dataset, mem_cmpd_tid2, H5S_ALL, H5S_ALL, H5P_DEFAULT, - orig_data) < 0) - goto error; + if(H5Dwrite(dataset, mem_cmpd_tid2, H5S_ALL, H5S_ALL, H5P_DEFAULT, orig_data) < 0) + FAIL_STACK_ERROR PASSED(); /*---------------------------------------------------------------------- @@ -3660,9 +3770,8 @@ test_nbit_compound_2(hid_t file) TESTING(" nbit compound complex (read)"); /* Read the dataset back */ - if(H5Dread(dataset, mem_cmpd_tid2, H5S_ALL, H5S_ALL, H5P_DEFAULT, - new_data) < 0) - goto error; + if(H5Dread(dataset, mem_cmpd_tid2, H5S_ALL, H5S_ALL, H5P_DEFAULT, new_data) < 0) + FAIL_STACK_ERROR /* Check that the values read are the same as the values written * Use mask for checking the significant bits, ignoring the padding bits @@ -3683,63 +3792,77 @@ test_nbit_compound_2(hid_t file) s_mask = ~((unsigned)~0 << (precision[2] + offset[2])) & ((unsigned)~0 << offset[2]); b_mask = ~((unsigned)~0 << (precision[4] + offset[4])) & ((unsigned)~0 << offset[4]); for(i=0; i<(size_t)size[0]; i++) { - for(j=0; j<(size_t)size[1]; j++) { - b_failed = 0; - d_failed = 0; + for(j=0; j<(size_t)size[1]; j++) { + b_failed = 0; + d_failed = 0; - for(m = 0; m < (size_t)array_dims[0]; m++) - for(n = 0; n < (size_t)array_dims[1]; n++) - if(((unsigned)new_data[i][j].b[m][n] & b_mask)!=((unsigned)orig_data[i][j].b[m][n] & b_mask)) { + for(m = 0; m < (size_t)array_dims[0]; m++) + for(n = 0; n < (size_t)array_dims[1]; n++) + if(((unsigned)new_data[i][j].b[m][n] & b_mask)!=((unsigned)orig_data[i][j].b[m][n] & b_mask)) { b_failed = 1; goto out; - } - - for(m = 0; m < (size_t)array_dims[0]; m++) - for(n = 0; n < (size_t)array_dims[1]; n++) - if(((unsigned)new_data[i][j].d[m][n].i & i_mask) != ((unsigned)orig_data[i][j].d[m][n].i & i_mask)|| - ((unsigned)new_data[i][j].d[m][n].c & c_mask) != ((unsigned)orig_data[i][j].d[m][n].c & c_mask)|| - ((unsigned)new_data[i][j].d[m][n].s & s_mask) != ((unsigned)orig_data[i][j].d[m][n].s & s_mask)|| - (new_data[i][j].d[m][n].f==new_data[i][j].d[m][n].f && - new_data[i][j].d[m][n].f != new_data[i][j].d[m][n].f)) { - d_failed = 1; - goto out; - } - - out: - if(((unsigned)new_data[i][j].a.i & i_mask) != ((unsigned)orig_data[i][j].a.i & i_mask)|| - ((unsigned)new_data[i][j].a.c & c_mask) != ((unsigned)orig_data[i][j].a.c & c_mask)|| - ((unsigned)new_data[i][j].a.s & s_mask) != ((unsigned)orig_data[i][j].a.s & s_mask)|| - (new_data[i][j].a.f==new_data[i][j].a.f && - new_data[i][j].a.f != new_data[i][j].a.f)|| - new_data[i][j].v != orig_data[i][j].v || b_failed || d_failed) { - H5_FAILED(); - printf(" Read different values than written.\n"); - printf(" At index %lu,%lu\n", (unsigned long)i, (unsigned long)j); - goto error; + } + + for(m = 0; m < (size_t)array_dims[0]; m++) + for(n = 0; n < (size_t)array_dims[1]; n++) + if(((unsigned)new_data[i][j].d[m][n].i & i_mask) != ((unsigned)orig_data[i][j].d[m][n].i & i_mask)|| + ((unsigned)new_data[i][j].d[m][n].c & c_mask) != ((unsigned)orig_data[i][j].d[m][n].c & c_mask)|| + ((unsigned)new_data[i][j].d[m][n].s & s_mask) != ((unsigned)orig_data[i][j].d[m][n].s & s_mask)|| + (new_data[i][j].d[m][n].f == new_data[i][j].d[m][n].f && !H5_FLT_ABS_EQUAL(new_data[i][j].d[m][n].f, new_data[i][j].d[m][n].f))) { + d_failed = 1; + goto out; + } + +out: + if(((unsigned)new_data[i][j].a.i & i_mask) != ((unsigned)orig_data[i][j].a.i & i_mask)|| + ((unsigned)new_data[i][j].a.c & c_mask) != ((unsigned)orig_data[i][j].a.c & c_mask)|| + ((unsigned)new_data[i][j].a.s & s_mask) != ((unsigned)orig_data[i][j].a.s & s_mask)|| + (new_data[i][j].a.f == new_data[i][j].a.f && !H5_FLT_ABS_EQUAL(new_data[i][j].a.f, new_data[i][j].a.f)) || + new_data[i][j].v != orig_data[i][j].v || b_failed || d_failed) { + H5_FAILED(); + printf(" Read different values than written.\n"); + printf(" At index %lu,%lu\n", (unsigned long)i, (unsigned long)j); + goto error; + } } - } } /*---------------------------------------------------------------------- * Cleanup *---------------------------------------------------------------------- */ - if(H5Tclose(i_tid) < 0) goto error; - if(H5Tclose(c_tid) < 0) goto error; - if(H5Tclose(s_tid) < 0) goto error; - if(H5Tclose(f_tid) < 0) goto error; - if(H5Tclose(v_tid) < 0) goto error; - if(H5Tclose(cmpd_tid2) < 0) goto error; - if(H5Tclose(cmpd_tid1) < 0) goto error; - if(H5Tclose(mem_cmpd_tid2) < 0) goto error; - if(H5Tclose(mem_cmpd_tid1) < 0) goto error; - if(H5Tclose(array_tid) < 0) goto error; - if(H5Tclose(base_tid) < 0) goto error; - if(H5Tclose(array_cmplx_tid) < 0) goto error; - if(H5Tclose(mem_array_cmplx_tid) < 0) goto error; - if(H5Pclose(dc) < 0) goto error; - if(H5Sclose(space) < 0) goto error; - if(H5Dclose(dataset) < 0) goto error; + if(H5Tclose(i_tid) < 0) + FAIL_STACK_ERROR + if(H5Tclose(c_tid) < 0) + FAIL_STACK_ERROR + if(H5Tclose(s_tid) < 0) + FAIL_STACK_ERROR + if(H5Tclose(f_tid) < 0) + FAIL_STACK_ERROR + if(H5Tclose(v_tid) < 0) + FAIL_STACK_ERROR + if(H5Tclose(cmpd_tid2) < 0) + FAIL_STACK_ERROR + if(H5Tclose(cmpd_tid1) < 0) + FAIL_STACK_ERROR + if(H5Tclose(mem_cmpd_tid2) < 0) + FAIL_STACK_ERROR + if(H5Tclose(mem_cmpd_tid1) < 0) + FAIL_STACK_ERROR + if(H5Tclose(array_tid) < 0) + FAIL_STACK_ERROR + if(H5Tclose(base_tid) < 0) + FAIL_STACK_ERROR + if(H5Tclose(array_cmplx_tid) < 0) + FAIL_STACK_ERROR + if(H5Tclose(mem_array_cmplx_tid) < 0) + FAIL_STACK_ERROR + if(H5Pclose(dc) < 0) + FAIL_STACK_ERROR + if(H5Sclose(space) < 0) + FAIL_STACK_ERROR + if(H5Dclose(dataset) < 0) + FAIL_STACK_ERROR PASSED(); @@ -3832,7 +3955,7 @@ test_nbit_compound_3(hid_t file) for(i = 0; i < (size_t)size[0]; i++) { power = HDpow(2.0F, 17.0F - 1.0F); HDmemset(&orig_data[i], 0, sizeof(orig_data[i])); - orig_data[i].i = HDrandom() % (long)power; + orig_data[i].i = (int)(HDrandom() % (long)power); HDstrcpy(orig_data[i].str, "fixed-length C string"); orig_data[i].vl_str = HDstrdup("variable-length C string"); @@ -4203,7 +4326,7 @@ test_nbit_flt_size(hid_t file) */ for (i=0; i < DSET_DIM1; i++) for (j=0; j < DSET_DIM2; j++) - orig_data[i][j] = (rand() % 1234567) / 2; + orig_data[i][j] = (float)(HDrandom() % 1234567) / 2; /* Describe the dataspace. */ @@ -4587,7 +4710,7 @@ test_scaleoffset_float(hid_t file) /* Initialize data */ for(i= 0;i< (size_t)size[0]; i++) for(j = 0; j < (size_t)size[1]; j++) { - orig_data[i][j] = (float)((HDrandom() % 100000) / 1000.0F); + orig_data[i][j] = (float)(HDrandom() % 100000) / 1000.0F; /* even-numbered values are negtive */ if((i*size[1]+j+1)%2 == 0) @@ -4718,10 +4841,10 @@ test_scaleoffset_float_2(hid_t file) /* Initialize data of hyperslab */ for(j = 0; j < (size_t)size[1]; j++) { - orig_data[0][j] = (float)((HDrandom() % 100000) / 1000.0F); + orig_data[0][j] = (float)(HDrandom() % 100000) / 1000.0F; /* even-numbered values are negtive */ - if((j+1)%2 == 0) + if((j + 1) % 2 == 0) orig_data[0][j] = -orig_data[0][j]; } @@ -4829,10 +4952,10 @@ test_scaleoffset_double(hid_t file) /* Initialize data */ for(i= 0;i< (size_t)size[0]; i++) for(j = 0; j < (size_t)size[1]; j++) { - orig_data[i][j] = (HDrandom() % 10000000) / 10000000.0F; + orig_data[i][j] = (float)(HDrandom() % 10000000) / 10000000.0F; /* even-numbered values are negtive */ - if((i*size[1]+j+1)%2 == 0) + if((i* size[1] + j + 1) % 2 == 0) orig_data[i][j] = -orig_data[i][j]; } @@ -4960,10 +5083,10 @@ test_scaleoffset_double_2(hid_t file) /* Initialize data of hyperslab */ for(j = 0; j < (size_t)size[1]; j++) { - orig_data[0][j] = (HDrandom() % 10000000) / 10000000.0F; + orig_data[0][j] = (float)(HDrandom() % 10000000) / 10000000.0F; /* even-numbered values are negtive */ - if((j+1)%2 == 0) + if((j + 1) % 2 == 0) orig_data[0][j] = -orig_data[0][j]; } @@ -5958,7 +6081,7 @@ test_set_local(hid_t fapl) for(j=0; j