Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
7 changes: 3 additions & 4 deletions sorc/ncep_post.fd/CLDRAD.f
Original file line number Diff line number Diff line change
Expand Up @@ -89,6 +89,7 @@
!> | logic, rather than a dedicated parameter number.
!> 2025-05-05 | Ben Blake | Add sanity checks for RRFSv1 implementation
!> 2025-05-08 | Jaymes Kenyon | For FV3 and MPAS applications, prevent cloud base from being diagnosed as below ground
!> 2025-11-13 | Jaymes Kenyon | Minor refactoring: the value of "cloud_def_p" (constant) is now set in params_mod
!>
!> @author Russ Treadon W/NP2 @date 1993-08-30
!---------------------------------------------------------------------------------
Expand Down Expand Up @@ -123,7 +124,7 @@ SUBROUTINE CLDRAD
PWAT,DUSTPM10,MAOD,NO3CB,NH4CB,aqm_aod550
use masks, only: LMH, HTM
use params_mod, only: TFRZ, D00, H99999, QCLDMIN, CFRmin_BASE_TOP, &
SMALL, D608, H1, ROG, &
CLOUD_DEF_P, SMALL, D608, H1, ROG, &
GI, RD, QCONV, ABSCOEFI, ABSCOEF, STBOL, PQ0, A2, &
A3, A4
use ctlblk_mod, only: JSTA, JEND, SPVAL, MODELNAME, SUBMODELNAME, &
Expand Down Expand Up @@ -156,7 +157,7 @@ SUBROUTINE CLDRAD
CLDP, CLDZ, CLDT, CLDZCu
REAL,dimension(lm) :: RHB, watericetotal, pabovesfc
REAL :: watericemax, wimin, zcldbase, zcldtop, zpbltop, &
rhoice, coeffp, exponfp, const1, cloud_def_p, &
rhoice, coeffp, exponfp, const1, &
pcldbase, rhoair, vovermd, concfp, betav, &
vertvis, tx, tv, pol, esx, es, e, zsf, zcld, frac
integer nfog, nfogn(7),npblcld,nlifr, k1, k2, ll, ii, ib, n, jj, &
Expand Down Expand Up @@ -1892,8 +1893,6 @@ SUBROUTINE CLDRAD
end do
npblcld = 0
Cloud_def_p = 0.0000001
DO J=JSTA,JEND
DO I=ISTA,IEND
!
Expand Down
62 changes: 59 additions & 3 deletions sorc/ncep_post.fd/INITPOST.F
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,9 @@
!> 2002-08-15 | H CHuang | Unit correction and generalize projection options
!> 2021-03-11 | Bo Cui | Change local arrays to dimension (im,jsta:jend)
!> 2023-01-24 | Sam Trahan | Comment-out wordy debug writes
!> 2025-11-13 | J Kenyon | Reintroduce a previous algorithm to create a
!> | "synthetic" cloud-fraction field, intended for
!> | RTMA applications
!>
!> @author Russ Treadon W/NP2 @date 1993-11-10
SUBROUTINE INITPOST
Expand Down Expand Up @@ -64,7 +67,7 @@ SUBROUTINE INITPOST
trdsw, theat, tclod, tprec, nprec, alsl, im, jm, lm, grib, &
prec_acc_dt1, submodelname
use params_mod, only: capa, g, rd, d608, tfrz, ad05, cft0, stbol, &
p1000, pi, rtd, lheat, dtr, erad
p1000, pi, rtd, lheat, dtr, erad, cloud_def_p
use lookup_mod, only: thl, plq, ptbl, ttbl, rdq, rdth, rdp, rdthe, pl, &
qs0, sqs, sthe, the0, ttblq, rdpq, rdtheq, stheq, the0q
use gridspec_mod, only: gridtype, dxval, latstart, latlast, lonstart, &
Expand Down Expand Up @@ -118,6 +121,7 @@ SUBROUTINE INITPOST
integer, external :: iw3jdn
real sun_zenith,sun_azimuth, ptop_low, ptop_mid, ptop_high
real delta_theta4gust
real watericetotal, radius, totcount, cloudcount
!
!
!***********************************************************************
Expand Down Expand Up @@ -1145,8 +1149,11 @@ SUBROUTINE INITPOST
end do
end do

! WRF EM outputs 3D cloud cover now
! Assign the cloud-fraction array (CFR)
IF(MODELNAME == 'RAPR')THEN
IF(SUBMODELNAME /= 'RTMA')THEN
! For non-RTMA RAPR applications (e.g., RAP, HRRR):
! Assign the CFR array using the model-state cloud fraction.
VarName='CLDFRA_BL'
call getVariable(fileName,DateStr,DataHandle,VarName,DUM3D, &
IM+1,1,JM+1,LM+1,IM,JS,JE,LM)
Expand All @@ -1157,7 +1164,56 @@ SUBROUTINE INITPOST
end do
end do
end do
ELSE
ELSE
! For RTMA: since cloud fraction is not an analysis
! variable, assign the CFR array by creating a "synthetic"
! cloud fraction. Namely, use the resolved cloud-water
! and cloud-ice fields surrounding each grid volume to
! calculate a neighborhood fraction of exceedance.
!
! --J Kenyon (13 Nov 2025): This fraction-of-exceedance
! algorithm was reintroduced to support 3DRTMA requirements.
! It essentially replicates previous code that was used for
! earlier RAP/HRRR versions.

radius = 16100. ! Use a horizontal neighborhood search of 16.1 km / 10 mi (arbitrary)
call ext_ncd_get_dom_ti_real(DataHandle,'DX',tmp, &
1,ioutcount,istatus)
dxval= nint(tmp)
numr = nint(radius/dxval)

do k = 1,lm
do j = jsta_2l, jend_2u
do i = 1, im
dummy(i,j)=QQW(i,j,k)
dummy2(i,j)=QQI(i,j,k)
enddo ! i
enddo ! j

call AllGETHERV(dummy)
call AllGETHERV(dummy2)

do j = jsta_2l, jend_2u
do i = 1, im
totcount =0.
cloudcount =0.
CFR(i,j,k) =0.
do ic = max(1,I-numr),min(im,I+numr)
do jc = max(1,J-numr),min(jm,J+numr)
totcount = totcount+1.
watericetotal = dummy(ic,jc) + dummy2(ic,jc)
if (watericetotal .gt. cloud_def_p) &
cloudcount=cloudcount+1.
! Note that the value of cloud_def_p is also arbitrary
enddo ! jc
enddo ! ic
CFR(i,j,k) = min(1.,cloudcount/totcount)
enddo ! i
enddo ! j
enddo ! k

ENDIF ! SUBMODELNAME
ELSE ! MODELNAME
VarName='CLDFRA'
call getVariable(fileName,DateStr,DataHandle,VarName,DUM3D, &
IM+1,1,JM+1,LM+1,IM,JS,JE,LM)
Expand Down
1 change: 1 addition & 0 deletions sorc/ncep_post.fd/params.F
Original file line number Diff line number Diff line change
Expand Up @@ -93,6 +93,7 @@ module params_mod
#else
real, parameter :: QCLDmin=1.E-5 !< Minimum cloud mixing ratio - was 1.E-6
#endif
real, parameter :: CLOUD_DEF_P=1.E-7 !< Cloud water + ice mixing ratio (qc + qi) threshold used by some GSL diagnostics

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

@jaymes-kenyon
Here CLOUD_DEF_P=1.E-7. I noticed that in GSI cloud analysis "gsdcloudanalysis.F90",
at line 208
data cloud_def_p / 0.000001_r_kind/
which is 1.0E-6. You did mentioned that "the value of cloud_def_p is also arbitrary" in INITPOST.F. I just want to confirm with you that this inconsistency is just a trivial thing, since it could be arbitrary.

Thank you!
-Gang

real, parameter :: CFRmin_BASE_TOP=0.02 !< Minimum cloud fraction for cloud base and top (used by GSL starting in 2023)
real, parameter :: NLImin=1.E3 !< Minimum number concentrations (m**-3) of large ice (snow/graupel/sleet)
! move definition of NLImax and T_ICE to MICROINIT 2012012018
Expand Down