Skip to content

Commit

Permalink
Fixes failures with gfortran 4.8 (#2979)
Browse files Browse the repository at this point in the history
  • Loading branch information
brtnfld authored May 18, 2023
1 parent dc3ef60 commit 4829208
Show file tree
Hide file tree
Showing 3 changed files with 25 additions and 19 deletions.
28 changes: 14 additions & 14 deletions fortran/src/H5Off.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1027,7 +1027,7 @@ SUBROUTINE h5ovisit_f(object_id, index_type, order, op, op_data, return_value, h
INTEGER, INTENT(IN) :: order

TYPE(C_FUNPTR), INTENT(IN) :: op
TYPE(C_PTR), INTENT(IN) :: op_data
TYPE(C_PTR), INTENT(IN) :: op_data
INTEGER, INTENT(OUT) :: return_value
INTEGER, INTENT(OUT) :: hdferr
INTEGER, INTENT(IN), OPTIONAL :: fields
Expand All @@ -1039,12 +1039,12 @@ INTEGER FUNCTION h5ovisit_c(object_id, index_type, order, op, op_data, fields) &
IMPORT :: C_FUNPTR, C_PTR
IMPORT :: HID_T
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: object_id
INTEGER, INTENT(IN) :: index_type
INTEGER, INTENT(IN) :: order
INTEGER(HID_T):: object_id
INTEGER :: index_type
INTEGER :: order
TYPE(C_FUNPTR), VALUE :: op
TYPE(C_PTR), VALUE :: op_data
INTEGER, INTENT(IN) :: fields
INTEGER :: fields
END FUNCTION h5ovisit_c
END INTERFACE

Expand Down Expand Up @@ -1343,15 +1343,15 @@ INTEGER FUNCTION h5ovisit_by_name_c(loc_id, object_name, namelen, index_type, or
IMPORT :: C_CHAR, C_PTR, C_FUNPTR
IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
INTEGER(HID_T) , INTENT(IN) :: loc_id
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: object_name
INTEGER(SIZE_T) :: namelen
INTEGER , INTENT(IN) :: index_type
INTEGER , INTENT(IN) :: order
TYPE(C_FUNPTR) , VALUE :: op
TYPE(C_PTR) , VALUE :: op_data
INTEGER(HID_T) , INTENT(IN) :: lapl_id
INTEGER , INTENT(IN) :: fields
INTEGER(HID_T) :: loc_id
CHARACTER(KIND=C_CHAR), DIMENSION(*) :: object_name
INTEGER(SIZE_T) :: namelen
INTEGER :: index_type
INTEGER :: order
TYPE(C_FUNPTR), VALUE :: op
TYPE(C_PTR) , VALUE :: op_data
INTEGER(HID_T) :: lapl_id
INTEGER :: fields
END FUNCTION h5ovisit_by_name_c
END INTERFACE

Expand Down
12 changes: 8 additions & 4 deletions fortran/test/tH5P_F03.F90
Original file line number Diff line number Diff line change
Expand Up @@ -532,6 +532,7 @@ SUBROUTINE external_test_offset(cleanup,total_error)
INTEGER(hid_t) :: dset=-1 ! dataset
INTEGER(hid_t) :: grp=-1 ! group to emit diagnostics
INTEGER(size_t) :: i, j ! miscellaneous counters
INTEGER :: k
CHARACTER(LEN=180) :: filename ! file names
INTEGER, DIMENSION(1:25) :: part
INTEGER, DIMENSION(1:100), TARGET :: whole ! raw data buffers
Expand Down Expand Up @@ -598,8 +599,9 @@ SUBROUTINE external_test_offset(cleanup,total_error)
CALL h5dread_f(dset, H5T_NATIVE_INTEGER, f_ptr, error, mem_space_id=space, file_space_id=space)
CALL check("h5dread_f", error, total_error)

DO i = 1, 100
IF(whole(i) .NE. i-1)THEN
DO k = 1, 100
CALL verify("h5dread_f", whole(k), k-1, error)
IF(error .NE. 0)THEN
WRITE(*,*) "Incorrect value(s) read."
total_error = total_error + 1
EXIT
Expand All @@ -619,8 +621,10 @@ SUBROUTINE external_test_offset(cleanup,total_error)

CALL h5sclose_f(hs_space, error)
CALL check("h5sclose_f", error, total_error)
DO i = INT(hs_start(1))+1, INT(hs_start(1)+hs_count(1))
IF(whole(i) .NE. i-1)THEN

DO k = INT(hs_start(1))+1, INT(hs_start(1)+hs_count(1))
CALL verify("h5dread_f", whole(k), k-1, error)
IF(error .NE. 0)THEN
WRITE(*,*) "Incorrect value(s) read."
total_error = total_error + 1
EXIT
Expand Down
4 changes: 3 additions & 1 deletion fortran/test/tf.F90
Original file line number Diff line number Diff line change
Expand Up @@ -69,9 +69,11 @@ SUBROUTINE write_test_header(title_header)

CHARACTER(LEN=*), INTENT(IN) :: title_header ! test name
INTEGER, PARAMETER :: width = TAB_SPACE+10
CHARACTER(LEN=2*width) ::title_centered =" "
CHARACTER(LEN=2*width) ::title_centered
INTEGER :: len, i

title_centered(:) = " "

len=LEN_TRIM(title_header)
title_centered(1:3) ="| |"
title_centered((width-len)/2:(width-len)/2+len) = TRIM(title_header)
Expand Down

0 comments on commit 4829208

Please sign in to comment.