mirror of
https://github.com/JHUAPL/kaiju.git
synced 2026-01-09 18:57:53 -05:00
First pass at BaseApp'ing raijuApp. SA compiles, needs testing. Some poking at raijuCoupler_T.
This commit is contained in:
@@ -509,12 +509,12 @@ module shellGrid
|
||||
!! Deallocates any allocated memory
|
||||
type(ShellGrid_T), intent(inout) :: sh
|
||||
|
||||
deallocate(sh%th)
|
||||
deallocate(sh%ph)
|
||||
deallocate(sh%thc)
|
||||
deallocate(sh%phc)
|
||||
deallocate(sh%lat)
|
||||
deallocate(sh%latc)
|
||||
if (allocated(sh%th) ) deallocate(sh%th)
|
||||
if (allocated(sh%ph) ) deallocate(sh%ph)
|
||||
if (allocated(sh%thc) ) deallocate(sh%thc)
|
||||
if (allocated(sh%phc) ) deallocate(sh%phc)
|
||||
if (allocated(sh%lat) ) deallocate(sh%lat)
|
||||
if (allocated(sh%latc)) deallocate(sh%latc)
|
||||
|
||||
end subroutine deallocShellGrid
|
||||
|
||||
|
||||
@@ -6,6 +6,8 @@ module raijutypes
|
||||
use ioclock
|
||||
use kronos
|
||||
|
||||
use basetypes
|
||||
|
||||
use raijudefs
|
||||
|
||||
implicit none
|
||||
@@ -317,6 +319,8 @@ module raijutypes
|
||||
|
||||
|
||||
type raijuState_T
|
||||
logical :: isFirstCpl = .true.
|
||||
|
||||
real(rp) :: t, dt
|
||||
!! Current time and last coupling dt made
|
||||
real(rp), dimension(:), allocatable :: dtk
|
||||
@@ -448,16 +452,83 @@ module raijutypes
|
||||
! Higher-level types, using above types
|
||||
!------
|
||||
|
||||
type raijuApp_T
|
||||
type, extends(BaseOptions_T) :: raiOptions_T
|
||||
|
||||
contains
|
||||
end type raiOptions_T
|
||||
|
||||
type, extends(BaseApp_T) :: raijuApp_T
|
||||
type(raijuModel_T) :: Model
|
||||
type(raijuGrid_T ) :: Grid
|
||||
type(raijuState_T) :: State
|
||||
|
||||
type(raiOptions_T) :: raiOptions
|
||||
|
||||
contains
|
||||
|
||||
procedure :: InitModel => raiInitModel
|
||||
procedure :: InitIO => raiInitIO
|
||||
procedure :: WriteRestart => raiWriteRestart
|
||||
procedure :: ReadRestart => raiReadRestart
|
||||
procedure :: WriteConsoleOutput => raiWriteConsoleOutput
|
||||
procedure :: WriteFileOutput => raiWriteFileOutput
|
||||
procedure :: WriteSlimFileOutput => raiWriteSlimFileOutput
|
||||
procedure :: AdvanceModel => raiAdvanceModel
|
||||
procedure :: Cleanup => raiCleanup
|
||||
end type raijuApp_T
|
||||
|
||||
!------
|
||||
! Interfaces
|
||||
!------
|
||||
|
||||
!raijuapp function placeholders, bodies are in src/raiju/raijutypessub.F90 to prevent circular dependency
|
||||
interface
|
||||
module subroutine raiInitModel(App, Xml)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
type(XML_Input_T), intent(inout) :: Xml
|
||||
end subroutine raiInitModel
|
||||
|
||||
module subroutine raiInitIO(App, Xml)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
type(XML_Input_T), intent(inout) :: Xml
|
||||
end subroutine raiInitIO
|
||||
|
||||
module subroutine raiWriteRestart(App, nRes)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
integer, intent(in) :: nRes
|
||||
end subroutine raiWriteRestart
|
||||
|
||||
module subroutine raiReadRestart(App, resId, nRes)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
character(len=*), intent(in) :: resId
|
||||
integer, intent(in) :: nRes
|
||||
end subroutine raiReadRestart
|
||||
|
||||
module subroutine raiWriteConsoleOutput(App)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
end subroutine raiWriteConsoleOutput
|
||||
|
||||
module subroutine raiWriteFileOutput(App, nStep)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
integer, intent(in) :: nStep
|
||||
end subroutine raiWriteFileOutput
|
||||
|
||||
module subroutine raiWriteSlimFileOutput(App, nStep)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
integer, intent(in) :: nStep
|
||||
end subroutine raiWriteSlimFileOutput
|
||||
|
||||
module subroutine raiAdvanceModel(App, dt)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
real(rp), intent(in) :: dt
|
||||
end subroutine raiAdvanceModel
|
||||
|
||||
module subroutine raiCleanup(App)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
end subroutine raiCleanup
|
||||
|
||||
end interface
|
||||
|
||||
abstract interface
|
||||
subroutine raijuStateIC_T(Model,Grid,State,inpXML)
|
||||
Import :: raijuModel_T, raijuGrid_T, raijuState_T, strLen, XML_Input_T
|
||||
|
||||
@@ -11,6 +11,9 @@ module volttypes
|
||||
use helpertypes
|
||||
use basetypes
|
||||
use gamtypes
|
||||
use raijutypes
|
||||
use shellGrid
|
||||
use voltCplTypes
|
||||
|
||||
implicit none
|
||||
|
||||
@@ -104,6 +107,33 @@ module volttypes
|
||||
|
||||
end type innerMagBase_T
|
||||
|
||||
type, extends(raijuApp_T) :: raijuCoupler_T
|
||||
|
||||
real(rp) :: tLastUpdate
|
||||
!! Time of last update, according to voltron
|
||||
type(ShellGrid_T) :: shGr
|
||||
!! Copy of raijuModel's shellGrid
|
||||
integer :: n_MHDfluids
|
||||
!! Number of MHD fluids to expect
|
||||
|
||||
type(magLine_T), dimension(:,:), allocatable :: magLines
|
||||
type(IMAGTube_T), dimension(:,:), allocatable :: ijTubes
|
||||
type(ShellGridVar_T) :: pot
|
||||
!! electrostatic potential from ionosphere [kV]
|
||||
|
||||
contains
|
||||
|
||||
procedure :: InitModel => raiCplInitModel
|
||||
procedure :: InitIO => raiCplInitIO
|
||||
!procedure :: WriteRestart =>
|
||||
!procedure :: ReadRestart =>
|
||||
!procedure :: WriteConsoleOutput =>
|
||||
!procedure :: WriteFileOutput =>
|
||||
!procedure :: WriteSlimFileOutput =>
|
||||
!procedure :: AdvanceModel =>
|
||||
|
||||
end type raijuCoupler_T
|
||||
|
||||
|
||||
integer, parameter :: mix2mhd_varn = 1 ! for now just the potential is sent back
|
||||
|
||||
@@ -273,6 +303,18 @@ module volttypes
|
||||
class(voltApp_T), intent(inout) :: voltApp
|
||||
end subroutine
|
||||
|
||||
! RAIJU
|
||||
module subroutine raiCplInitModel(App, xml)
|
||||
class(raijuCoupler_T), intent(inout) :: App
|
||||
type(XML_Input_T), intent(inout) :: Xml
|
||||
end subroutine raiCplInitModel
|
||||
|
||||
|
||||
module subroutine raiCplInitIO(App, xml)
|
||||
class(raijuCoupler_T), intent(inout) :: App
|
||||
type(XML_Input_T), intent(inout) :: Xml
|
||||
end subroutine raiCplInitIO
|
||||
|
||||
end interface
|
||||
|
||||
! functions for squish helper specific gamera coupler
|
||||
|
||||
@@ -39,8 +39,9 @@ program raijuOWDx
|
||||
!Holder for remix data
|
||||
type(rmReader_T) :: rmReader
|
||||
|
||||
type(raijuApp_T ) :: raiApp
|
||||
type(raiju_cplBase_T) :: raijuCplBase
|
||||
!type(raijuApp_T ) :: raiApp
|
||||
!type(raiju_cplBase_T) :: raijuCplBase
|
||||
type(raijuCoupler_T) :: raiCplApp
|
||||
|
||||
character(len=strLen) :: XMLStr, gStr, ftag
|
||||
type(XML_Input_T) :: inpXML
|
||||
@@ -48,7 +49,6 @@ program raijuOWDx
|
||||
character(len=strLen) :: FLH5
|
||||
|
||||
logical :: doChmpOut,doFLOut
|
||||
logical :: isFirstCpl = .true.
|
||||
|
||||
real(rp) :: mjd0
|
||||
|
||||
|
||||
@@ -31,9 +31,7 @@ program raijuSAx
|
||||
|
||||
logical :: doChmpOut,doFLOut
|
||||
logical :: doClawAdvance = .false.
|
||||
logical :: doPosFix = .false.
|
||||
logical :: isfirstCpl = .true.
|
||||
|
||||
logical :: doPosFix = .false.
|
||||
|
||||
real(rp) :: mjd0
|
||||
|
||||
@@ -68,10 +66,12 @@ program raijuSAx
|
||||
call inpXML%Set_Val(doPosFix ,'hax/doPosFix',doPosFix )
|
||||
|
||||
! Init RAIJU
|
||||
call raijuInit(raiApp, inpXML)
|
||||
isFirstCpl = .false.
|
||||
call raiApp%InitModel(inpXML)
|
||||
call raiApp%InitIO(inpXML)
|
||||
raiApp%State%isFirstCpl = .false.
|
||||
if (raiApp%Model%isRestart) then
|
||||
isFirstCpl = .false.
|
||||
call raiApp%ReadRestart(raiApp%Model%RunID, raiApp%Model%nResIn)
|
||||
raiApp%State%isFirstCpl = .false.
|
||||
endif
|
||||
|
||||
|
||||
@@ -96,12 +96,18 @@ program raijuSAx
|
||||
call Tic("Output")
|
||||
! Output if ready
|
||||
if (raiApp%State%IO%doRestart(raiApp%State%t)) then
|
||||
call raiApp%WriteRestart(raiApp%State%IO%nRes)
|
||||
call raijuResOutput(raiApp%Model,raiApp%Grid,raiApp%State)
|
||||
!call raijuResInput(raiApp%Model,raiApp%Grid,raiApp%State)
|
||||
endif
|
||||
|
||||
if (raiApp%State%IO%doOutput(raiApp%State%t)) then
|
||||
call raijuOutput(raiApp%Model,raiApp%Grid,raiApp%State)
|
||||
call raiApp%WriteFileOutput(raiApp%State%IO%nOut)
|
||||
!call raijuOutput(raiApp%Model,raiApp%Grid,raiApp%State)
|
||||
endif
|
||||
|
||||
if (raiApp%State%IO%doConsole(raiApp%State%t)) then
|
||||
call raiApp%WriteConsoleOutput()
|
||||
endif
|
||||
call Toc("Output")
|
||||
|
||||
@@ -113,8 +119,8 @@ program raijuSAx
|
||||
if (doClawAdvance) then
|
||||
call raijuAdvance_claw(raiApp%Model,raiApp%Grid,raiApp%State, raiApp%Model%dt, doPosFixO=doPosFix)
|
||||
else
|
||||
call raijuAdvance(raiApp%Model,raiApp%Grid,raiApp%State, raiApp%Model%dt, isfirstCplO=isfirstCpl)
|
||||
isfirstCpl = .false.
|
||||
call raiApp%AdvanceModel(raiApp%State%dt)
|
||||
!call raijuAdvance(raiApp%Model,raiApp%Grid,raiApp%State, raiApp%Model%dt, isfirstCplO=isfirstCpl)
|
||||
endif
|
||||
call Toc("RAIJU Advance")
|
||||
|
||||
|
||||
@@ -16,12 +16,11 @@ module raijuAdvancer
|
||||
|
||||
contains
|
||||
|
||||
|
||||
!------
|
||||
! Advance entry point
|
||||
!------
|
||||
|
||||
subroutine raijuAdvance(Model, Grid, State, dtCpl, isFirstCplO)
|
||||
subroutine raijuAdvance(Model, Grid, State, dtCpl)
|
||||
!! Controls entirety of eta evolution over time dtCpl
|
||||
!! Assumes that any coupling setup has been completed
|
||||
!! Calculates velocities and dt, evolves all etas over
|
||||
@@ -30,22 +29,15 @@ module raijuAdvancer
|
||||
type(raijuGrid_T) , intent(in) :: Grid
|
||||
type(raijuState_T), intent(inout) :: State
|
||||
real(rp), intent(in) :: dtCpl
|
||||
logical, optional, intent(in) :: isFirstCplO
|
||||
|
||||
logical :: isFirstCpl
|
||||
integer :: k
|
||||
|
||||
if (present(isFirstCplO)) then
|
||||
isFirstCpl = isFirstCplO
|
||||
else
|
||||
isFirstCpl = .false.
|
||||
endif
|
||||
|
||||
State%dt = dtCpl
|
||||
|
||||
call Tic("Pre-Advance")
|
||||
call raijuPreAdvance(Model, Grid, State, isfirstCpl)
|
||||
call raijuPreAdvance(Model, Grid, State)
|
||||
call Toc("Pre-Advance")
|
||||
State%isFirstCpl = .false.
|
||||
|
||||
! Step
|
||||
call Tic("AdvanceState")
|
||||
|
||||
@@ -415,6 +415,30 @@ module raijugrids
|
||||
end subroutine finalizeLLGrid
|
||||
|
||||
|
||||
!------
|
||||
! Grid helpers
|
||||
!------
|
||||
|
||||
function checkResGrid(sh, shR) result(isSame)
|
||||
type(ShellGrid_T), intent(in) :: sh
|
||||
!! Raiju's currently loaded grid
|
||||
type(ShellGrid_T), intent(in) :: shR
|
||||
!! ShellGrid read from restart file
|
||||
logical :: isSame
|
||||
!! Whether or not we things these are equivalent
|
||||
|
||||
if ( (sh%Nt .ne. shR%Nt) &
|
||||
.or. (sh%Np .ne. shR%Np) &
|
||||
.or. (sh%minGTheta .ne. shR%minGTheta) &
|
||||
.or. (sh%maxGTheta .ne. shR%maxGTheta) ) then
|
||||
isSame = .false.
|
||||
else
|
||||
isSame = .true.
|
||||
endif
|
||||
|
||||
end function checkResGrid
|
||||
|
||||
|
||||
!------
|
||||
! Spatial grid operations
|
||||
!------
|
||||
|
||||
@@ -1,6 +1,7 @@
|
||||
module raijuOut
|
||||
use raijuIO
|
||||
use timeHelpers
|
||||
use dates
|
||||
|
||||
implicit none
|
||||
|
||||
@@ -82,26 +83,63 @@ module raijuOut
|
||||
end subroutine raijuResInput
|
||||
|
||||
|
||||
subroutine raijuConsoleOut(Model, Grid, State)
|
||||
type(raijuModel_T), intent(in) :: Model
|
||||
type(raijuGrid_T) , intent(in) :: Grid
|
||||
type(raijuState_T), intent(inout) :: State
|
||||
|
||||
character(len=strLen) :: utStr, tStr, tStr2
|
||||
integer :: minDtLoc, maxDtLoc
|
||||
real(rp) :: minDt, maxDt
|
||||
|
||||
call mjd2utstr(State%mjd,utStr)
|
||||
minDtLoc = minloc(State%dtk,dim=1)
|
||||
maxDtLoc = maxloc(State%dtk,dim=1)
|
||||
|
||||
|
||||
write(*,*) ANSIPURPLE
|
||||
write(*,*) 'RAIJU'
|
||||
call timeStrFmt(State%t, tStr)
|
||||
write(*,'(a,a)') ' Time = ', trim(tStr)
|
||||
call timeStrFmt(State%dt, tStr)
|
||||
write(*,'(a,a)') ' dtCpl = ', trim(tStr)
|
||||
call timeStrFmt(State%dtk(minDtLoc), tStr )
|
||||
call timeStrFmt(State%dtk(maxDtLoc), tStr2)
|
||||
write(*,'(a)' ) ' min/max dt @ k:'
|
||||
write(*,'(a,a,a,I0.5)') 'Min', trim(tStr) , ' @ ', minDtLoc
|
||||
write(*,'(a,a,a,I0.5)') 'Max', trim(tStr2), ' @ ', maxDtLoc
|
||||
write(*,'(a)',advance="no") ANSIRESET
|
||||
|
||||
State%IO%tCon = State%IO%tCon + State%IO%dtCon
|
||||
|
||||
end subroutine raijuConsoleOut
|
||||
|
||||
!------
|
||||
! Helpers
|
||||
!------
|
||||
|
||||
subroutine genResInFname(Model, ResF)
|
||||
subroutine genResInFname(Model, ResF, runIdO)
|
||||
!!! Using Model mambers, defermine the restart name to read from
|
||||
type(raijuModel_T), intent(in) :: Model
|
||||
character(len=strLen), intent(out) :: ResF
|
||||
character(len=*), optional, intent(in) :: runIdO
|
||||
|
||||
character(len=strLen) :: runId
|
||||
character(len=strLen) :: nStr
|
||||
|
||||
if (present(runIdO)) then
|
||||
runId = trim(runIdO)
|
||||
else
|
||||
runId = Model%RunID
|
||||
endif
|
||||
|
||||
if (Model%nResIn == -1) then
|
||||
|
||||
nStr = "XXXXX"
|
||||
else
|
||||
write (nStr,'(I0.5)') Model%nResIn
|
||||
endif
|
||||
|
||||
write (ResF, '(A,A,A,A)') trim(Model%RunID), ".raiju.Res.", trim(nStr), ".h5"
|
||||
write (ResF, '(A,A,A,A)') trim(runId), ".raiju.Res.", trim(nStr), ".h5"
|
||||
end subroutine genResInFname
|
||||
|
||||
end module raijuOut
|
||||
@@ -22,22 +22,14 @@ module raijuPreAdvancer
|
||||
! Main high-level functions
|
||||
!------
|
||||
|
||||
subroutine raijuPreAdvance(Model, Grid, State, isFirstCplO)
|
||||
subroutine raijuPreAdvance(Model, Grid, State)
|
||||
!! Takes a state and calculates what is needed in order to advance
|
||||
type(raijuModel_T), intent(inout) :: Model
|
||||
type(raijuGrid_T ), intent(in) :: Grid
|
||||
type(raijuState_T), intent(inout) :: State
|
||||
logical, optional, intent(in) :: isFirstCplO
|
||||
|
||||
logical :: isFirstCpl
|
||||
integer :: k
|
||||
|
||||
if (present(isFirstCplO)) then
|
||||
isFirstCpl = isFirstCplO
|
||||
else
|
||||
isFirstCpl = .false.
|
||||
endif
|
||||
|
||||
! Clear things that will be accumulated over the advance
|
||||
State%dEta_dt = 0.0
|
||||
State%precipType_ele = 0.0
|
||||
@@ -47,12 +39,12 @@ module raijuPreAdvancer
|
||||
|
||||
! Moments to etas, initial active shell calculation
|
||||
call Tic("BCs")
|
||||
call applyRaijuBCs(Model, Grid, State, doWholeDomainO=isFirstCpl) ! If fullEtaMap=True, mom2eta map is applied to the whole domain
|
||||
call applyRaijuBCs(Model, Grid, State, doWholeDomainO=State%isFirstCpl) ! If fullEtaMap=True, mom2eta map is applied to the whole domain
|
||||
call Toc("BCs")
|
||||
|
||||
! Handle edge cases that may effect the validity of information carried over from last coupling period
|
||||
! TODO: do this in predictor function
|
||||
call prepEtaLast(Grid%shGrid, State, isFirstCpl)
|
||||
call prepEtaLast(Grid%shGrid, State, State%isFirstCpl)
|
||||
|
||||
! Calc cell velocities
|
||||
!call Tic("Calc face velocities")
|
||||
|
||||
@@ -36,11 +36,6 @@ module raijustarter
|
||||
call raijuInitModel(app%Model, iXML)
|
||||
call raijuInitGrid(app%Model, app%Grid, iXML)
|
||||
|
||||
! TODO: Handle restart here. For now, assuming no restart
|
||||
|
||||
! Init output file
|
||||
call raijuInitIO(app%Model, app%Grid, app%Model%writeGhosts)
|
||||
|
||||
call raijuInitState(app%Model,app%Grid,app%State,iXML)
|
||||
|
||||
! Do losses after everything else has been set, just in case they need something from it
|
||||
@@ -282,7 +277,7 @@ module raijustarter
|
||||
call iXML%Set_Val(Grid%nB, "grid/Nbnd", 4 ) ! Number of cells between open boundary and active domain
|
||||
call iXML%Set_Val(tmpStr, "grid/gType","UNISPH")
|
||||
|
||||
if (.not. Model%isRestart) then
|
||||
!if (.not. Model%isRestart) then
|
||||
! Fill out Grid object depending on chosen method
|
||||
select case(tmpStr)
|
||||
case("UNISPH")
|
||||
@@ -308,9 +303,9 @@ module raijustarter
|
||||
write(*,*) " Dying."
|
||||
stop
|
||||
end select
|
||||
else
|
||||
call GenShellGridFromFile(Grid%shGrid, RAI_SG_NAME, Model%ResF)
|
||||
endif
|
||||
!else
|
||||
! call GenShellGridFromFile(Grid%shGrid, RAI_SG_NAME, Model%ResF)
|
||||
!endif
|
||||
|
||||
! Finalize the spatial part of the grid
|
||||
call finalizeLLGrid(Grid, Model%planet)
|
||||
@@ -420,8 +415,9 @@ module raijustarter
|
||||
end associate
|
||||
|
||||
if (Model%isRestart) then
|
||||
call raijuResInput(Model, Grid, State)
|
||||
return
|
||||
!call raijuResInput(Model, Grid, State)
|
||||
!return
|
||||
continue
|
||||
endif
|
||||
|
||||
! For now, just set t to tStart and ts to 0
|
||||
|
||||
116
src/raiju/raijuTypesSub.F90
Normal file
116
src/raiju/raijuTypesSub.F90
Normal file
@@ -0,0 +1,116 @@
|
||||
submodule (raijutypes) raijuTypesSub
|
||||
|
||||
use raijuStarter
|
||||
use raijuGrids
|
||||
use raijuIO
|
||||
use raijuOut
|
||||
use raijuAdvancer
|
||||
|
||||
implicit none
|
||||
|
||||
contains
|
||||
|
||||
module subroutine raiInitModel(App, xml)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
type(XML_Input_T), intent(inout) :: Xml
|
||||
|
||||
call raijuInit(App, Xml)
|
||||
|
||||
end subroutine raiInitModel
|
||||
|
||||
|
||||
module subroutine raiInitIO(App, Xml)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
type(XML_Input_T), intent(inout) :: Xml
|
||||
|
||||
! Init output file
|
||||
call raijuInitIO(App%Model, App%Grid, App%Model%writeGhosts)
|
||||
|
||||
end subroutine raiInitIO
|
||||
|
||||
|
||||
module subroutine raiWriteRestart(App, nRes)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
integer, intent(in) :: nRes
|
||||
|
||||
! synchronize restart output number
|
||||
App%State%IO%nRes = nRes
|
||||
|
||||
call raijuResOutput(App%Model, App%Grid, App%State)
|
||||
|
||||
end subroutine raiWriteRestart
|
||||
|
||||
|
||||
module subroutine raiReadRestart(App, resId, nRes)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
character(len=*), intent(in) :: resId
|
||||
integer, intent(in) :: nRes
|
||||
|
||||
type(ShellGrid_T) :: shRes
|
||||
!! ShellGrid saved to file. Just use to make sure we are using the same grid as was used previously
|
||||
|
||||
! synchronize restart output number
|
||||
App%State%IO%nRes = nRes
|
||||
! Build restart filename
|
||||
App%Model%nResIn = nRes
|
||||
call genResInFname(App%Model, App%Model%ResF, runIdO=resId)
|
||||
|
||||
! Handle grid reading first
|
||||
call GenShellGridFromFile(shRes, RAI_SG_NAME, App%Model%ResF)
|
||||
if(.not. checkResGrid(App%Grid%shGrid, shRes)) then
|
||||
write(*,*)"RAIJU restart error: Grid generated from XML doesn't match that from restart file, that's not allowed"
|
||||
stop
|
||||
endif
|
||||
|
||||
! Now read State info
|
||||
call raijuResInput(App%Model, App%Grid, App%State)
|
||||
|
||||
end subroutine raiReadRestart
|
||||
|
||||
|
||||
module subroutine raiWriteConsoleOutput(App)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
|
||||
call raijuConsoleOut(App%Model, App%Grid, App%State)
|
||||
|
||||
end subroutine raiWriteConsoleOutput
|
||||
|
||||
|
||||
module subroutine raiWriteFileOutput(App, nStep)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
integer, intent(in) :: nStep
|
||||
|
||||
! synchronize file output number
|
||||
App%State%IO%nOut = nStep
|
||||
|
||||
call raijuOutput(App%Model, App%Grid, App%State)
|
||||
|
||||
end subroutine raiWriteFileOutput
|
||||
|
||||
|
||||
module subroutine raiWriteSlimFileOutput(App, nStep)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
integer, intent(in) :: nStep
|
||||
|
||||
call raiWriteFileOutput(App, nStep)
|
||||
|
||||
end subroutine raiWriteSlimFileOutput
|
||||
|
||||
|
||||
module subroutine raiAdvanceModel(App, dt)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
real(rp), intent(in) :: dt
|
||||
|
||||
call raijuAdvance(App%Model, App%Grid, App%State, dt)
|
||||
|
||||
end subroutine raiAdvanceModel
|
||||
|
||||
|
||||
module subroutine raiCleanup(App)
|
||||
class(raijuApp_T), intent(inout) :: App
|
||||
|
||||
write(*,*) "RAIJU doing nothing for cleanup, idk what to do here yet"
|
||||
|
||||
end subroutine raiCleanup
|
||||
|
||||
end submodule raijuTypesSub
|
||||
17
src/voltron/modelInterfaces/raiCplTypesSub.F90
Normal file
17
src/voltron/modelInterfaces/raiCplTypesSub.F90
Normal file
@@ -0,0 +1,17 @@
|
||||
submodule (volttypes) raijuCplTypesSub
|
||||
|
||||
use raijjuCplHelpers
|
||||
|
||||
|
||||
module subroutine raiCplInitModel(App, xml)
|
||||
class(raijuCoupler_T), intent(inout) :: App
|
||||
type(XML_Input_T), intent(inout) :: Xml
|
||||
end subroutine raiCplInitModel
|
||||
|
||||
|
||||
module subroutine raiCplInitIO(App, xml)
|
||||
class(raijuCoupler_T), intent(inout) :: App
|
||||
type(XML_Input_T), intent(inout) :: Xml
|
||||
end subroutine raiCplInitIO
|
||||
|
||||
end submodule raijuCplTypesSub
|
||||
Reference in New Issue
Block a user