Skip to content
Open
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
31 changes: 31 additions & 0 deletions Registry/registry.dyn_light
Original file line number Diff line number Diff line change
@@ -0,0 +1,31 @@
rconfig integer dyn_lightning_option namelist,physics max_domains 0 rh "dynlight" "Dynamic Lightning Scheme option, 1: on"


#dynamic lightning
rconfig integer num_light_periods namelist,physics 1 1 irh "num_light_periods" "" ""
rconfig real coul_pos namelist,physics max_domains 0.25E-4 rh "Constant for Positive Charging of Clouds" "Coulombs" ""
rconfig real coul_neg namelist,physics max_domains 0.25E-4 rh "Constant for Negative Charging of Clouds" "Coulombs" ""
rconfig real coul_neu namelist,physics max_domains 0.25E-4 rh "Constant for Charging of Intracloud Lightning" "Coulombs" ""
rconfig real j_pos namelist,physics max_domains 5.E9 rh "Threshold for Producing Positive Event" "J" ""
rconfig real j_neg namelist,physics max_domains 1.E9 rh "Threshold for Producing Negative Event" "J" ""
rconfig real j_neu namelist,physics max_domains 1.E9 rh "Threshold for Producing IC Event" "" "J"
# end dynamic lightning

# state real - ikjftb scalar 1 - - -
state real light_ne ikjftb scalar 1 - \
i0rhusdf=(bdy_interp:dt) "LIGHTNING_NE" "LIGHTNING NEG TOTAL ENERGY " "J"
state real light_pe ikjftb scalar 1 - \
i0rhusdf=(bdy_interp:dt) "LIGHTNING_PE" "LIGHTNING POS TOTAL ENERGY" "J"
state real light_neu ikjftb scalar 1 - \
i0rhusdf=(bdy_interp:dt) "LIGHTNING_NEU" "LIGHTNING NEU TOTAL ENERGY" "J"
#
state real LPOS ij misc 1 - irh05du "LPOS" "Positive Cloud to Ground Lightning Density" "# time-l"
state real LNEG ij misc 1 - irh05du "LNEG" "Negative Cloud to Ground Lightning Density" "# time-1"
state real LNEU ij misc 1 - irh05du "LNEU" "Intra-Cloud Lightning Density" "# time-1"
state real LPI2D ij misc 1 - rh05 "LPI2D" "Lightning Potential Index (2D)" "J/kg"
state real LPI3D ikj misc 1 - rh05 "LPI3D" "Lightning Potential Index (3D)" "J/kg"
state real l_obs i{lp}j misc 1 - irh05 "L_OBS" "Lightning OBS" " "

package dynlight_output dyn_lightning_option==1 - scalar:light_pe,light_ne,light_neu;state:lneu,lneg,lpos,l_obs,lpi2d,lpi3d


25 changes: 13 additions & 12 deletions dyn_em/solve_em.F
Original file line number Diff line number Diff line change
Expand Up @@ -183,8 +183,7 @@ SUBROUTINE solve_em ( grid , config_flags &
LOGICAL :: leapfrog
INTEGER :: l,kte,kk
LOGICAL :: f_flux ! flag for computing averaged fluxes in cu_gd
REAL :: curr_secs, curr_secs2, curr_mins2
REAL(8) :: curr_secs_r8, curr_secs2_r8
REAL :: curr_secs, curr_secs2
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I don't think you should be making this change. The two lines in the code should be retained.

INTEGER :: num_sound_steps
INTEGER :: idex, jdex
REAL :: max_msft
Expand All @@ -199,7 +198,6 @@ SUBROUTINE solve_em ( grid , config_flags &

TYPE(WRFU_TimeInterval) :: tmpTimeInterval, tmpTimeInterval2
REAL :: real_time
REAL(8) :: real_time_r8
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

The same for this line, which should not be removed.

LOGICAL :: adapt_step_flag
LOGICAL :: fill_w_flag

Expand Down Expand Up @@ -333,9 +331,6 @@ END SUBROUTINE CMAQ_DRIVER
tmpTimeInterval2 = domain_get_current_time ( grid ) - domain_get_start_time ( grid )
curr_secs = real_time(tmpTimeInterval)
curr_secs2 = real_time(tmpTimeInterval2)
curr_secs_r8 = real_time_r8(tmpTimeInterval)
curr_secs2_r8 = real_time_r8(tmpTimeInterval2)
curr_mins2 = REAL( curr_secs2_r8 / 60.0d0 )
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

The same applies here.


old_dt = grid%dt ! store old time step for flux averaging code at end of RK loop

Expand Down Expand Up @@ -816,7 +811,7 @@ END SUBROUTINE CMAQ_DRIVER
, ph_tendf, mu_tendf &
, tke_tend &
, config_flags%use_adaptive_time_step &
, curr_secs, curr_mins2 &
, curr_secs &
, psim , psih , gz1oz0 &
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

The same applies here.

, chklowq &
, cu_act_flag , hol , th_phy &
Expand Down Expand Up @@ -3729,7 +3724,6 @@ END SUBROUTINE CMAQ_DRIVER
& ,P8W=p8w ,P=p_phy ,PI_PHY=pi_phy &
& ,RHO=grid%rho ,SPEC_ZONE=grid%spec_zone &
& ,SR=grid%sr ,TH=th_phy &
& ,ssat=grid%ssat, ssati=grid%ssati &
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Here too.

& ,refl_10cm=grid%refl_10cm & ! hm, 9/22/09 for refl
& ,vmi3d=grid%vmi3d & ! for P3
& ,di3d=grid%di3d & ! for P3
Expand Down Expand Up @@ -3763,7 +3757,7 @@ END SUBROUTINE CMAQ_DRIVER
& ,DGNUM4D=grid%dgnum4d,DGNUMWET4D=grid%dgnumwet4d &
!======================
#endif
& ,XLAND=grid%xland,SNOWH=grid%SNOW,XICE=grid%XICE &
& ,XLAND=grid%xland,SNOWH=grid%SNOW & !PMA
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

The same here.

& ,SPECIFIED=specified_bdy, CHANNEL_SWITCH=channel_bdy &
& ,F_RAIN_PHY=grid%f_rain_phy &
& ,F_RIMEF_PHY=grid%f_rimef_phy &
Expand Down Expand Up @@ -3983,9 +3977,16 @@ END SUBROUTINE CMAQ_DRIVER
& ,pert_thom_qc=config_flags%pert_thom_qc &
& ,pert_thom_qi=config_flags%pert_thom_qi &
& ,pert_thom_qs=config_flags%pert_thom_qs &
& ,pert_thom_ni=config_flags%pert_thom_ni &
& ,cloudnc=grid%cloudnc &
)
& ,pert_thom_ni=config_flags%pert_thom_ni &
! Dynamic Lightning Scheme
& , light_pe_curr=scalar(ims,kms,jms,P_light_pe), F_light_pe=F_light_pe &
& , light_ne_curr=scalar(ims,kms,jms,P_light_ne), F_light_ne=F_light_ne &
& , light_neu_curr=scalar(ims,kms,jms,P_light_neu), F_light_neu=F_light_neu &
& ,lpos=grid%lpos,lneg=grid%lneg,lneu=grid%lneu &
& ,l_obs=grid%l_obs&
& ,lpi2d=grid%lpi2d,lpi3d=grid%lpi3d &
& ,num_light_periods=config_flags%num_light_periods &
& ,curr_secs=curr_secs )


BENCH_END(micro_driver_tim)
Expand Down
24 changes: 7 additions & 17 deletions phys/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -43,9 +43,9 @@ MODULES = \
module_bl_myjpbl.o \
module_bl_qnsepbl.o \
module_bl_acm.o \
module_bl_mynnedmf_common.o \
module_bl_mynnedmf.o \
module_bl_mynnedmf_driver.o \
module_bl_mynn_common.o \
module_bl_mynn.o \
module_bl_mynn_wrapper.o \
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

These should not be changed in your PR.

module_bl_fogdes.o \
module_bl_gwdo.o \
module_bl_gwdo_gsl.o \
Expand Down Expand Up @@ -97,7 +97,6 @@ MODULES = \
module_mp_etanew.o \
module_mp_fer_hires.o \
module_mp_thompson.o \
module_mp_rcon.o \
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This should not be removed.

module_fire_emis.o \
module_mp_SBM_polar_radar.o \
module_mp_full_sbm.o \
Expand All @@ -114,7 +113,6 @@ MODULES = \
module_mp_wdm5.o \
module_mp_wdm6.o \
module_mp_wdm7.o \
module_mp_udm.o \
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This one too, should not be removed.

module_mp_ntu.o \
module_mp_cammgmp_driver.o \
module_ra_sw.o \
Expand Down Expand Up @@ -197,6 +195,9 @@ MODULES = \
module_radiation_driver.o \
module_surface_driver.o \
module_lightning_driver.o \
module_calc_lpi_new.o \
module_ltng_pe.o \
module_ltng_strokes.o \
module_ltng_cpmpr92z.o \
module_ltng_crmpr92.o \
module_ltng_iccg.o \
Expand Down Expand Up @@ -251,7 +252,6 @@ LIBTARGET = physics
TARGETDIR = ./

$(LIBTARGET) :
(cd .. && ./tools/manage_externals/checkout_externals --externals ./arch/Externals.cfg)
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

You definitely should not remove this line.

$(MAKE) $(J) non_nmm ; \
$(AR) $(ARFLAGS) ../main/$(LIBWRFLIB) $(MODULES) $(OBJS) \
$(FIRE_MODULES) $(DIAGNOSTIC_MODULES_EM) $(PHYSMMM_MODULES)
Expand All @@ -273,17 +273,7 @@ submodules :
else \
echo No action required for NoahMP submodule ; \
fi
@if [ \( ! -f module_bl_mynnedmf.F \) -o \( ! -f module_bl_mynedmf_common.F \) -o \
\( ! -f module_bl_mynnedmf_driver.F \) ] ; then \
echo Pulling in MYNN-EDMF submodule ; \
( cd .. ; git submodule update --init --recursive ) ; \
ln -sf MYNN-EDMF/module_bl_mynnedmf.F90 module_bl_mynnedmf.F ; \
ln -sf MYNN-EDMF/WRF/module_bl_mynnedmf_common.F90 module_bl_mynnedmf_common.F ; \
ln -sf MYNN-EDMF/WRF/module_bl_mynnedmf_driver.F90 module_bl_mynnedmf_driver.F ; \
else \
echo No action required for MYNN-EDMF submodule ; \
fi

Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

You should not remove these lines either.


clean:
@ echo 'use the clean script'

Expand Down
214 changes: 214 additions & 0 deletions phys/module_calc_lpi_new.F
Original file line number Diff line number Diff line change
@@ -0,0 +1,214 @@
MODULE module_calc_lpi_new
CONTAINS
SUBROUTINE calc_lpi_new(qc, qr, qi, qs, qg &
,w,dz8w,pi_phy,th_phy,p_phy,rho_phy &
,lpi2d,lpi3d &
,ids,ide, jds,jde, kds,kde &
,ims,ime, jms,jme, kms,kme &
,its,ite, jts,jte, kts,kte &
)

IMPLICIT NONE
!-------------------------------------------------------------------
!
!
INTEGER, INTENT(IN ) :: ids,ide, jds,jde, kds,kde , &
ims,ime, jms,jme, kms,kme , &
its,ite, jts,jte, kts,kte
REAL, DIMENSION( ims:ime , kms:kme , jms:jme ), &
INTENT(IN) :: &
qc, &
qi, &
qr, &
qs, &
qg
REAL, DIMENSION( ims:ime , kms:kme , jms:jme ), &
INTENT(INOUT),OPTIONAL :: &
lpi3d
! ,&
! light_ne, &

REAL, DIMENSION( ims:ime, kms:kme, jms:jme ), &
INTENT(IN ) :: w
REAL, DIMENSION( ims:ime , kms:kme , jms:jme ), &
INTENT(IN) :: th_phy
!

!
REAL, DIMENSION( ims:ime , kms:kme , jms:jme ), &
INTENT(IN ) :: &
rho_phy, &
dz8w, &
pi_phy, &
p_phy

! REAL, INTENT(INOUT), DIMENSION(ims:ime,jms:jme):: &
! & prec_ice,wqg_m15
REAL, DIMENSION(ims:ime,jms:jme):: &
& lpi2d
! REAL, DIMENSION(ims:ime,jms:jme):: &
! & LPI,LPOS,LNEG,LNEU,plpi,nlpi,neulpi,prec_ice,wqg_m15




REAL, DIMENSION(kms:kme):: tempk,rh,qtot,qitot
REAL, DIMENSION(kms:kme):: p1d,rho1d,qti1d
REAL, DIMENSION(kms:kme):: temp,qc1d,ql1d,qi1d,qs1d,qg1d,lpi1d,del_z
REAL, DIMENSION(0:kme):: w1d,height
REAL, DIMENSION(kms:kme):: e1d,height_t,w1d_t
REAL z_full,qrs,teten,RELHUM,LOC,Td_850,Td_700,PC_DWPT
INTEGER level
REAL :: t_base,t_top
real top, bot
real num,den,ave_z
real num_s,den_s
real num_i,den_i
real q_isg,del_z_tot

INTEGER I_COLLAPSE
LOGICAL LOOK_T
INTEGER I_START,I_END,J_START,J_END


INTEGER :: i,j,k
!-------------------------------------------------------------------
! ! print*,'ims,ime,jms,jme,kms,kme = ',ims,ime,jms,jme,kms,kme
! print*,'its,ite,jts,jte,kts,kte = ',its,ite,jts,jte,kts,kte
! parameter(t_pos=0.12,t_neg=0.06,t_neu=0.03)
! note: t_pos is modified based on the height of the top of the cloud
! I believe that the value of 60000 m/s might be a typical speed
! See: https\://en.wikipedia.org/wiki/Lightning
! print*,'dt = ',dt
! print*,'dx = ',dx
! print*,'coul_pos = ',coul_pos
! print*,'coul_neg = ',coul_neg
! print*,'coul_neu = ',coul_neu
! return (1)
! if (MAXVAL(light_pe).ne.0)print*,'maxval light_pe'
! if (MAXVAL(light_pe).ne.0)write(MAXVAL(light_pe))
! if (MAXVAL(light_ne).ne.0)print*,'maxval light_ne'
! if (MAXVAL(light_ne).ne.0)write(MAXVAL(light_ne))
!-------------------------------------------------------------------
t_base = 0
t_top = -20.

DO j = jts,jte
DO i = its,ite
z_full=0.
height(0)=z_full
w1d(0)=w(i,1,j)
do k = kts,kte-1
if (k.lt.kte-1)then
w1d(k)=w(i,k+1,j)
else
w1d(k)=0.
end if
temp(k) = th_phy(i,k,j)*pi_phy(i,k,j)-273.16
tempk(k) = th_phy(i,k,j)*pi_phy(i,k,j)
p1d(k)=p_phy(i,k,j)
rho1d(k)=rho_phy(i,k,j)
z_full=z_full+dz8w(i,k,j)
height(k)=z_full
qc1d(k)=qc(i,k,j)
ql1d(k)=qc(i,k,j)+qr(i,k,j)
qi1d(k)=qi(i,k,j)
! qti1d(k)=qi(i,k,j)+qs(i,k,j)+qg(i,k,j)+qh(i,k,j)
qti1d(k)=qi(i,k,j)+qs(i,k,j)+qg(i,k,j)
qs1d(k)=qs(i,k,j)
! qg1d(k)=qg(i,k,j)+qh(i,k,j)
! Hail doesn't usually charge
qg1d(k)=qg(i,k,j)
! For conservative advection multiply by rho1d and divide by it below
enddo
do k = kts,kte-1
w1d_t(k)=0.5*(w1d(k-1)+w1d(k))
end do
do k=kts,kte
lpi3d(i,k,j) = 0
top=height(k+1)
bot=height(k)
del_z(k)=top-bot
! if (max_w(i,j).gt.0.5)print*,"max_w > 0.5"
end do

ave_z = 0
del_z_tot = 0
lpi2d(i,j) = 0

do k=kts,kte
if (temp(k).le.t_base.and.temp(k).gt.t_top)then ! set t1d range

den_i = qi1d(k)+qg1d(k)
den_s = qs1d(k)+qg1d(k)
if (qs1d(k).eq.0.or.qg1d(k).eq.0.)then !checks for zeroes
den_s=10000.
num_s = 0.
else
num_s = sqrt(qs1d(k)*qg1d(k))
end if
if (qi1d(k).eq.0.or.qg1d(k).eq.0.)then ! checks for zeroes
den_i=10000.
num_i = 0.
else
num_i = sqrt(qi1d(k)*qg1d(k))
end if
q_isg = qg1d(k)*(num_i/den_i+num_s/den_s) ! ice "fract"-content

if (ql1d(k).eq.0.or.q_isg.eq.0)then
num=0
den=10000.
else
num = sqrt(ql1d(k)*q_isg)
den = ql1d(k)+q_isg
end if
del_z_tot=del_z_tot+del_z(k)
if (num.gt.0)then
ave_z=ave_z+del_z(k)*(2.*num/den)*w1d_t(k)**2 ! power index J/unit-mass
end if
end if
if (lpi2d(i,j).lt.0)lpi2d(i,j)=0
end do
!
if (del_z_tot.eq.0)del_z_tot=100000
lpi2d(i,j)=ave_z/del_z_tot
ave_z = 0.
do k=kts,kte

den_i = qi1d(k)+qg1d(k)
den_s = qs1d(k)+qg1d(k)
if (qs1d(k).eq.0.or.qg1d(k).eq.0.)then !checks for zeroes
den_s=10000.
num_s = 0.
else
num_s = sqrt(qs1d(k)*qg1d(k))
end if
if (qi1d(k).eq.0.or.qg1d(k).eq.0.)then ! checks for zeroes
den_i=10000.
num_i = 0.
else
num_i = sqrt(qi1d(k)*qg1d(k))
end if
q_isg = qg1d(k)*(num_i/den_i+num_s/den_s) ! ice "fract"-content

if (ql1d(k).eq.0.or.q_isg.eq.0)then
num=0
den=10000.
else
num = sqrt(ql1d(k)*q_isg)
den = ql1d(k)+q_isg
end if
del_z_tot=del_z_tot+del_z(k)
if (num.gt.0)then
ave_z=(2.*num/den)*w1d_t(k)**2 ! power index J/unit-mass
lpi3d(i,k,j) = ave_z
end if
end do
end do
end do
! check cell for active cell
! go to 10!
! Check within five grid elements that a majority of max_w > 0.5 m/s
return
end subroutine calc_lpi_new
END MODULE module_calc_lpi_new
Loading