diff --git a/parm/fv3lam_rrfs.xml b/parm/fv3lam_rrfs.xml index 108e69d27..9bef8bb8f 100755 --- a/parm/fv3lam_rrfs.xml +++ b/parm/fv3lam_rrfs.xml @@ -1158,7 +1158,7 @@ TMP_ON_SPEC_HGT_LVL_ABOVE_GRND_FDHGT TMP - 30. 50. 80. 100. + 30. 50. 80. 100. 160. 320. 3.0 @@ -1172,7 +1172,7 @@ UGRD_ON_SPEC_HGT_LVL_ABOVE_GRND_FDHGT UGRD - 30. 50. 80. 100. + 30. 50. 80. 100. 160. 320. 4.0 @@ -1186,7 +1186,7 @@ VGRD_ON_SPEC_HGT_LVL_ABOVE_GRND_FDHGT VGRD - 30. 50. 80. 100. + 30. 50. 80. 100. 160. 320. 4.0 @@ -1200,14 +1200,14 @@ SPFH_ON_SPEC_HGT_LVL_ABOVE_GRND_FDHGT SPFH - 30. 50. 80. 100. + 30. 50. 80. 100. 160. 320. 5.0 PRES_ON_SPEC_HGT_LVL_ABOVE_GRND_FDHGT PRES - 30. 50. 80. 100. + 30. 50. 80. 100. 160. 320. 3.0 diff --git a/parm/postxconfig-NT-fv3lam_rrfs.txt b/parm/postxconfig-NT-fv3lam_rrfs.txt index 38f05cbb9..f37f18b06 100644 --- a/parm/postxconfig-NT-fv3lam_rrfs.txt +++ b/parm/postxconfig-NT-fv3lam_rrfs.txt @@ -6171,8 +6171,8 @@ TMP spec_hgt_lvl_above_grnd 0 ? -4 -30. 50. 80. 100. +6 +30. 50. 80. 100. 160. 320. ? 0 ? @@ -6245,8 +6245,8 @@ UGRD spec_hgt_lvl_above_grnd 0 ? -4 -30. 50. 80. 100. +6 +30. 50. 80. 100. 160. 320. ? 0 ? @@ -6319,8 +6319,8 @@ VGRD spec_hgt_lvl_above_grnd 0 ? -4 -30. 50. 80. 100. +6 +30. 50. 80. 100. 160. 320. ? 0 ? @@ -6393,8 +6393,8 @@ SPFH spec_hgt_lvl_above_grnd 0 ? -4 -30. 50. 80. 100. +6 +30. 50. 80. 100. 160. 320. ? 0 ? @@ -6430,8 +6430,8 @@ PRES spec_hgt_lvl_above_grnd 0 ? -4 -30. 50. 80. 100. +6 +30. 50. 80. 100. 160. 320. ? 0 ? diff --git a/sorc/ncep_post.fd/ALLOCATE_ALL.f b/sorc/ncep_post.fd/ALLOCATE_ALL.f index 01d6df2c6..dc322998b 100644 --- a/sorc/ncep_post.fd/ALLOCATE_ALL.f +++ b/sorc/ncep_post.fd/ALLOCATE_ALL.f @@ -615,7 +615,6 @@ SUBROUTINE ALLOCATE_ALL() allocate(mean_frp(ista_2l:iend_2u,jsta_2l:jend_2u)) allocate(ebb(ista_2l:iend_2u,jsta_2l:jend_2u)) allocate(hwp(ista_2l:iend_2u,jsta_2l:jend_2u)) - allocate(aodtot(ista_2l:iend_2u,jsta_2l:jend_2u)) !Initialization !$omp parallel do private(i,j) do j=jsta_2l,jend_2u @@ -643,7 +642,6 @@ SUBROUTINE ALLOCATE_ALL() mean_frp(i,j)=spval ebb(i,j)=spval hwp(i,j)=spval - aodtot(i,j)=spval enddo enddo allocate(smoke(ista_2l:iend_2u,jsta_2l:jend_2u,lm,nbin_sm)) diff --git a/sorc/ncep_post.fd/CLDRAD.f b/sorc/ncep_post.fd/CLDRAD.f index 7d2f8cfbc..a45e7eda1 100644 --- a/sorc/ncep_post.fd/CLDRAD.f +++ b/sorc/ncep_post.fd/CLDRAD.f @@ -73,6 +73,7 @@ !> 2023-02-10 | Eric James | Removing neighbourhood check from GSL exp2 ceiling diagnostic !> 2023-02-23 | Eric James | Adding coarse PM from RRFS, and using AOD from FV3 for RRFS !> 2023-04-04 | Li(Kate Zhang) | Add namelist optoin for CCPP-Chem (UFS-Chem) model. +!> 2023-04-17 | Eric James | Getting rid of special treatment for RRFS AOD (use RAP/HRRR approach) !> !> @author Russ Treadon W/NP2 @date 1993-08-30 SUBROUTINE CLDRAD @@ -97,7 +98,7 @@ SUBROUTINE CLDRAD ALWINC, ALWTOAC, SWDDNI, SWDDIF, SWDNBC, SWDDNIC, & SWDDIFC, SWUPBC, LWDNBC, LWUPBC, SWUPT, & TAOD5502D, AERSSA2D, AERASY2D, MEAN_FRP, EBB, HWP, & - AODTOT, LWP, IWP, AVGCPRATE, & + LWP, IWP, AVGCPRATE, & DUSTCB,SSCB,BCCB,OCCB,SULFCB,DUSTPM,SSPM,aod550, & du_aod550,ss_aod550,su_aod550,oc_aod550,bc_aod550, & PWAT,DUSTPM10,MAOD,NO3CB,NH4CB,aqm_aod550 @@ -446,16 +447,9 @@ SUBROUTINE CLDRAD ! TOTAL COLUMN AOD (TAOD553D FROM HRRR-SMOKE) ! IF (IGET(735) > 0) THEN - IF (MODELNAME == 'RAPR') THEN + IF (MODELNAME == 'RAPR' .OR. MODELNAME == 'FV3R') THEN CALL CALPW(GRID1(ista:iend,jsta:jend),19) CALL BOUND(GRID1,D00,H99999) - ELSE IF (MODELNAME == 'FV3R') THEN - GRID1=SPVAL - DO J=JSTA,JEND - DO I=ISTA,IEND - if (AODTOT(I,J) < SPVAL) GRID1(I,J) = AODTOT(I,J) - ENDDO - ENDDO ENDIF if(grib == "grib2" )then cfld = cfld + 1 diff --git a/sorc/ncep_post.fd/CTLBLK.f b/sorc/ncep_post.fd/CTLBLK.f index f8078ce71..a2530a43e 100644 --- a/sorc/ncep_post.fd/CTLBLK.f +++ b/sorc/ncep_post.fd/CTLBLK.f @@ -16,6 +16,7 @@ module CTLBLK_mod ! 2023-03-21 Jesse Meng - Add slrutah_on option to use U Utah SLR ! 2023-04-04 Li(Kate Zhang) Add namelist optoin for CCPP-Chem (UFS-Chem) ! and 2D diag. output (d2d_chem) for GEFS-Aerosols and CCPP-Chem model. +! 2023-04-17 Eric James - Adding 160 and 320 m above ground to HTFD for RRFS output. !----------------------------------------------------------------------- ! implicit none @@ -29,7 +30,7 @@ module CTLBLK_mod end type integer, parameter :: komax=70 integer, parameter :: LSMDEF=46 ! default number of p levels - integer,PARAMETER :: NFD=18,NBND=6 + integer,PARAMETER :: NFD=20,NBND=6 REAL, PARAMETER :: QMIN = 1.E-15 ! integer :: novegtype ! max number of veg type @@ -115,7 +116,7 @@ module CTLBLK_mod integer, parameter :: nbin_sm = 1 ! smoke ! ! SET FD LEVEL HEIGHTS IN GEOPOTENTAL METERS. - DATA HTFD / 20.E0,30.E0,40.E0,50.E0,80.E0,100.E0,305.E0,457.E0,610.E0, & + DATA HTFD / 20.E0,30.E0,40.E0,50.E0,80.E0,100.E0,160.E0,305.E0,320.E0,457.E0,610.E0, & 914.E0,1524.E0,1829.E0,2134.E0,2743.E0,3658.E0,4572.E0, & 6000.E0,7010.E0/ ! diff --git a/sorc/ncep_post.fd/DEALLOCATE.f b/sorc/ncep_post.fd/DEALLOCATE.f index 5710e2b0d..96816bacf 100644 --- a/sorc/ncep_post.fd/DEALLOCATE.f +++ b/sorc/ncep_post.fd/DEALLOCATE.f @@ -209,7 +209,6 @@ SUBROUTINE DE_ALLOCATE deallocate(mean_frp) deallocate(ebb) deallocate(hwp) - deallocate(aodtot) deallocate(smoke) deallocate(fv3dust) deallocate(coarsepm) diff --git a/sorc/ncep_post.fd/INITPOST_NETCDF.f b/sorc/ncep_post.fd/INITPOST_NETCDF.f index 15437de62..42e870f07 100644 --- a/sorc/ncep_post.fd/INITPOST_NETCDF.f +++ b/sorc/ncep_post.fd/INITPOST_NETCDF.f @@ -31,8 +31,9 @@ !> 2023-02-23 | Eric James | Read coarse PM and aodtot from RRFS !> 2023-03-02 | Sam Trahan | Read lightning threat index fields !> 2023-03-22 | WM Lewis | Read RRFS effective radii (EFFRL, EFFRI, EFFRS) -!> !> 2023-04-04 |Li(Kate Zhang) |Add namelist optoin for CCPP-Chem(UFS-Chem) +!> 2023-04-04 |Li(Kate Zhang) |Add namelist optoin for CCPP-Chem(UFS-Chem) ! and 2D diag. output (d2d_chem) for GEFS-Aerosols and CCPP-Chem model. +!> 2023-04-17 | Eric James | Read in unified ext550 extinction (and remove aodtot) for RRFS !> !> @author Hui-Ya Chuang @date 2016-03-04 SUBROUTINE INITPOST_NETCDF(ncid2d,ncid3d) @@ -73,7 +74,7 @@ SUBROUTINE INITPOST_NETCDF(ncid2d,ncid3d) alwoutc,alwtoac,aswoutc,aswtoac,alwinc,aswinc,avgpotevp,snoavg, & ti,aod550,du_aod550,ss_aod550,su_aod550,oc_aod550,bc_aod550,prate_max,maod,dustpm10, & dustcb,bccb,occb,sulfcb,sscb,dustallcb,ssallcb,dustpm,sspm,pp25cb,pp10cb,no3cb,nh4cb,& - pwat, ebb, hwp, aodtot, aqm_aod550, ltg1_max,ltg2_max,ltg3_max + pwat, ebb, hwp, aqm_aod550, ltg1_max,ltg2_max,ltg3_max use soil, only: sldpth, sllevel, sh2o, smc, stc use masks, only: lmv, lmh, htm, vtm, gdlat, gdlon, dx, dy, hbm2, sm, sice use physcons_post, only: grav => con_g, fv => con_fvirt, rgas => con_rd, & @@ -200,11 +201,10 @@ SUBROUTINE INITPOST_NETCDF(ncid2d,ncid3d) real, allocatable :: div3d(:,:,:) real(kind=4),allocatable :: vcrd(:,:) real :: dum_const - real, allocatable :: extsmoke(:,:,:), extdust(:,:,:) + real, allocatable :: ext550(:,:,:) if (modelname == 'FV3R') then - allocate(extsmoke(ista_2l:iend_2u,jsta_2l:jend_2u,lm)) - allocate(extdust(ista_2l:iend_2u,jsta_2l:jend_2u,lm)) + allocate(ext550(ista_2l:iend_2u,jsta_2l:jend_2u,lm)) endif !*********************************************************************** @@ -506,13 +506,13 @@ SUBROUTINE INITPOST_NETCDF(ncid2d,ncid3d) end if if(me==0)print*,'nhcas= ',nhcas if (nhcas == 0 ) then !non-hydrostatic case - nrec=19 + nrec=18 allocate (recname(nrec)) recname=[character(len=20) :: 'ugrd','vgrd','spfh','tmp','o3mr', & 'presnh','dzdt', 'clwmr','dpres', & 'delz','icmr','rwmr', & 'snmr','grle','smoke','dust', & - 'coarsepm','smoke_ext','dust_ext'] + 'coarsepm','ext550'] else nrec=8 allocate (recname(nrec)) @@ -874,9 +874,7 @@ SUBROUTINE INITPOST_NETCDF(ncid2d,ncid3d) call read_netcdf_3d_para(ncid3d,im,jm,ista,ista_2l,iend,iend_2u,jsta,jsta_2l,jend,jend_2u, & spval,recname(17),coarsepm(ista_2l,jsta_2l,1,1),lm) call read_netcdf_3d_para(ncid2d,im,jm,ista,ista_2l,iend,iend_2u,jsta,jsta_2l,jend,jend_2u, & - spval,recname(18),extsmoke(ista_2l,jsta_2l,1),lm) - call read_netcdf_3d_para(ncid2d,im,jm,ista,ista_2l,iend,iend_2u,jsta,jsta_2l,jend,jend_2u, & - spval,recname(19),extdust(ista_2l,jsta_2l,1),lm) + spval,recname(18),ext550(ista_2l,jsta_2l,1),lm) endif ! calculate CWM from FV3 output @@ -1024,11 +1022,6 @@ SUBROUTINE INITPOST_NETCDF(ncid2d,ncid3d) call read_netcdf_2d_para(ncid2d,ista,ista_2l,iend,iend_2u,jsta,jsta_2l,jend,jend_2u, & spval,VarName,hwp(ista_2l,jsta_2l)) if(debugprint)print*,'sample ',VarName,' =',hwp(isa,jsa) -! total aod - VarName='aodtot' - call read_netcdf_2d_para(ncid2d,ista,ista_2l,iend,iend_2u,jsta,jsta_2l,jend,jend_2u, & - spval,VarName,aodtot(ista_2l,jsta_2l)) - if(debugprint)print*,'sample ',VarName,' =',aodtot(isa,jsa) endif ! lightning threat index 1 @@ -2472,8 +2465,8 @@ SUBROUTINE INITPOST_NETCDF(ncid2d,ncid3d) do l = 1, lm do j = jsta_2l, jend_2u do i = ista_2l, iend_2u - if(extsmoke(i,j,l)