Skip to content

Commit

Permalink
fixing some misc. NAG warnings
Browse files Browse the repository at this point in the history
  • Loading branch information
brtnfld committed Oct 11, 2023
1 parent 799028d commit 856c921
Show file tree
Hide file tree
Showing 5 changed files with 1 addition and 76 deletions.
1 change: 0 additions & 1 deletion fortran/src/H5Dff.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1816,7 +1816,6 @@ END SUBROUTINE h5dwrite_reference_obj

SUBROUTINE h5dwrite_reference_dsetreg(dset_id, mem_type_id, buf, dims, hdferr, &
mem_space_id, file_space_id, xfer_prp)
USE, INTRINSIC :: ISO_C_BINDING, ONLY : C_PTR
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: dset_id
INTEGER(HID_T), INTENT(IN) :: mem_type_id
Expand Down
2 changes: 1 addition & 1 deletion fortran/src/H5Sff.F90
Original file line number Diff line number Diff line change
Expand Up @@ -71,7 +71,7 @@ INTEGER FUNCTION h5screate_simple_c(rank, dims, maxdims, space_id) BIND(C,NAME='
IMPLICIT NONE
INTEGER, INTENT(IN) :: rank
INTEGER(HSIZE_T), INTENT(IN) :: dims(rank)
INTEGER(HSIZE_T), DIMENSION(:),INTENT(IN) :: maxdims(rank)
INTEGER(HSIZE_T), INTENT(IN) :: maxdims(rank)
INTEGER(HID_T), INTENT(OUT) :: space_id
END FUNCTION h5screate_simple_c
END INTERFACE
Expand Down
1 change: 0 additions & 1 deletion fortran/src/H5_buildiface.F90
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,6 @@
#include <H5config_f.inc>

PROGRAM H5_buildiface
USE, INTRINSIC :: ISO_C_BINDING, ONLY : C_PTR, C_CHAR, C_LOC
IMPLICIT NONE

! These values are valid REAL KINDs (with corresponding C float) found during configure
Expand Down
3 changes: 0 additions & 3 deletions fortran/test/tH5D.F90
Original file line number Diff line number Diff line change
Expand Up @@ -644,7 +644,6 @@ SUBROUTINE test_dset_fill(cleanup, total_error)
INTEGER, PARAMETER :: int_kind_16 = SELECTED_INT_KIND(18) !should map to INTEGER*8 on most modern processors
INTEGER(KIND=int_kind_1) , DIMENSION(1:DIM0), TARGET :: data_i1
INTEGER(KIND=int_kind_4) , DIMENSION(1:DIM0), TARGET :: data_i4
INTEGER(KIND=int_kind_8) , DIMENSION(1:DIM0), TARGET :: data_i8
INTEGER(KIND=int_kind_16), DIMENSION(1:DIM0), TARGET :: data_i16
INTEGER(KIND=int_kind_1) , TARGET :: data0_i1 = 4
INTEGER(KIND=int_kind_4) , TARGET :: data0_i4 = 4
Expand Down Expand Up @@ -683,7 +682,6 @@ SUBROUTINE test_dset_fill(cleanup, total_error)
! Initialize memory buffer
data_i1 = -2
data_i4 = -2
data_i8 = -2
data_i16 = -2
data_int = -2
#if H5_HAVE_Fortran_INTEGER_SIZEOF_16!=0
Expand Down Expand Up @@ -798,7 +796,6 @@ SUBROUTINE test_dset_fill(cleanup, total_error)
! Initialize memory buffer
data_i1 = -2
data_i4 = -2
data_i8 = -2
data_i16 = -2
#if H5_HAVE_Fortran_INTEGER_SIZEOF_16!=0
data_i32 = -2
Expand Down
70 changes: 0 additions & 70 deletions fortran/test/tH5G_1_8.F90
Original file line number Diff line number Diff line change
Expand Up @@ -192,48 +192,18 @@ SUBROUTINE group_info(cleanup, fapl, total_error)
IF(idx_type == H5_INDEX_CRT_ORDER_F)THEN
IF(iorder == H5_ITER_INC_F)THEN
order = H5_ITER_INC_F
!!$ IF(use_index(i))THEN
!!$ WRITE(*,'(5x,A)')"query group info by creation order index in increasing order w/creation order index"
!!$ ELSE
!!$ WRITE(*,'(5x,A)')"query group info by creation order index in increasing order w/o creation order index"
!!$ ENDIF
ELSE IF (iorder == H5_ITER_DEC_F) THEN
order = H5_ITER_DEC_F
!!$ IF(use_index(i))THEN
!!$ WRITE(*,'(5x,A)')"query group info by creation order index in decreasing order w/creation order index"
!!$ ELSE
!!$ WRITE(*,'(5x,A)')"query group info by creation order index in decreasing order w/o creation order index"
!!$ ENDIF
ELSE
order = H5_ITER_NATIVE_F
!!$ IF(use_index(i))THEN
!!$ WRITE(*,'(5x,A)')"query group info by creation order index in native order w/creation order index"
!!$ ELSE
!!$ WRITE(*,'(5x,A)')"query group info by creation order index in native order w/o creation order index"
!!$ ENDIF
ENDIF
ELSE
IF(iorder == H5_ITER_INC_F)THEN
order = H5_ITER_INC_F
!!$ IF(use_index(i))THEN
!!$ WRITE(*,'(5x,A)')"query group info by creation order index in increasing order w/creation order index"
!!$ ELSE
!!$ WRITE(*,'(5x,A)')"query group info by creation order index in increasing order w/o creation order index"
!!$ ENDIF
ELSE IF (iorder == H5_ITER_DEC_F) THEN
order = H5_ITER_DEC_F
!!$ IF(use_index(i))THEN
!!$ WRITE(*,'(5x,A)')"query group info by creation order index in decreasing order w/creation order index"
!!$ ELSE
!!$ WRITE(*,'(5x,A)')"query group info by creation order index in decreasing order w/o creation order index"
!!$ ENDIF
ELSE
order = H5_ITER_NATIVE_F
!!$ IF(use_index(i))THEN
!!$ WRITE(*,'(5x,A)')"query group info by creation order index in native order w/creation order index"
!!$ ELSE
!!$ WRITE(*,'(5x,A)')"query group info by creation order index in native order w/o creation order index"
!!$ ENDIF
ENDIF
END IF

Expand Down Expand Up @@ -1263,56 +1233,16 @@ SUBROUTINE delete_by_idx(cleanup, fapl, total_error)
CHARACTER(LEN=2) :: chr2
INTEGER :: error
INTEGER :: id_type
!
!
!
CHARACTER(LEN=80) :: fix_filename1
CHARACTER(LEN=80) :: fix_filename2
INTEGER(HSIZE_T) :: htmp

LOGICAL :: cleanup

DO i = 1, 80
fix_filename1(i:i) = " "
fix_filename2(i:i) = " "
ENDDO

! Loop over operating on different indices on link fields
DO idx_type = H5_INDEX_NAME_F, H5_INDEX_CRT_ORDER_F
! Loop over operating in different orders
DO iorder = H5_ITER_INC_F, H5_ITER_DEC_F
! Loop over using index for creation order value
DO i = 1, 2
! Print appropriate test message
!!$ IF(idx_type == H5_INDEX_CRT_ORDER_F)THEN
!!$ IF(iorder == H5_ITER_INC_F)THEN
!!$ IF(use_index(i))THEN
!!$ WRITE(*,'(5x,A)')"deleting links by creation order index in increasing order w/creation order index"
!!$ ELSE
!!$ WRITE(*,'(5x,A)')"deleting links by creation order index in increasing order w/o creation order index"
!!$ ENDIF
!!$ ELSE
!!$ IF(use_index(i))THEN
!!$ WRITE(*,'(5x,A)')"deleting links by creation order index in decreasing order w/creation order index"
!!$ ELSE
!!$ WRITE(*,'(5x,A)')"deleting links by creation order index in decreasing order w/o creation order index"
!!$ ENDIF
!!$ ENDIF
!!$ ELSE
!!$ IF(iorder == H5_ITER_INC_F)THEN
!!$ IF(use_index(i))THEN
!!$ WRITE(*,'(5x,A)')"deleting links by name index in increasing order w/creation order index"
!!$ ELSE
!!$ WRITE(*,'(5x,A)')"deleting links by name index in increasing order w/o creation order index"
!!$ ENDIF
!!$ ELSE
!!$ IF(use_index(i))THEN
!!$ WRITE(*,'(5x,A)')"deleting links by name index in decreasing order w/creation order index"
!!$ ELSE
!!$ WRITE(*,'(5x,A)')"deleting links by name index in decreasing order w/o creation order index"
!!$ ENDIF
!!$ ENDIF
!!$ ENDIF

! Create file
CALL H5Fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, error, access_prp=fapl)
Expand Down

0 comments on commit 856c921

Please sign in to comment.