Skip to content

Commit

Permalink
cleaning some diagnostics
Browse files Browse the repository at this point in the history
  • Loading branch information
lisa-bengtsson committed Apr 20, 2022
1 parent 4f84ed7 commit b530db1
Show file tree
Hide file tree
Showing 5 changed files with 7 additions and 29 deletions.
5 changes: 1 addition & 4 deletions physics/progsigma_calc.f90
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@
subroutine progsigma_calc (im,km,flag_init,flag_restart, &
flag_shallow,del,tmf,qmicro,dbyo1,zdqca,omega_u,zeta,hvap, &
delt,qgrs_dsave,q,kbcon1,ktcon,cnvflg,gdx, &
ca_micro,sigmain,sigmaout,sigmab,errmsg,errflg)
sigmain,sigmaout,sigmab,errmsg,errflg)
!
!
use machine, only : kind_phys
Expand All @@ -31,7 +31,6 @@ subroutine progsigma_calc (im,km,flag_init,flag_restart, &
qmicro(im,km),tmf(im,km),dbyo1(im,km),zdqca(im,km), &
omega_u(im,km),zeta(im,km),gdx(im)
logical, intent(in) :: flag_init,flag_restart,cnvflg(im),flag_shallow
real(kind=kind_phys), intent(out):: ca_micro(im)
real(kind=kind_phys), intent(in) :: sigmain(im,km)

! intent out
Expand Down Expand Up @@ -79,7 +78,6 @@ subroutine progsigma_calc (im,km,flag_init,flag_restart, &
termD(i)=0.
fdqa(i)=0.
mcons(i)=0.
ca_micro(i)=0.
enddo

!Initial computations, place maximum sigmain in sigmab
Expand Down Expand Up @@ -207,7 +205,6 @@ subroutine progsigma_calc (im,km,flag_init,flag_restart, &
sigmab(i)=MIN(sigmab(i),sigmamax(i))
sigmab(i)=MAX(sigmab(i),0.01)
endif
ca_micro(i)=sigmab(i)
endif!cnvflg
enddo

Expand Down
8 changes: 3 additions & 5 deletions physics/samfdeepcnv.f
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,7 @@ subroutine samfdeepcnv_run (im,km,first_time_step,restart, &
& 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, ca_micro, &
& rainevap, sigmain, sigmaout, &
& errmsg,errflg)
!
use machine , only : kind_phys
Expand All @@ -108,7 +108,7 @@ subroutine samfdeepcnv_run (im,km,first_time_step,restart, &
real(kind=kind_phys), intent(in) :: ca_deep(:)
real(kind=kind_phys), intent(in) :: sigmain(:,:),qmicro(:,:), &
& tmf(:,:),q(:,:), qgrs_dsave(:,:)
real(kind=kind_phys), intent(out) :: rainevap(:),ca_micro(:)
real(kind=kind_phys), intent(out) :: rainevap(:)
real(kind=kind_phys), intent(out) :: sigmaout(:,:)
logical, intent(in) :: do_ca,ca_closure,ca_entr,ca_trigger

Expand Down Expand Up @@ -919,8 +919,6 @@ subroutine samfdeepcnv_run (im,km,first_time_step,restart, &
enddo
if(totflg) return
!!
!
!Lisa: at this point only trigger criteria is set

! turbulent entrainment rate assumed to be proportional
! to subcloud mean TKE
Expand Down Expand Up @@ -2895,7 +2893,7 @@ subroutine samfdeepcnv_run (im,km,first_time_step,restart, &
call progsigma_calc(im,km,first_time_step,restart,flag_shallow,
& del,tmf,qmicro,dbyo1,zdqca,omega_u,zeta,hvap,delt,
& qgrs_dsave,q,kbcon1,ktcon,cnvflg,gdx,
& ca_micro,sigmain,sigmaout,sigmab,errmsg,errflg)
& sigmain,sigmaout,sigmab,errmsg,errflg)
endif

!> - 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.
Expand Down
8 changes: 0 additions & 8 deletions physics/samfdeepcnv.meta
Original file line number Diff line number Diff line change
Expand Up @@ -326,14 +326,6 @@
dimensions = ()
type = logical
intent = in
[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
[cldwrk]
standard_name = cloud_work_function
long_name = cloud work function
Expand Down
7 changes: 3 additions & 4 deletions physics/samfshalcnv.f
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@ subroutine samfshalcnv_run(im,km,itc,ntc,cliq,cp,cvap, &
& rn,kbot,ktop,kcnv,islimsk,garea, &
& dot,ncloud,hpbl,ud_mf,dt_mf,cnvw,cnvc, &
& clam,c0s,c1,evef,pgcon,asolfac,hwrf_samfshal,
& ca_micro,sigmain,sigmaout,errmsg,errflg)
& sigmain,sigmaout,errmsg,errflg)
!
use machine , only : kind_phys
use funcphys , only : fpvs
Expand All @@ -86,7 +86,7 @@ subroutine samfshalcnv_run(im,km,itc,ntc,cliq,cp,cvap, &
& q1(:,:), t1(:,:), u1(:,:), v1(:,:)
!
integer, intent(out) :: kbot(:), ktop(:)
real(kind=kind_phys), intent(out) :: rn(:), ca_micro(:), &
real(kind=kind_phys), intent(out) :: rn(:), &
& cnvw(:,:), cnvc(:,:), ud_mf(:,:), dt_mf(:,:), sigmaout(:,:)
!
real(kind=kind_phys), intent(in) :: clam, c0s, c1, &
Expand Down Expand Up @@ -334,7 +334,6 @@ subroutine samfshalcnv_run(im,km,itc,ntc,cliq,cp,cvap, &
! vshear(i) = 0.
gdx(i) = sqrt(garea(i))
xmb(i) = 0.
ca_micro(i) = 0.
enddo
endif
!!
Expand Down Expand Up @@ -1932,7 +1931,7 @@ subroutine samfshalcnv_run(im,km,itc,ntc,cliq,cp,cvap, &
call progsigma_calc(im,km,first_time_step,restart,flag_shallow,
& del,tmf,qmicro,dbyo1,zdqca,omega_u,zeta,hvap,delt,
& qgrs_dsave,q,kbcon1,ktcon,cnvflg,gdx,
& ca_micro,sigmain,sigmaout,sigmab,errmsg,errflg)
& sigmain,sigmaout,sigmab,errmsg,errflg)
endif

!> - 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.
Expand Down
8 changes: 0 additions & 8 deletions physics/samfshalcnv.meta
Original file line number Diff line number Diff line change
Expand Up @@ -466,14 +466,6 @@
dimensions = ()
type = logical
intent = in
[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
[sigmain]
standard_name = prognostic_updraft_area_fraction_in_convection
long_name = convective updraft area fraction
Expand Down

0 comments on commit b530db1

Please sign in to comment.