Skip to content

Commit

Permalink
cleaning out some print statements
Browse files Browse the repository at this point in the history
  • Loading branch information
lisa-bengtsson committed Apr 27, 2022
1 parent 0200e2d commit e2d5a2a
Show file tree
Hide file tree
Showing 3 changed files with 37 additions and 26 deletions.
12 changes: 6 additions & 6 deletions physics/progsigma_calc.f90
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ subroutine progsigma_calc (im,km,flag_init,flag_restart, &
integer :: i,k,km1
real(kind=kind_phys) :: termA(im),termB(im),termC(im),termD(im), &
mcons(im),fdqa(im),form(im,km), &
qadv(im,km),sigmamax(im),dp(im),inbu(im,km)
qadv(im,km),sigmamax(im),dp(im,km),inbu(im,km)


real(kind=kind_phys) :: gcvalmx,epsilon,ZZ,cvg,mcon,buy2, &
Expand Down Expand Up @@ -82,7 +82,7 @@ subroutine progsigma_calc (im,km,flag_init,flag_restart, &
do k = 2,km1
do i = 1,im
if(cnvflg(i))then
dp(i) = 1000. * del(i,k)
dp(i,k) = 1000. * del(i,k)
endif
enddo
enddo
Expand Down Expand Up @@ -128,7 +128,7 @@ subroutine progsigma_calc (im,km,flag_init,flag_restart, &
endif
enddo
enddo

!compute termD "The vertical integral of the latent heat convergence is limited to the
!buoyant layers with positive moisture convergence (accumulated from the surface).
!Lowest level:
Expand All @@ -140,7 +140,7 @@ subroutine progsigma_calc (im,km,flag_init,flag_restart, &
do k = 2,km1
do i = 1,im
if(cnvflg(i))then
mcon = (hvap*(qadv(i,k)+tmf(i,k)+qmicro(i,k))*dp(i))
mcon = (hvap*(qadv(i,k)+tmf(i,k)+qmicro(i,k))*dp(i,k))
buy2 = termD(i)+mcon+mcons(i)
! Do the integral over buoyant layers with positive mcon acc from surface
if(k > kbcon1(i) .and. k < ktcon(i) .and. buy2 > 0.)then
Expand All @@ -157,7 +157,7 @@ subroutine progsigma_calc (im,km,flag_init,flag_restart, &
do k = 2,km1
do i = 1,im
if(cnvflg(i))then
tem=(sigmab(i)*zeta(i,k)*inbu(i,k)*dbyo1(i,k))*dp(i)
tem=(sigmab(i)*zeta(i,k)*inbu(i,k)*dbyo1(i,k))*dp(i,k)
termA(i)=termA(i)+tem
endif
enddo
Expand All @@ -167,7 +167,7 @@ subroutine progsigma_calc (im,km,flag_init,flag_restart, &
do k = 2,km1
do i = 1,im
if(cnvflg(i))then
tem=(dbyo1(i,k)*inbu(i,k))*dp(i)
tem=(dbyo1(i,k)*inbu(i,k))*dp(i,k)
termB(i)=termB(i)+tem
endif
enddo
Expand Down
36 changes: 23 additions & 13 deletions physics/samfdeepcnv.f
Original file line number Diff line number Diff line change
Expand Up @@ -80,13 +80,13 @@ subroutine samfdeepcnv_run (im,km,first_time_step,restart, &
& eps,epsm1,fv,grav,hvap,rd,rv, &
& t0c,delt,ntk,ntr,delp, &
& prslp,psp,phil,qtr,prevsq,q,q1,t1,u1,v1,fscav, &
& hwrf_samfdeep,progsigma,wclosureflg,cldwrk,rn,kbot,ktop,kcnv, &
& hwrf_samfdeep,progsigma,cldwrk,rn,kbot,ktop,kcnv, &
& islimsk,garea,dot,ncloud,hpbl,ud_mf,dd_mf,dt_mf,cnvw,cnvc, &
& QLCN, QICN, w_upi, cf_upi, CNV_MFD, &
& CNV_DQLDT,CLCN,CNV_FICE,CNV_NDROP,CNV_NICE,mp_phys,mp_phys_mg,&
& clam,c0s,c1,betal,betas,evef,pgcon,asolfac, &
& do_ca, ca_closure, ca_entr, ca_trigger, nthresh, ca_deep, &
& rainevap, sigmain, sigmaout, &
& rainevap, sigmain, sigmaout, ca_micro, &
& errmsg,errflg)
!
use machine , only : kind_phys
Expand All @@ -103,12 +103,12 @@ subroutine samfdeepcnv_run (im,km,first_time_step,restart, &
& prslp(:,:), garea(:), hpbl(:), dot(:,:), phil(:,:)
real(kind=kind_phys), dimension(:), intent(in) :: fscav
logical, intent(in) :: first_time_step,restart,hwrf_samfdeep, &
& progsigma, wclosureflg
& progsigma
real(kind=kind_phys), intent(in) :: nthresh
real(kind=kind_phys), intent(in) :: ca_deep(:)
real(kind=kind_phys), intent(in) :: sigmain(:,:),qmicro(:,:), &
& tmf(:,:),q(:,:), prevsq(:,:)
real(kind=kind_phys), intent(out) :: rainevap(:)
real(kind=kind_phys), intent(out) :: rainevap(:), ca_micro(:)
real(kind=kind_phys), intent(out) :: sigmaout(:,:)
logical, intent(in) :: do_ca,ca_closure,ca_entr,ca_trigger

Expand Down Expand Up @@ -243,7 +243,7 @@ subroutine samfdeepcnv_run (im,km,first_time_step,restart, &
! parameter(cinacrmx=-120.,cinacrmn=-120.)
parameter(cinacrmx=-120.,cinacrmn=-80.)
parameter(bet1=1.875,cd1=.506,f1=2.0,gam1=.5)
parameter(betaw=.03,dxcrtas=8.e3,dxcrtuf=15.e3)
parameter(betaw=.03,dxcrtuf=15.e3)

!
! local variables and arrays
Expand Down Expand Up @@ -380,6 +380,7 @@ subroutine samfdeepcnv_run (im,km,first_time_step,restart, &
advfac(i) = 0.
rainevap(i) = 0.
omegac(i)=0.
ca_micro(i)=0.
gdx(i) = sqrt(garea(i))
enddo

Expand Down Expand Up @@ -2456,22 +2457,22 @@ subroutine samfdeepcnv_run (im,km,first_time_step,restart, &
c
c------- final changed variable per unit mass flux
c
!> - If grid size is less than a threshold value (dxcrtas: currently 8km), the quasi-equilibrium assumption of Arakawa-Schubert is not used any longer.
!> - If grid size is less than a threshold value (dxcrtas: currently 8km if progsigma is not used and 30km if progsigma is used), the quasi-equilibrium assumption of Arakawa-Schubert is not used any longer.
!
if(progsigma)then
dxcrtas=30.e3
else
dxcrtas=8.e3
endif


do i = 1, im
asqecflg(i) = cnvflg(i)
if(asqecflg(i) .and. gdx(i) < dxcrtas) then
asqecflg(i) = .false.
endif
enddo

!> - If wclosureflg is true, then quasi-equilibrium closure of Arakawa-Schubert is not used any longer, regardless of resolution
if(wclosureflg)then
do i = 1, im
asqecflg(i) = .false.
enddo
endif

!
!> - If grid size is larger than the threshold value (i.e., asqecflg=.true.), the quasi-equilibrium assumption is used to obtain the cloud base mass flux. To begin with, calculate the change in the temperature and moisture profiles per unit cloud base mass flux.
do k = 1, km
Expand Down Expand Up @@ -2884,6 +2885,15 @@ subroutine samfdeepcnv_run (im,km,first_time_step,restart, &

!> - From Han et al.'s (2017) \cite han_et_al_2017 equation 6, calculate cloud base mass flux as a function of the mean updraft velcoity for the grid sizes where the quasi-equilibrium assumption of Arakawa-Schubert is not valid any longer.
!! As discussed in Han et al. (2017) \cite han_et_al_2017 , when dtconv is larger than tauadv, the convective mixing is not fully conducted before the cumulus cloud is advected out of the grid cell. In this case, therefore, the cloud base mass flux is further reduced in proportion to the ratio of tauadv to dtconv.
if(progsigma)then
do i= 1, im
if(cnvflg(i))then
ca_micro(i)=sigmab(i)
endif
enddo
endif
do i= 1, im
if(cnvflg(i) .and. .not.asqecflg(i)) then
k = kbcon(i)
Expand Down
15 changes: 8 additions & 7 deletions physics/samfdeepcnv.meta
Original file line number Diff line number Diff line change
Expand Up @@ -312,13 +312,6 @@
dimensions = ()
type = logical
intent = in
[wclosureflg]
standard_name = flag_for_wclosure
long_name = flag for vertical velocity closure
units = flag
dimensions = ()
type = logical
intent = in
[progsigma]
standard_name = do_prognostic_updraft_area_fraction
long_name = flag for prognostic sigma in cumuls scheme
Expand Down Expand Up @@ -667,6 +660,14 @@
type = real
kind = kind_phys
intent = out
[ca_micro]
standard_name = output_prognostic_sigma_two
long_name = output of prognostic area fraction two
units = frac
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = out
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down

0 comments on commit e2d5a2a

Please sign in to comment.