Merged in deterministicRaiju (pull request #33)

DeterministicRaiju

Approved-by: Anthony Sciola
Approved-by: ksorathia
This commit is contained in:
Jeff
2025-08-18 20:40:15 +00:00
24 changed files with 363 additions and 78 deletions

View File

@@ -106,7 +106,7 @@ module shellInterp
case(SHGR_CC)
!$OMP PARALLEL DO default(shared) &
!$OMP schedule(dynamic) &
!$OMP private(i,j)
!$OMP private(i,j,goodInterp)
do j=sgDest%jsg,sgDest%jeg
do i=sgDest%isg,sgDest%ieg
if (.not. varOut%mask(i,j)) cycle
@@ -125,7 +125,7 @@ module shellInterp
case(SHGR_CORNER)
!$OMP PARALLEL DO default(shared) &
!$OMP schedule(dynamic) &
!$OMP private(i,j)
!$OMP private(i,j,goodinterp)
do j=sgDest%jsg,sgDest%jeg+1
do i=sgDest%isg,sgDest%ieg+1
if (.not. varOut%mask(i,j)) cycle
@@ -142,7 +142,7 @@ module shellInterp
case(SHGR_FACE_THETA)
!$OMP PARALLEL DO default(shared) &
!$OMP schedule(dynamic) &
!$OMP private(i,j)
!$OMP private(i,j,goodInterp)
do j=sgDest%jsg,sgDest%jeg
do i=sgDest%isg,sgDest%ieg+1
if (.not. varOut%mask(i,j)) cycle
@@ -159,7 +159,7 @@ module shellInterp
case(SHGR_FACE_PHI)
!$OMP PARALLEL DO default(shared) &
!$OMP schedule(dynamic) &
!$OMP private(i,j)
!$OMP private(i,j,goodInterp)
do j=sgDest%jsg,sgDest%jeg+1
do i=sgDest%isg,sgDest%ieg
if (.not. varOut%mask(i,j)) cycle

View File

@@ -413,7 +413,8 @@ module gioH5
!Write current
if (Model%isMagsphere) then
!Subtract dipole before calculating current
!$OMP PARALLEL DO default(shared) collapse(2)
!$OMP PARALLEL DO default(shared) collapse(2) &
!$OMP private(i,j,k)
do k=Gr%ksg,Gr%keg
do j=Gr%jsg,Gr%jeg
do i=Gr%isg,Gr%ieg
@@ -440,7 +441,8 @@ module gioH5
if (doFat) then
!Divide by edge-length to go from potential to field
!$OMP PARALLEL DO default(shared) collapse(2)
!$OMP PARALLEL DO default(shared) collapse(2) &
!$OMP private(i,j,k)
do k=Gr%ksg,Gr%keg
do j=Gr%jsg,Gr%jeg
do i=Gr%isg,Gr%ieg
@@ -465,19 +467,19 @@ module gioH5
if (Model%doSource .and. Model%isMagsphere) then
!Volt variables
call GameraOut("SrcX1" ,"deg",rad2deg,Gr%Gas0(Gr%is:Gr%ie,Gr%js:Gr%je,Gr%ks:Gr%ke,PROJLAT))
call GameraOut("SrcX2" ,"deg",rad2deg,Gr%Gas0(Gr%is:Gr%ie,Gr%js:Gr%je,Gr%ks:Gr%ke,PROJLON))
call GameraOut("SrcX1" ,"deg",rad2deg,Gr%Gas0(iMin:iMax,jMin:jMax,kMin:kMax,PROJLAT))
call GameraOut("SrcX2" ,"deg",rad2deg,Gr%Gas0(iMin:iMax,jMin:jMax,kMin:kMax,PROJLON))
call GameraOut("SrcIONEx" ,gamOut%eID,gamOut%eScl,Gr%Gas0(Gr%is:Gr%ie,Gr%js:Gr%je,Gr%ks:Gr%ke,IONEX))
call GameraOut("SrcIONEy" ,gamOut%eID,gamOut%eScl,Gr%Gas0(Gr%is:Gr%ie,Gr%js:Gr%je,Gr%ks:Gr%ke,IONEY))
call GameraOut("SrcIONEz" ,gamOut%eID,gamOut%eScl,Gr%Gas0(Gr%is:Gr%ie,Gr%js:Gr%je,Gr%ks:Gr%ke,IONEZ))
call GameraOut("SrcIONEx" ,gamOut%eID,gamOut%eScl,Gr%Gas0(iMin:iMax,jMin:jMax,kMin:kMax,IONEX))
call GameraOut("SrcIONEy" ,gamOut%eID,gamOut%eScl,Gr%Gas0(iMin:iMax,jMin:jMax,kMin:kMax,IONEY))
call GameraOut("SrcIONEz" ,gamOut%eID,gamOut%eScl,Gr%Gas0(iMin:iMax,jMin:jMax,kMin:kMax,IONEZ))
!IMAG variables
call GameraOut("SrcD_RING" ,gamOut%dID,gamOut%dScl,Gr%Gas0(Gr%is:Gr%ie,Gr%js:Gr%je,Gr%ks:Gr%ke,IM_D_RING))
call GameraOut("SrcP_RING" ,gamOut%pID,gamOut%pScl,Gr%Gas0(Gr%is:Gr%ie,Gr%js:Gr%je,Gr%ks:Gr%ke,IM_P_RING))
call GameraOut("SrcD_COLD" ,gamOut%dID,gamOut%dScl,Gr%Gas0(Gr%is:Gr%ie,Gr%js:Gr%je,Gr%ks:Gr%ke,IM_D_COLD))
call GameraOut("SrcP_COLD" ,gamOut%pID,gamOut%pScl,Gr%Gas0(Gr%is:Gr%ie,Gr%js:Gr%je,Gr%ks:Gr%ke,IM_P_COLD))
call GameraOut("SrcDT" ,"s" ,gamOut%tScl,Gr%Gas0(Gr%is:Gr%ie,Gr%js:Gr%je,Gr%ks:Gr%ke,IM_TSCL ))
call GameraOut("SrcD_RING" ,gamOut%dID,gamOut%dScl,Gr%Gas0(iMin:iMax,jMin:jMax,kMin:kMax,IM_D_RING))
call GameraOut("SrcP_RING" ,gamOut%pID,gamOut%pScl,Gr%Gas0(iMin:iMax,jMin:jMax,kMin:kMax,IM_P_RING))
call GameraOut("SrcD_COLD" ,gamOut%dID,gamOut%dScl,Gr%Gas0(iMin:iMax,jMin:jMax,kMin:kMax,IM_D_COLD))
call GameraOut("SrcP_COLD" ,gamOut%pID,gamOut%pScl,Gr%Gas0(iMin:iMax,jMin:jMax,kMin:kMax,IM_P_COLD))
call GameraOut("SrcDT" ,"s" ,gamOut%tScl,Gr%Gas0(iMin:iMax,jMin:jMax,kMin:kMax,IM_TSCL ))
endif

View File

@@ -112,7 +112,7 @@ module mhdgroup
call Tic("Reynolds")
!$OMP PARALLEL DO default(shared) collapse(2) &
!$OMP private(U,dPg)
!$OMP private(i,j,k,U,dPg)
do k=Grid%ks,Grid%ke
do j=Grid%js,Grid%je
do i=Grid%is,Grid%ie
@@ -169,7 +169,7 @@ module mhdgroup
call Tic("Maxwell")
!$OMP PARALLEL DO default(shared) collapse(2) &
!$OMP private(U,oU,B,oB,dPg,dPm)
!$OMP private(i,j,k,U,oU,B,oB,dPg,dPm)
do k=Grid%ks,Grid%ke
do j=Grid%js,Grid%je
do i=Grid%is,Grid%ie
@@ -225,7 +225,8 @@ module mhdgroup
!Let's goddamn do this thing w/ interleaved memory copies
!Open one big-ass // block
!$OMP PARALLEL default(shared)
!$OMP PARALLEL default(shared) &
!$OMP private(i,j,k)
!$OMP DO collapse(2)
do k=Grid%ksg,Grid%keg

View File

@@ -360,6 +360,7 @@ module gamapp_mpi
! print *, 'Over-writing min I BC to be an MPI BC'
deallocate(Grid%externalBCs(INI)%p)
allocate(Grid%externalBCs(INI)%p,source=mpiNullBc_T(INI))
Grid%isDT = Grid%is
endif
END SELECT
@@ -377,6 +378,7 @@ module gamapp_mpi
! print *, 'Over-writing max I BC to be an MPI BC'
deallocate(Grid%externalBCs(OUTI)%p)
allocate(Grid%externalBCs(OUTI)%p,source=mpiNullBc_T(OUTI))
Grid%ieDT = Grid%ie
endif
END SELECT
@@ -399,6 +401,7 @@ module gamapp_mpi
! print *, 'Over-writing min J BC to be an MPI BC'
deallocate(Grid%externalBCs(INJ)%p)
allocate(Grid%externalBCs(INJ)%p,source=mpiNullBc_T(INJ))
Grid%jsDT = Grid%js
endif
END SELECT
@@ -416,6 +419,7 @@ module gamapp_mpi
! print *, 'Over-writing max J BC to be an MPI BC'
deallocate(Grid%externalBCs(OUTJ)%p)
allocate(Grid%externalBCs(OUTJ)%p,source=mpiNullBc_T(OUTJ))
Grid%jeDT = Grid%je
endif
END SELECT
@@ -438,6 +442,7 @@ module gamapp_mpi
! print *, 'Over-writing min K BC to be an MPI BC'
deallocate(Grid%externalBCs(INK)%p)
allocate(Grid%externalBCs(INK)%p,source=mpiNullBc_T(INK))
Grid%ksDT = Grid%ks
endif
END SELECT
@@ -455,6 +460,7 @@ module gamapp_mpi
! print *, 'Over-writing max K BC to be an MPI BC'
deallocate(Grid%externalBCs(OUTK)%p)
allocate(Grid%externalBCs(OUTK)%p,source=mpiNullBc_T(OUTK))
Grid%keDT = Grid%ke
endif
END SELECT
@@ -671,11 +677,13 @@ module gamapp_mpi
call Toc("Sync Math")
endif
!Update BCs MPI style
call updateMpiBCs(gamAppMpi, gamAppmpi%State)
!Calculate new timestep
call CalcDT_mpi(gamAppMpi)
! *** THIS MUST BE BEFORE updateMpiBCs
! *** CalcDT can adjust cell values via CPR and other emergency correction schemes
!Update BCs MPI style
call updateMpiBCs(gamAppMpi, gamAppmpi%State)
end subroutine stepGamera_mpi

View File

@@ -119,7 +119,7 @@ module raijuBCs
eleIdx = spcIdx(Grid, F_HOTE)
!$OMP PARALLEL DO default(shared) &
!$OMP schedule(dynamic) &
!$OMP private(i,j,s,fIdx,fm,vm,kT,etaBelow,tmp_kti,tmp_kte,tmp_D,tmp_P)
!$OMP private(i,j,s,fIdx,fm,vm,kT,etaBelow,tmp_kti,tmp_kte,eMin,tmp_D,tmp_P)
do j=Grid%shGrid%jsg,Grid%shGrid%jeg
do i=Grid%shGrid%isg,Grid%shGrid%ieg
if (State%active(i,j) .eq. RAIJUINACTIVE) then
@@ -309,4 +309,4 @@ module raijuBCs
end subroutine setActiveShellsByContribution
end module raijuBCs
end module raijuBCs

View File

@@ -5,6 +5,7 @@ module raijustarter
use shellgrid
use xml_input
use planethelper
use arrayutil
! Raiju
use raijudefs
@@ -382,71 +383,116 @@ module raijustarter
! dt for every lambda channel
allocate( State%dtk (Grid%Nk) )
call fillArray(State%dtk, 0.0_rp)
! nSteps for each channel
allocate( State%nStepk(Grid%Nk) )
call fillArray(State%nStepk, 0)
! Where we keep all our stuff
allocate( State%eta (sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
call fillArray(State%eta, 0.0_rp)
! Where we keep all our stuff but a half-step ahead of now
allocate( State%eta_half (sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
call fillArray(State%eta_half, 0.0_rp)
! Where we kept all our stuff one step ago
allocate( State%eta_last (sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
call fillArray(State%eta_last, 0.0_rp)
! Where all the stuff sorta was over the last State%dt
allocate( State%eta_avg (sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
call fillArray(State%eta_avg, 0.0_rp)
! I shells shat should be evolved for each k
allocate( State%activeShells (sh%isg:sh%ieg, Grid%Nk) )
State%activeShells = .false.
! Effective potential (used for output only)
allocate( State%pEff(sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1, Grid%Nk) )
call fillArray(State%pEff, 0.0_rp)
! Gradient of ionspheric potential
allocate( State%gradPotE (sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1, 2) )
call fillArray(State%gradPotE, 0.0_rp)
! Gradient of corotation potential
allocate( State%gradPotCorot (sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1, 2) )
call fillArray(State%gradPotCorot, 0.0_rp)
! Gradient of (flux tube volume ^ -2/3)
allocate( State%gradVM (sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1, 2) )
call fillArray(State%gradVM, 0.0_rp)
! Interface and cell velocities
allocate( State%gradPotE_cc (sh%isg:sh%ieg, sh%jsg:sh%jeg, 2) )
call fillArray(State%gradPotE_cc, 0.0_rp)
allocate( State%gradPotCorot_cc(sh%isg:sh%ieg, sh%jsg:sh%jeg, 2) )
call fillArray(State%gradPotCorot_cc, 0.0_rp)
allocate( State%gradVM_cc (sh%isg:sh%ieg, sh%jsg:sh%jeg, 2) )
call fillArray(State%gradVM_cc, 0.0_rp)
allocate( State%iVel (sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1, Grid%Nk, 2) )
call fillArray(State%iVel, 0.0_rp)
allocate( State%iVelL(sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1, Grid%Nk, 2) )
call fillArray(State%iVelL, 0.0_rp)
allocate( State%iVelR(sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1, Grid%Nk, 2) )
call fillArray(State%iVelR, 0.0_rp)
allocate( State%cVel (sh%isg:sh%ieg , sh%jsg:sh%jeg , Grid%Nk, 2) )
call fillArray(State%cVel, 0.0_rp)
! Coupling input moments
allocate( State%Pavg(sh%isg:sh%ieg , sh%jsg:sh%jeg, 0:Grid%nFluidIn) )
call fillArray(State%Pavg, 0.0_rp)
allocate( State%Davg(sh%isg:sh%ieg , sh%jsg:sh%jeg, 0:Grid%nFluidIn) )
call fillArray(State%Davg, 0.0_rp)
allocate( State%Pstd(sh%isg:sh%ieg , sh%jsg:sh%jeg, 0:Grid%nFluidIn) )
call fillArray(State%Pstd, 0.0_rp)
allocate( State%Dstd(sh%isg:sh%ieg , sh%jsg:sh%jeg, 0:Grid%nFluidIn) )
call fillArray(State%Dstd, 0.0_rp)
allocate( State%domWeights(sh%isg:sh%ieg , sh%jsg:sh%jeg) )
call fillArray(State%domWeights, 0.0_rp)
allocate( State%tiote(sh%isg:sh%ieg , sh%jsg:sh%jeg) )
call fillArray(State%tiote, 0.0_rp)
call initShellVar(Grid%shGrid, SHGR_CC, State%Tb)
State%Tb%data = 0.0
State%Tb%mask = .false.
! Bmin surface
allocate( State%Bmin (sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1, 3 ) )
call fillArray(State%Bmin, 0.0_rp)
allocate( State%xyzMin (sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1, 3 ) )
call fillArray(State%xyzMin, 0.0_rp)
allocate( State%xyzMincc(sh%isg:sh%ieg , sh%jsg:sh%jeg , 3 ) )
call fillArray(State%xyzMincc, 0.0_rp)
allocate( State%thcon (sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1 ) )
call fillArray(State%thcon, 0.0_rp)
allocate( State%phcon (sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1 ) )
call fillArray(State%phcon, 0.0_rp)
! 2D corner quantities
allocate( State%topo (sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1) )
call fillArray(State%topo, 0)
allocate( State%espot (sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1) )
call fillArray(State%espot, 0.0_rp)
allocate( State%pot_corot(sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1) )
call fillArray(State%pot_corot, 0.0_rp)
allocate( State%bvol (sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1) )
call fillArray(State%bvol, 0.0_rp)
allocate( State%bvol_cc (sh%isg:sh%ieg , sh%jsg:sh%jeg ) )
call fillArray(State%bvol_cc, 0.0_rp)
allocate( State%vaFrac (sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1) )
call fillArray(State%vaFrac, 0.0_rp)
! 1D cell-centered quantities
allocate( State%bndLoc(sh%jsg:sh%jeg) )
call fillArray(State%bndLoc, 0)
! 2D cell-centered quantities
allocate( State%active (sh%isg:sh%ieg, sh%jsg:sh%jeg) )
call fillArray(State%active, 0)
allocate( State%active_last (sh%isg:sh%ieg, sh%jsg:sh%jeg) )
call fillArray(State%active_last, 0)
allocate( State%OCBDist(sh%isg:sh%ieg, sh%jsg:sh%jeg) )
call fillArray(State%OCBDist, 0)
allocate( State%lossRates (sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
call fillArray(State%lossRates, 0.0_rp)
allocate( State%precipType_ele (sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
call fillArray(State%precipType_ele, 0.0_rp)
allocate( State%lossRatesPrecip(sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
call fillArray(State%lossRatesPrecip, 0.0_rp)
!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) )
call fillArray(State%dEta_dt, 0.0_rp)
allocate( State%CCHeatFlux (sh%isg:sh%ieg, sh%jsg:sh%jeg, Grid%Nk) )
call fillArray(State%CCHeatFlux, 0.0_rp)
! Coupling output data
allocate(State%Den (0:Model%nSpc))
allocate(State%Press(0:Model%nSpc))
@@ -481,10 +527,15 @@ module raijustarter
! Only bother allocating persistent versions of debug stuff if we need them
if (Model%doOutput_debug) then
allocate( State%etaFaceReconL(sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1, Grid%Nk, 2) )
call fillArray(State%etaFaceReconL, 0.0_rp)
allocate( State%etaFaceReconR(sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1, Grid%Nk, 2) )
call fillArray(State%etaFaceReconR, 0.0_rp)
allocate( State%etaFacePDML (sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1, Grid%Nk, 2) )
call fillArray(State%etaFacePDML, 0.0_rp)
allocate( State%etaFacePDMR (sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1, Grid%Nk, 2) )
call fillArray(State%etaFacePDMR, 0.0_rp)
allocate( State%etaFlux (sh%isg:sh%ieg+1, sh%jsg:sh%jeg+1, Grid%Nk, 2) )
call fillArray(State%etaFlux, 0.0_rp)
endif
State%KpTS%wID = Model%tsF
@@ -492,7 +543,6 @@ module raijustarter
end associate
! For now, just set t to tStart and ts to 0
State%t = Model%t0
State%ts = 0

View File

@@ -29,6 +29,7 @@ module uservoltic
real(rp), private :: Rho0,P0
real(rp), private :: Kp0
logical , private :: doPP0 !Use MF starter plasmasphere
logical , private :: writeBCData ! Whether to write IC BC data
! type for remix BC
type, extends(innerIBC_T) :: IonInnerBC_T
@@ -58,6 +59,7 @@ module uservoltic
procedure(HackStep_T), pointer :: tsHack
procedure(HackSaveRestart_T), pointer :: saveResHack
procedure(HackLoadRestart_T), pointer :: loadResHack
procedure(HackIO_T), pointer :: saveIOHack
real(rp) :: M0g
integer :: s,s0
@@ -68,10 +70,12 @@ module uservoltic
tsHack => NULL()
saveResHack => NULL()
loadResHack => NULL()
saveIOHack => NULL()
Model%HackE => eHack
Model%HackStep => tsHack
Model%HackSaveRestart => saveResHack
Model%HackLoadRestart => loadResHack
Model%HackIO => saveIOHack
!Get defaults from input deck
@@ -79,6 +83,7 @@ module uservoltic
call inpXML%Set_Val(Rho0 ,"prob/Rho0",0.2_rp)
call inpXML%Set_Val(P0 ,"prob/P0" ,0.001_rp)
call inpXML%Set_Val(doPP0,"prob/doPP0",.false.)
call inpXML%Set_Val(writeBCData,"prob/writeBC",.false.)
!Set magnetosphere parameters
call setMagsphere(Model,inpXML)
@@ -159,6 +164,9 @@ module uservoltic
Model%HackLoadRestart => loadResHack
saveResHack => SaveUserRes
Model%HackSaveRestart => saveResHack
saveIOHack => SaveUserIO
Model%HackIO => saveIOHack
!Local functions
!NOTE: Don't put BCs here as they won't be visible after the initialization call
@@ -603,13 +611,13 @@ module uservoltic
nbc = FindBC(Model,Grid,INI)
SELECT type(iiBC=>Grid%externalBCs(nbc)%p)
TYPE IS (IonInnerBC_T)
if(ioExist(inH5,"inEijk")) then
if(ioExist(inH5,"_inEijk")) then
call ClearIO(IOVars)
call AddInVar(IOVars,"inEijk")
call AddInVar(IOVars,"inExyz")
call AddInVar(IOVars,"_inEijk")
call AddInVar(IOVars,"_inExyz")
call ReadVars(IOVars,.false.,inH5)
call IOArray4DFill(IOVars, "inEijk", iiBC%inEijk(:,:,:,:) )
call IOArray4DFill(IOVars, "inExyz", iiBC%inExyz(:,:,:,:) )
call IOArray4DFill(IOVars, "_inEijk", iiBC%inEijk(:,:,:,:) )
call IOArray4DFill(IOVars, "_inExyz", iiBC%inExyz(:,:,:,:) )
endif
CLASS DEFAULT
! do nothing on gamera ranks without this BC
@@ -627,18 +635,47 @@ module uservoltic
integer :: nbc
if (.not. writeBCData) return
if ( Grid%hasLowerBC(IDIR) ) then
nbc = FindBC(Model,Grid,INI)
SELECT type(iiBC=>Grid%externalBCs(nbc)%p)
TYPE IS (IonInnerBC_T)
call AddOutVar(IOVars, "inEijk", iiBC%inEijk(:,:,:,:) )
call AddOutVar(IOVars, "inExyz", iiBC%inExyz(:,:,:,:) )
call AddOutVar(IOVars, "_inEijk", iiBC%inEijk(:,:,:,:) )
call AddOutVar(IOVars, "_inExyz", iiBC%inExyz(:,:,:,:) )
CLASS DEFAULT
! do nothing on gamera ranks without this BC
END SELECT
endif
end subroutine SaveUserRes
subroutine SaveUserIO(Model,Grid,State,IOVars)
class(Model_T), intent(in) :: Model
class(Grid_T) , intent(in) :: Grid
class(State_T), intent(in) :: State
type(IOVAR_T), dimension(:), intent(inout) :: IOVars
integer :: nbc
if (.not. writeBCData) return
if ( Grid%hasLowerBC(IDIR) ) then
nbc = FindBC(Model,Grid,INI)
SELECT type(iiBC=>Grid%externalBCs(nbc)%p)
TYPE IS (IonInnerBC_T)
if (writeGhosts) then
!call AddOutVar(IOVars, "_inEijk", iiBC%inEijk(:,:,:,:) )
call AddOutVar(IOVars, "_inExyz", iiBC%inExyz(:,:,:,:) )
else
!call AddOutVar(IOVars, "_inEijk", iiBC%inEijk(:,Grid%js:Grid%je+1,Grid%ks:Grid%ke+1,:) )
call AddOutVar(IOVars, "_inExyz", iiBC%inExyz(:,Grid%js:Grid%je,Grid%ks:Grid%ke,:) )
endif
CLASS DEFAULT
! do nothing on gamera ranks without this BC
END SELECT
endif
end subroutine SaveUserIO
end module uservoltic

View File

@@ -286,17 +286,21 @@ module imag2mhd_interface
integer :: i,j,k,ip,jp,kp
logical :: isActive
!$OMP PARALLEL DO default(shared) collapse(2) &
!$OMP private(i,j,k,isActive,ip,jp,kp)
!!$OMP PARALLEL DO default(shared) collapse(2) &
!!$OMP private(i,j,k,isActive,ip,jp,kp)
! this causes a race condition copying values between ghost cells
! probably a false positive since some of the cells are just copying
! values onto themselves, but easier to remove for now
do k=Gr%ksg,Gr%keg
do j=Gr%jsg,Gr%jeg
do i=Gr%isg,Gr%ieg
isActive = (j >= Gr%js) .and. (j <= Gr%je) .and. &
(k >= Gr%ks) .and. (k <= Gr%ks)
if (isActive) cycle
!If still here map this ghost to active and set value based on active
call lfmIJKcc(Model,Gr,i,j,k,ip,jp,kp)
Q(i,j,k) = Q(ip,jp,kp)
if(.not. isActive) then
!If still here map this ghost to active and set value based on active
call lfmIJKcc(Model,Gr,i,j,k,ip,jp,kp)
Q(i,j,k) = Q(ip,jp,kp)
endif
enddo
enddo !j
enddo !k

View File

@@ -360,7 +360,12 @@ def main():
)
if debug:
print(f"slack_response_summary = {slack_response_summary}")
# Also write a summary file to the root folder of this test
with open(os.path.join(MAGE_TEST_SET_ROOT,'testSummary.out'), 'w', encoding='utf-8') as f:
f.write(test_report_details_string)
f.write('\n')
# ------------------------------------------------------------------------
if debug:

View File

@@ -378,7 +378,12 @@ def main():
)
if debug:
print(f"slack_response_summary = {slack_response_summary}")
# Also write a summary file to the root folder of this test
with open(os.path.join(MAGE_TEST_SET_ROOT,'testSummary.out'), 'w', encoding='utf-8') as f:
f.write(test_report_details_string)
f.write('\n')
# ------------------------------------------------------------------------
if debug:

View File

@@ -41,6 +41,9 @@ from kaipy import kaiH5
# Program description.
DESCRIPTION = "Compare MAGE model runs numerically."
# Root of directory tree for this set of tests.
MAGE_TEST_SET_ROOT = os.environ['MAGE_TEST_SET_ROOT']
# Strings to represent test pass and fail.
TEST_PASS = "PASS"
TEST_FAIL = "FAIL"
@@ -482,7 +485,12 @@ def compare_mage_runs_numerical(args: dict):
slack_client, test_report_details_string, thread_ts=thread_ts,
is_test=test
)
# Also write a summary file to the root folder of this test
with open(os.path.join(MAGE_TEST_SET_ROOT,'testSummary.out'), 'w', encoding='utf-8') as f:
f.write(test_report_details_string)
f.write('\n')
# ------------------------------------------------------------------------
if debug:

View File

@@ -52,6 +52,7 @@ export TMPDIR={{ tmpdir }}
export SLACK_BOT_TOKEN={{ slack_bot_token }}
export DERECHO_TESTING_ACCOUNT={{ account }}
export BRANCH_OR_COMMIT={{ branch_or_commit }}
export MAGE_TEST_SET_ROOT={{ mage_test_set_root }}
echo 'The active environment variables are:'
printenv

View File

@@ -378,6 +378,8 @@ def intelChecks(args: dict):
pbs_options["slack_bot_token"] = os.environ["SLACK_BOT_TOKEN"]
pbs_options["mage_test_root"] = os.environ["MAGE_TEST_ROOT"]
pbs_options["branch_or_commit"] = BRANCH_OR_COMMIT
pbs_options["mage_test_set_root"] = os.environ["MAGE_TEST_SET_ROOT"]
pbs_options["conda_environment"] = os.environ["CONDA_ENVIRONMENT"]
# Set options specific to the memory check, then render the template.
pbs_options["job_name"] = "mage_intelCheckSubmitMem"

View File

@@ -35,6 +35,9 @@ DESCRIPTION = 'Create report for Intel Inspector tests.'
# Branch or commit (or tag) used for testing.
BRANCH_OR_COMMIT = os.environ['BRANCH_OR_COMMIT']
# Root of directory tree for this set of tests.
MAGE_TEST_SET_ROOT = os.environ["MAGE_TEST_SET_ROOT"]
def main():
"""Begin main program.
@@ -255,7 +258,12 @@ def main():
)
if debug:
print(f"slack_response_summary = {slack_response_summary}")
# Also write a summary file to the root folder of this test
with open(os.path.join(MAGE_TEST_SET_ROOT,'testSummary.out'), 'w', encoding='utf-8') as f:
f.write(test_report_details_string)
f.write('\n')
# ------------------------------------------------------------------------
if debug:

View File

@@ -19,22 +19,27 @@ module load {{ module }}
echo 'The currently loaded modules are:'
module list
echo 'Loading python environment.'
export CONDARC="{{ condarc }}"
export CONDA_ENVS_PATH="{{ conda_envs_path }}"
mage_miniconda3="{{ mage_test_root }}/miniconda3"
mage_conda="${mage_miniconda3}/bin/conda"
__conda_setup="$($mage_conda 'shell.bash' 'hook' 2> /dev/null)"
if [ $? -eq 0 ]; then
eval "$__conda_setup"
else
if [ -f "$mage_miniconda3/etc/profile.d/conda.sh" ]; then
. "$mage_miniconda3/etc/profile.d/conda.sh"
if [ -d "${mage_test_root}/miniconda3" ]; then
echo 'Loading local miniconda3'
export CONDARC="{{ condarc }}"
export CONDA_ENVS_PATH="{{ conda_envs_path }}"
mage_miniconda3="{{ mage_test_root }}/miniconda3"
mage_conda="${mage_miniconda3}/bin/conda"
__conda_setup="$($mage_conda 'shell.bash' 'hook' 2> /dev/null)"
if [ $? -eq 0 ]; then
eval "$__conda_setup"
else
export PATH="$mage_miniconda3/bin:$PATH"
if [ -f "$mage_miniconda3/etc/profile.d/conda.sh" ]; then
. "$mage_miniconda3/etc/profile.d/conda.sh"
else
export PATH="$mage_miniconda3/bin:$PATH"
fi
fi
unset __conda_setup
else
echo 'Loading conda module'
module load conda
fi
unset __conda_setup
conda activate {{ conda_environment }}
echo "The current conda environment is ${CONDA_PREFIX}."

View File

@@ -218,6 +218,7 @@ def mage_reproducibility_check(args: dict):
"cda2wind.py -t0 2016-08-09T02:00:00 -t1 2016-08-09T12:00:00"
)
genRCM_cmd = "genRCM.py"
genRaiju_cmd = "genRAIJU.py"
mpiexec_cmd = f"mpiexec {KAIJUHOME}/scripts/preproc/pinCpuCores.sh"
voltron_cmd = "../bin/voltron_mpi.x weeklyDashGo.xml"
@@ -255,6 +256,7 @@ def mage_reproducibility_check(args: dict):
pbs_options["genLFM_cmd"] = genLFM_cmd
pbs_options["cda2wind_cmd"] = cda2wind_cmd
pbs_options["genRCM_cmd"] = genRCM_cmd
pbs_options["genRaiju_cmd"] = genRaiju_cmd
pbs_options["mpiexec_cmd"] = mpiexec_cmd
pbs_options["voltron_cmd"] = voltron_cmd

View File

@@ -165,6 +165,20 @@ Suppression = {
}
}
Suppression = {
Name = "MPI-related gamera initialization False Positive";
Type = { uninitialized_memory_access }
Stacks = {
{
...;
func=writeh5res, src=gioH5.F90;
}
allocation = {
func=voltron_mpix, src=voltron_mpix.F90;
}
}
}
Suppression = {
Name = "MPI-related gamera initialization False Positive";
Type = { uninitialized_memory_access }

View File

@@ -56,5 +56,8 @@ printenv
# Process the data and generate the output video
python $KAIPYHOME/kaipy/scripts/quicklook/gamerrVid.py -d1 {{ case1F }} -id1 {{ case1id }} -d2 {{ case2F }} -id2 {{ case2id }} -o {{ frameFolder }}/{{ caseName }} -ts {{ ts }} -te {{ te }} -dt {{ dt }} -Nth 9 >& {{ caseName }}.out
# copy output video to test root folder
cp {{ frameFolder }}/{{ caseName }}.mp4 $MAGE_TEST_SET_ROOT/.
echo "Job $PBS_JOBID ended at `date` on `hostname` in directory `pwd`."

View File

@@ -60,6 +60,10 @@ def create_command_line_parser():
"--intelChecks", action='store_true',default=False,
help="Run Intel Inspector memory and thread check tests (default: %(default)s)."
)
parser.add_argument(
"--reproTests", action='store_true',default=False,
help="Run reproducibility tests (default: %(default)s)."
)
parser.add_argument(
"--all", action='store_true',default=False,
@@ -114,6 +118,10 @@ def main():
os.environ['MAGE_TEST_SET_ROOT'] = os.path.join(os.environ['MAGE_TEST_RUNS_ROOT'],test_set_dir)
os.makedirs(os.environ['MAGE_TEST_SET_ROOT'], exist_ok=True)
os.chdir(os.environ['MAGE_TEST_SET_ROOT'])
os.environ['CONDARC'] = '' # these must be specified to avoid errors
os.environ['CONDA_ENVS_PATH'] = ''
os.environ['KAIPY_PRIVATE_ROOT'] = os.environ['KAIPYHOME'] # some scripts use this alternate
print(f"Running tests on branch {gitBranch}")
print(f"Using charge code {args.A} with priority {args.p}")
@@ -128,6 +136,7 @@ def main():
args.buildTests = True
args.icTests = True
args.intelChecks = True
args.reproTests = True
if args.compTestsFull:
args.compTests = False
@@ -154,6 +163,9 @@ def main():
if args.intelChecks:
print("Running memory and thread tests")
subprocess.call(['python', os.path.join(os.environ['MAGE_TEST_ROOT'],'testingScripts','intelChecks.py'),'-tv'])
if args.reproTests:
print("Running reproducibility tests")
subprocess.call(['python', os.path.join(os.environ['MAGE_TEST_ROOT'],'testingScripts','mage_reproducibility_check.py'),'-tv'])
if __name__ == "__main__":
main()

View File

@@ -19,22 +19,27 @@ module load {{ module }}
echo 'The currently loaded modules are:'
module list
echo 'Loading python environment.'
export CONDARC="{{ condarc }}"
export CONDA_ENVS_PATH="{{ conda_envs_path }}"
mage_miniconda3="{{ mage_test_root }}/miniconda3"
mage_conda="${mage_miniconda3}/bin/conda"
__conda_setup="$($mage_conda 'shell.bash' 'hook' 2> /dev/null)"
if [ $? -eq 0 ]; then
eval "$__conda_setup"
else
if [ -f "$mage_miniconda3/etc/profile.d/conda.sh" ]; then
. "$mage_miniconda3/etc/profile.d/conda.sh"
if [ -d "${mage_test_root}/miniconda3" ]; then
echo 'Loading local miniconda3'
export CONDARC="{{ condarc }}"
export CONDA_ENVS_PATH="{{ conda_envs_path }}"
mage_miniconda3="{{ mage_test_root }}/miniconda3"
mage_conda="${mage_miniconda3}/bin/conda"
__conda_setup="$($mage_conda 'shell.bash' 'hook' 2> /dev/null)"
if [ $? -eq 0 ]; then
eval "$__conda_setup"
else
export PATH="$mage_miniconda3/bin:$PATH"
if [ -f "$mage_miniconda3/etc/profile.d/conda.sh" ]; then
. "$mage_miniconda3/etc/profile.d/conda.sh"
else
export PATH="$mage_miniconda3/bin:$PATH"
fi
fi
unset __conda_setup
else
echo 'Loading conda module'
module load conda
fi
unset __conda_setup
conda activate {{ conda_environment }}
echo "The current conda environment is ${CONDA_PREFIX}."
@@ -69,10 +74,10 @@ echo 'Generating the solar wind boundary condition file.'
{{ cda2wind_cmd }}
echo "The solar wind boundary condition file is `ls bcwind.h5`."
# Generate the RCM configuration file.
echo 'Generating the RCM configuration file.'
{{ genRCM_cmd }}
echo "The RCM configuration file is `ls rcmconfig.h5`."
# Generate the Raiju configuration file.
echo 'Generating the Raiju configuration file.'
{{ genRaiju_cmd }}
echo "The Raiju configuration file is `ls raijuconfig.h5`."
# Run the model.
MPICOMMAND="{{ mpiexec_cmd }}"

View File

@@ -234,7 +234,12 @@ def main():
)
if debug:
print(f"slack_response_summary = {slack_response_summary}")
# Also write a summary file to the root folder of this test
with open(os.path.join(MAGE_TEST_SET_ROOT,'testSummary.out'), 'w', encoding='utf-8') as f:
f.write(test_report_details_string)
f.write('\n')
# ------------------------------------------------------------------------
if debug:

View File

@@ -0,0 +1,17 @@
<?xml version="1.0"?>
<Kaiju>
<Gamera>
<sim runid="blast3d_large2" doH5init="F" icType="BW" pdmb="4.0"/>
<idir min="-0.5" max="0.5" N="128"/>
<jdir min="-0.5" max="0.5" N="128"/>
<kdir min="-0.5" max="0.5" N="128"/>
<iPdir N="2" bcPeriodic="T"/>
<jPdir N="1" bcPeriodic="T"/>
<kPdir N="1" bcPeriodic="T"/>
<time tFin="1.0"/>
<output dtOut="0.01" tsOut="10"/>
<physics doMHD="F" do25D="T"/>
<coupling blockHalo="T"/>
<prob B0="0.1"/>>
</Gamera>
</Kaiju>

View File

@@ -1,7 +1,7 @@
<?xml version="1.0"?>
<Kaiju>
<Gamera>
<sim runid="blast3d_large" doH5init="F" icType="BW" pdmb="4.0"/>
<sim runid="blast3d_large8" doH5init="F" icType="BW" pdmb="4.0"/>
<idir min="-0.5" max="0.5" N="128"/>
<jdir min="-0.5" max="0.5" N="128"/>
<kdir min="-0.5" max="0.5" N="128"/>

View File

@@ -21,7 +21,7 @@ contains
end subroutine lastSerial
@test(npes=[8])
subroutine testBlast3D(this)
subroutine testBlast3D_8(this)
class (MpiTestMethod), intent(inout) :: this
type(gamAppMpi_T) :: gameraAppMpi
@@ -31,7 +31,7 @@ contains
gameraAppMpi%gOptions%userInitFunc => initUser
gameraAppMpi%gOptionsMpi%gamComm = getMpiF08Communicator(this)
xmlInp = New_XML_Input('blast3d_large.xml','Kaiju',.true.)
xmlInp = New_XML_Input('blast3d_large8.xml','Kaiju',.true.)
call gameraAppMpi%InitModel(xmlInp)
do while ((gameraAppMpi%Model%tFin - gameraAppMpi%Model%t) > 1e-15)
@@ -48,7 +48,98 @@ contains
end do
write(*,*) 'End time = ', gameraAppMpi%Model%t
end subroutine testBlast3D
end subroutine testBlast3D_8
@test(npes=[2])
subroutine testBlast3D_2(this)
class (MpiTestMethod), intent(inout) :: this
type(gamAppMpi_T) :: gameraAppMpi
type(XML_Input_T) :: xmlInp
call setMpiReal()
gameraAppMpi%gOptions%userInitFunc => initUser
gameraAppMpi%gOptionsMpi%gamComm = getMpiF08Communicator(this)
xmlInp = New_XML_Input('blast3d_large2.xml','Kaiju',.true.)
call gameraAppMpi%InitModel(xmlInp)
do while ((gameraAppMpi%Model%tFin - gameraAppMpi%Model%t) > 1e-15)
call stepGamera_mpi(gameraAppMpi)
if (gameraAppMpi%Model%IO%doConsole(gameraAppMpi%Model%t)) then
call consoleOutput(gameraAppMpi%Model,gameraAppMpi%Grid,gameraAppMpi%State)
endif
if (gameraAppMpi%Model%IO%doOutput(gameraAppMpi%Model%t)) then
call fOutput(gameraAppMpi%Model,gameraAppMpi%Grid,gameraAppMpi%State)
endif
end do
write(*,*) 'End time = ', gameraAppMpi%Model%t
end subroutine testBlast3D_2
!this test must be at the bottom so that the data is generated by the two tests above
@test(npes=[1])
subroutine compareBlastWaves(this)
class (MpiTestMethod), intent(inout) :: this
type(IOVAR_T), dimension(25) :: IOVars
real(rp), allocatable :: p8(:,:,:), p2(:,:,:)
integer :: i,j,k,ni,nj,nk,ni2,nj2,nk2
character(len=strLen) :: h5Str, gStr, errMsg
call setMpiReal()
h5Str = trim('blast')
gStr = '/Step#99'
call ClearIO(IOVars)
call AddInVar(IOVars,"P")
! manually read in the 2 parts of blast3d_large2 and also determine the size of the data
h5Str = 'blast3d_large2_0002_0001_0001_0000_0000_0000.gam.h5'
call ReadVars(IOVars,.false.,h5Str,gStr)
ni = 2*IOVars(1)%dims(1)
nj = IOVars(1)%dims(2)
nk = IOVars(1)%dims(3)
ni2 = ni/2
nj2 = nj/2
nk2 = nk/2
allocate(p2(ni,nj,nk))
allocate(p8(ni,nj,nk))
call IOArray3DFill(IOVars,"P",p2(1:ni2,:,:))
call ClearIO(IOVars)
call AddInVar(IOVars,"P")
h5Str = 'blast3d_large2_0002_0001_0001_0001_0000_0000.gam.h5'
call ReadVars(IOVars,.false.,h5Str,gStr)
call IOArray3DFill(IOVars,"P",p2(ni2+1:ni,:,:))
call ClearIO(IOVars)
! loop to read in the parts blast3d_large8
do i=1,2
do j=1,2
do k=1,2
call AddInVar(IOVars,"P")
write(h5Str,'(A,I0,A)') 'blast3d_large8_0002_0002_0002_000',i-1,'_0000_0000.gam.h5'
call ReadVars(IOVars,.false.,h5Str,gStr)
call IOArray3DFill(IOVars,"P",p8(1+(i-1)*ni2:i*ni2,1+(j-1)*nj2:j*nj2,1+(k-1)*nk2:k*nk2))
call ClearIO(IOVars)
enddo
enddo
enddo
! check values
do i=1,ni
do j=1,nj
do k=1,nk
write(errMsg,'(A,I0,A,I0,A,I0,A)') 'Blast wave values not equal at (',i,',',j,',',k,')'
@assertEqual(p2(i,j,k),p8(i,j,k),1e-12,trim(errMsg))
enddo
enddo
enddo
end subroutine compareBlastWaves
end module testCasesMpi