Skip to content

Commit

Permalink
Fix out-of-bounds access in U10 & V10 calculation, and add some missi…
Browse files Browse the repository at this point in the history
…ng halo exchanges (#652)

* put in two missing halos needed in i direction

* Eliminate an out-of-bounds access in MDLFLD.f

* initialize USTORE & VSTORE in halo regions outside computational domain boundary

* update author changelog
  • Loading branch information
SamuelTrahanNOAA authored Mar 3, 2023
1 parent e180613 commit 7ef3564
Show file tree
Hide file tree
Showing 2 changed files with 19 additions and 3 deletions.
19 changes: 16 additions & 3 deletions sorc/ncep_post.fd/MDLFLD.f
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,7 @@
!! 22-11-08 W Meng - Output hourly averaged PM2.5 and O3 for AQM model only (aqf_on)
!! 22-11-16 E James - Adding dust from RRFS
!! 23-02-10 E James - Adding an extra IGET value to if statement for NGMSLP calculation
!! 23-03-03 S Trahan - Avoid out-of-bounds access in U2H & V2H by using USTORE & VSTORE with halo bounds
!!
!! USAGE: CALL MDLFLD
!! INPUT ARGUMENT LIST:
Expand Down Expand Up @@ -144,7 +145,8 @@ SUBROUTINE MDLFLD
DBZI1, DBZC1, EGRID6, EGRID7, NLICE1, &
QI, QINT, TT, PPP, QV, &
QCD, QICE1, QRAIN1, QSNO1, refl, &
QG1, refl1km, refl4km, RH, GUST, NRAIN1,Zm10c
QG1, refl1km, refl4km, RH, GUST, NRAIN1,Zm10c, &
USTORE, VSTORE
! T700, TH700
!
REAL, ALLOCATABLE :: EL(:,:,:),RICHNO(:,:,:) ,PBLRI(:,:), PBLREGIME(:,:)
Expand Down Expand Up @@ -188,6 +190,15 @@ SUBROUTINE MDLFLD
!
! ALLOCATE LOCAL ARRAYS
!
! Initialize halo regions of USTORE & VSTORE for cases when the halo extends
! beyond the computational domain boundary.
!$OMP PARALLEL DO COLLAPSE(2)
DO J=jsta_2l,jend_2u
DO I=ista_2l,iend_2u
USTORE(I,J) = 0
VSTORE(I,J) = 0
ENDDO
ENDDO
! Set up logical flag to indicate whether model outputs radar directly
Model_Radar = .false.
! IF (ABS(MAXVAL(REF_10CM)-SPVAL)>SMALL)Model_Radar=.True.
Expand Down Expand Up @@ -3861,6 +3872,7 @@ SUBROUTINE MDLFLD
ELSE
GRID1(I,J) = U10(I,J) ! IF NO MIX LAYER, SPECIFY 10 M WIND, PER DIMEGO,
END IF
USTORE(I,J) = GRID1(I,J)
END DO
END DO
! compute v component now
Expand Down Expand Up @@ -3906,12 +3918,13 @@ SUBROUTINE MDLFLD
ELSE
GRID2(I,J) = V10(I,J) ! IF NO MIX LAYER, SPECIFY 10 M WIND, PER DIMEGO,
END IF
VSTORE(I,J) = GRID2(I,J)
END DO
END DO


CALL U2H(GRID1(ISTA_2L:IEND_2U,JSTA_2L:JEND_2U),EGRID1)
CALL V2H(GRID2(ISTA_2L:IEND_2U,JSTA_2L:JEND_2U),EGRID2)
CALL U2H(USTORE,EGRID1)
CALL V2H(VSTORE,EGRID2)
!$omp parallel do private(i,j)
DO J=JSTA,JEND
DO I=ista,iend
Expand Down
3 changes: 3 additions & 0 deletions sorc/ncep_post.fd/UPP_MATH.f
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@
!> -----|------------|---------
!> 2020-05-20 | Jesse Meng | Initial
!> 2022-06-10 | Wen Meng | Modify dvdxdudy to retrict computation on undefined grids
!> 2023-03-03 | Sam Trahan | Add some missing exchanges (grids that only need i-direction exchanges)
!>
!> @author Jesse Meng @date 2020-05-20
module upp_math
Expand Down Expand Up @@ -169,6 +170,7 @@ subroutine H2U(ingrid,outgrid)
END DO
END IF
ELSE IF(GRIDTYPE == 'C')THEN
call exch(ingrid(ista_2l,jsta_2l))
DO J=JSTA,JEND
DO I=ISTA,IEND_M
outgrid(i,j)=(ingrid(i,j)+ingrid(i+1,j))/2.0
Expand Down Expand Up @@ -262,6 +264,7 @@ subroutine U2H(ingrid,outgrid)
end do
end do
ELSE IF(GRIDTYPE == 'C')THEN
call exch(ingrid(ista_2l,jsta_2l))
DO J=JSTA,JEND
DO I=ISTA_M,IEND
outgrid(i,j)=(ingrid(i-1,j)+ingrid(i,j))/2.0
Expand Down

0 comments on commit 7ef3564

Please sign in to comment.