Skip to content

Commit

Permalink
Merge pull request danieljprice#352 from jameswurster/master
Browse files Browse the repository at this point in the history
 (timing) added option to create restart dumps if we go > 24h without a dump
  • Loading branch information
danieljprice authored Feb 14, 2023
2 parents 3b19fba + 23c4a5f commit 8a12bf5
Show file tree
Hide file tree
Showing 13 changed files with 187 additions and 107 deletions.
15 changes: 9 additions & 6 deletions docs/DiAL.rst
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,11 @@ Getting started on DiAL (Data Intensive@Leicester, DiRAC cluster at Leicester)
Apply for an account
--------------------

Follow the instructions for how to apply for an account:
https://www2.le.ac.uk/offices/itservices/ithelp/services/hpc/dirac/request-access
| Follow the instructions for how to apply for an account:
| https://www2.le.ac.uk/offices/itservices/ithelp/services/hpc/dirac/request-access
| Be sure to also set up two-factor authentication:
| https://dial3-docs.dirac.ac.uk/Getting_started/connecting_dial3/
First time you log in
---------------------
Expand Down Expand Up @@ -240,7 +243,7 @@ ST/R001014/1. DiRAC is part of the National e-Infrastructure.
More info
---------

More info is available on the following websites:
https://dirac.ac.uk/
https://dirac.ac.uk/resources/#DataIntensive1
https://www630.lamp.le.ac.uk/Getting_started/connecting_dial3/
| More info is available on the following websites:
| https://dirac.ac.uk/
| https://dirac.ac.uk/resources/#DataIntensive1
| https://www630.lamp.le.ac.uk/Getting_started/connecting_dial3/
5 changes: 5 additions & 0 deletions src/main/config.F90
Original file line number Diff line number Diff line change
Expand Up @@ -341,6 +341,11 @@ module dim
integer :: maxphase = 0
integer :: maxgradh = 0

!--------------------
! a place to store the number of the dumpfile; required for restart dumps
!--------------------
integer :: idumpfile = 0

contains

subroutine update_max_sizes(n,ntot)
Expand Down
67 changes: 47 additions & 20 deletions src/main/evolve.F90
Original file line number Diff line number Diff line change
Expand Up @@ -33,13 +33,14 @@ subroutine evol(infile,logfile,evfile,dumpfile)
use io, only:iprint,iwritein,id,master,iverbose,&
flush_warnings,nprocs,fatal,warning
use timestep, only:time,tmax,dt,dtmax,nmax,nout,nsteps,dtextforce,rhomaxnow,&
dtmax_ifactor,dtmax_dratio,check_dtmax_for_decrease
dtmax_ifactor,dtmax_ifactorWT,dtmax_dratio,check_dtmax_for_decrease,&
idtmax_n,idtmax_frac,idtmax_n_next,idtmax_frac_next
use evwrite, only:write_evfile,write_evlog
use energies, only:etot,totmom,angtot,mdust,np_cs_eq_0,np_e_eq_0,hdivBB_xa
use checkconserved, only:etot_in,angtot_in,totmom_in,mdust_in,&
init_conservation_checks,check_conservation_error,&
check_magnetic_stability
use dim, only:maxvxyzu,mhd,periodic
use dim, only:maxvxyzu,mhd,periodic,idumpfile
use fileutils, only:getnextfilename
use options, only:nfulldump,twallmax,nmaxdumps,rhofinal1,iexternalforce,rkill
use readwrite_infile, only:write_infile
Expand Down Expand Up @@ -131,7 +132,7 @@ subroutine evol(infile,logfile,evfile,dumpfile)
logical :: should_conserve_dustmass
logical :: use_global_dt
integer :: j,nskip,nskipped,nevwrite_threshold,nskipped_sink,nsinkwrite_threshold
real, parameter :: xor(3)=0.
character(len=120) :: dumpfile_orig

tprint = 0.
nsteps = 0
Expand Down Expand Up @@ -227,7 +228,7 @@ subroutine evol(infile,logfile,evfile,dumpfile)
! for global timestepping, this is called in the block where at_dump_time==.true.
if (istepfrac==2**nbinmax) then
twallperdump = reduceall_mpi('max', timers(itimer_lastdump)%wall)
call check_dtmax_for_decrease(iprint,dtmax,twallperdump,dtmax_ifactor,dtmax_log_dratio,&
call check_dtmax_for_decrease(iprint,dtmax,twallperdump,dtmax_log_dratio,&
rhomaxold,rhomaxnow,nfulldump,use_global_dt)
endif

Expand Down Expand Up @@ -409,28 +410,48 @@ subroutine evol(infile,logfile,evfile,dumpfile)
!--write to data file if time is right
!
if (at_dump_time) then
#ifndef IND_TIMESTEPS
!
!--Global timesteps: Decrease dtmax if requested (done in step for individual timesteps)
twallperdump = timers(itimer_lastdump)%wall
call check_dtmax_for_decrease(iprint,dtmax,twallperdump,dtmax_log_dratio,&
rhomaxold,rhomaxnow,nfulldump,use_global_dt)
dt = min(dt,dtmax) ! required if decreasing dtmax to ensure that the physically motivated timestep is not too long
#endif

!--modify evfile and logfile names with new number
if ((nout <= 0) .or. (mod(noutput,nout)==0)) then
if (noutput==1) then
evfile = getnextfilename(evfile)
logfile = getnextfilename(logfile)
endif
dumpfile = getnextfilename(dumpfile)
! Update values for restart dumps
if (dtmax_ifactorWT ==0) then
idtmax_n_next = idtmax_n
idtmax_frac_next = idtmax_frac
elseif (dtmax_ifactorWT > 0) then
idtmax_n_next = idtmax_n *dtmax_ifactorWT
idtmax_frac_next = idtmax_frac*dtmax_ifactorWT
elseif (dtmax_ifactorWT < 0) then
idtmax_n_next = -idtmax_n /dtmax_ifactorWT
idtmax_frac_next = -idtmax_frac/dtmax_ifactorWT
endif
idtmax_frac_next = idtmax_frac_next + 1
idtmax_frac_next = mod(idtmax_frac_next,idtmax_n_next)
dumpfile_orig = trim(dumpfile)
if (idtmax_frac==0) then
dumpfile = getnextfilename(dumpfile,idumpfile)
dumpfile_orig = trim(dumpfile)
else
write(dumpfile,'(2a)') dumpfile(:index(dumpfile,'_')-1),'.restart'
endif
writedump = .true.
else
writedump = .false.
endif

!--do not dump dead particles into dump files
if (ideadhead > 0) call shuffle_part(npart)

#ifndef IND_TIMESTEPS
!
!--Global timesteps: Decrease dtmax if requested (done in step for individual timesteps)
twallperdump = timers(itimer_lastdump)%wall
call check_dtmax_for_decrease(iprint,dtmax,twallperdump,dtmax_ifactor,dtmax_log_dratio,&
rhomaxold,rhomaxnow,nfulldump,use_global_dt)
#endif
!
!--get timings since last dump and overall code scaling
! (get these before writing the dump so we can check whether or not we
Expand Down Expand Up @@ -500,7 +521,7 @@ subroutine evol(infile,logfile,evfile,dumpfile)
call increment_timer(itimer_io,t2-t1,tcpu2-tcpu1)

#ifdef LIVE_ANALYSIS
if (id==master) then
if (id==master .and. idtmax_frac==0) then
call do_analysis(dumpfile,numfromfile(dumpfile),xyzh,vxyzu, &
massoftype(igas),npart,time,ianalysis)
endif
Expand Down Expand Up @@ -548,15 +569,21 @@ subroutine evol(infile,logfile,evfile,dumpfile)
call reset_timer(i)
enddo

noutput_dtmax = noutput_dtmax + 1
noutput = noutput + 1
if (idtmax_frac==0) then
noutput = noutput + 1 ! required to determine frequency of full dumps
endif
noutput_dtmax = noutput_dtmax + 1 ! required to adjust tprint; will account for varying dtmax
idtmax_n = idtmax_n_next
idtmax_frac = idtmax_frac_next
tprint = tzero + noutput_dtmax*dtmaxold
nsteplast = nsteps
dumpfile = trim(dumpfile_orig)
if (dtmax_ifactor/=0) then
tzero = tprint - dtmaxold
tprint = tzero + dtmax
noutput_dtmax = 1
dtmax_ifactor = 0
tzero = tprint - dtmaxold
tprint = tzero + dtmax
noutput_dtmax = 1
dtmax_ifactor = 0
dtmax_ifactorWT = 0
endif
endif

Expand Down
4 changes: 2 additions & 2 deletions src/main/evwrite.F90
Original file line number Diff line number Diff line change
Expand Up @@ -336,7 +336,7 @@ end subroutine fill_ev_header
!+
!----------------------------------------------------------------
subroutine write_evfile(t,dt)
use timestep, only:dtmax
use timestep, only:dtmax_user
use energies, only:compute_energies,ev_data_update
use io, only:id,master,ievfile
#ifndef GR
Expand All @@ -354,7 +354,7 @@ subroutine write_evfile(t,dt)
!--fill in additional details that are not calculated in energies.f
#ifndef GR
ev_data(iev_sum,iev_dt) = dt
ev_data(iev_sum,iev_dtx) = dtmax
ev_data(iev_sum,iev_dtx) = dtmax_user
if (iexternalforce==iext_binary) then
ev_data(iev_sum,iev_maccsink(1)) = accretedmass1
ev_data(iev_sum,iev_maccsink(2)) = accretedmass2
Expand Down
18 changes: 15 additions & 3 deletions src/main/initial.F90
Original file line number Diff line number Diff line change
Expand Up @@ -112,7 +112,7 @@ end subroutine initialise
subroutine startrun(infile,logfile,evfile,dumpfile,noread)
use mpiutils, only:reduceall_mpi,barrier_mpi,reduce_in_place_mpi
use dim, only:maxp,maxalpha,maxvxyzu,maxptmass,maxdusttypes, itau_alloc,&
nalpha,mhd,do_radiation,gravity,use_dust,mpi,do_nucleation
nalpha,mhd,do_radiation,gravity,use_dust,mpi,do_nucleation,idumpfile
use deriv, only:derivs
use evwrite, only:init_evfile,write_evfile,write_evlog
use io, only:idisk1,iprint,ievfile,error,iwritein,flush_warnings,&
Expand Down Expand Up @@ -151,11 +151,12 @@ subroutine startrun(infile,logfile,evfile,dumpfile,noread)
use ptmass, only:init_ptmass,get_accel_sink_gas,get_accel_sink_sink, &
h_acc,r_crit,r_crit2,rho_crit,rho_crit_cgs,icreate_sinks, &
r_merge_uncond,r_merge_cond,r_merge_uncond2,r_merge_cond2,r_merge2
use timestep, only:time,dt,dtextforce,C_force,dtmax
use timestep, only:time,dt,dtextforce,C_force,dtmax,dtmax_user,idtmax_n
use timestep_ind, only:istepfrac
use timing, only:get_timings
#ifdef IND_TIMESTEPS
use timestep_ind, only:ibinnow,maxbins,init_ibin
use timing, only:get_timings
use part, only:ibin,ibin_old,ibin_wake,alphaind
use readwrite_dumps, only:dt_read_in
#else
Expand Down Expand Up @@ -218,7 +219,7 @@ subroutine startrun(infile,logfile,evfile,dumpfile,noread)
character(len=*), intent(in) :: infile
character(len=*), intent(out) :: logfile,evfile,dumpfile
logical, intent(in), optional :: noread
integer :: ierr,i,j,nerr,nwarn,ialphaloc,merge_n,merge_ij(maxptmass)
integer :: ierr,i,j,nerr,nwarn,ialphaloc,irestart,merge_n,merge_ij(maxptmass)
real :: poti,dtf,hfactfile,fextv(3)
real :: hi,pmassi,rhoi1
real :: dtsinkgas,dtsinksink,fonrmax,dtphi2,dtnew_first,dtinject
Expand Down Expand Up @@ -274,8 +275,19 @@ subroutine startrun(infile,logfile,evfile,dumpfile,noread)
call warning('initial','WARNINGS from particle data in file',var='# of warnings',ival=nwarn)
endif
if (nerr > 0) call fatal('initial','errors in particle data from file',var='errors',ival=nerr)
!
!--if starting from a restart dump, rename the dumpefile to that of the previous non-restart dump


irestart = index(dumpfile,'.restart')
if (irestart > 0) write(dumpfile,'(2a,I5.5)') dumpfile(:irestart-1),'_',idumpfile
endif
!
!--reset dtmax (required only to permit restart dumps)
!
dtmax_user = dtmax ! the user defined dtmax
dtmax = dtmax/idtmax_n ! dtmax required to satisfy the walltime constraints
!
!--initialise values for non-ideal MHD
!
#ifdef NONIDEALMHD
Expand Down
2 changes: 1 addition & 1 deletion src/main/ptmass.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1646,7 +1646,7 @@ subroutine pt_open_sinkev(num)
9,'spinx', &
10,'spiny', &
11,'spinz', &
12,'macc', &
12,'macc', & ! total mass accreted
13,'fx', &
14,'fy', &
15,'fz', &
Expand Down
41 changes: 25 additions & 16 deletions src/main/readwrite_dumps_fortran.F90
Original file line number Diff line number Diff line change
Expand Up @@ -225,6 +225,7 @@ subroutine write_fulldump_fortran(t,dumpfile,ntotal,iorder,sphNG)
use dump_utils, only:tag,open_dumpfile_w,allocate_header,&
free_header,write_header,write_array,write_block_header
use mpiutils, only:reduce_mpi,reduceall_mpi
use timestep, only:idtmax_n,idtmax_frac
#ifdef IND_TIMESTEPS
use timestep, only:dtmax
use part, only:ibin
Expand Down Expand Up @@ -252,12 +253,13 @@ subroutine write_fulldump_fortran(t,dumpfile,ntotal,iorder,sphNG)
integer, parameter :: isteps_sphNG = 0, iphase0 = 0
integer(kind=8) :: ilen(4)
integer :: nums(ndatatypes,4)
integer :: ipass,k,l
integer :: ipass,k,l,ioffset
integer :: ierr,ierrs(30)
integer :: nblocks,nblockarrays,narraylengths
integer(kind=8) :: nparttot
logical :: sphNGdump,write_itype,use_gas
character(len=lenid) :: fileid
character(len=120) :: blankarray
type(dump_h) :: hdr
real, allocatable :: temparr(:)
!
Expand Down Expand Up @@ -305,9 +307,16 @@ subroutine write_fulldump_fortran(t,dumpfile,ntotal,iorder,sphNG)
!
masterthread: if (id==master) then

write(iprint,"(/,/,'--------> TIME = ',g12.4,"// &
"': full dump written to file ',a,' <--------',/)") t,trim(dumpfile)

if (idtmax_frac==0) then
write(iprint,"(/,/,'--------> TIME = ',g12.4,': full dump written to file ',a,' <--------',/)") t,trim(dumpfile)
else
ioffset = max(0,len(trim(dumpfile))-1)
write(blankarray,'(a)') ' '
write(iprint,"(/,/,'--------> TIME = ',g12.4,': full dump written to file ',a,' <--------')") &
t,trim(dumpfile)
write(iprint,"('--------> Writing sub-dumps: ',I4,' of',I4,a,'<--------',/)") &
idtmax_frac,idtmax_n,blankarray(1:ioffset)
endif
call open_dumpfile_w(idump,dumpfile,fileid,ierr)
if (ierr /= 0) then
call error('write_fulldump','error creating new dumpfile '//trim(dumpfile))
Expand Down Expand Up @@ -667,7 +676,6 @@ subroutine read_dump_fortran(dumpfile,tfile,hfactfile,idisk1,iprint,id,nprocs,ie
! open dump file
!
call open_dumpfile_r(idisk1,dumpfile,fileidentr,ierr)

!
! exit with error if file not readable by current routine
!
Expand Down Expand Up @@ -925,6 +933,7 @@ subroutine read_smalldump_fortran(dumpfile,tfile,hfactfile,idisk1,iprint,id,npro
! open dump file
!
call open_dumpfile_r(idisk1,dumpfile,fileidentr,ierr,singleprec=.true.)

if (ierr /= 0) then
call error('read_smalldump',get_error_text(ierr))
if (ierr == ierr_realsize) then
Expand Down Expand Up @@ -1522,12 +1531,12 @@ subroutine fill_header(sphNGdump,t,nparttot,npartoftypetot,nblocks,nptmass,hdr,i
idust,grainsize,graindens,ndusttypes
use checkconserved, only:get_conserv,etot_in,angtot_in,totmom_in,mdust_in
use setup_params, only:rhozero
use timestep, only:dtmax,dtmax0,C_cour,C_force
use timestep, only:dtmax_user,idtmax_n_next,idtmax_frac_next,C_cour,C_force
use externalforces, only:write_headeropts_extern
use boundary, only:xmin,xmax,ymin,ymax,zmin,zmax
use dump_utils, only:reset_header,add_to_rheader,add_to_header,add_to_iheader,num_in_header
use dim, only:use_dust,maxtypes,use_dustgrowth,do_nucleation, &
phantom_version_major,phantom_version_minor,phantom_version_micro,periodic
phantom_version_major,phantom_version_minor,phantom_version_micro,periodic,idumpfile
use units, only:udist,umass,utime,unit_Bfield
use dust_formation, only:write_headeropts_dust_formation

Expand All @@ -1549,6 +1558,9 @@ subroutine fill_header(sphNGdump,t,nparttot,npartoftypetot,nblocks,nptmass,hdr,i
call add_to_iheader(ndustlarge,'ndustlarge',hdr,ierr)
call add_to_iheader(ndustsmall,'ndustsmall',hdr,ierr)
call add_to_iheader(idust,'idust',hdr,ierr)
call add_to_iheader(idtmax_n_next,'idtmax_n',hdr,ierr)
call add_to_iheader(idtmax_frac_next,'idtmax_frac',hdr,ierr)
call add_to_iheader(idumpfile,'idumpfile',hdr,ierr)
call add_to_iheader(phantom_version_major,'majorv',hdr,ierr)
call add_to_iheader(phantom_version_minor,'minorv',hdr,ierr)
call add_to_iheader(phantom_version_micro,'microv',hdr,ierr)
Expand All @@ -1565,12 +1577,7 @@ subroutine fill_header(sphNGdump,t,nparttot,npartoftypetot,nblocks,nptmass,hdr,i

! default real variables
call add_to_rheader(t,'time',hdr,ierr)
call add_to_rheader(dtmax,'dtmax',hdr,ierr)
if (dtmax0 > 0.) then
call add_to_rheader(dtmax0,'dtmax0',hdr,ierr)
else
call add_to_rheader(dtmax, 'dtmax0',hdr,ierr)
endif
call add_to_rheader(dtmax_user,'dtmax',hdr,ierr)
call add_to_rheader(rhozero,'rhozero',hdr,ierr)
if (sphNGdump) then ! number = 23
call add_to_rheader(0.,'escaptot',hdr,ierr)
Expand Down Expand Up @@ -1648,7 +1655,7 @@ end subroutine fill_header
subroutine unfill_rheader(hdr,phantomdump,ntypesinfile,nptmass,&
tfile,hfactfile,alphafile,iprint,ierr)
use io, only:id,master
use dim, only:maxvxyzu,nElements,use_dust,use_dustgrowth,use_krome,do_nucleation
use dim, only:maxvxyzu,nElements,use_dust,use_dustgrowth,use_krome,do_nucleation,idumpfile
use eos, only:extract_eos_from_hdr, read_headeropts_eos
use options, only:ieos,iexternalforce
use part, only:massoftype,Bextx,Bexty,Bextz,mhd,periodic,&
Expand All @@ -1660,7 +1667,7 @@ subroutine unfill_rheader(hdr,phantomdump,ntypesinfile,nptmass,&
use dump_utils, only:extract
use dust, only:grainsizecgs,graindenscgs
use units, only:unit_density,udist
use timestep, only:dtmax0
use timestep, only:idtmax_n,idtmax_frac
use dust_formation, only:read_headeropts_dust_formation
type(dump_h), intent(in) :: hdr
logical, intent(in) :: phantomdump
Expand All @@ -1678,7 +1685,9 @@ subroutine unfill_rheader(hdr,phantomdump,ntypesinfile,nptmass,&
call extract('time',tfile,hdr,ierr)
if (ierr/=0) call extract('gt',tfile,hdr,ierr) ! this is sphNG's label for time
call extract('dtmax',dtmaxi,hdr,ierr)
call extract('dtmax0',dtmax0,hdr,ierr)
call extract('idtmax_n',idtmax_n,hdr,ierr)
call extract('idtmax_frac',idtmax_frac,hdr,ierr)
call extract('idumpfile',idumpfile,hdr,ierr)
call extract('rhozero',rhozero,hdr,ierr)
Bextx = 0.
Bexty = 0.
Expand Down
Loading

0 comments on commit 8a12bf5

Please sign in to comment.