Skip to content

Commit

Permalink
Merge branch 'NOAA-EMC:develop' into develop
Browse files Browse the repository at this point in the history
  • Loading branch information
FernandoAndrade-NOAA authored Oct 11, 2023
2 parents e31f6e5 + fae617b commit 0c65bb2
Show file tree
Hide file tree
Showing 2 changed files with 22 additions and 10 deletions.
6 changes: 4 additions & 2 deletions sorc/ncep_post.fd/MDLFLD.f
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,7 @@
!! 23-06-26 | W Meng | Output composite radar reflectivity when GFS uses Thompson MP
!! 23-08-16 | Y Mao | For gtg_algo, add tke as an input and cit as an output
!! 23-08-16 | Y Mao | For GTG, replace iget(ID) with namelist option 'gtg_on'.
!! 23-10-04 | W Meng | Read 3D radar reflectivity from model when GFS use Thmopson MP
!! USAGE: CALL MDLFLD
!! INPUT ARGUMENT LIST:
!!
Expand Down Expand Up @@ -583,8 +584,9 @@ SUBROUTINE MDLFLD
ENDDO
END DO

ELSE IF(((MODELNAME == 'NMM' .and. GRIDTYPE=='B') .OR. MODELNAME == 'FV3R') &
.and. imp_physics==8)THEN !NMMB or FV3R +THOMPSON
ELSE IF(((MODELNAME == 'NMM' .and. GRIDTYPE=='B') .OR. MODELNAME == 'FV3R' &
.OR. MODELNAME == 'GFS') &
.and. imp_physics==8)THEN !NMMB or FV3R or GFS +THOMPSON
DO L=1,LM
DO J=JSTA,JEND
DO I=ista,iend
Expand Down
26 changes: 18 additions & 8 deletions sorc/ncep_post.fd/SURFCE.f
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,8 @@
!> 2023-04-21 | E James | Enabling GSL precip type for RRFS
!> 2023-05-19 | E James | Cleaning up GRIB2 encoding for 1-h max precip rate
!> 2023-06-15 | E James | Correcting bug fix in GSL precip type for RRFS (use 1h pcp, not run total pcp)
!> 2023-10-04 | W Meng | Fix mismatched IDs from 526-530
!> 2023-10-05 | E James | Correcting bug fix in GSL precip type for RRFS (was using 1000x 1h pcp)
!>
!> @note
!> USAGE: CALL SURFCE
Expand Down Expand Up @@ -4372,7 +4374,7 @@ SUBROUTINE SURFCE
IFINCR = NINT(PREC_ACC_DT1)
if(grib=='grib2') then
cfld=cfld+1
fld_info(cfld)%ifld=IAVBLFLD(IGET(518))
fld_info(cfld)%ifld=IAVBLFLD(IGET(526))
if(fld_info(cfld)%ntrange==0) then
if (ifhr==0 .and. ifmin==0) then
fld_info(cfld)%tinvstat=0
Expand Down Expand Up @@ -4406,7 +4408,7 @@ SUBROUTINE SURFCE
IFINCR = NINT(PREC_ACC_DT1)
if(grib=='grib2') then
cfld=cfld+1
fld_info(cfld)%ifld=IAVBLFLD(IGET(519))
fld_info(cfld)%ifld=IAVBLFLD(IGET(527))
if(fld_info(cfld)%ntrange==0) then
if (ifhr==0 .and. ifmin==0) then
fld_info(cfld)%tinvstat=0
Expand Down Expand Up @@ -4440,7 +4442,7 @@ SUBROUTINE SURFCE
IFINCR = NINT(PREC_ACC_DT1)
if(grib=='grib2') then
cfld=cfld+1
fld_info(cfld)%ifld=IAVBLFLD(IGET(520))
fld_info(cfld)%ifld=IAVBLFLD(IGET(528))
if(fld_info(cfld)%ntrange==0) then
if (ifhr==0 .and. ifmin==0) then
fld_info(cfld)%tinvstat=0
Expand Down Expand Up @@ -4475,7 +4477,7 @@ SUBROUTINE SURFCE
! if(me==0)print*,'maxval BUCKET1 SNOWFALL: ', maxval(GRID1)
if(grib=='grib2') then
cfld=cfld+1
fld_info(cfld)%ifld=IAVBLFLD(IGET(521))
fld_info(cfld)%ifld=IAVBLFLD(IGET(529))
if(fld_info(cfld)%ntrange==0) then
if (ifhr==0 .and. ifmin==0) then
fld_info(cfld)%tinvstat=0
Expand Down Expand Up @@ -4510,7 +4512,7 @@ SUBROUTINE SURFCE
! print*,'maxval BUCKET1 GRAUPEL: ', maxval(GRID1)
if(grib=='grib2') then
cfld=cfld+1
fld_info(cfld)%ifld=IAVBLFLD(IGET(522))
fld_info(cfld)%ifld=IAVBLFLD(IGET(530))
if(fld_info(cfld)%ntrange==0) then
if (ifhr==0 .and. ifmin==0) then
fld_info(cfld)%tinvstat=0
Expand Down Expand Up @@ -5140,7 +5142,15 @@ SUBROUTINE SURFCE
!-- TOTPRCP is total 1-hour accumulated precipitation in [m]
!-- RAP/HRRR and RRFS use 1-h bucket. GFS uses 3-h bucket
!-- so this section will need to be revised for GFS
totprcp = (AVGPREC(I,J)*3600.*1000./DTQ2)
IF (MODELNAME .eq. 'FV3R') THEN
if(AVGPREC(I,J)/=spval)then
totprcp = (AVGPREC(I,J)*3600./DTQ2)
else
totprcp = 0.0
endif
ELSE
totprcp = (RAINC_BUCKET(I,J) + RAINNC_BUCKET(I,J))*1.e-3
ENDIF
snowratio = 0.0
if(graup_bucket(i,j)*1.e-3 > totprcp.and.graup_bucket(i,j)/=spval)then
print *,'WARNING - Graupel is higher that total precip at point',i,j
Expand Down Expand Up @@ -5169,7 +5179,7 @@ SUBROUTINE SURFCE
!-- SNOW is time step non-convective snow [m]
! -- based on either instantaneous snowfall or 1h snowfall and
! snowratio
if( (SNOWNC(i,j)/DT > 0.2e-9 .and. snowratio>=0.25) &
if( (SNOWNC(i,j)/DT > 0.2e-9 .and. snowratio>=0.25 .and. SNOWNC(i,j)/=spval) &
.or. &
(totprcp>0.00001.and.snowratio>=0.25)) then
DOMS(i,j) = 1.
Expand Down Expand Up @@ -5205,7 +5215,7 @@ SUBROUTINE SURFCE
!-- graupel/ice pellets vs. snow or rain
! ---------------------------------------------------------------
!-- GRAUPEL is time step non-convective graupel in [m]
if(GRAUPELNC(i,j)/DT > 1.e-9) then
if(GRAUPELNC(i,j)/DT > 1.e-9 .and. GRAUPELNC(i,j)/=spval) then
if (t2<=276.15) then
! This T2m test excludes convectively based hail
! from cold-season ice pellets.
Expand Down

0 comments on commit 0c65bb2

Please sign in to comment.