@@ -1456,8 +1456,8 @@ SUBROUTINE GF2020_DRV(mxp,myp,mzp,mtp,nmp &
14561456 cum_ztexec(:)= ztexec(:) ; cum_zqexec(:)= zqexec(:)
14571457 elseif (use_excess == 2 ) then
14581458 do i= its,itf
1459- cum_zqexec(i)= min ( 5.e-4 , max (1.e-4 ,zqexec(i) ))! kg kg^-1
1460- cum_ztexec(i)= min ( 0.5 , max (0.2 ,ztexec(i) ))! Kelvin
1459+ cum_zqexec(i)= max (1.e-4 ,zqexec(i))! kg kg^-1
1460+ cum_ztexec(i)= max (0.2 ,ztexec(i))! Kelvin
14611461 enddo
14621462 else
14631463 do i= its,itf
@@ -4200,24 +4200,31 @@ SUBROUTINE CUP_gf(its,ite,kts,kte ,itf,ktf, mtp, nmp &
42004200 dellabuoy,outbuoy, &
42014201 dellampqi,outmpqi,dellampql,outmpql,dellampcf,outmpcf,nmp )
42024202
4203- !
4204- !
4205- !- -- get the net precipitation flux (after downdraft evaporation)
4206- call get_precip_fluxes(cumulus,klcl,kbcon,ktop,k22,ierr,xland,pre,xmb &
4207- ,pwo,pwavo,edto,pwevo,pwdo,t_cup,tempco &
4208- ,prec_flx,evap_flx &
4209- ,itf,ktf,its,ite, kts,kte)
4203+ if (USE_REBCB == 1 ) then
4204+ !- -- rainfall evap below cloud base
4205+ call rain_evap_below_cloudbase(cumulus,itf,ktf, its,ite, kts,kte,ierr,kbcon,ktop&
4206+ ,xmb,psur,xland,qo_cup,t_cup &
4207+ ,po_cup,qes_cup,pwavo,edto,pwevo,pwo,pwdo &
4208+ ,pre,prec_flx,evap_flx,outt,outq,outbuoy,evap_bcb)
4209+ else
4210+ !- -- get the net precipitation flux (after downdraft evaporation)
4211+ call get_precip_fluxes(cumulus,klcl,kbcon,ktop,k22,ierr,xland,pre,xmb &
4212+ ,pwo,pwavo,edto,pwevo,pwdo,t_cup,tempco &
4213+ ,prec_flx,evap_flx &
4214+ ,itf,ktf,its,ite, kts,kte)
4215+ endif
42104216
42114217!
4212- !- -- rainfall evap below cloud base
4218+ !- - get the total (deep+congestus) evaporation flux for output (units kg/kg/s)
42134219!
4214- if (USE_REBCB == 1 ) &
4215- call rain_evap_below_cloudbase(cumulus,itf,ktf, its,ite, kts,kte,ierr,kbcon,ktop&
4216- ,xmb,psur,xland,qo_cup,t_cup &
4217- ,po_cup,qes_cup,pwavo,edto,pwevo,pwo,pwdo &
4218- ,pre,prec_flx,evap_flx,outt,outq,outbuoy,evap_bcb)
4219-
4220-
4220+ do i= its,itf
4221+ if (ierr(i) /= 0 ) cycle
4222+ do k= kts,ktop(i)
4223+ dp= 100 .* (po_cup(i,k)- po_cup(i,k+1 ))
4224+ !- -- add all plumes, and convert to kg/kg/s
4225+ revsu_gf(i,k) = revsu_gf(i,k) + evap_flx(i,k)* g/ dp
4226+ enddo
4227+ enddo
42214228!
42224229!- -- includes effects of the remained cloud dissipation into the enviroment
42234230!
@@ -4228,17 +4235,6 @@ SUBROUTINE CUP_gf(its,ite,kts,kte ,itf,ktf, mtp, nmp &
42284235 ,heso_cup,zo)
42294236
42304237!
4231- !- -- get the total (deep+congestus) evaporation flux for output (units kg/kg/s)
4232- !
4233- do i= its,itf
4234- if (ierr(i) /= 0 ) cycle
4235- do k= kts,ktop(i)
4236- dp= 100 .* (po_cup(i,k)- po_cup(i,k+1 ))
4237- !- -- add congestus and deep plumes, and convert to kg/kg/s
4238- revsu_gf(i,k) = revsu_gf(i,k) + evap_flx(i,k)* g/ dp
4239- enddo
4240- enddo
4241- !
42424238!
42434239!- -- get lightning flashes density (parameterization from Lopez 2016, MWR)
42444240!
@@ -6550,11 +6546,10 @@ SUBROUTINE get_zu_zd_pdf(cumulus, draft,ierr,kb,kt,zu,kts,kte,ktf,kpbli,k22,kbco
65506546 zuh= 0.0
65516547 zul= 0.0
65526548 IF (ZERO_DIFF_LAND== 1 ) then
6553- if (draft == " deep_up" .and. xland > 0.90 ) itest= 11 ! ocean
6549+ if (draft == " deep_up" .and. xland > 0.90 ) itest= 20 ! ocean
65546550 if (draft == " deep_up" .and. xland <= 0.90 ) itest= 12 ! land
6555- if (draft == " mid_up" ) itest= 5
6551+ if (draft == " mid_up" ) itest= 20
65566552 ELSE
6557- ! if(draft == "deep_up" ) itest=21 !ocean/land
65586553 if (draft == " deep_up" ) itest= 20 ! ocean/land
65596554 if (draft == " mid_up" ) itest= 20
65606555 ENDIF
@@ -6666,26 +6661,18 @@ SUBROUTINE get_zu_zd_pdf(cumulus, draft,ierr,kb,kt,zu,kts,kte,ktf,kpbli,k22,kbco
66666661 ENDIF
66676662 zu(kts)= 0 .
66686663 !- --------------------------------------------------------
6669- ! ELSEIF(itest==20 .and. draft == "deep_up") then !--- land/ocean
66706664 ELSEIF (itest== 20 ) then !- -- land/ocean
66716665
66726666 hei_updf= (1 .- xland)* hei_updf_LAND+ xland* hei_updf_OCEAN
66736667 !- add a randomic perturbation
66746668 hei_updf = hei_updf + random
66756669
6676- !- for gate soundings
6677- ! hei_updf = max(0.1, min(1.,float(JL)/100.))
6678- ! beta =1.0+float(JL)/100. * 5.
6679-
66806670 !- -hei_updf parameter goes from 0 to 1 = rainfall decreases with hei_updf
66816671 pmaxzu = (psur-100 .) * (1 .- 0.5 * hei_updf) + 0.6 * ( po_cup(kt) ) * 0.5 * hei_updf
66826672
66836673 !- beta parameter: must be larger than 1, higher makes the profile sharper around the maximum zu
66846674 beta = max (1.1 , 2.1 - 0.5 * hei_updf)
66856675
6686- !- -- tmp IF(trim(cumulus) == 'deep') beta =beta_sh
6687- ! print*,"hei=",jl,pmaxzu,hei_updf,beta!(pmaxzu-(psur-100.))/( -(psur-100.) + 0.5*( 0.25*(psur-100.) + 0.75*po_cup(kt) ))
6688-
66896676 kb_adj= minloc (abs (po_cup(kts:kt)- pmaxzu),1 )
66906677 kb_adj= max (kb,kb_adj) ; kb_adj= min (kb_adj,kt)
66916678
@@ -6731,10 +6718,6 @@ SUBROUTINE get_zu_zd_pdf(cumulus, draft,ierr,kb,kt,zu,kts,kte,ktf,kpbli,k22,kbco
67316718
67326719 hei_updf= (1 .- xland)* hei_updf_LAND+ xland* hei_updf_OCEAN
67336720
6734- !- for gate soundings
6735- ! if(gate) hei_updf = max(0.1, min(1.,float(JL)/160.))
6736- ! print*,"JL=",jl,hei_updf
6737-
67386721 pmaxzu= 850 .
67396722 kb_adj= minloc (abs (po_cup(kts:kt)- pmaxzu),1 )! ;print*,"1=",kb_adj,po_cup(kb_adj)
67406723 kb_adj= max (kb,kb_adj)
@@ -6801,18 +6784,14 @@ SUBROUTINE get_zu_zd_pdf(cumulus, draft,ierr,kb,kt,zu,kts,kte,ktf,kpbli,k22,kbco
68016784 ELSEIF (itest== 12 .and. draft == " deep_up" ) then
68026785 !- kb cannot be at 1st level
68036786
6804- if (xland < 0.90 ) then !- over land
6805- hei_updf= hei_updf_LAND
6806- else
6807- hei_updf= hei_updf_OCEAN
6808- endif
6809-
6810- !- for gate soundings
6811- ! if(gate) hei_updf = max(0.1, min(1.,float(JL)/100.)) ! for gate soundings
6812-
68136787 IF ( ZERO_DIFF_LAND== 1 ) then
68146788 pmaxzu= psur- px* (psur- po_cup(kt))
68156789 ELSE
6790+ if (xland < 0.90 ) then !- over land
6791+ hei_updf= hei_updf_LAND
6792+ else
6793+ hei_updf= hei_updf_OCEAN
6794+ endif
68166795 pmaxzu= psur- hei_updf* (psur- po_cup(kt))
68176796 ENDIF
68186797
@@ -6873,16 +6852,6 @@ SUBROUTINE get_zu_zd_pdf(cumulus, draft,ierr,kb,kt,zu,kts,kte,ktf,kpbli,k22,kbco
68736852 !- --------------------------------------------------------
68746853 ELSEIF (itest== 11 .and. draft == " deep_up" ) then
68756854
6876- if (xland < 0.90 ) then !- over land
6877- hei_updf= hei_updf_LAND
6878- else
6879- hei_updf= hei_updf_OCEAN
6880- endif
6881-
6882- !- for gate soundings
6883- ! if(gate) hei_updf = max(0.1, min(1.,float(JL)/100.))
6884- ! print*,"JL=",jl,hei_updf
6885-
68866855 pmaxzu= 850 .
68876856 kb_adj= minloc (abs (po_cup(kts:kt)- pmaxzu),1 )! ;print*,"1=",kb_adj,po_cup(kb_adj)
68886857 kb_adj= max (kb,kb_adj)
@@ -6918,6 +6887,11 @@ SUBROUTINE get_zu_zd_pdf(cumulus, draft,ierr,kb,kt,zu,kts,kte,ktf,kpbli,k22,kbco
69186887 IF (ZERO_DIFF_LAND== 1 ) then
69196888 zu(:)= 0.65 * zul(:)+ 0.35 * zuh(:)
69206889 ELSE
6890+ if (xland < 0.90 ) then !- over land
6891+ hei_updf= hei_updf_LAND
6892+ else
6893+ hei_updf= hei_updf_OCEAN
6894+ endif
69216895 zu(:)= (1 .- hei_updf)* zul(:) + hei_updf* zuh(:)
69226896 ENDIF
69236897
@@ -6967,8 +6941,6 @@ SUBROUTINE get_zu_zd_pdf(cumulus, draft,ierr,kb,kt,zu,kts,kte,ktf,kpbli,k22,kbco
69676941 !- location of the maximum Zu: dp_layer mbar above k1 height
69686942 hei_updf = (1 .- xland)* hei_updf_LAND+ xland* hei_updf_OCEAN
69696943
6970- ! hei_updf = (float(JL)-20)/40. ; print*,"JL=",jl,hei_updf
6971-
69726944 dp_layer = hei_updf* (po_cup(k1)- po_cup(kt))
69736945
69746946 level_max_zu = minloc (abs (po_cup(kts:kt+1 )- (po_cup(k1)- dp_layer)),1 )
@@ -7029,11 +7001,9 @@ SUBROUTINE get_zu_zd_pdf(cumulus, draft,ierr,kb,kt,zu,kts,kte,ktf,kpbli,k22,kbco
70297001 !- --------------------------------------------------------
70307002 ELSEIF (draft == " DOWN" ) then
70317003 IF (trim (cumulus) == ' shallow' ) return
7032- IF (trim (cumulus) == ' mid' ) beta = 2 .5
7004+ IF (trim (cumulus) == ' mid' ) beta = 6 .5
70337005 IF (trim (cumulus) == ' deep' ) beta = 2.5
70347006
7035- hei_down= (1 .- xland)* hei_down_LAND+ xland* hei_down_OCEAN
7036-
70377007 IF (ZERO_DIFF_LAND== 1 ) then
70387008 hei_down= 0.5
70397009 ELSE
@@ -9025,15 +8995,15 @@ SUBROUTINE cup_forcing_ens_3d(itf,ktf,its,ite, kts,kte,ens4,ensdim,ichoice,maxen
90258995 xf_ens(i,1 :16 ) = xf_ens(i,ichoice)
90268996 endif
90278997
9028- !- --special combination for 'ensemble closure':
9029- !- --over the land, only applies closures 1 and 10.
9030- ! if(ichoice == 0 .and. xland(i) < 0.1)then
9031- ! xf_ens(i,1:16) =0.5*(xf_ens(i,10)+xf_ens(i,1))
9032- ! endif
9033-
9034- !- --over the land, only applies closure 10.
90358998if (ZERO_DIFF_LAND == 0 .and. ichoice == 0 ) then
8999+ !- --over the land, only applies closure 10.
90369000 xf_ens(i,1 :16 )= (1 .- xland(i))* xf_ens(i,10 )+ xland(i)* xf_ens(i,1 :16 )
9001+ else
9002+ !- --special combination for 'ensemble closure':
9003+ !- --over the land, only applies closures 1 and 10.
9004+ if (ichoice == 0 .and. xland(i) < 0.1 )then
9005+ xf_ens(i,1 :16 ) = 0.5 * (xf_ens(i,10 )+ xf_ens(i,1 ))
9006+ endif
90379007endif
90389008
90399009!- -----------------------------------
@@ -9651,12 +9621,6 @@ SUBROUTINE rain_evap_below_cloudbase(cumulus,itf,ktf, its,ite, kts,kte,ierr,kbco
96519621 !- - critical rel humidity - check this, if the value is too small, not evapo will take place.
96529622 RH_cr= RH_cr_OCEAN* xland(i)+ RH_cr_LAND* (1.0 - xland(i))
96539623
9654- ! if(xland(i) < 0.90 ) then !- over land
9655- ! RH_cr = RH_cr_LAND
9656- ! else
9657- ! RH_cr = RH_cr_OCEAN
9658- ! endif
9659-
96609624 do k= ktop(i),kts,- 1
96619625
96629626 dp = 100 .* (po_cup(i,k)- po_cup(i,k+1 ))
0 commit comments