Skip to content

Commit

Permalink
(gr sink) cleaning the file so that variable names are consistent for…
Browse files Browse the repository at this point in the history
… ptmass
  • Loading branch information
Megha Sharma committed Dec 18, 2024
1 parent 025de37 commit 23954b6
Showing 1 changed file with 10 additions and 13 deletions.
23 changes: 10 additions & 13 deletions src/main/substepping.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1264,7 +1264,7 @@ end subroutine predict_gr
!+
!----------------------------------------------------------------
subroutine predict_gr_sink(xyzmh_ptmass,vxyz_ptmass,ntypes,pxyzu_ptmass,fxyz_ptmass,fxyz_ptmass_sinksink,nptmass,dt,timei,hdt, &
metrics,metricderivs,dtextforcenew,pitsmax,perrmax, &
metrics_ptmass,metricderivs_ptmass,dtextforcenew,pitsmax,perrmax, &
xitsmax,xerrmax)
use dim, only:maxptmass
use io, only:master,warning,fatal
Expand All @@ -1276,7 +1276,7 @@ subroutine predict_gr_sink(xyzmh_ptmass,vxyz_ptmass,ntypes,pxyzu_ptmass,fxyz_ptm
use ptmass, only:get_accel_sink_sink

real, intent(inout) :: xyzmh_ptmass(:,:),vxyz_ptmass(:,:),fxyz_ptmass(:,:),fxyz_ptmass_sinksink(:,:),pxyzu_ptmass(:,:)
real, intent(inout) :: metrics(:,:,:,:),metricderivs(:,:,:,:),dtextforcenew
real, intent(inout) :: metrics_ptmass(:,:,:,:),metricderivs_ptmass(:,:,:,:),dtextforcenew
real, intent(in) :: dt,hdt,timei
integer, intent(in) :: nptmass,ntypes
integer, intent(inout) :: pitsmax,xitsmax
Expand Down Expand Up @@ -1304,7 +1304,7 @@ subroutine predict_gr_sink(xyzmh_ptmass,vxyz_ptmass,ntypes,pxyzu_ptmass,fxyz_ptm
!$omp parallel do default(none) &
!$omp shared(xyzmh_ptmass,vxyz_ptmass,fxyz_ptmass,fxyz_ptmass_sinksink) &
!$omp shared(dt,hdt,xtol,ptol,nptmass) &
!$omp shared(pxyzu_ptmass,metrics,metricderivs) &
!$omp shared(pxyzu_ptmass,metrics_ptmass,metricderivs_ptmass) &
!$omp shared(dtsinksink,epot_sinksink,merge_ij,merge_n,dsdt_ptmass) &
!$omp private(i,its,tempi,rhoi,hi,eni,uui,densi,xyzhi) &
!$omp private(converged,pmom_err,x_err,pri,ierr,gammai,pmassi) &
Expand Down Expand Up @@ -1346,12 +1346,12 @@ subroutine predict_gr_sink(xyzmh_ptmass,vxyz_ptmass,ntypes,pxyzu_ptmass,fxyz_ptm
pmom_iterations: do while (its <= itsmax .and. .not. converged)
its = its + 1
pprev = pxyz
call conservative2primitive(xyz,metrics(:,:,:,i),vxyz,densi,uui,pri,&
call conservative2primitive(xyz,metrics_ptmass(:,:,:,i),vxyz,densi,uui,pri,&
tempi,gammai,rhoi,pxyz,eni,ierr,1)

if (ierr > 0) call warning('cons2primsolver [in substep_gr (a)]','enthalpy did not converge',i=i)

call get_grforce(xyzhi,metrics(:,:,:,i),metricderivs(:,:,:,i),vxyz,densi,uui,pri,fstar)
call get_grforce(xyzhi,metrics_ptmass(:,:,:,i),metricderivs_ptmass(:,:,:,i),vxyz,densi,uui,pri,fstar)

fstar = fstar + fxyz_ptmass_sinksink(1:3,i)

Expand All @@ -1365,12 +1365,12 @@ subroutine predict_gr_sink(xyzmh_ptmass,vxyz_ptmass,ntypes,pxyzu_ptmass,fxyz_ptm
pitsmax = max(its,pitsmax)
perrmax = max(pmom_err,perrmax)

call conservative2primitive(xyz,metrics(:,:,:,i),vxyz,densi,uui,pri,tempi,&
call conservative2primitive(xyz,metrics_ptmass(:,:,:,i),vxyz,densi,uui,pri,tempi,&
gammai,rhoi,pxyz,eni,ierr,1)

if (ierr > 0) call warning('cons2primsolver [in substep_gr (b)]','enthalpy did not converge',i=i)
xyz = xyz + dt*vxyz
call pack_metric(xyz,metrics(:,:,:,i))
call pack_metric(xyz,metrics_ptmass(:,:,:,i))

its = 0
converged = .false.
Expand All @@ -1383,17 +1383,17 @@ subroutine predict_gr_sink(xyzmh_ptmass,vxyz_ptmass,ntypes,pxyzu_ptmass,fxyz_ptm
xyz_iterations: do while (its <= itsmax .and. .not. converged)
its = its+1
xyz_prev = xyz
call conservative2primitive(xyz,metrics(:,:,:,i),vxyz_star,densi,uui,&
call conservative2primitive(xyz,metrics_ptmass(:,:,:,i),vxyz_star,densi,uui,&
pri,tempi,gammai,rhoi,pxyz,eni,ierr,1)
if (ierr > 0) call warning('cons2primsolver [in substep_gr (c)]','enthalpy did not converge',i=i)
xyz = xyz_prev + hdt*(vxyz_star - vxyz)
x_err = maxval(abs(xyz-xyz_prev))
if (x_err < xtol) converged = .true.
vxyz = vxyz_star
! UPDATE METRIC HERE
call pack_metric(xyz,metrics(:,:,:,i))
call pack_metric(xyz,metrics_ptmass(:,:,:,i))
enddo xyz_iterations
call pack_metricderivs(xyz,metricderivs(:,:,:,i))
call pack_metricderivs(xyz,metricderivs_ptmass(:,:,:,i))
if (its > itsmax ) call warning('substep_gr','Reached max number of x iterations. x_err ',val=x_err)
xitsmax = max(its,xitsmax)
xerrmax = max(x_err,xerrmax)
Expand Down Expand Up @@ -1459,12 +1459,9 @@ subroutine accrete_gr(xyzh,vxyzu,dens,fext,metrics,metricderivs,nlive,naccreted,
real :: bin_info(6,nptmass),dsdt_ptmass(3,nptmass)
real :: dtphi2,dtsinksink,fonrmax,poti
integer :: merge_ij(nptmass),merge_n
real :: fext_gas(4,npart)

pmassi = massoftype(igas)
itype = igas
fext_gas = 0.

!----------------------------------------------
! calculate acceleration sink-sink
!----------------------------------------------
Expand Down

0 comments on commit 23954b6

Please sign in to comment.