Skip to content
This repository has been archived by the owner on Nov 8, 2024. It is now read-only.

Commit

Permalink
Further modification of icloud=3 scheme (#149)
Browse files Browse the repository at this point in the history
TYPE: enhancement

KEYWORDS: cloud fraction, sub-grid scale clouds, icloud=3

SOURCE: Greg Thompson, RAL

DESCRIPTION OF CHANGES:
Some tuning for grid spacing dependence of critical RH (used in Sundqvist equation) based on 2015 year-long simulations validated against USCRN surface incoming solar radiation. Tests were run at 10km spacing, also 10 &3.3km spacing by Pedro Jimenez and evaluated against observations by Mei Xu. Total liquid and ice water paths from fractional clouds plus explicit clouds (microphysics created) permitted to be slightly larger (1.5kg/m^2). Draft journal manuscript describing sub-grid scale (SGS) cloud parameterization is in progress.

LIST OF MODIFIED FILES:
modified: phys/module_radiation_driver.F

TESTS CONDUCTED: Regtested with WTF-3.06. RAL conducted 52 individual 36-h simulations for 2015, and obtained near-zero downward solar radiation bias over CONUS.
  • Loading branch information
weiwangncar committed Mar 1, 2017
1 parent 074c9d3 commit 10af784
Showing 1 changed file with 12 additions and 20 deletions.
32 changes: 12 additions & 20 deletions phys/module_radiation_driver.F
Original file line number Diff line number Diff line change
Expand Up @@ -3164,7 +3164,7 @@ SUBROUTINE cal_cldfra3(CLDFRA, qv, qc, qi, qs, &
REAL, DIMENSION(ims:ime,kms:kme,jms:jme):: qvsat
INTEGER:: i,j,k
REAL:: TK, TC, qvsi, qvsw, RHUM, xx, yy
REAL, DIMENSION(kms:kme):: qvs1d, cfr1d, T1d, &
REAL, DIMENSION(kts:kte):: qvs1d, cfr1d, T1d, &
& P1d, R1d, qc1d, qi1d, qs1d

character*512 dbg_msg
Expand All @@ -3178,8 +3178,8 @@ SUBROUTINE cal_cldfra3(CLDFRA, qv, qc, qi, qs, &
!.. to get near 100% RH as grid spacing moves toward 1.0km, but higher
!.. RH over ocean required as compared to over land.

RH_00L = 0.781 + SQRT(1./(35.0+gridkm*gridkm*gridkm*0.5))
RH_00O = 0.831 + SQRT(1./(70.0+gridkm*gridkm*gridkm*0.5))
RH_00L = 0.7 + SQRT(1./(25.0+gridkm*gridkm*gridkm))
RH_00O = 0.81 + SQRT(1./(50.0+gridkm*gridkm*gridkm))

DO j = jts,jte
DO k = kts,kte
Expand Down Expand Up @@ -3215,10 +3215,9 @@ SUBROUTINE cal_cldfra3(CLDFRA, qv, qc, qi, qs, &
if (tc .ge. -12.0) then
RHUM = MIN(0.999, RHUM)
CLDFRA(I,K,J) = MAX(0.0, 1.0-SQRT((1.0-RHUM)/(1.-RH_00)))
elseif (tc.lt.-12..and.tc.gt.-70. .and. RHUM.gt.RH_00O) then
RHUM = MAX(0.01, MIN(qv(i,k,j)/qvsat(i,k,j), qvsw/qvsi - 1.E-6))
RHI_max = MAX(RHUM+1.E-6, qvsw/qvsi)
CLDFRA(I,K,J) = MAX(0., 1.0-SQRT((RHI_max-RHUM)/(RHI_max-RH_00O)))
elseif (tc.lt.-12..and.tc.gt.-70. .and. RHUM.gt.RH_00L) then
RHUM = MAX(0.01, MIN(qv(i,k,j)/qvsat(i,k,j), 1.0 - 1.E-6))
CLDFRA(I,K,J) = MAX(0., 1.0-SQRT((1.0-RHUM)/(1.0-RH_00L)))
endif
CLDFRA(I,K,J) = MIN(0.90, CLDFRA(I,K,J))

Expand Down Expand Up @@ -3302,8 +3301,8 @@ SUBROUTINE find_cloudLayers(qvs1d, cfr1d, T1d, P1d, R1d, entrmnt, &
k_m40C = 0
DO k = kte, kts, -1
theta(k) = T1d(k)*((100000.0/P1d(k))**(287.05/1004.))
if (T1d(k)-273.16 .gt. -40.0) k_m40C = MAX(k_m40C, k)
if (T1d(k)-273.16 .gt. -12.0) k_m12C = MAX(k_m12C, k)
if (T1d(k)-273.16 .gt. -40.0 .and. P1d(k).gt.7000.0) k_m40C = MAX(k_m40C, k)
if (T1d(k)-273.16 .gt. -12.0 .and. P1d(k).gt.10000.0) k_m12C = MAX(k_m12C, k)
ENDDO
if (k_m40C .le. kts) k_m40C = kts
if (k_m12C .le. kts) k_m12C = kts
Expand Down Expand Up @@ -3491,7 +3490,6 @@ SUBROUTINE adjust_cloudIce(cfr,qi,qs,qvs, T,Rho,dz, entr, k1,k2,kts,kte)
do k = k1, k2
iwp_exists = iwp_exists + (qi(k)+qs(k))*Rho(k)*dz(k)
enddo
if (iwp_exists .gt. 1.0) RETURN

this_dz = 0.0
do k = k1, k2
Expand Down Expand Up @@ -3535,7 +3533,6 @@ SUBROUTINE adjust_cloudH2O(cfr, qc, qvs, T,Rho,dz, entr, k1,k2,kts,kte)
do k = k1, k2
lwp_exists = lwp_exists + qc(k)*Rho(k)*dz(k)
enddo
if (lwp_exists .gt. 1.0) RETURN

this_dz = 0.0
do k = k1, k2
Expand Down Expand Up @@ -3571,20 +3568,15 @@ SUBROUTINE adjust_cloudFinal(cfr, qc, qi, Rho,dz, kts,kte,k_tropo)
INTEGER:: k

lwp = 0.
do k = kts, k_tropo
if (cfr(k).gt.0.01 .and. cfr(k).lt.0.99) then
lwp = lwp + qc(k)*Rho(k)*dz(k)
endif
enddo

iwp = 0.
do k = kts, k_tropo
if (cfr(k).gt.0.01 .and. cfr(k).lt.0.99) then
if (cfr(k).gt.0.0) then
lwp = lwp + qc(k)*Rho(k)*dz(k)
iwp = iwp + qi(k)*Rho(k)*dz(k)
endif
enddo

if (lwp .gt. 1.0) then
if (lwp .gt. 1.5) then
xfac = 1./lwp
do k = kts, k_tropo
if (cfr(k).gt.0.01 .and. cfr(k).lt.0.99) then
Expand All @@ -3593,7 +3585,7 @@ SUBROUTINE adjust_cloudFinal(cfr, qc, qi, Rho,dz, kts,kte,k_tropo)
enddo
endif

if (iwp .gt. 1.0) then
if (iwp .gt. 1.5) then
xfac = 1./iwp
do k = kts, k_tropo
if (cfr(k).gt.0.01 .and. cfr(k).lt.0.99) then
Expand Down

0 comments on commit 10af784

Please sign in to comment.