Skip to content

Commit

Permalink
merge pull request #21
Browse files Browse the repository at this point in the history
  • Loading branch information
danieljprice committed Jul 12, 2020
2 parents a8710dc + 75c5cce commit 1db5894
Show file tree
Hide file tree
Showing 8 changed files with 28 additions and 31 deletions.
5 changes: 3 additions & 2 deletions build/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -864,10 +864,11 @@ endif

ifeq ($(SETUP), jet)
# Jet simulation from Price, Tricco & Bate (2012)
FPPFLAGS= -DPERIODIC -DGRAVITY
SETUPFILE= setup_sphereinbox.f90
#ANALYSIS= analysis_jet.f90
ANALYSIS= ${SRCNIMHD} analysis_protostar_environ.F90
PERIODIC=yes
GRAVITY=yes
ISOTHERMAL=yes
MHD=yes
IND_TIMESTEPS=yes
Expand Down Expand Up @@ -963,7 +964,7 @@ endif

ifeq ($(SETUP), testgrav)
# self-gravity unit tests
FPPFLAGS= -DGRAVITY
GRAVITY=yes
KNOWN_SETUP=yes
CONST_ARTRES=yes
CURLV=yes
Expand Down
9 changes: 5 additions & 4 deletions src/main/energies.F90
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ module energies
real, public :: xmom,ymom,zmom
real, public :: totlum
integer, public :: iquantities
integer(kind=8), public :: ndead,np_cs_eq_0,np_e_eq_0
integer(kind=8), public :: ndead,npartall,np_cs_eq_0,np_e_eq_0
integer, public :: iev_time,iev_ekin,iev_etherm,iev_emag,iev_epot,iev_etot,iev_totmom,iev_com(3),&
iev_angmom,iev_rho,iev_dt,iev_dtx,iev_entrop,iev_rmsmach,iev_vrms,iev_rhop(6),&
iev_alpha,iev_B,iev_divB,iev_hdivB,iev_beta,iev_temp,iev_etaar,iev_etao(2),iev_etah(4),&
Expand Down Expand Up @@ -605,9 +605,10 @@ subroutine compute_energies(t)
!$omp end parallel

!--Determing the number of active gas particles
nptot = reduce_fn('+',np)
npgas = reduce_fn('+',npgas)
ndead = npart - nptot
nptot = reduce_fn('+',np)
npgas = reduce_fn('+',npgas)
npartall = reduce_fn('+',npart)
ndead = npartall - nptot
if (nptot > 0) then
dnptot = 1./real(nptot)
else
Expand Down
17 changes: 7 additions & 10 deletions src/main/evwrite.F90
Original file line number Diff line number Diff line change
Expand Up @@ -47,12 +47,12 @@
!+
!--------------------------------------------------------------------------
module evwrite
use io, only: fatal
use io, only: fatal,iverbose
use options, only: iexternalforce
use timestep, only: dtmax_dratio
use externalforces, only: iext_binary,was_accreted
use energies, only: inumev,iquantities,ev_data
use energies, only: ndead
use energies, only: ndead,npartall
use energies, only: gas_only,track_mass,track_lum
use energies, only: iev_sum,iev_max,iev_min,iev_ave
use energies, only: iev_time,iev_ekin,iev_etherm,iev_emag,iev_epot,iev_etot,iev_totmom,iev_com,&
Expand Down Expand Up @@ -427,15 +427,12 @@ subroutine write_evlog(iprint)
character(len=120) :: string,Mdust_label(maxdusttypes)
integer :: i

!***Uncomment this once debugging is complete
! if (ndead > 0 .or. nptmass > 0 .or. icreate_sinks > 0 .or. particles_are_injected) then
! write(iprint,"(1x,4(a,I10))") 'npart=',npart,', n_alive=',npart-ndead,', n_dead_or_accreted=',ndead,', nptmass=',nptmass
! endif
!***Remove the following once debugging is complete
write(iprint,"(1x,4(a,I10))") 'npart=',npart,', n_alive=',npart-ndead,', n_dead_or_accreted=',ndead,', nptmass=',nptmass
if (ndead > 0 .or. nptmass > 0 .or. icreate_sinks > 0 .or. particles_are_injected .or. iverbose > 0) then
write(iprint,"(1x,4(a,I10))") 'npart=',npartall,', n_alive=',npartall-ndead, &
', n_dead_or_accreted=',ndead,', nptmass=',nptmass
endif

write(iprint,"(1x,3('E',a,'=',es10.3,', '),('E',a,'=',es10.3))") &
'tot',etot,'kin',ekin,'therm',etherm,'pot',epot
write(iprint,"(1x,3('E',a,'=',es10.3,', '),('E',a,'=',es10.3))") 'tot',etot,'kin',ekin,'therm',etherm,'pot',epot

if (mhd) write(iprint,"(1x,('E',a,'=',es10.3))") 'mag',emag
if (do_radiation) write(iprint,"(1x,('E',a,'=',es10.3))") 'rad',erad
Expand Down
5 changes: 1 addition & 4 deletions src/main/phantom.F90
Original file line number Diff line number Diff line change
Expand Up @@ -34,13 +34,10 @@ program phantom
use io, only:id,master,nprocs,set_io_unit_numbers,die
use evolve, only:evol
implicit none
integer :: nargs,i,ntests,npass,nfail
integer :: nargs
character(len=120) :: infile,logfile,evfile,dumpfile

id = 0
ntests = 0
npass = 0
nfail = 0

call init_mpi(id,nprocs)
call set_io_unit_numbers
Expand Down
6 changes: 3 additions & 3 deletions src/main/utils_indtimesteps.F90
Original file line number Diff line number Diff line change
Expand Up @@ -385,17 +385,17 @@ subroutine write_binsummary(npart,nbinmax,dtmax,timeperbin,iphase,ibin,xyzh)
endif
enddo over_part

!ninbin(:) = int(reduce_mpi('+',ninbin(:)))
ninbin(:) = reduce_mpi('+',ninbin(:))
ntypesprint = 0
itypelist(:) = 0
do itype=1,maxtypes
!noftypeinbin(:,itype) = int(reduce_mpi('+',noftypeinbin(:,itype)))
noftypeinbin(:,itype) = reduce_mpi('+',noftypeinbin(:,itype))
if (any(noftypeinbin(:,itype) > 0)) then
ntypesprint = ntypesprint + 1
itypelist(ntypesprint) = itype
endif
enddo
ntot = np !reduce_mpi('+',np)
ntot = reduce_mpi('+',np)
timeperbintot(:) = reduce_mpi('+',timeperbin(:))

if (id==master) then
Expand Down
10 changes: 5 additions & 5 deletions src/tests/test_nonidealmhd.F90
Original file line number Diff line number Diff line change
Expand Up @@ -402,7 +402,7 @@ subroutine test_standingshock(ntests,npass)
gamma = 1.0
dt = 2.0d-3
nsteps = 500
t = 0
t = 0.
iverbose = 0
tmax = nsteps*dt
eta_const_type = icnstsemi
Expand Down Expand Up @@ -610,10 +610,10 @@ subroutine test_etaval(ntests,npass)
ion_rays = .true.
ion_thermal = .true.
use_sts = .false.
itmp = 1 ! avoids compiler warning
itmp = 1 ! avoids compiler warning

! initialise eos, & the Nicil library
call init_eos(8,ierr)
call init_eos(ieos,ierr)
call nicil_initialise(real(utime),real(udist),real(umass),real(unit_Bfield),ierr)
!
!--Loop over both sets of calculations
Expand Down Expand Up @@ -649,8 +649,8 @@ subroutine test_etaval(ntests,npass)
tempi = get_temperature(ieos,xyzh(1:3,itmp),rhoi,vxyzu(:,itmp))

print*, ' '
write(*,'(1x,a,3Es18.11)') 'Used rho,B_z,temp (cgs): ',rhoi*unit_density,Bi*unit_Bfield,tempi
write(*,'(1x,a,3Es18.11)') 'eta_ohm, eta_hall, eta_ambi (cgs): ', eta_nimhd(1:3,itmp)*unit_eta
write(*,'(1x,a,3Es18.10)') 'Used rho,B_z,temp (cgs): ',rhoi*unit_density,Bi*unit_Bfield,tempi
write(*,'(1x,a,3Es18.10)') 'eta_ohm, eta_hall, eta_ambi (cgs): ', eta_nimhd(1:3,itmp)*unit_eta
call checkval(eta_nimhd(iohm, itmp)*unit_eta,eta_act(1,k),tol,nerr(3*(k-1)+1),'calculated non-constant eta_ohm')
call checkval(eta_nimhd(ihall,itmp)*unit_eta,eta_act(2,k),tol,nerr(3*(k-1)+2),'calculated non-constant eta_hall')
call checkval(eta_nimhd(iambi,itmp)*unit_eta,eta_act(3,k),tol,nerr(3*(k-1)+3),'calculated non-constant eta_ambi')
Expand Down
5 changes: 3 additions & 2 deletions src/utils/analysis_MWpdf.f90
Original file line number Diff line number Diff line change
Expand Up @@ -45,8 +45,9 @@ subroutine do_analysis(dumpfile,num,xyzh,vxyzu,particlemass,npart,time,iunit)
real :: vx2,vy2,vz2,rhoi,rmsv
real :: rhomean, rho(maxp), hi, pmassi

rhomin = huge(rhomin)
rhomax = 0.
rho = 0.
rhomin = huge(rhomin)
rhomax = 0.
rhomean = 0.
totmass = 0.
print*,'hfact = ',hfact
Expand Down
2 changes: 1 addition & 1 deletion src/utils/analysis_clumpfind.F90
Original file line number Diff line number Diff line change
Expand Up @@ -411,7 +411,7 @@ subroutine read_analysis_options(dumpfile)
write(10,*) trim(dumpfile), " Previous SPH dump analysed"
close(10)
previousdumpfile = ""
runningclumpmax = ""
runningclumpmax = 0
endif

if (checkbound) then
Expand Down

0 comments on commit 1db5894

Please sign in to comment.