Skip to content
Merged
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
5 changes: 3 additions & 2 deletions physics/CONV/C3/cu_c3_deep.F90
Original file line number Diff line number Diff line change
Expand Up @@ -100,6 +100,7 @@ subroutine cu_c3_deep_run( &
,betascu & ! Tuning parameter for shallow clouds
,betamcu & ! Tuning parameter for mid-level clouds
,betadcu & ! Tuning parameter for deep clouds
,sigmab_coldstart & ! whether cold start variables when initializating sigmab
,sigmain & ! input area fraction after advection
,sigmaout & ! updated prognostic area fraction
,z1 & ! terrain
Expand Down Expand Up @@ -377,7 +378,7 @@ subroutine cu_c3_deep_run( &

integer, dimension (its:), intent(inout) :: ierr
integer, dimension (its:), intent(in) :: csum
logical, intent(in) :: do_ca, progsigma
logical, intent(in) :: do_ca, progsigma,sigmab_coldstart
logical, intent(in) :: flag_init, flag_restart
!$acc declare copy(ierr) copyin(csum)
integer :: &
Expand Down Expand Up @@ -2013,7 +2014,7 @@ subroutine cu_c3_deep_run( &
endif
enddo
call progsigma_calc(itf,ktf,flag_init,flag_restart,flag_shallow, &
flag_mid,del,tmf,qmicro,dbyo1,zdqca,omega_u,zeta,xlv,dtime, &
flag_mid,sigmab_coldstart,del,tmf,qmicro,dbyo1,zdqca,omega_u,zeta,xlv,dtime, &
forceqv_spechum,kbcon,ktop,cnvflg,betascu,betamcu,betadcu, &
sigmind,sigminm,sigmins,sigmain,sigmaout,sigmab)
endif
Expand Down
8 changes: 5 additions & 3 deletions physics/CONV/C3/cu_c3_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -71,7 +71,7 @@ subroutine cu_c3_driver_run(ntracer,garea,im,km,dt,flag_init,flag_restart,&
do_ca,progsigma,cactiv,cactiv_m,g,cp,fv,r_d,xlv,r_v,forcet, &
forceqv_spechum,phil,delp,raincv,tmf,qmicro,sigmain, &
betascu,betamcu,betadcu,qv_spechum,t,cld1d,us,vs,t2di,w, &
qv2di_spechum,p2di,psuri, &
qv2di_spechum,p2di,psuri,sigmab_coldstart, &
hbot,htop,kcnv,xland,hfx2,qfx2,aod_gf,cliw,clcw,ca_deep,rainevap,&
pbl,ud_mf,dd_mf,dt_mf,cnvw_moist,cnvc,imfshalcnv, &
flag_for_scnv_generic_tend,flag_for_dcnv_generic_tend, &
Expand Down Expand Up @@ -110,7 +110,7 @@ subroutine cu_c3_driver_run(ntracer,garea,im,km,dt,flag_init,flag_restart,&
do_ca
real (kind=kind_phys), intent(in) :: g,cp,fv,r_d,xlv,r_v,betascu,betamcu,betadcu
logical, intent(in ) :: ldiag3d
logical, intent(in ) :: progsigma
logical, intent(in ) :: progsigma,sigmab_coldstart
real(kind=kind_phys), intent(inout) :: dtend(:,:,:)
!$acc declare copy(dtend)
integer, intent(in) :: dtidx(:,:), &
Expand Down Expand Up @@ -681,7 +681,7 @@ subroutine cu_c3_driver_run(ntracer,garea,im,km,dt,flag_init,flag_restart,&
! Prog closure
flag_init, flag_restart,fv,r_d,delp,tmfq,qmicro, &
forceqv_spechum,betascu,betamcu,betadcu,sigmain, &
sigmaout,progsigma,dx, &
sigmaout,progsigma,sigmab_coldstart,dx, &
! output tendencies
outts,outqs,outqcs,outus,outvs,cnvwt,prets,cupclws, &
! dimesnional variables
Expand Down Expand Up @@ -729,6 +729,7 @@ subroutine cu_c3_driver_run(ntracer,garea,im,km,dt,flag_init,flag_restart,&
,betascu &
,betamcu &
,betadcu &
,sigmab_coldstart &
,sigmain &
,sigmaout &
,ter11 &
Expand Down Expand Up @@ -823,6 +824,7 @@ subroutine cu_c3_driver_run(ntracer,garea,im,km,dt,flag_init,flag_restart,&
,betascu &
,betamcu &
,betadcu &
,sigmab_coldstart &
,sigmain &
,sigmaout &
,ter11 &
Expand Down
7 changes: 7 additions & 0 deletions physics/CONV/C3/cu_c3_driver.meta
Original file line number Diff line number Diff line change
Expand Up @@ -259,6 +259,13 @@
type = real
kind = kind_phys
intent = out
[sigmab_coldstart]
standard_name = flag_to_cold_start_for_sigmab_init
long_name = flag to cold start for sigmab initialization
units = flag
dimensions = ()
type = logical
intent = in
[betascu]
standard_name = tuning_param_for_shallow_cu
long_name = tuning param for shallow cu in case prognostic closure is used
Expand Down
6 changes: 3 additions & 3 deletions physics/CONV/C3/cu_c3_sh.F90
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,7 @@ subroutine cu_c3_sh_run ( &
zuo,xmb_out,kbcon,ktop,k22,ierr,ierrc, &
flag_init, flag_restart,fv,r_d,delp,tmf,qmicro, &
forceqv_spechum,betascu,betamcu,betadcu,sigmain,&
sigmaout,progsigma,dx, &
sigmaout,progsigma,sigmab_coldstart,dx, &
outt,outq,outqc,outu,outv,cnvwt,pre,cupclw, & ! output tendencies
itf,ktf,its,ite, kts,kte,ipr,tropics) ! dimesnional variables
!
Expand All @@ -85,7 +85,7 @@ subroutine cu_c3_sh_run ( &
,intent (in ) :: &
itf,ktf, &
its,ite, kts,kte,ipr
logical, intent(in) :: flag_init, flag_restart, progsigma
logical, intent(in) :: flag_init, flag_restart, progsigma, sigmab_coldstart
logical :: make_calc_for_xk = .true.
integer, intent (in ) :: &
ichoice
Expand Down Expand Up @@ -979,7 +979,7 @@ subroutine cu_c3_sh_run ( &
endif
enddo
call progsigma_calc(itf,ktf,flag_init,flag_restart,flag_shallow, &
flag_mid,del,tmf,qmicro,dbyo,zdqca,omega_u,zeta,xlv,dtime, &
flag_mid,sigmab_coldstart,del,tmf,qmicro,dbyo,zdqca,omega_u,zeta,xlv,dtime, &
forceqv_spechum,kbcon,ktop,cnvflg,betascu,betamcu,betadcu, &
sigmind,sigminm,sigmins,sigmain,sigmaout,sigmab)

Expand Down
2 changes: 1 addition & 1 deletion physics/CONV/Grell_Freitas/cu_gf_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -427,7 +427,7 @@ subroutine cu_gf_driver_run(ntracer,garea,im,km,dt,flag_init,flag_restart, gf_co
ccn_m(i) = 0.

! set aod and ccn
if ((flag_init .and. .not.flag_restart) .or. gf_coldstart) then
if ((flag_init) .and. (.not.flag_restart .or. gf_coldstart)) then
aod_gf(i)=aodc0
else
if((cactiv(i).eq.0) .and. (cactiv_m(i).eq.0))then
Expand Down
2 changes: 1 addition & 1 deletion physics/CONV/Grell_Freitas/cu_gf_driver_pre.F90
Original file line number Diff line number Diff line change
Expand Up @@ -59,7 +59,7 @@ subroutine cu_gf_driver_pre_run (flag_init, flag_restart, gf_coldstart, kdt, fho
! For restart runs, can assume that prevst and prevsq
! are read from the restart files beforehand, same
! for conv_act.
if((flag_init .and. .not.flag_restart) .or. gf_coldstart) then
if((flag_init) .and. (.not.flag_restart .or. gf_coldstart)) then
!$acc kernels
forcet(:,:)=0.0
forceq(:,:)=0.0
Expand Down
3 changes: 2 additions & 1 deletion physics/CONV/SAMF/samfdeepcnv.f
Original file line number Diff line number Diff line change
Expand Up @@ -2939,7 +2939,8 @@ subroutine samfdeepcnv_run (im,km,first_time_step,restart, &
flag_shallow = .false.
flag_mid = .false.
call progsigma_calc(im,km,first_time_step,restart,flag_shallow,
& flag_mid,del,tmfq,qmicro,dbyo1,zdqca,omega_u,zeta,hvap,
& flag_mid,sigmab_coldstart,del,tmfq,qmicro,dbyo1,zdqca,
& omega_u,zeta,hvap,
& delt,qadv,kbcon1,ktcon,cnvflg,betascu,betamcu,betadcu,
& sigmind,sigminm,sigmins,sigmain,sigmaout,sigmab)
endif
Expand Down
11 changes: 7 additions & 4 deletions physics/CONV/SAMF/samfshalcnv.f
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,8 @@ 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, &
& sigmain,sigmaout,betadcu,betamcu,betascu,errmsg,errflg)
& sigmain,sigmaout,betadcu,betamcu,betascu,sigmab_coldstart, &
& errmsg,errflg)
!
use machine , only : kind_phys
use funcphys , only : fpvs
Expand Down Expand Up @@ -89,7 +90,7 @@ subroutine samfshalcnv_run(im,km,itc,ntc,cliq,cp,cvap, &
real(kind=kind_phys), intent(in) :: clam, c0s, c1, &
& asolfac, evef, pgcon
logical, intent(in) :: hwrf_samfshal,first_time_step, &
& restart,progsigma
& restart,progsigma,sigmab_coldstart
character(len=*), intent(out) :: errmsg
integer, intent(out) :: errflg
!
Expand Down Expand Up @@ -1955,7 +1956,8 @@ subroutine samfshalcnv_run(im,km,itc,ntc,cliq,cp,cvap, &
!> - From Bengtsson et al. (2022) \cite Bengtsson_2022 prognostic closure scheme, equation 8, call progsigma_calc() to compute updraft area fraction based on a moisture budget
if(progsigma)then
! Initial computations, dynamic q-tendency
if(first_time_step .and. .not.restart)then
if(first_time_step .and. (.not.restart
& .or. sigmab_coldstart))then
do k = 1,km
do i = 1,im
qadv(i,k)=0.
Expand All @@ -1978,7 +1980,8 @@ subroutine samfshalcnv_run(im,km,itc,ntc,cliq,cp,cvap, &
flag_shallow = .true.
flag_mid = .false.
call progsigma_calc(im,km,first_time_step,restart,flag_shallow,
& flag_mid,del,tmfq,qmicro,dbyo1,zdqca,omega_u,zeta,hvap,
& flag_mid,sigmab_coldstart,del,tmfq,qmicro,dbyo1,zdqca,
& omega_u,zeta,hvap,
& delt,qadv,kbcon1,ktcon,cnvflg,betascu,betamcu,betadcu,
& sigmind,sigminm,sigmins,sigmain,sigmaout,sigmab)
endif
Expand Down
7 changes: 7 additions & 0 deletions physics/CONV/SAMF/samfshalcnv.meta
Original file line number Diff line number Diff line change
Expand Up @@ -505,6 +505,13 @@
dimensions = ()
type = real
intent = in
[sigmab_coldstart]
standard_name = flag_to_cold_start_for_sigmab_init
long_name = flag to cold start for sigmab initialization
units = flag
dimensions = ()
type = logical
intent = in
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down
6 changes: 4 additions & 2 deletions physics/CONV/progsigma_calc.f90
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ module progsigma
!! used in the closure computations in the samfshalcnv. scheme
!!\section gen_progsigma progsigma_calc General Algorithm
subroutine progsigma_calc (im,km,flag_init,flag_restart,flag_shallow,&
flag_mid,del,tmf,qmicro,dbyo1,zdqca,omega_u,zeta,hvap, &
flag_mid,sigmab_coldstart,del,tmf,qmicro,dbyo1,zdqca,omega_u,zeta,hvap, &
delt,qadv,kbcon1,ktcon,cnvflg,betascu,betamcu,betadcu, &
sigmind,sigminm,sigmins,sigmain,sigmaout,sigmab)
!
Expand All @@ -38,6 +38,7 @@ subroutine progsigma_calc (im,km,flag_init,flag_restart,flag_shallow,&
qmicro(im,km),tmf(im,km),dbyo1(im,km),zdqca(im,km), &
omega_u(im,km),zeta(im,km)
logical, intent(in) :: flag_init,flag_restart,cnvflg(im),flag_shallow,flag_mid
logical, intent(in) :: sigmab_coldstart
real(kind=kind_phys), intent(in) :: sigmain(im,km)

! intent out
Expand All @@ -63,7 +64,8 @@ subroutine progsigma_calc (im,km,flag_init,flag_restart,flag_shallow,&
km1=km-1
invdelt = 1./delt

if (flag_init) then
if (flag_init .and. (.not. flag_restart &
.or. sigmab_coldstart)) then
sigmind_new=0.0
else
sigmind_new=sigmind
Expand Down
Loading