Skip to content

Commit

Permalink
Merge pull request ESMCI#1529 from NCAR/ejh_warn_4
Browse files Browse the repository at this point in the history
even more fortran warning fixes
  • Loading branch information
edhartnett authored Jun 26, 2019
2 parents 9a6b5eb + d5aa624 commit 001640d
Show file tree
Hide file tree
Showing 5 changed files with 17 additions and 25 deletions.
8 changes: 4 additions & 4 deletions tests/general/pio_decomp_frame_tests.F90.in
Original file line number Diff line number Diff line change
Expand Up @@ -129,7 +129,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN nc_write_read_4d_col_decomp
(start(2) - 1 + j - 1) * dims(1) + i
wbuf(i,j,k,f) = wbuf(i,j,k,f) + (f - 1) * (dims(1) * dims(2) * dims(3))
tmp_idx = (k - 1) * (ncols * nrows) + (j - 1) * nrows + i
compdof(tmp_idx) = wbuf(i,j,k,1)
compdof(tmp_idx) = int(wbuf(i,j,k,1))
end do
end do
end do
Expand Down Expand Up @@ -275,7 +275,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN nc_reuse_3d_decomp
do j=1,ncols
do i=1,nrows
tmp_idx = (k - 1) * (ncols * nrows) + (j - 1) * nrows + i
compdof(tmp_idx) = wbuf4d(i,j,k,1)
compdof(tmp_idx) = int(wbuf4d(i,j,k,1))
end do
end do
end do
Expand Down Expand Up @@ -319,7 +319,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN nc_reuse_3d_decomp
do j=1,ncols
do i=1,nrows
tmp_idx = (k - 1) * (ncols * nrows) + (j - 1) * nrows + i
compdof(tmp_idx) = exp_val4d(i,j,k,1)
compdof(tmp_idx) = int(exp_val4d(i,j,k,1))
end do
end do
end do
Expand Down Expand Up @@ -457,7 +457,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN nc_test_limited_time_dim
(start(2) - 1 + j - 1) * dims(1) + i
wbuf(i,j,k,f) = wbuf(i,j,k,f) + (f - 1) * (dims(1) * dims(2) * dims(3))
tmp_idx = (k - 1) * (ncols * nrows) + (j - 1) * nrows + i
compdof(tmp_idx) = wbuf(i,j,k,1)
compdof(tmp_idx) = int(wbuf(i,j,k,1))
end do
end do
end do
Expand Down
6 changes: 3 additions & 3 deletions tests/general/pio_decomp_tests.F90.in
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN nc_write_1d_darray
PIO_TF_FC_DATA_TYPE, dimension(VEC_LOCAL_SZ) :: buf
integer, dimension(1) :: dims
integer :: pio_dim
integer :: i, ierr, lsz
integer :: i, ierr
! iotypes = valid io types
integer, dimension(:), allocatable :: iotypes
character(len=PIO_TF_MAX_STR_LEN), dimension(:), allocatable :: iotype_descs
Expand Down Expand Up @@ -117,7 +117,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN nc_wr_1d_const_buf_sz
PIO_TF_FC_DATA_TYPE, dimension(MAX_VEC_SZ) :: wbuf, rbuf
integer, dimension(1) :: dims
integer :: pio_dim
integer :: i, ierr, lsz
integer :: i, ierr
! iotypes = valid io types
integer, dimension(:), allocatable :: iotypes
character(len=PIO_TF_MAX_STR_LEN), dimension(:), allocatable :: iotype_descs
Expand Down Expand Up @@ -207,7 +207,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN nc_write_1d_reuse_decomp
PIO_TF_FC_DATA_TYPE, dimension(VEC_LOCAL_SZ) :: buf, rbuf
integer, dimension(1) :: dims
integer :: pio_dim_file1, pio_dim_file2
integer :: i, ierr, lsz
integer :: i, ierr
! iotypes = valid io types
integer, dimension(:), allocatable :: iotypes
character(len=PIO_TF_MAX_STR_LEN), dimension(:), allocatable :: iotype_descs
Expand Down
8 changes: 4 additions & 4 deletions tests/general/pio_decomp_tests_1d.F90.in
Original file line number Diff line number Diff line change
Expand Up @@ -139,7 +139,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN nc_wr_rd_1d_bc
PIO_TF_FC_DATA_TYPE, dimension(:), allocatable :: rbuf, wbuf, exp_val
integer, dimension(1) :: dims
integer :: pio_dim
integer :: i, ierr, lsz
integer :: i, ierr
! iotypes = valid io types
integer, dimension(:), allocatable :: iotypes
character(len=PIO_TF_MAX_STR_LEN), dimension(:), allocatable :: iotype_descs
Expand Down Expand Up @@ -249,7 +249,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN nc_wr_1d_bc_with_holes
PIO_TF_FC_DATA_TYPE, dimension(:), allocatable :: rbuf, wbuf, exp_val
integer, dimension(1) :: dims
integer :: pio_dim
integer :: i, ierr, lsz
integer :: i, ierr
! iotypes = valid io types
integer, dimension(:), allocatable :: iotypes
character(len=PIO_TF_MAX_STR_LEN), dimension(:), allocatable :: iotype_descs
Expand All @@ -263,7 +263,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN nc_wr_1d_bc_with_holes
allocate(exp_val(count(1)))
do i=1,count(1)
wbuf(i) = start(1) + i - 1
compdof(i) = wbuf(i)
compdof(i) = int(wbuf(i))
exp_val(i) = wbuf(i)
end do

Expand Down Expand Up @@ -327,7 +327,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN nc_wr_1d_bc_random
PIO_TF_FC_DATA_TYPE, dimension(:), allocatable :: rbuf, wbuf
integer, dimension(1) :: dims
integer :: pio_dim
integer :: i, j, ierr, lsz
integer :: i, j, ierr
integer :: tmp
real :: u
! iotypes = valid io types
Expand Down
13 changes: 4 additions & 9 deletions tests/general/pio_rearr_opts.F90.in
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,6 @@ PIO_TF_AUTO_TEST_SUB_BEGIN init_fin_with_rearr_opts

integer, parameter :: NUM_REARRANGERS = 2
integer :: rearrs(NUM_REARRANGERS) = (/pio_rearr_subset,pio_rearr_box/)
character(len=PIO_TF_MAX_STR_LEN) :: rearrs_info(NUM_REARRANGERS) = (/"PIO_REARR_SUBSET","PIO_REARR_BOX "/)
type(pio_rearr_opt_t) :: pio_rearr_opts
! Dummy val for max pend req
integer, parameter :: MAX_PEND_REQ = 10
Expand Down Expand Up @@ -187,7 +186,6 @@ SUBROUTINE create_decomp_and_init_buf(iosys, iocomm, iodesc, wbuf, dims, ret)
integer, dimension(1), intent(out) :: dims
integer, intent(out) :: ret

integer :: pio_dim
integer, dimension(:), allocatable :: compdof
integer, dimension(1) :: start, count
integer :: i
Expand All @@ -203,7 +201,7 @@ SUBROUTINE create_decomp_and_init_buf(iosys, iocomm, iodesc, wbuf, dims, ret)
allocate(compdof(count(1)))
do i=1,count(1)
wbuf(i) = start(1) + i - 1
compdof(i) = wbuf(i)
compdof(i) = int(wbuf(i))
end do

call PIO_initdecomp(iosys, PIO_real, dims, compdof, iodesc)
Expand Down Expand Up @@ -248,7 +246,7 @@ END SUBROUTINE
! Open file and inq var
! All details are picked from pio_rearr_opts_tgv module
! Note: The file is kept open so the called needs to close it
SUBROUTINE open_file_and_get_var(iosys, pio_file, iotype, pio_var, dims, ret)
SUBROUTINE open_file_and_get_var(iosys, pio_file, iotype, pio_var, ret)
use pio_tutil
use pio_rearr_opts_tgv
implicit none
Expand All @@ -257,11 +255,8 @@ SUBROUTINE open_file_and_get_var(iosys, pio_file, iotype, pio_var, dims, ret)
type(file_desc_t), intent(out) :: pio_file
integer, intent(in) :: iotype
type(var_desc_t), intent(out) :: pio_var
integer, dimension(1), intent(in) :: dims
integer, intent(out) :: ret

integer :: pio_dim

ret = PIO_openfile(iosys, pio_file, iotype, tgv_fname, pio_write)
PIO_TF_CHECK_ERR(ret, "Could not create file " // trim(tgv_fname))

Expand Down Expand Up @@ -331,7 +326,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN write_with_rearr_opts
integer, dimension(:), allocatable :: iotypes
character(len=PIO_TF_MAX_STR_LEN), dimension(:), allocatable :: iotype_descs
integer :: num_iotypes
integer :: ret, ierr, i
integer :: ret, i

num_iotypes = 0
call PIO_TF_Get_nc_iotypes(iotypes, iotype_descs, num_iotypes)
Expand Down Expand Up @@ -436,7 +431,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN write_with_rearr_opts
rbuf = 0

call open_file_and_get_var(dup_iosys, pio_file, iotypes(i),&
pio_var, dims, ret)
pio_var, ret)
PIO_TF_CHECK_ERR(ret, dup_comm, "Creating file/decomp/var reqd for test failed :" // trim(tgv_fname))

call PIO_write_darray(pio_file, pio_var, iodesc, wbuf, ret)
Expand Down
7 changes: 2 additions & 5 deletions tests/general/pio_rearr_opts2.F90.in
Original file line number Diff line number Diff line change
Expand Up @@ -141,7 +141,6 @@ SUBROUTINE create_decomp_and_init_buf(iodesc, wbuf, dims, ret)
integer, dimension(1), intent(out) :: dims
integer, intent(out) :: ret

integer :: pio_dim
integer, dimension(:), allocatable :: compdof
integer, dimension(1) :: start, count
integer :: i
Expand All @@ -153,7 +152,7 @@ SUBROUTINE create_decomp_and_init_buf(iodesc, wbuf, dims, ret)
allocate(compdof(count(1)))
do i=1,count(1)
wbuf(i) = start(1) + i - 1
compdof(i) = wbuf(i)
compdof(i) = int(wbuf(i))
end do

call PIO_initdecomp(pio_tf_iosystem_, PIO_real, dims, compdof, iodesc)
Expand Down Expand Up @@ -208,8 +207,6 @@ SUBROUTINE open_file_and_get_var(pio_file, iotype, pio_var, ret)
type(var_desc_t), intent(out) :: pio_var
integer, intent(out) :: ret

integer :: pio_dim

ret = PIO_openfile(pio_tf_iosystem_, pio_file, iotype, tgv_fname, pio_write)
PIO_TF_CHECK_ERR(ret, "Could not create file " // trim(tgv_fname))

Expand Down Expand Up @@ -273,7 +270,7 @@ PIO_TF_AUTO_TEST_SUB_BEGIN set_rearr_opts_and_write
integer, dimension(:), allocatable :: iotypes
character(len=PIO_TF_MAX_STR_LEN), dimension(:), allocatable :: iotype_descs
integer :: num_iotypes
integer :: ret, ierr, i
integer :: ret, i

num_iotypes = 0
call PIO_TF_Get_nc_iotypes(iotypes, iotype_descs, num_iotypes)
Expand Down

0 comments on commit 001640d

Please sign in to comment.