Lots of interface changes and test corrections

This commit is contained in:
Jeffrey Garretson
2024-05-09 09:49:09 -07:00
parent 8fbfa3ba37
commit 2bb3fbd8c2
28 changed files with 258 additions and 200 deletions

View File

@@ -15,8 +15,12 @@ then
else else
# split the CPUs on this node between me and the other jobs # split the CPUs on this node between me and the other jobs
#echo "myHost = $myHost" #echo "myHost = $myHost"
#echo "numJobsOnMyNode = $numJobsOnMyNode" echo "numJobsOnMyNode = $numJobsOnMyNode"
let newNumThreads=$OMP_NUM_THREADS/$numJobsOnMyNode let newNumThreads=$OMP_NUM_THREADS/$numJobsOnMyNode
if [ $newNumThreads -lt 1 ]
then
newNumThreads=1
fi
export OMP_NUM_THREADS=$newNumThreads export OMP_NUM_THREADS=$newNumThreads
#echo "Setting OMP_NUM_THREADS = $OMP_NUM_THREADS" #echo "Setting OMP_NUM_THREADS = $OMP_NUM_THREADS"
fi fi

View File

@@ -17,6 +17,9 @@ let numCpus=`lscpu | sed --quiet "s/^CPU(s): \\+\\([0-9]\\+\\)$/\\1/p"`
let threadsPerCore=`lscpu | sed --quiet "s/^Thread(s) per core: \\+\\([0-9]\\+\\)$/\\1/p"` let threadsPerCore=`lscpu | sed --quiet "s/^Thread(s) per core: \\+\\([0-9]\\+\\)$/\\1/p"`
let numCores=$numCpus/$threadsPerCore let numCores=$numCpus/$threadsPerCore
let newNumThreads=$numCores/$PMI_LOCAL_SIZE let newNumThreads=$numCores/$PMI_LOCAL_SIZE
if [[ $newNumThreads -lt 1 ]]; then
newNumThreads=1
fi
let minThread=$newNumThreads*$PMI_LOCAL_RANK let minThread=$newNumThreads*$PMI_LOCAL_RANK
let maxThread=$minThread+$newNumThreads-1 let maxThread=$minThread+$newNumThreads-1
export OMP_NUM_THREADS=$newNumThreads export OMP_NUM_THREADS=$newNumThreads

View File

@@ -128,14 +128,16 @@ module ioclock
end function doTimerIOClock end function doTimerIOClock
! Returns the time sim time when sime kind of IO should occur ! Returns the time sim time when sime kind of IO should occur
function doNextIOTime(this, curTs, curDt) function doNextIOTime(this, curT, curTs, curDt)
class(IOClock_T), intent(in) :: this class(IOClock_T), intent(in) :: this
real(rp), intent(in) :: curT
integer, intent(in) :: curTs integer, intent(in) :: curTs
real(rp), intent(in) :: curDt real(rp), intent(in) :: curDt
real(rp) :: doNextIOTime real(rp) :: doNextIOTime
doNextIOTime = HUGE doNextIOTime = HUGE
if(this%doConOut) doNextIOTime = min(doNextIOTime, curDt*(0.5+this%tsNext-curTs)) ! console output time is a prediction based on current DT and timesteps until output
if(this%doConOut) doNextIOTime = min(doNextIOTime, curT + curDt*(0.5+this%tsNext-curTs))
if(this%doResOut) doNextIOTime = min(doNextIOTime, this%tRes) if(this%doResOut) doNextIOTime = min(doNextIOTime, this%tRes)
if(this%doDataOut) doNextIOTime = min(doNextIOTime, this%tOut) if(this%doDataOut) doNextIOTime = min(doNextIOTime, this%tOut)
! don't check for clock cleaning timer, it's not important enough (?) ! don't check for clock cleaning timer, it's not important enough (?)

View File

@@ -54,9 +54,10 @@ module basetypes
type(XML_Input_T), intent(inout) :: Xml type(XML_Input_T), intent(inout) :: Xml
end subroutine InitIO_interface end subroutine InitIO_interface
subroutine WriteRestart_interface(App) subroutine WriteRestart_interface(App,nRes)
import BaseApp_T import BaseApp_T
class(BaseApp_T), intent(inout) :: App class(BaseApp_T), intent(inout) :: App
integer, intent(in) :: nRes
end subroutine WriteRestart_interface end subroutine WriteRestart_interface
subroutine ReadRestart_interface(App,resId,nRes) subroutine ReadRestart_interface(App,resId,nRes)
@@ -71,14 +72,16 @@ module basetypes
class(BaseApp_T), intent(inout) :: App class(BaseApp_T), intent(inout) :: App
end subroutine WriteConsoleOutput_interface end subroutine WriteConsoleOutput_interface
subroutine WriteFileOutput_interface(App) subroutine WriteFileOutput_interface(App,nStep)
import BaseApp_T import BaseApp_T
class(BaseApp_T), intent(inout) :: App class(BaseApp_T), intent(inout) :: App
integer, intent(in) :: nStep
end subroutine WriteFileOutput_interface end subroutine WriteFileOutput_interface
subroutine WriteSlimFileOutput_interface(App) subroutine WriteSlimFileOutput_interface(App,nStep)
import BaseApp_T import BaseApp_T
class(BaseApp_T), intent(inout) :: App class(BaseApp_T), intent(inout) :: App
integer, intent(in) :: nStep
end subroutine WriteSlimFileOutput_interface end subroutine WriteSlimFileOutput_interface
subroutine AdvanceModel_interface(App, dt) subroutine AdvanceModel_interface(App, dt)

View File

@@ -316,8 +316,9 @@ module gamtypes
type(XML_Input_T), intent(inout) :: Xml type(XML_Input_T), intent(inout) :: Xml
end subroutine gamInitIO end subroutine gamInitIO
module subroutine gamWriteRestart(App) module subroutine gamWriteRestart(App, nRes)
class(gamApp_T), intent(inout) :: App class(gamApp_T), intent(inout) :: App
integer, intent(in) :: nRes
end subroutine gamWriteRestart end subroutine gamWriteRestart
module subroutine gamReadRestart(App, resId, nRes) module subroutine gamReadRestart(App, resId, nRes)
@@ -330,12 +331,14 @@ module gamtypes
class(gamApp_T), intent(inout) :: App class(gamApp_T), intent(inout) :: App
end subroutine gamWriteConsoleOutput end subroutine gamWriteConsoleOutput
module subroutine gamWriteFileOutput(App) module subroutine gamWriteFileOutput(App, nStep)
class(gamApp_T), intent(inout) :: App class(gamApp_T), intent(inout) :: App
integer, intent(in) :: nStep
end subroutine gamWriteFileOutput end subroutine gamWriteFileOutput
module subroutine gamWriteSlimFileOutput(App) module subroutine gamWriteSlimFileOutput(App, nStep)
class(gamApp_T), intent(inout) :: App class(gamApp_T), intent(inout) :: App
integer, intent(in) :: nStep
end subroutine gamWriteSlimFileOutput end subroutine gamWriteSlimFileOutput
module subroutine gamAdvanceModel(App, dt) module subroutine gamAdvanceModel(App, dt)

View File

@@ -128,7 +128,8 @@ module volttypes
! add new coupling function which can be over-ridden by children ! add new coupling function which can be over-ridden by children
procedure :: InitMhdCoupler => gamInitMhdCoupler procedure :: InitMhdCoupler => gamInitMhdCoupler
procedure :: UpdateMhdData => gamUpdateMhdData procedure :: StartUpdateMhdData => gamStartUpdateMhdData
procedure :: FinishUpdateMhdData => gamFinishUpdateMhdData
end type gamCoupler_T end type gamCoupler_T
@@ -189,6 +190,7 @@ module volttypes
!Local gamera object to couple to !Local gamera object to couple to
class(gamCoupler_T), allocatable :: gApp class(gamCoupler_T), allocatable :: gApp
logical :: doSerialMHD = .true.
!voltron specific options !voltron specific options
type(VoltOptions_T) :: vOptions type(VoltOptions_T) :: vOptions
@@ -202,8 +204,9 @@ module volttypes
type(XML_Input_T), intent(inout) :: Xml type(XML_Input_T), intent(inout) :: Xml
end subroutine end subroutine
module subroutine gamCplWriteRestart(App) module subroutine gamCplWriteRestart(App, nRes)
class(gamCoupler_T), intent(inout) :: App class(gamCoupler_T), intent(inout) :: App
integer, intent(in) :: nRes
end subroutine end subroutine
module subroutine gamCplReadRestart(App, resId, nRes) module subroutine gamCplReadRestart(App, resId, nRes)
@@ -216,12 +219,14 @@ module volttypes
class(gamCoupler_T), intent(inout) :: App class(gamCoupler_T), intent(inout) :: App
end subroutine end subroutine
module subroutine gamCplWriteFileOutput(App) module subroutine gamCplWriteFileOutput(App, nStep)
class(gamCoupler_T), intent(inout) :: App class(gamCoupler_T), intent(inout) :: App
integer, intent(in) :: nStep
end subroutine end subroutine
module subroutine gamCplWriteSlimFileOutput(App) module subroutine gamCplWriteSlimFileOutput(App, nStep)
class(gamCoupler_T), intent(inout) :: App class(gamCoupler_T), intent(inout) :: App
integer, intent(in) :: nStep
end subroutine end subroutine
module subroutine gamInitMhdCoupler(App, voltApp) module subroutine gamInitMhdCoupler(App, voltApp)
@@ -229,7 +234,12 @@ module volttypes
class(voltApp_T), intent(inout) :: voltApp class(voltApp_T), intent(inout) :: voltApp
end subroutine end subroutine
module subroutine gamUpdateMhdData(App, voltApp) module subroutine gamStartUpdateMhdData(App, voltApp)
class(gamCoupler_T), intent(inout) :: App
class(voltApp_T), intent(inout) :: voltApp
end subroutine
module subroutine gamFinishUpdateMhdData(App, voltApp)
class(gamCoupler_T), intent(inout) :: App class(gamCoupler_T), intent(inout) :: App
class(voltApp_T), intent(inout) :: voltApp class(voltApp_T), intent(inout) :: voltApp
end subroutine end subroutine

View File

@@ -61,7 +61,7 @@ program gamera_mpix
call Tic("Omega") !Start root timer call Tic("Omega") !Start root timer
!Step model !Step model
nextDT = min(gAppMpi%Model%tFin-gAppMpi%Model%t, gAppMpi%Model%IO%nextIOTime(gAppMpi%Model%ts, gAppMpi%Model%dt)) nextDT = min(gAppMpi%Model%tFin-gAppMpi%Model%t, gAppMpi%Model%IO%nextIOTime(gAppMpi%Model%t, gAppMpi%Model%ts, gAppMpi%Model%dt)-gAppMpi%Model%t)
call gAppMpi%AdvanceModel(nextDT) call gAppMpi%AdvanceModel(nextDT)
!Output if necessary !Output if necessary
@@ -80,11 +80,11 @@ program gamera_mpix
endif endif
if (gAppMpi%Model%IO%doOutput(gAppMpi%Model%t)) then if (gAppMpi%Model%IO%doOutput(gAppMpi%Model%t)) then
call gAppMpi%WriteFileOutput() call gAppMpi%WriteFileOutput(gAppMpi%Model%IO%nOut)
endif endif
if (gAppMpi%Model%IO%doRestart(gAppMpi%Model%t)) then if (gAppMpi%Model%IO%doRestart(gAppMpi%Model%t)) then
call gAppMpi%WriteRestart() call gAppMpi%WriteRestart(gAppMpi%Model%IO%nRes)
endif endif
call Toc("IO") call Toc("IO")

View File

@@ -31,7 +31,7 @@ program gamerax
call Tic("Omega") !Start root timer call Tic("Omega") !Start root timer
!Step model !Step model
nextDT = min(gApp%Model%tFin-gApp%Model%t, gApp%Model%IO%nextIOTime(gApp%Model%ts, gApp%Model%dt)) nextDT = min(gApp%Model%tFin-gApp%Model%t, gApp%Model%IO%nextIOTime(gApp%Model%t, gApp%Model%ts, gApp%Model%dt)-gApp%Model%t)
call gApp%AdvanceModel(nextDT) call gApp%AdvanceModel(nextDT)
!Output if necessary !Output if necessary
@@ -50,11 +50,11 @@ program gamerax
endif endif
if (gApp%Model%IO%doOutput(gApp%Model%t)) then if (gApp%Model%IO%doOutput(gApp%Model%t)) then
call gApp%WriteFileOutput() call gApp%WriteFileOutput(gApp%Model%IO%nOut)
endif endif
if (gApp%Model%IO%doRestart(gApp%Model%t)) then if (gApp%Model%IO%doRestart(gApp%Model%t)) then
call gApp%WriteRestart() call gApp%WriteRestart(gApp%Model%IO%nRes)
endif endif
call Toc("IO") call Toc("IO")

View File

@@ -175,7 +175,7 @@ program voltron_mpix
call Tic("Omega") !Start root timer call Tic("Omega") !Start root timer
!Step model !Step model
nextDT = min(gApp%Model%tFin-gApp%Model%t, gApp%Model%IO%nextIOTime(gApp%Model%ts, gApp%Model%dt)) nextDT = min(gApp%Model%tFin-gApp%Model%t, gApp%Model%IO%nextIOTime(gApp%Model%t, gApp%Model%ts, gApp%Model%dt)-gApp%Model%t)
call gApp%AdvanceModel(nextDT) call gApp%AdvanceModel(nextDT)
!Output if necessary !Output if necessary
@@ -194,11 +194,11 @@ program voltron_mpix
endif endif
if (gApp%Model%IO%doOutput(gApp%Model%t)) then if (gApp%Model%IO%doOutput(gApp%Model%t)) then
call gApp%WriteFileOutput() call gApp%WriteFileOutput(gApp%Model%IO%nOut)
endif endif
if (gApp%Model%IO%doRestart(gApp%Model%t)) then if (gApp%Model%IO%doRestart(gApp%Model%t)) then
call gApp%WriteRestart() call gApp%WriteRestart(gApp%Model%IO%nRes)
endif endif
call Toc("IO") call Toc("IO")

View File

@@ -22,8 +22,12 @@ submodule (gamtypes) gamtypessub
end subroutine gamInitIO end subroutine gamInitIO
module subroutine gamWriteRestart(App) module subroutine gamWriteRestart(App, nRes)
class(gamApp_T), intent(inout) :: App class(gamApp_T), intent(inout) :: App
integer, intent(in) :: nRes
! synchronize restart output number
App%Model%IO%nRes = nRes
call resOutput(App%Model, App%Grid, App%oState, App%State) call resOutput(App%Model, App%Grid, App%oState, App%State)
@@ -48,17 +52,22 @@ submodule (gamtypes) gamtypessub
end subroutine gamWriteConsoleOutput end subroutine gamWriteConsoleOutput
module subroutine gamWriteFileOutput(App) module subroutine gamWriteFileOutput(App, nStep)
class(gamApp_T), intent(inout) :: App class(gamApp_T), intent(inout) :: App
integer, intent(in) :: nStep
! synchronize file output number
App%Model%IO%nOut = nStep
call fOutput(App%Model, App%Grid, App%State) call fOutput(App%Model, App%Grid, App%State)
end subroutine gamWriteFileOutput end subroutine gamWriteFileOutput
module subroutine gamWriteSlimFileOutput(App) module subroutine gamWriteSlimFileOutput(App, nStep)
class(gamApp_T), intent(inout) :: App class(gamApp_T), intent(inout) :: App
integer, intent(in) :: nStep
call App%WriteFileOutput() call App%WriteFileOutput(nStep)
end subroutine gamWriteSlimFileOutput end subroutine gamWriteSlimFileOutput

View File

@@ -21,8 +21,9 @@ module gamCouple
end subroutine getCPCP end subroutine getCPCP
subroutine writeCouplerFileOutput(App) subroutine writeCouplerFileOutput(App, nStep)
class(gamCoupler_T), intent(inout) :: App class(gamCoupler_T), intent(inout) :: App
integer, intent(in) :: nStep
integer :: i,j,k integer :: i,j,k
real(rp) :: cpcp(2) real(rp) :: cpcp(2)
@@ -74,22 +75,23 @@ module gamCouple
call AddOutVar(IOVars,"cpcpN",cpcp(1)) call AddOutVar(IOVars,"cpcpN",cpcp(1))
call AddOutVar(IOVars,"cpcpS",cpcp(2)) call AddOutVar(IOVars,"cpcpS",cpcp(2))
write(gStr,'(A,I0)') "Step#", App%Model%IO%nOut write(gStr,'(A,I0)') "Step#", nStep
call WriteVars(IOVars,.true., App%vh5File,gStr) call WriteVars(IOVars,.true., App%vh5File,gStr)
end associate end associate
end subroutine end subroutine
subroutine writeGamCouplerRestart(App) subroutine writeGamCouplerRestart(App, nRes)
class(gamCoupler_T), intent(inout) :: App class(gamCoupler_T), intent(inout) :: App
integer, intent(in) :: nRes
character(len=strLen) :: ResF character(len=strLen) :: ResF,lnResF
integer, parameter :: MAXGCIOVAR = 20 integer, parameter :: MAXGCIOVAR = 20
type(IOVAR_T), dimension(MAXGCIOVAR) :: IOVars type(IOVAR_T), dimension(MAXGCIOVAR) :: IOVars
!Restart Filename !Restart Filename
write (ResF, '(A,A,I0.5,A)') trim(App%Model%RunID), ".mix2gam.Res.", App%Model%IO%nRes, ".h5" write (ResF, '(A,A,I0.5,A)') trim(App%Model%RunID), ".gamCpl.Res.", nRes, ".h5"
!Reset IO chain !Reset IO chain
call ClearIO(IOVars) call ClearIO(IOVars)
@@ -104,6 +106,10 @@ module gamCouple
!Write out, force real precision !Write out, force real precision
call WriteVars(IOVars,.false.,ResF) call WriteVars(IOVars,.false.,ResF)
!Create link to latest restart
write (lnResF, '(A,A,A,A)') trim(App%Model%RunID), ".gamCpl.Res.", "XXXXX", ".h5"
call MapSymLink(ResF,lnResF)
end subroutine end subroutine
subroutine readGamCouplerRestart(App, resId, nRes) subroutine readGamCouplerRestart(App, resId, nRes)
@@ -117,7 +123,7 @@ module gamCouple
type(IOVAR_T), dimension(MAXGCIOVAR) :: IOVars type(IOVAR_T), dimension(MAXGCIOVAR) :: IOVars
!Restart Filename !Restart Filename
write (ResF, '(A,A,I0.5,A)') trim(resId), ".mix2gam.Res.", nRes, ".h5" write (ResF, '(A,A,I0.5,A)') trim(resId), ".gamCpl.Res.", nRes, ".h5"
inquire(file=ResF,exist=fExist) inquire(file=ResF,exist=fExist)
if (.not. fExist) then if (.not. fExist) then

View File

@@ -19,7 +19,7 @@ module gamCouple_mpi_G2V
type(MPI_Comm) :: couplingComm type(MPI_Comm) :: couplingComm
integer :: myRank, voltRank integer :: myRank, voltRank
logical :: doSerialVoltron = .false., doAsyncCoupling = .true. logical :: doSerialVoltron = .false., doAsyncCoupling = .true.
logical :: firstCoupling = .true. logical :: firstCoupling = .true., processingData = .false.
real(rp) :: DeepT real(rp) :: DeepT
logical :: doDeep logical :: doDeep
@@ -55,7 +55,7 @@ module gamCouple_mpi_G2V
! only over-riding specific functions ! only over-riding specific functions
procedure :: InitModel => gamCplMpiGInitModel procedure :: InitModel => gamCplMpiGInitModel
!procedure :: InitIO => gamCplInitIO procedure :: InitIO => gamCplMpiGInitIO
!procedure :: WriteRestart => gamCplWriteRestart !procedure :: WriteRestart => gamCplWriteRestart
!procedure :: ReadRestart => gamCplReadRestart !procedure :: ReadRestart => gamCplReadRestart
!procedure :: WriteConsoleOutput => gamCplWriteConsoleOutput !procedure :: WriteConsoleOutput => gamCplWriteConsoleOutput
@@ -167,6 +167,48 @@ module gamCouple_mpi_G2V
! receive the initial coupling time ! receive the initial coupling time
call recvCplTimeMpi(App) call recvCplTimeMpi(App)
! couple one time to update mhd data on voltron node
call sendVoltronCplDataMpi(App)
! then over-ride some IO terms from voltron
call mpi_bcast(App%Model%IO%tRes, 1, MPI_MYFLOAT, App%voltRank, App%couplingComm, ierr)
call mpi_bcast(App%Model%IO%dtRes, 1, MPI_MYFLOAT, App%voltRank, App%couplingComm, ierr)
call mpi_bcast(App%Model%IO%nRes, 1, MPI_INTEGER, App%voltRank, App%couplingComm, ierr)
call mpi_bcast(App%Model%IO%tOut, 1, MPI_MYFLOAT, App%voltRank, App%couplingComm, ierr)
call mpi_bcast(App%Model%IO%dtOut, 1, MPI_MYFLOAT, App%voltRank, App%couplingComm, ierr)
call mpi_bcast(App%Model%IO%nOut, 1, MPI_INTEGER, App%voltRank, App%couplingComm, ierr)
end subroutine
subroutine gamCplMpiGInitIO(App, Xml)
class(gamCouplerMpi_gam_T), intent(inout) :: App
type(XML_Input_T), intent(inout) :: Xml
real(rp) :: save_tRes, save_dtRes, save_tOut, save_dtOut
integer :: save_nRes, save_nOut
integer :: ierr
! save and restore parameters over-written by voltron
! doing it this way allows all comms and setup with voltron to happen in the init function
! and prevents some issues
save_tRes = App%Model%IO%tRes
save_dtRes = App%Model%IO%dtRes
save_nRes = App%Model%IO%nRes
save_tOut = App%Model%IO%tOut
save_dtOut = App%Model%IO%dtOut
save_nOut = App%Model%IO%nOut
! initialize parent's IO
call gamInitIO(App, Xml)
! restore saved IO options
App%Model%IO%tRes = save_tRes
App%Model%IO%dtRes = save_dtRes
App%Model%IO%nRes = save_nRes
App%Model%IO%tOut = save_tOut
App%Model%IO%dtOut = save_dtOut
App%Model%IO%nOut = save_nOut
end subroutine end subroutine
subroutine gamCplMpiGAdvanceModel(App, dt) subroutine gamCplMpiGAdvanceModel(App, dt)
@@ -182,19 +224,25 @@ module gamCouple_mpi_G2V
! may need to step around coupling intervals ! may need to step around coupling intervals
do while(App%Model%t < targetSimT) do while(App%Model%t < targetSimT)
if(App%DeepT > targetSimT) then if(.not. App%processingData) then
! no additional coupling required here ! receive new data to process
call gamMpiAdvanceModel(App, targetSimT-App%Model%t) call recvVoltronCplDataMpi(App)
App%processingData = .true.
elseif(App%DeepT <= App%Model%t) then elseif(App%DeepT <= App%Model%t) then
! couple immediately ! send results
call sendVoltronCplDataMpi(App) call sendVoltronCplDataMpi(App)
call recvVoltronCplDatampi(App) App%processingData = .false.
else else
! math then couple if(targetSimT < App%DeepT) then
call gamMpiAdvanceModel(App, App%DeepT-App%Model%t) ! advance to the current step target time
call gamMpiAdvanceModel(App, targetSimT-App%Model%t)
call sendVoltronCplDataMpi(App) else
call recvVoltronCplDatampi(App) ! advance to next coupling time
call gamMpiAdvanceModel(App, App%DeepT-App%Model%t)
! send results
call sendVoltronCplDataMpi(App)
App%processingData = .false.
endif
endif endif
end do end do

View File

@@ -23,8 +23,7 @@ module gamCouple_mpi_V2G
! voltron to gamera comms variables ! voltron to gamera comms variables
type(MPI_Comm) :: couplingComm type(MPI_Comm) :: couplingComm
integer :: myRank integer :: myRank
logical :: doSerialVoltron = .false., doAsyncCoupling = .true. logical :: doAsyncCoupling = .true.
logical :: firstRecv= .true., firstSend=.true.
logical :: doDeep logical :: doDeep
! array of all zeroes to simplify various send/receive calls ! array of all zeroes to simplify various send/receive calls
@@ -74,7 +73,8 @@ module gamCouple_mpi_V2G
procedure :: Cleanup => gamCplMpiVCleanup procedure :: Cleanup => gamCplMpiVCleanup
procedure :: InitMhdCoupler => gamCplMpiVInitMhdCoupler procedure :: InitMhdCoupler => gamCplMpiVInitMhdCoupler
procedure :: UpdateMhdData => gamCplMpiVUpdateMhdData procedure :: StartUpdateMhdData => gamCplMpiVStartUpdateMhdData
procedure :: FinishUpdateMhdData => gamCplMpiVFinishUpdateMhdData
end type end type
@@ -112,13 +112,8 @@ module gamCouple_mpi_V2G
call MPI_Comm_rank(App%gOptionsCplMpiV%allComm, commSize, ierr) call MPI_Comm_rank(App%gOptionsCplMpiV%allComm, commSize, ierr)
call MPI_comm_split(App%gOptionsCplMpiV%allComm, 0, commSize, voltComm, ierr) call MPI_comm_split(App%gOptionsCplMpiV%allComm, 0, commSize, voltComm, ierr)
call Xml%Set_Val(App%doSerialVoltron,"coupling/doSerial",.false.)
call Xml%Set_Val(App%doAsyncCoupling,"coupling/doAsyncCoupling",.true.) call Xml%Set_Val(App%doAsyncCoupling,"coupling/doAsyncCoupling",.true.)
call Xml%Set_Val(App%doDeep, "coupling/doDeep", .true.) call Xml%Set_Val(App%doDeep, "coupling/doDeep", .true.)
if(App%doSerialVoltron) then
! don't do asynchronous coupling if comms are serial
App%doAsyncCoupling = .false.
endif
! create a new communicator using MPI Topology ! create a new communicator using MPI Topology
call MPI_Comm_Size(voltComm, commSize, ierr) call MPI_Comm_Size(voltComm, commSize, ierr)
@@ -383,11 +378,12 @@ module gamCouple_mpi_V2G
end subroutine end subroutine
subroutine gamCplMpiVWriteRestart(App) subroutine gamCplMpiVWriteRestart(App, Nres)
class(gamCouplerMpi_volt_T), intent(inout) :: App class(gamCouplerMpi_volt_T), intent(inout) :: App
integer, intent(in) :: nRes
! write only my own restart data ! write only my own restart data
call writeGamCouplerRestart(App) call writeGamCouplerRestart(App, nRes)
end subroutine end subroutine
@@ -414,18 +410,20 @@ module gamCouple_mpi_V2G
end subroutine end subroutine
subroutine gamCplMpiVWriteFileOutput(App) subroutine gamCplMpiVWriteFileOutput(App, nStep)
class(gamCouplerMpi_volt_T), intent(inout) :: App class(gamCouplerMpi_volt_T), intent(inout) :: App
integer, intent(in) :: nStep
! write ony my own file output ! write ony my own file output
call writeCouplerFileOutput(App) call writeCouplerFileOutput(App, nStep)
end subroutine end subroutine
subroutine gamCplMpiVWriteSlimFileOutput(App) subroutine gamCplMpiVWriteSlimFileOutput(App, nStep)
class(gamCouplerMpi_volt_T), intent(inout) :: App class(gamCouplerMpi_volt_T), intent(inout) :: App
integer, intent(in) :: nStep
call gamCplMpiVWriteFileOutput(App) call gamCplMpiVWriteFileOutput(App, nStep)
end subroutine end subroutine
@@ -468,34 +466,35 @@ module gamCouple_mpi_V2G
! send initial coupling time to Gamera ! send initial coupling time to Gamera
call sendCplTimeMpi(App, voltApp%DeepT) call sendCplTimeMpi(App, voltApp%DeepT)
! perform initial coupling to collect data on voltron
call recvGameraCplDataMpi(App)
! over-ride IO parameters on gamera during gamera's IO init subroutine
call mpi_bcast(App%Model%IO%tRes, 1, MPI_MYFLOAT, App%myRank, App%couplingComm, ierr)
call mpi_bcast(App%Model%IO%dtRes, 1, MPI_MYFLOAT, App%myRank, App%couplingComm, ierr)
call mpi_bcast(App%Model%IO%nRes, 1, MPI_INTEGER, App%myRank, App%couplingComm, ierr)
call mpi_bcast(App%Model%IO%tOut, 1, MPI_MYFLOAT, App%myRank, App%couplingComm, ierr)
call mpi_bcast(App%Model%IO%dtOut, 1, MPI_MYFLOAT, App%myRank, App%couplingComm, ierr)
call mpi_bcast(App%Model%IO%nOut, 1, MPI_INTEGER, App%myRank, App%couplingComm, ierr)
end subroutine end subroutine
subroutine gamCplMpiVUpdateMhdData(App, voltApp) subroutine gamCplMpiVStartUpdateMhdData(App, voltApp)
class(gamCouplerMpi_volt_T), intent(inout) :: App class(gamCouplerMpi_volt_T), intent(inout) :: App
class(voltApp_T), intent(inout) :: voltApp class(voltApp_T), intent(inout) :: voltApp
call Tic("Coupling", .true.) call Tic("Coupling", .true.)
if(App%firstRecv) then call sendGameraCplDataMpi(App, voltApp%DeepT)
! need data to process call Toc("Coupling", .true.)
App%firstRecv = .false.
call recvGameraCplDataMpi(App)
return
endif
if(App%doSerialVoltron) then end subroutine
! doing serial
call sendGameraCplDataMpi(App, voltApp%DeepT)
call recvGameraCplDataMpi(App)
else
! doing asynchronous
if(App%firstSend) then
call sendGameraCplDataMpi(App, voltApp%DeepT)
App%firstSend = .false.
endif
call recvGameraCplDataMpi(App) subroutine gamCplMpiVFinishUpdateMhdData(App, voltApp)
call sendGameraCplDataMpi(App, voltApp%DeepT) class(gamCouplerMpi_volt_T), intent(inout) :: App
endif class(voltApp_T), intent(inout) :: voltApp
call Tic("Coupling", .true.)
call recvGameraCplDataMpi(App)
call Toc("Coupling", .true.) call Toc("Coupling", .true.)
end subroutine end subroutine

View File

@@ -57,7 +57,6 @@ module voltapp_mpi
END SELECT END SELECT
endif endif
! read helper XML options ! read helper XML options
if(present(optFilename)) then if(present(optFilename)) then
inpXML = optFilename inpXML = optFilename
@@ -190,6 +189,9 @@ module voltapp_mpi
call mpi_Abort(MPI_COMM_WORLD, 1, ierr) call mpi_Abort(MPI_COMM_WORLD, 1, ierr)
endif endif
! additional MPI options
call xmlInp%Set_Val(vApp%doSerialMHD,"coupling/doSerial",.false.)
! now initialize basic voltron structures from gamera data ! now initialize basic voltron structures from gamera data
if(present(optFilename)) then if(present(optFilename)) then
call initVoltron(vApp, optFilename) call initVoltron(vApp, optFilename)
@@ -260,6 +262,14 @@ module voltapp_mpi
call mpi_Abort(MPI_COMM_WORLD, 1, ierr) call mpi_Abort(MPI_COMM_WORLD, 1, ierr)
end if end if
endif endif
if(.not. vApp%doserialMHD) then
! prepare data for MHD before first loop since MHD is concurrent
! call base update function with local data
call Tic("DeepUpdate")
call DeepUpdate_mpi(vApp)
call Toc("DeepUpdate")
endif
end subroutine initVoltron_mpi end subroutine initVoltron_mpi
@@ -267,22 +277,28 @@ module voltapp_mpi
subroutine stepVoltron_mpi(vApp) subroutine stepVoltron_mpi(vApp)
type(voltAppMpi_T), intent(inout) :: vApp type(voltAppMpi_T), intent(inout) :: vApp
if(vApp%time >= vApp%DeepT) then ! loop always starts with updated Gamera data
! advance to the NEXT coupling interval
vApp%DeepT = vApp%DeepT + vApp%DeepDT
endif
! this will step coupled Gamera ! if gamera running concurrently, start it not
call vApp%gApp%UpdateMhdData(vApp) if(.not. vApp%doSerialMHD) call vApp%gApp%StartUpdateMhdData(vApp)
! call base update function with local data ! call base update function with local data
call Tic("DeepUpdate") call Tic("DeepUpdate")
call DeepUpdate_mpi(vApp) call DeepUpdate_mpi(vApp)
call Toc("DeepUpdate") call Toc("DeepUpdate")
! if Gamera running serially, start it now
if(vApp%doSerialMHD) call vApp%gApp%StartUpdateMhdData(vApp)
! get Gamera results
call vApp%gApp%FinishUpdateMhdData(vApp)
! step complete ! step complete
vApp%time = vApp%DeepT vApp%time = vApp%DeepT
! update the next predicted coupling interval
vApp%DeepT = vApp%DeepT + vApp%DeepDT
end subroutine stepVoltron_mpi end subroutine stepVoltron_mpi
!---------- !----------

View File

@@ -38,14 +38,14 @@ module voltapp
logical :: doSpin,isK,doRestart logical :: doSpin,isK,doRestart
integer :: nRes integer :: nRes
associate(gApp=>vApp%gApp)
if(.not. allocated(vApp%gApp)) then if(.not. allocated(vApp%gApp)) then
! non-mpi voltron uses non-mpi local coupled gamera ! non-mpi voltron uses non-mpi local coupled gamera
! but don't over-ride if someone else allocated first ! but don't over-ride if someone else allocated first
allocate(gamCoupler_T :: vApp%gApp) allocate(gamCoupler_T :: vApp%gApp)
endif endif
associate(gApp=>vApp%gApp)
if(present(optFilename)) then if(present(optFilename)) then
! read from the prescribed file ! read from the prescribed file
inpXML = optFilename inpXML = optFilename
@@ -86,7 +86,7 @@ module voltapp
call SetOMP(xmlInp) call SetOMP(xmlInp)
!initialize coupled Gamera !initialize coupled Gamera
call xmlInp%SetRootStr('Kaiju/Gamera') call xmlInp%SetRootStr('Kaiju/Gamera')
gApp%gOptions%userInitFunc => vApp%vOptions%gamUserInitFunc gApp%gOptions%userInitFunc => vApp%vOptions%gamUserInitFunc
call gApp%InitModel(xmlInp) call gApp%InitModel(xmlInp)
call gApp%InitIO(xmlInp) call gApp%InitIO(xmlInp)
@@ -182,8 +182,8 @@ module voltapp
tsMJD%wID = vApp%tilt%wID tsMJD%wID = vApp%tilt%wID
call tsMJD%initTS("MJD",doLoudO=.false.) call tsMJD%initTS("MJD",doLoudO=.false.)
vApp%MJD = T2MJD(vApp%time,tsMJD%evalAt(0.0_rp)) vApp%MJD = T2MJD(vApp%time,tsMJD%evalAt(0.0_rp))
!Set first deep coupling (defaulting to coupling right away since shallow is part of deep now) !Set first deep coupling (defaulting to coupling one step in the future)
call xmlInp%Set_Val(vApp%DeepT, "coupling/tCouple", vApp%time) call xmlInp%Set_Val(vApp%DeepT, "coupling/tCouple", vApp%time+vApp%DeepDT)
endif endif
if (vApp%doDeep) then if (vApp%doDeep) then
@@ -261,17 +261,6 @@ module voltapp
endif endif
endif endif
!Do first coupling
if (vApp%doDeep .and. (vApp%time>=vApp%DeepT)) then
call Tic("DeepCoupling", .true.)
call DeepUpdate(vApp,gApp)
call Toc("DeepCoupling", .true.)
endif
!Recalculate timestep
gApp%Model%dt = CalcDT(gApp%Model,gApp%Grid,gApp%State)
if (gApp%Model%dt0<TINY) gApp%Model%dt0 = gApp%Model%dt
!Bring overview info !Bring overview info
if (vApp%isLoud) call printConfigStamp() if (vApp%isLoud) call printConfigStamp()
@@ -291,20 +280,23 @@ module voltapp
subroutine stepVoltron(vApp) subroutine stepVoltron(vApp)
class(voltApp_T), intent(inout) :: vApp class(voltApp_T), intent(inout) :: vApp
! advance to the NEXT coupling interval ! loop always starts with updated Gamera data
vApp%DeepT = vApp%DeepT + vApp%DeepDT
! this will step coupled Gamera
call vApp%gApp%UpdateMhdData(vApp)
! call base update function with local data ! call base update function with local data
call Tic("DeepUpdate") call Tic("DeepUpdate")
call DeepUpdate(vApp, vApp%gApp) call DeepUpdate(vApp, vApp%gApp)
call Toc("DeepUpdate") call Toc("DeepUpdate")
! this will step coupled Gamera
call vApp%gApp%StartUpdateMhdData(vApp)
call vApp%gApp%FinishUpdateMhdData(vApp)
! step complete ! step complete
vApp%time = vApp%DeepT vApp%time = vApp%DeepT
! update the next predicted coupling interval
vApp%DeepT = vApp%DeepT + vApp%DeepDT
end subroutine stepVoltron end subroutine stepVoltron
!Initialize Voltron app based on Gamera data !Initialize Voltron app based on Gamera data

View File

@@ -177,7 +177,7 @@ module voltio
class(voltApp_T), intent(inout) :: vApp class(voltApp_T), intent(inout) :: vApp
!Write Gamera restart !Write Gamera restart
call gApp%WriteRestart() call gApp%WriteRestart(vApp%IO%nRes)
!Write Voltron restart data !Write Voltron restart data
call resOutputVOnly(vApp,gApp) call resOutputVOnly(vApp,gApp)
@@ -310,7 +310,7 @@ module voltio
class(voltApp_T), intent(inout) :: vApp class(voltApp_T), intent(inout) :: vApp
!Write gamera data !Write gamera data
call gApp%WriteFileOutput() call gApp%WriteFileOutput(vApp%IO%nOut)
!Write voltron data !Write voltron data
call fOutputVOnly(vApp,gApp) call fOutputVOnly(vApp,gApp)

View File

@@ -21,14 +21,15 @@ submodule (volttypes) volttypessub
end subroutine end subroutine
module subroutine gamCplWriteRestart(App) module subroutine gamCplWriteRestart(App, nRes)
class(gamCoupler_T), intent(inout) :: App class(gamCoupler_T), intent(inout) :: App
integer, intent(in) :: nRes
! write parent's restart data ! write parent's restart data
call gamWriteRestart(App) call gamWriteRestart(App, nRes)
! then my own ! then my own
call writeGamCouplerRestart(App) call writeGamCouplerRestart(App, nRes)
end subroutine end subroutine
@@ -61,21 +62,23 @@ submodule (volttypes) volttypessub
end subroutine end subroutine
module subroutine gamCplWriteFileOutput(App) module subroutine gamCplWriteFileOutput(App, nStep)
class(gamCoupler_T), intent(inout) :: App class(gamCoupler_T), intent(inout) :: App
integer, intent(in) :: nStep
! write parent's file ! write parent's file
call gamWriteFileOutput(App) call gamWriteFileOutput(App, nStep)
! then my own ! then my own
call writeCouplerFileOutput(App) call writeCouplerFileOutput(App, nStep)
end subroutine end subroutine
module subroutine gamCplWriteSlimFileOutput(App) module subroutine gamCplWriteSlimFileOutput(App, nStep)
class(gamCoupler_T), intent(inout) :: App class(gamCoupler_T), intent(inout) :: App
integer, intent(in) :: nStep
call gamCplWriteFileOutput(App) call gamCplWriteFileOutput(App, nStep)
end subroutine end subroutine
@@ -95,9 +98,22 @@ submodule (volttypes) volttypessub
call tsMJD%initTS("MJD",doLoudO=.false.) call tsMJD%initTS("MJD",doLoudO=.false.)
App%Model%MJD0 = tsMJD%evalAt(0.0_rp) !Evaluate at T=0 App%Model%MJD0 = tsMJD%evalAt(0.0_rp) !Evaluate at T=0
call ioSync(voltApp%IO, App%Model%IO, 1.0_rp/App%Model%Units%gT0)
App%Model%IO%nRes = voltApp%IO%nRes
App%Model%IO%nOut = voltApp%IO%nOut
end subroutine end subroutine
module subroutine gamUpdateMhdData(App, voltApp) module subroutine gamStartUpdateMhdData(App, voltApp)
class(gamCoupler_T), intent(inout) :: App
class(voltApp_T), intent(inout) :: voltApp
! for local coupling this function doesn't do anything
! all of the work is in gamFinishUpdateMhdData
end subroutine
module subroutine gamFinishUpdateMhdData(App, voltApp)
class(gamCoupler_T), intent(inout) :: App class(gamCoupler_T), intent(inout) :: App
class(voltApp_T), intent(inout) :: voltApp class(voltApp_T), intent(inout) :: voltApp
@@ -110,5 +126,4 @@ submodule (volttypes) volttypessub
end subroutine end subroutine
end submodule end submodule

View File

@@ -229,7 +229,7 @@ contains
type(voltApp_T) :: voltronApp type(voltApp_T) :: voltronApp
character(len=strLen) :: caseInput = 'cmiD.xml' character(len=strLen) :: caseInput = 'cmiD.xml'
call caseTestInit(voltronApp%gApp, caseInput) voltronApp%vOptions%gamUserInitFunc => initUser
call initVoltron(voltronApp, caseInput) call initVoltron(voltronApp, caseInput)
! run for one coupling interval ! run for one coupling interval

View File

@@ -5,7 +5,7 @@ module testMpiFields
implicit none implicit none
type(gamAppMpi_T), pointer :: gamAppMpi type(gamAppMpi_T), allocatable :: gamAppMpi
contains contains
@@ -17,6 +17,8 @@ contains
call setMpiReal() call setMpiReal()
allocate(gamAppMpi)
! set options for gamera app ! set options for gamera app
gamAppMpi%gOptions%userInitFunc => initUser gamAppMpi%gOptions%userInitFunc => initUser
gamAppMpi%gOptionsMpi%gamComm = getMpiF08Communicator(this) gamAppMpi%gOptionsMpi%gamComm = getMpiF08Communicator(this)
@@ -38,7 +40,7 @@ contains
class (MpiTestMethod), intent(inout) :: this class (MpiTestMethod), intent(inout) :: this
deallocate(gamAppMpi) deallocate(gamAppMpi)
gamAppMpi => null()
end subroutine teardown end subroutine teardown
subroutine copyFaces4(var,is,ie,js,je,ks,ke) subroutine copyFaces4(var,is,ie,js,je,ks,ke)

View File

@@ -20,18 +20,6 @@ contains
subroutine lastSerial() subroutine lastSerial()
end subroutine lastSerial end subroutine lastSerial
subroutine caseTestInit(gameraApp, caseFile)
class(gamApp_T), intent(inout) :: gameraApp
character(len=*), intent(in) :: caseFile
type(XML_Input_T) :: xmlInp
gameraApp%gOptions%userInitFunc => initUser
xmlInp = New_XML_Input(trim(caseFile),'Kaiju',.true.)
call gameraApp%InitModel(xmlInp)
end subroutine
@test @test
subroutine testZeroInput() subroutine testZeroInput()
! testing that an input of all zeroes gets output of all zeroes ! testing that an input of all zeroes gets output of all zeroes
@@ -40,8 +28,7 @@ contains
character(len=strLen) :: caseInput = 'cmiD.xml' character(len=strLen) :: caseInput = 'cmiD.xml'
write(*,*) 'Doing testZeroInput ...' write(*,*) 'Doing testZeroInput ...'
call caseTestInit(voltronApp%gApp, caseInput) voltronApp%vOptions%gamUserInitFunc => initUser
call initVoltron(voltronApp, caseInput) call initVoltron(voltronApp, caseInput)
call convertGameraToRemix(voltronApp%mhd2mix, voltronApp%gApp, voltronApp%remixApp) call convertGameraToRemix(voltronApp%mhd2mix, voltronApp%gApp, voltronApp%remixApp)
@@ -78,8 +65,7 @@ contains
character(len=strLen) :: caseInput = 'cmiD.xml' character(len=strLen) :: caseInput = 'cmiD.xml'
write(*,*) 'Doing testConstantSolution ...' write(*,*) 'Doing testConstantSolution ...'
call caseTestInit(voltronApp%gApp, caseInput) voltronApp%vOptions%gamUserInitFunc => initUser
call initVoltron(voltronApp, caseInput) call initVoltron(voltronApp, caseInput)
call convertGameraToRemix(voltronApp%mhd2mix, voltronApp%gApp, voltronApp%remixApp) call convertGameraToRemix(voltronApp%mhd2mix, voltronApp%gApp, voltronApp%remixApp)
@@ -116,8 +102,7 @@ contains
real(rp) :: thetaMin, thetaDelta real(rp) :: thetaMin, thetaDelta
write(*,*) 'Doing testAzimuthallyDependentFAC ...' write(*,*) 'Doing testAzimuthallyDependentFAC ...'
call caseTestInit(voltronApp%gApp, caseInput) voltronApp%vOptions%gamUserInitFunc => initUser
call initVoltron(voltronApp, caseInput) call initVoltron(voltronApp, caseInput)
call convertGameraToRemix(voltronApp%mhd2mix, voltronApp%gApp, voltronApp%remixApp) call convertGameraToRemix(voltronApp%mhd2mix, voltronApp%gApp, voltronApp%remixApp)

View File

@@ -60,14 +60,6 @@ date
echo "Voltron Tests Complete" echo "Voltron Tests Complete"
echo | tail -n 3 ./voltTests.out echo | tail -n 3 ./voltTests.out
echo ""
echo "Running RCM Tests"
date
./rcmTests > rcmTests.out
date
echo "RCM Tests Complete"
echo | tail -n 3 ./rcmTests.out
echo "" echo ""
echo "Running Base MPI Tests" echo "Running Base MPI Tests"
date date

View File

@@ -26,14 +26,11 @@ contains
real(rp) testValue real(rp) testValue
type(XML_Input_T) :: xmlInp type(XML_Input_T) :: xmlInp
associate(gameraApp=>voltronapp%gApp) voltronApp%vOptions%gamUserInitFunc => initUser
gameraApp%gOptions%userInitFunc => initUser
xmlInp = New_XML_Input(trim(caseInput),'Kaiju',.true.)
call gameraApp%InitModel(xmlInp)
call initVoltron(voltronApp, caseInput) call initVoltron(voltronApp, caseInput)
associate(gameraApp=>voltronApp%gApp)
! create a dipole field in Gamera. This code is copied from prob.F90 ! create a dipole field in Gamera. This code is copied from prob.F90
Axyz => VP_Dipole Axyz => VP_Dipole
call VectorPot2Flux(gameraApp%Model,gameraApp%Grid,gameraApp%State,Axyz) call VectorPot2Flux(gameraApp%Model,gameraApp%Grid,gameraApp%State,Axyz)

View File

@@ -36,9 +36,7 @@ contains
RIn = 1.0 RIn = 1.0
Psi0 = 10.0 Psi0 = 10.0
voltronApp%gApp%gOptions%userInitFunc => initUser voltronApp%vOptions%gamUserInitFunc => initUser
xmlInp = New_XML_Input(trim(caseInput),'Kaiju',.true.)
call initVoltron(voltronApp, caseInput) call initVoltron(voltronApp, caseInput)
associate(rApp=>voltronApp%remixApp) associate(rApp=>voltronApp%remixApp)

View File

@@ -86,24 +86,12 @@ contains
end associate end associate
end subroutine checkChimp end subroutine checkChimp
subroutine caseTestInit(gameraApp, caseFile)
class(gamApp_T), intent(inout) :: gameraApp
character(len=*), intent(in) :: caseFile
type(XML_Input_T) :: xmlInp
gameraApp%gOptions%userInitFunc => initUser
xmlInp = New_XML_Input(trim(caseFile),'Kaiju',.true.)
call gameraApp%InitModel(xmlInp)
end subroutine
@test @test
subroutine testEarth() subroutine testEarth()
type(voltApp_T) :: vApp type(voltApp_T) :: vApp
character(len=strLen) :: xmlName = 'cmriD_Earth.xml' character(len=strLen) :: xmlName = 'cmriD_Earth.xml'
call caseTestInit(vApp%gApp, xmlName) vApp%vOptions%gamUserInitFunc => initUser
call initVoltron(vApp, xmlName) call initVoltron(vApp, xmlName)
! Run tests ! Run tests
@@ -121,7 +109,7 @@ contains
character(len=strLen) :: xmlName = 'cmriD_Jupiter.xml' character(len=strLen) :: xmlName = 'cmriD_Jupiter.xml'
real(rp) :: jupCorot = -2.5*1702.9*92.0 real(rp) :: jupCorot = -2.5*1702.9*92.0
call caseTestInit(vApp%gApp, xmlName) vApp%vOptions%gamUserInitFunc => initUser
call initVoltron(vApp, xmlName) call initVoltron(vApp, xmlName)
! Run tests ! Run tests
@@ -140,7 +128,7 @@ contains
type(XML_Input_T) :: inpXML type(XML_Input_T) :: inpXML
real(rp) :: corotXML real(rp) :: corotXML
call caseTestInit(vApp%gApp, xmlName) vApp%vOptions%gamUserInitFunc => initUser
call initVoltron(vApp, xmlName) call initVoltron(vApp, xmlName)
! For this test, we should get corot potential right from xml cause we don't have a real pre-set value for a fake planet. ! For this test, we should get corot potential right from xml cause we don't have a real pre-set value for a fake planet.

View File

@@ -28,13 +28,11 @@ contains
character(len=strLen) :: checkMessage character(len=strLen) :: checkMessage
type(XML_Input_T) :: xmlInp type(XML_Input_T) :: xmlInp
associate(gameraApp=>voltronApp%gApp) voltronApp%vOptions%gamUserInitFunc => initUser
gameraApp%gOptions%userInitFunc => initUser
xmlInp = New_XML_Input(trim(caseInput),'Kaiju',.true.)
call initVoltron(voltronApp, caseInput) call initVoltron(voltronApp, caseInput)
associate(gameraApp=>voltronApp%gApp)
! set specific values to gas and magFlux ! set specific values to gas and magFlux
do k=gameraApp%Grid%ks,gameraApp%Grid%ke do k=gameraApp%Grid%ks,gameraApp%Grid%ke
do r=1,gameraApp%Model%Ring%NumR do r=1,gameraApp%Model%Ring%NumR

View File

@@ -69,7 +69,8 @@ contains
real(rp), intent(in) :: tFin real(rp), intent(in) :: tFin
if(allocated(gamCplMpi)) then if(allocated(gamCplMpi)) then
call gamCplMpi%AdvanceModel(tFin-gamCplMpi%Model%t) ! adjust tFin time to gamera units
call gamCplMpi%AdvanceModel(tFin/gamCplMpi%Model%Units%gT0 - gamCplMpi%Model%t)
else else
do while (voltAppMpi%time < tFin) do while (voltAppMpi%time < tFin)
call stepVoltron_mpi(voltAppMpi) call stepVoltron_mpi(voltAppMpi)
@@ -96,10 +97,8 @@ contains
SELECT type(cpl=>voltAppMpi%gApp) SELECT type(cpl=>voltAppMpi%gApp)
TYPE IS (gamCouplerMpi_volt_T) TYPE IS (gamCouplerMpi_volt_T)
call endVoltronWaits(voltAppMpi) call endVoltronWaits(voltAppMpi)
cpl%doSerialVoltron = .true. voltAppMPi%doSerialMHD = .true.
cpl%doAsyncCoupling = .false. cpl%doAsyncCoupling = .false.
cpl%firstRecv = .true.
cpl%firstSend = .true.
CLASS DEFAULT CLASS DEFAULT
@assertTrue(.false., "Voltron Allocated non-mpi Gamera coupler for MPI Voltron Coupling Test. Failure") @assertTrue(.false., "Voltron Allocated non-mpi Gamera coupler for MPI Voltron Coupling Test. Failure")
ENDSELECT ENDSELECT
@@ -128,10 +127,8 @@ contains
SELECT type(cpl=>voltAppMpi%gApp) SELECT type(cpl=>voltAppMpi%gApp)
TYPE IS (gamCouplerMpi_volt_T) TYPE IS (gamCouplerMpi_volt_T)
call endVoltronWaits(voltAppMpi) call endVoltronWaits(voltAppMpi)
cpl%doSerialVoltron = .false. voltAppMpi%doSerialMHD = .false.
cpl%doAsyncCoupling = .false. cpl%doAsyncCoupling = .false.
cpl%firstRecv = .true.
cpl%firstSend = .true.
CLASS DEFAULT CLASS DEFAULT
@assertTrue(.false., "Voltron Allocated non-mpi Gamera coupler for MPI Voltron Coupling Test. Failure") @assertTrue(.false., "Voltron Allocated non-mpi Gamera coupler for MPI Voltron Coupling Test. Failure")
ENDSELECT ENDSELECT
@@ -160,10 +157,8 @@ contains
SELECT type(cpl=>voltAppMpi%gApp) SELECT type(cpl=>voltAppMpi%gApp)
TYPE IS (gamCouplerMpi_volt_T) TYPE IS (gamCouplerMpi_volt_T)
call endVoltronWaits(voltAppMpi) call endVoltronWaits(voltAppMpi)
cpl%doSerialVoltron = .false. voltAppMpi%doSerialMHD = .false.
cpl%doAsyncCoupling = .true. cpl%doAsyncCoupling = .true.
cpl%firstRecv = .true.
cpl%firstSend = .true.
CLASS DEFAULT CLASS DEFAULT
@assertTrue(.false., "Voltron Allocated non-mpi Gamera coupler for MPI Voltron Coupling Test. Failure") @assertTrue(.false., "Voltron Allocated non-mpi Gamera coupler for MPI Voltron Coupling Test. Failure")
ENDSELECT ENDSELECT
@@ -193,10 +188,8 @@ contains
SELECT type(cpl=>voltAppMpi%gApp) SELECT type(cpl=>voltAppMpi%gApp)
TYPE IS (gamCouplerMpi_volt_T) TYPE IS (gamCouplerMpi_volt_T)
call endVoltronWaits(voltAppMpi) call endVoltronWaits(voltAppMpi)
cpl%doSerialVoltron = .false. voltAppMpi%doSerialMHD = .false.
cpl%doAsyncCoupling = .true. cpl%doAsyncCoupling = .true.
cpl%firstRecv = .true.
cpl%firstSend = .true.
CLASS DEFAULT CLASS DEFAULT
@assertTrue(.false., "Voltron Allocated non-mpi Gamera coupler for MPI Voltron Coupling Test. Failure") @assertTrue(.false., "Voltron Allocated non-mpi Gamera coupler for MPI Voltron Coupling Test. Failure")
ENDSELECT ENDSELECT
@@ -238,10 +231,8 @@ contains
SELECT type(cpl=>voltAppMpi%gApp) SELECT type(cpl=>voltAppMpi%gApp)
TYPE IS (gamCouplerMpi_volt_T) TYPE IS (gamCouplerMpi_volt_T)
call endVoltronWaits(voltAppMpi) call endVoltronWaits(voltAppMpi)
cpl%doSerialVoltron = .false. voltAppMpi%doSerialMHD = .false.
cpl%doAsyncCoupling = .true. cpl%doAsyncCoupling = .true.
cpl%firstRecv = .true.
cpl%firstSend = .true.
CLASS DEFAULT CLASS DEFAULT
@assertTrue(.false., "Voltron Allocated non-mpi Gamera coupler for MPI Voltron Coupling Test. Failure") @assertTrue(.false., "Voltron Allocated non-mpi Gamera coupler for MPI Voltron Coupling Test. Failure")
ENDSELECT ENDSELECT
@@ -296,10 +287,8 @@ contains
SELECT type(cpl=>voltAppMpi%gApp) SELECT type(cpl=>voltAppMpi%gApp)
TYPE IS (gamCouplerMpi_volt_T) TYPE IS (gamCouplerMpi_volt_T)
call endVoltronWaits(voltAppMpi) call endVoltronWaits(voltAppMpi)
cpl%doSerialVoltron = .false. voltAppMpi%doSerialMHD = .false.
cpl%doAsyncCoupling = .true. cpl%doAsyncCoupling = .true.
cpl%firstRecv = .true.
cpl%firstSend = .true.
CLASS DEFAULT CLASS DEFAULT
@assertTrue(.false., "Voltron Allocated non-mpi Gamera coupler for MPI Voltron Coupling Test. Failure") @assertTrue(.false., "Voltron Allocated non-mpi Gamera coupler for MPI Voltron Coupling Test. Failure")
ENDSELECT ENDSELECT

View File

@@ -70,7 +70,8 @@ contains
logical :: helperQuit logical :: helperQuit
if(allocated(gamCplMpi)) then if(allocated(gamCplMpi)) then
call gamCplMpi%AdvanceModel(gamCplMpi%Model%tFin-gamCplMpi%Model%t) ! adjust tFin time to gamera units
call gamCplMpi%AdvanceModel(gamCplMpi%Model%tFin - gamCplMpi%Model%t)
else else
if(voltAppMpi%amHelper) then if(voltAppMpi%amHelper) then
helperQuit = .false. helperQuit = .false.

View File

@@ -413,9 +413,7 @@ contains
END SELECT END SELECT
endif endif
do while (gamCplMpi%Model%t < 30.0) call gamCplMpi%AdvanceModel(30.0/gamCplMpi%Model%Units%gT0 - gamCplMpi%Model%t)
call gamCplMpi%AdvanceModel(30.0-gamCplMpi%Model%t)
end do
if(gamCplMpi%Grid%hasLowerBC(IDIR)) then if(gamCplMpi%Grid%hasLowerBC(IDIR)) then
SELECT type(iiBC=>gamCplMpi%Grid%externalBCs(INI)%p) SELECT type(iiBC=>gamCplMpi%Grid%externalBCs(INI)%p)