Turn raiju PrecipNFlux/PrecipEFlux into shell grid variables to make use TCS interpolation. SH mapping is still by mirroring.

This commit is contained in:
Dong Lin
2025-04-28 13:04:13 -06:00
parent dcb41344d7
commit 125a19a8b3
6 changed files with 63 additions and 24 deletions

View File

@@ -465,9 +465,11 @@ module raijutypes
!! (Ngi, Ngj, Nk) [1/s] Loss rates that result in precipitation. Should be <= lossRates
real(rp), dimension(:,:,:), allocatable :: precipType_ele
!! (Ngi, Ngj, Nk) Prepication type used for electrons
real(rp), dimension(:,:,:), allocatable :: precipNFlux
!real(rp), dimension(:,:,:), allocatable :: precipNFlux
type(ShellGridVar_T), dimension(:), allocatable :: precipNFlux
!! (Ngi, Ngj, Nk) [#/cm^2/s] Precipitation number fluxes
real(rp), dimension(:,:,:), allocatable :: precipEFlux
!real(rp), dimension(:,:,:), allocatable :: precipEFlux
type(ShellGridVar_T), dimension(:), allocatable :: precipEFlux
!! (Ngi, Ngj, Nk) [erg/cm^2/s] Precipitation energy fluxes
real(rp), dimension(:,:,:), allocatable :: dEta_dt
!! (Ngi, Ngj, Nk) [eta units/s] Average

View File

@@ -145,8 +145,10 @@ module raijuAdvancer
if (Model%doLosses) then
! Divide losses and precip fluxes by big dt to turn them into proper rates
! Quantities going into the ionosphere divided by 2 for per-hemisphere output
State%precipNFlux(:,:,k) = State%precipNFlux(:,:,k)/State%dt/2.0_rp
State%precipEFlux(:,:,k) = State%precipEFlux(:,:,k)/State%dt/2.0_rp
!State%precipNFlux(:,:,k) = State%precipNFlux(:,:,k)/State%dt/2.0_rp
!State%precipEFlux(:,:,k) = State%precipEFlux(:,:,k)/State%dt/2.0_rp
State%precipNFlux(k)%data = State%precipNFlux(k)%data/State%dt/2.0_rp
State%precipEFlux(k)%data = State%precipEFlux(k)%data/State%dt/2.0_rp
State%CCHeatFlux(:,:,k) = State%CCHeatFlux (:,:,k)/State%dt/2.0_rp
State%dEta_dt(:,:,k) = State%dEta_dt (:,:,k)/State%dt
endif

View File

@@ -318,8 +318,12 @@ module raijuIO
do s=1,Grid%nSpc
ks = Grid%spc(s)%kStart
ke = Grid%spc(s)%kEnd
outPrecipN(:,:,s) = sum(State%precipNFlux(is:ie,js:je,kS:kE), dim=3)
outPrecipE(:,:,s) = sum(State%precipEFlux(is:ie,js:je,kS:kE), dim=3)
do k=ks,ke !1,Grid%Nk
outPrecipN(:,:,s) = outPrecipN(:,:,s) + State%precipNFlux(k)%data(is:ie,js:je)
outPrecipE(:,:,s) = outPrecipE(:,:,s) + State%precipEFlux(k)%data(is:ie,js:je)
enddo
!outPrecipN(:,:,s) = sum(State%precipNFlux(is:ie,js:je,kS:kE), dim=3)
!outPrecipE(:,:,s) = sum(State%precipEFlux(is:ie,js:je,kS:kE), dim=3)
outCCHeatFlux(:,:,s) = sum(State%CCHeatFlux (is:ie,js:je,kS:kE), dim=3)
where (outPrecipN(:,:,s) > TINY)
@@ -342,9 +346,11 @@ module raijuIO
if (Model%doOutput_3DLoss) then
call AddOutVar(IOVars, "dEta_dt" , State%dEta_dt(is:ie,js:je,:), uStr="eta_units/s")
call AddOutVar(IOVars, "precipNFlux_Nk" , State%precipNFlux(is:ie,js:je,:), uStr="#/cm^2/s")
call AddOutVar(IOVars, "precipEFlux_Nk" , State%precipEFlux(is:ie,js:je,:), uStr="erg/cm^2/s")
!call AddOutVar(IOVars, "precipNFlux_Nk" , State%precipNFlux(is:ie,js:je,:), uStr="#/cm^2/s")
!call AddOutVar(IOVars, "precipEFlux_Nk" , State%precipEFlux(is:ie,js:je,:), uStr="erg/cm^2/s")
call AddOutVar(IOVars, "CCHeatFlux_Nk" , State%CCHeatFlux (is:ie,js:je,:), uStr="eV/cm^2/s")
call AddOutSGV(IOVars, "precipNFlux_Nk", State%precipNFlux, outBndsO=outBnds2D, uStr="#/cm^2/s" , dStr="precipNFlux from RAIJU flavors", doWriteMaskO=.false.)
call AddOutSGV(IOVars, "precipEFlux_Nk", State%precipEFlux, outBndsO=outBnds2D, uStr="erg/cm^2/s" , dStr="precipEFlux from RAIJU flavors", doWriteMaskO=.false.)
endif
endif
@@ -538,8 +544,10 @@ module raijuIO
call AddOutSGV(IOVars, "Pressure", State%Press, doWriteMaskO=.true., uStr="nPa")
call AddOutSGV(IOVars, "Density" , State%Den , doWriteMaskO=.true., uStr="#/cc")
! Precip
call AddOutVar(IOVars,"precipNFlux",State%precipNFlux(:,:,:),uStr="#/cm^2/s")
call AddOutVar(IOVars,"precipEFlux",State%precipEFlux(:,:,:),uStr="erg/cm^2/s")
!call AddOutVar(IOVars,"precipNFlux",State%precipNFlux(:,:,:),uStr="#/cm^2/s")
!call AddOutVar(IOVars,"precipEFlux",State%precipEFlux(:,:,:),uStr="erg/cm^2/s")
call AddOutSGV(IOVars, "precipNFlux_Nk", State%precipNFlux, doWriteMaskO=.true., uStr="#/cm^2/s")
call AddOutSGV(IOVars, "precipEFlux_Nk", State%precipEFlux, doWriteMaskO=.true., uStr="erg/cm^2/s")
call AddOutVar(IOVars,"precipLossRates_Nk", State%lossRates(:,:,:), uStr="1/s")
! (Probably not needed but we will save anyways)
call AddOutVar(IOVars, "gradPotE" , State%gradPotE (:,:,:), uStr="V/m")
@@ -617,8 +625,8 @@ module raijuIO
!call AddInVar(IOVars,"Pressure")
!call AddInVar(IOVars,"Density")
call AddInVar(IOVars,"precipNFlux")
call AddInVar(IOVars,"precipEFlux")
!call AddInVar(IOVars,"precipNFlux")
!call AddInVar(IOVars,"precipEFlux")
call AddInVar(IOVars,"precipLossRates_Nk")
call AddInVar(IOVars, "gradPotE" )
@@ -673,8 +681,8 @@ module raijuIO
!call IOArray3DFill(IOVars, "Pressure", State%Press(:,:,:))
!call IOArray3DFill(IOVars, "Density" , State%Den (:,:,:))
call IOArray3DFill(IOVars, "precipNFlux", State%precipNFlux(:,:,:))
call IOArray3DFill(IOVars, "precipEFlux", State%precipEFlux(:,:,:))
!call IOArray3DFill(IOVars, "precipNFlux", State%precipNFlux(:,:,:))
!call IOArray3DFill(IOVars, "precipEFlux", State%precipEFlux(:,:,:))
call IOArray3DFill(IOVars, "precipLossRates_Nk", State%lossRates(:,:,:))
call IOArray3DFill(IOVars, "gradPotE" , State%gradPotE (:,:,:))
@@ -728,6 +736,8 @@ module raijuIO
! ShellGridVars
call ReadInSGV(State%Press, inH5, "Pressure", "State", doIOpO=.false.)
call ReadInSGV(State%Den , inH5, "Density" , "State", doIOpO=.false.)
call ReadInSGV(State%precipNFlux, inH5, "precipNFlux_Nk", "State", doIOpO=.false.)
call ReadInSGV(State%precipEFlux, inH5, "precipEFlux_Nk", "State", doIOpO=.false.)
end associate

View File

@@ -428,8 +428,8 @@ module raijustarter
allocate( State%lossRates (sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
allocate( State%precipType_ele (sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
allocate( State%lossRatesPrecip(sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
allocate( State%precipNFlux (sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
allocate( State%precipEFlux (sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
!allocate( State%precipNFlux (sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
!allocate( State%precipEFlux (sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
allocate( State%dEta_dt (sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
allocate( State%CCHeatFlux (sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
! Coupling output data
@@ -447,6 +447,16 @@ module raijustarter
State%Press(s)%mask = .false.
State%vAvg (s)%mask = .false.
enddo
allocate(State%precipNFlux(Grid%Nk))
allocate(State%precipEFlux(Grid%Nk))
do s=1,Grid%Nk
call initShellVar(Grid%shGrid, SHGR_CC, State%precipNFlux(s))
call initShellVar(Grid%shGrid, SHGR_CC, State%precipEFlux(s))
State%precipNFlux(s)%data = 0.0
State%precipEFlux(s)%data = 0.0
State%precipNFlux(s)%mask = .false.
State%precipEFlux(s)%mask = .false.
enddo
! Only bother allocating persistent versions of debug stuff if we need them
if (Model%doOutput_debug) then

View File

@@ -78,6 +78,7 @@ module raijulosses
type(raijuState_T), intent(inout) :: State
integer :: nLP, iLP
integer :: k
if (allocated(State%lps)) then
nLP = size(State%lps)
@@ -93,9 +94,16 @@ module raijulosses
! Prep for accumulation this coupling step
State%dEta_dt = 0.0
State%precipType_ele = 0.0
State%precipNFlux = 0.0
State%precipEFlux = 0.0
!State%precipNFlux = 0.0
!State%precipEFlux = 0.0
State%CCHeatFlux = 0.0
! initialize all precip fluxes to zero and masks to false.
do k=1,Grid%Nk
State%precipNFlux(k)%data = 0.0
State%precipEFlux(k)%data = 0.0
State%precipNFlux(k)%mask = .false.
State%precipEFlux(k)%mask = .false.
enddo
end subroutine updateRaiLosses
@@ -221,8 +229,12 @@ module raijulosses
deleta = eta0*(1.0-exp(-dt*State%lossRatesPrecip(i,j,k)))
pNFlux = deleta2NFlux(deleta, Model%planet%rp_m, Grid%Brcc(i,j), dt)
! Just accumulate total #/cm2 and erg/cm2, we divide by coupling dt at the end of advance
State%precipNFlux(i,j,k) = State%precipNFlux(i,j,k) + pNFlux*dt
State%precipEFlux(i,j,k) = State%precipEFlux(i,j,k) + nFlux2EFlux(pNFlux, Grid%alamc(k), State%bVol_cc(i,j))
!State%precipNFlux(i,j,k) = State%precipNFlux(i,j,k) + pNFlux*dt
!State%precipEFlux(i,j,k) = State%precipEFlux(i,j,k) + nFlux2EFlux(pNFlux, Grid%alamc(k), State%bVol_cc(i,j))
State%precipNFlux(k)%data(i,j) = State%precipNFlux(k)%data(i,j) + pNFlux*dt
State%precipEFlux(k)%data(i,j) = State%precipEFlux(k)%data(i,j) + nFlux2EFlux(pNFlux, Grid%alamc(k), State%bVol_cc(i,j))
State%precipNFlux(k)%mask(i,j) = .true.
State%precipEFlux(k)%mask(i,j) = .true.
! Do special stuff for Coulomb collision effects
if (Model%doCC .and. State%lps(State%lp_cc_idx)%p%isValidSpc(Grid%spc(Grid%k2spc(k)))) then

View File

@@ -258,14 +258,17 @@ submodule (volttypes) raijuCplTypesSub
call InterpShellVar_TSC_pnt(sh, State%Press(s), th, ph, p_hot)
imP(RAI_EPRE ) = imP(RAI_EPRE ) + p_hot*1.0e-9 ! uStr="nPa" -> Pa , dStr="Pressure from RAIJU flavors"
do k=ks,ke
if(.not. isnan(State%precipNFlux(i0,j0,k))) then
!if(.not. isnan(State%precipNFlux(i0,j0,k))) then
if(.not. isnan(State%precipNFlux(k)%data(i0,j0))) then ! use mask?
! need to turn precipNFlux and precipEFlux into a shell grid variable.
! now assumes nearest neighbor interpolation.
!call InterpShellVar_TSC_pnt(sh, State%precipNFlux(i0,j0,k), th, ph, dn_flux)
dn_flux = State%precipNFlux(i0,j0,k)
! refer to: call InterpShellVar_TSC_pnt(sh, State%Press(s), th, ph, p_hot)
!dn_flux = State%precipNFlux(i0,j0,k)
call InterpShellVar_TSC_pnt(sh, State%precipNFlux(k), th, ph, dn_flux)
imP(RAI_ENFLX) = imP(RAI_ENFLX) + dn_flux ! uStr="#/cm^2/s"
!call InterpShellVar_TSC_pnt(sh, State%precipEFlux(i0,j0,k), th, ph, de_flux)
de_flux = State%precipEFlux(i0,j0,k)
!de_flux = State%precipEFlux(i0,j0,k)
call InterpShellVar_TSC_pnt(sh, State%precipEFlux(k), th, ph, de_flux)
imP(RAI_EFLUX) = imP(RAI_EFLUX) + de_flux ! uStr="erg/cm^2/s"
endif
enddo