Skip to content

Commit

Permalink
(#349,#55) remove ifdefs, use ind_timesteps flag instead, fixes compi…
Browse files Browse the repository at this point in the history
…ler warnings
  • Loading branch information
danieljprice committed Mar 22, 2023
1 parent 220583e commit f28e853
Show file tree
Hide file tree
Showing 4 changed files with 69 additions and 84 deletions.
5 changes: 5 additions & 0 deletions src/main/config.F90
Original file line number Diff line number Diff line change
Expand Up @@ -334,6 +334,7 @@ module dim
integer :: maxmhdan = 0
integer :: maxdustan = 0
integer :: maxgran = 0
integer :: maxindan = 0

!--------------------
! Phase and gradh sizes - inconsistent with everything else, but keeping to original logic
Expand Down Expand Up @@ -434,6 +435,10 @@ subroutine update_max_sizes(n,ntot)
maxgran = maxgr
#endif

#ifdef IND_TIMESTEPS
maxindan = maxan
#endif

#ifdef RADIATION
maxprad = maxp
maxlum = maxp
Expand Down
66 changes: 29 additions & 37 deletions src/main/initial.F90
Original file line number Diff line number Diff line change
Expand Up @@ -101,7 +101,6 @@ subroutine initialise()

call init_readwrite_dumps()

return
end subroutine initialise

!----------------------------------------------------------------
Expand All @@ -112,7 +111,8 @@ 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,idumpfile
nalpha,mhd,do_radiation,gravity,use_dust,mpi,do_nucleation,&
use_dustgrowth,ind_timesteps,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 @@ -152,29 +152,21 @@ subroutine startrun(infile,logfile,evfile,dumpfile,noread)
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,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 timestep_ind, only:ibinnow,maxbins,init_ibin,istepfrac
use timing, only:get_timings
use part, only:ibin,ibin_old,ibin_wake,alphaind
use readwrite_dumps, only:dt_read_in
#else
use timestep, only:dtcourant,dtforce
#endif
#ifdef STS_TIMESTEPS
use timestep, only:dtdiff
#endif
use timestep_sts, only:sts_initialise
#ifdef DRIVING
use forcing, only:init_forcing
#endif
#ifdef DUST
use dust, only:init_drag
#ifdef DUSTGROWTH
use growth, only:init_growth
#endif
#endif
#ifdef MFLOW
use mf_write, only:mflow_write,mflow_init
use io, only:imflow
Expand Down Expand Up @@ -328,14 +320,14 @@ subroutine startrun(infile,logfile,evfile,dumpfile,noread)
call init_forcing(dumpfile,infile,time)
#endif

#ifdef DUST
call init_drag(ierr)
if (ierr /= 0) call fatal('initial','error initialising drag coefficients')
#ifdef DUSTGROWTH
call init_growth(ierr)
if (ierr /= 0) call fatal('initial','error initialising growth variables')
#endif
#endif
if (use_dust) then
call init_drag(ierr)
if (ierr /= 0) call fatal('initial','error initialising drag coefficients')
if (use_dustgrowth) then
call init_growth(ierr)
if (ierr /= 0) call fatal('initial','error initialising growth variables')
endif
endif
!
!--initialise cooling function
! this will initialise all cooling variables, including if h2chemistry = true
Expand Down Expand Up @@ -377,17 +369,17 @@ subroutine startrun(infile,logfile,evfile,dumpfile,noread)
enddo
endif

#ifdef IND_TIMESTEPS
ibin(:) = 0
ibin_old(:) = 0
ibin_wake(:) = 0
if (dt_read_in) call init_ibin(npart,dtmax)
istepfrac = 0
ibinnow = 0
#else
dtcourant = huge(dtcourant)
dtforce = huge(dtforce)
#endif
if (ind_timesteps) then
ibin(:) = 0
ibin_old(:) = 0
ibin_wake(:) = 0
if (dt_read_in) call init_ibin(npart,dtmax)
istepfrac = 0
ibinnow = 0
else
dtcourant = huge(dtcourant)
dtforce = huge(dtforce)
endif
dtinject = huge(dtinject)

!
Expand Down Expand Up @@ -610,14 +602,14 @@ subroutine startrun(infile,logfile,evfile,dumpfile,noread)
!
!--set initial timestep
!
#ifndef IND_TIMESTEPS
dt = min(dtnew_first,dtinject)
if (id==master) then
write(iprint,*) 'dt(forces) = ',dtforce
write(iprint,*) 'dt(courant) = ',dtcourant
write(iprint,*) 'dt initial = ',dt
if (.not.ind_timesteps) then
dt = min(dtnew_first,dtinject)
if (id==master) then
write(iprint,*) 'dt(forces) = ',dtforce
write(iprint,*) 'dt(courant) = ',dtcourant
write(iprint,*) 'dt initial = ',dt
endif
endif
#endif
!
!--Calculate current centre of mass
!
Expand Down
80 changes: 35 additions & 45 deletions src/main/part.F90
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ module part
!
use dim, only:ndim,maxp,maxsts,ndivcurlv,ndivcurlB,maxvxyzu,maxalpha,&
maxptmass,maxdvdx,nsinkproperties,mhd,maxmhd,maxBevol,&
maxp_h2,nabundances,periodic,&
maxp_h2,maxindan,nabundances,periodic,ind_timesteps,&
maxgrav,ngradh,maxtypes,h2chemistry,gravity,maxp_dustfrac,&
use_dust,use_dustgrowth,lightcurve,maxlum,nalpha,maxmhdni, &
maxp_growth,maxdusttypes,maxdustsmall,maxdustlarge, &
Expand Down Expand Up @@ -283,15 +283,11 @@ module part
real, allocatable :: Bpred(:,:)
real, allocatable :: dustproppred(:,:)
real, allocatable :: radpred(:,:)
#ifdef IND_TIMESTEPS
integer(kind=1), allocatable :: ibin(:)
integer(kind=1), allocatable :: ibin_old(:)
integer(kind=1), allocatable :: ibin_wake(:)
real(kind=4), allocatable :: dt_in(:)
real, allocatable :: twas(:)
#else
integer(kind=1) :: ibin_wake(1)
#endif

integer(kind=1), allocatable :: iphase(:)
integer(kind=1), allocatable :: iphase_soa(:)
Expand Down Expand Up @@ -489,13 +485,11 @@ subroutine allocate_part
call allocate_array('radpred', radpred, maxirad, maxprad)
call allocate_array('drad', drad, maxirad, maxprad)
call allocate_array('radprop', radprop, maxradprop, maxprad)
#ifdef IND_TIMESTEPS
call allocate_array('ibin', ibin, maxan)
call allocate_array('ibin_old', ibin_old, maxan)
call allocate_array('ibin_wake', ibin_wake, maxan)
call allocate_array('dt_in', dt_in, maxan)
call allocate_array('twas', twas, maxan)
#endif
call allocate_array('ibin', ibin, maxindan)
call allocate_array('ibin_old', ibin_old, maxindan)
call allocate_array('ibin_wake', ibin_wake, maxindan)
call allocate_array('dt_in', dt_in, maxindan)
call allocate_array('twas', twas, maxindan)
call allocate_array('iphase', iphase, maxphase)
call allocate_array('iphase_soa', iphase_soa, maxphase)
call allocate_array('gradh', gradh, ngradh, maxgradh)
Expand Down Expand Up @@ -562,13 +556,11 @@ subroutine deallocate_part
if (allocated(dustpred)) deallocate(dustpred)
if (allocated(Bpred)) deallocate(Bpred)
if (allocated(dustproppred)) deallocate(dustproppred)
#ifdef IND_TIMESTEPS
if (allocated(ibin)) deallocate(ibin)
if (allocated(ibin_old)) deallocate(ibin_old)
if (allocated(ibin_wake)) deallocate(ibin_wake)
if (allocated(dt_in)) deallocate(dt_in)
if (allocated(twas)) deallocate(twas)
#endif
if (allocated(nucleation)) deallocate(nucleation)
if (allocated(tau)) deallocate(tau)
if (allocated(gamma_chem)) deallocate(gamma_chem)
Expand Down Expand Up @@ -648,13 +640,13 @@ subroutine init_part
dustgasprop(:,:) = 0.
VrelVf(:) = 0.
#endif
#ifdef IND_TIMESTEPS
ibin(:) = 0
ibin_old(:) = 0
ibin_wake(:) = 0
dt_in(:) = 0.
twas(:) = 0.
#endif
if (ind_timesteps) then
ibin(:) = 0
ibin_old(:) = 0
ibin_wake(:) = 0
dt_in(:) = 0.
twas(:) = 0.
endif

ideadhead = 0
!
Expand Down Expand Up @@ -1168,13 +1160,13 @@ subroutine copy_particle(src,dst,new_part)
if (maxgradh ==maxp) gradh(:,dst) = gradh(:,src)
if (maxphase ==maxp) iphase(dst) = iphase(src)
if (maxgrav ==maxp) poten(dst) = poten(src)
#ifdef IND_TIMESTEPS
ibin(dst) = ibin(src)
ibin_old(dst) = ibin_old(src)
ibin_wake(dst) = ibin_wake(src)
dt_in(dst) = dt_in(src)
twas(dst) = twas(src)
#endif
if (ind_timesteps) then
ibin(dst) = ibin(src)
ibin_old(dst) = ibin_old(src)
ibin_wake(dst) = ibin_wake(src)
dt_in(dst) = dt_in(src)
twas(dst) = twas(src)
endif
if (use_dust) then
dustfrac(:,dst) = dustfrac(:,src)
dustevol(:,dst) = dustevol(:,src)
Expand Down Expand Up @@ -1251,15 +1243,13 @@ subroutine copy_particle_all(src,dst,new_part)
if (maxphase ==maxp) iphase_soa(dst) = iphase_soa(src)
if (maxgrav ==maxp) poten(dst) = poten(src)
if (maxlum ==maxp) luminosity(dst) = luminosity(src)
#ifdef IND_TIMESTEPS
if (maxan==maxp) then
if (maxindan==maxp) then
ibin(dst) = ibin(src)
ibin_old(dst) = ibin_old(src)
ibin_wake(dst) = ibin_wake(src)
dt_in(dst) = dt_in(src)
twas(dst) = twas(src)
endif
#endif
if (use_dust) then
if (maxp_dustfrac==maxp) dustfrac(:,dst) = dustfrac(:,src)
dustevol(:,dst) = dustevol(:,src)
Expand Down Expand Up @@ -1499,13 +1489,13 @@ subroutine fill_sendbuf(i,xtemp)
if (maxgrav==maxp) then
call fill_buffer(xtemp, poten(i),nbuf)
endif
#ifdef IND_TIMESTEPS
call fill_buffer(xtemp,ibin(i),nbuf)
call fill_buffer(xtemp,ibin_old(i),nbuf)
call fill_buffer(xtemp,ibin_wake(i),nbuf)
call fill_buffer(xtemp,dt_in(i),nbuf)
call fill_buffer(xtemp,twas(i),nbuf)
#endif
if (ind_timesteps) then
call fill_buffer(xtemp,ibin(i),nbuf)
call fill_buffer(xtemp,ibin_old(i),nbuf)
call fill_buffer(xtemp,ibin_wake(i),nbuf)
call fill_buffer(xtemp,dt_in(i),nbuf)
call fill_buffer(xtemp,twas(i),nbuf)
endif
call fill_buffer(xtemp,iorig(i),nbuf)
endif
if (nbuf /= ipartbufsize) call fatal('fill_sendbuf','error in send buffer size')
Expand Down Expand Up @@ -1581,13 +1571,13 @@ subroutine unfill_buffer(ipart,xbuf)
if (maxgrav==maxp) then
poten(ipart) = real(unfill_buf(xbuf,j),kind=kind(poten))
endif
#ifdef IND_TIMESTEPS
ibin(ipart) = nint(unfill_buf(xbuf,j),kind=1)
ibin_old(ipart) = nint(unfill_buf(xbuf,j),kind=1)
ibin_wake(ipart) = nint(unfill_buf(xbuf,j),kind=1)
dt_in(ipart) = real(unfill_buf(xbuf,j),kind=kind(dt_in))
twas(ipart) = unfill_buf(xbuf,j)
#endif
if (ind_timesteps) then
ibin(ipart) = nint(unfill_buf(xbuf,j),kind=1)
ibin_old(ipart) = nint(unfill_buf(xbuf,j),kind=1)
ibin_wake(ipart) = nint(unfill_buf(xbuf,j),kind=1)
dt_in(ipart) = real(unfill_buf(xbuf,j),kind=kind(dt_in))
twas(ipart) = unfill_buf(xbuf,j)
endif
iorig(ipart) = nint(unfill_buf(xbuf,j),kind=8)

!--just to be on the safe side, set other things to zero
Expand Down
2 changes: 0 additions & 2 deletions src/main/utils_indtimesteps.F90
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,6 @@ pure real function get_dt(dtmax,ibini)

end function get_dt

#ifdef IND_TIMESTEPS
!----------------------------------------------------------------
!+
! If dt is read in from a dump file, then initialise ibin & ibin_old.
Expand Down Expand Up @@ -158,7 +157,6 @@ subroutine set_active_particles(npart,nactive,nalive,iphase,ibin,xyzh)
endif

end subroutine set_active_particles
#endif

!----------------------------------------------------------------
!+
Expand Down

0 comments on commit f28e853

Please sign in to comment.