Skip to content

Commit

Permalink
[indent-bot] standardised indentation
Browse files Browse the repository at this point in the history
  • Loading branch information
becnealon committed Oct 16, 2024
1 parent b5ceb03 commit 3759ed3
Show file tree
Hide file tree
Showing 15 changed files with 1,033 additions and 1,033 deletions.
1,366 changes: 683 additions & 683 deletions src/main/apr.f90

Large diffs are not rendered by default.

70 changes: 35 additions & 35 deletions src/main/apr_region.f90
Original file line number Diff line number Diff line change
Expand Up @@ -16,53 +16,53 @@ module apr_region
!
! :Dependencies: part
!
implicit none
implicit none

logical, public :: dynamic_apr = .false., apr_region_is_circle = .false.
public :: set_apr_centre, set_apr_regions
logical, public :: dynamic_apr = .false., apr_region_is_circle = .false.
public :: set_apr_centre, set_apr_regions

private
private

contains

!-----------------------------------------------------------------------
!+
! Setting/updating the centre of the apr region (as it may move)
!+
!-----------------------------------------------------------------------
!-----------------------------------------------------------------------
!+
! Setting/updating the centre of the apr region (as it may move)
!+
!-----------------------------------------------------------------------

subroutine set_apr_centre(apr_type,apr_centre,ntrack,track_part)
use part, only: xyzmh_ptmass,xyzh
integer, intent(in) :: apr_type
real, intent(out) :: apr_centre(3)
integer, optional, intent(in) :: ntrack,track_part
use part, only: xyzmh_ptmass,xyzh
integer, intent(in) :: apr_type
real, intent(out) :: apr_centre(3)
integer, optional, intent(in) :: ntrack,track_part

select case (apr_type)
select case (apr_type)

case(1) ! a static circle
case(1) ! a static circle
! do nothing here

case(2) ! around sink particle named track_part
case(2) ! around sink particle named track_part
dynamic_apr = .true.
apr_centre(1) = xyzmh_ptmass(1,track_part)
apr_centre(2) = xyzmh_ptmass(2,track_part)
apr_centre(3) = xyzmh_ptmass(3,track_part)

case(3) ! to derefine a clump - only activated when the centre of the clump
! has been found
dynamic_apr = .true.
case(3) ! to derefine a clump - only activated when the centre of the clump
! has been found
dynamic_apr = .true.
if (present(ntrack)) then
apr_centre(1) = xyzh(1,track_part)
apr_centre(2) = xyzh(2,track_part)
apr_centre(3) = xyzh(3,track_part)
apr_centre(1) = xyzh(1,track_part)
apr_centre(2) = xyzh(2,track_part)
apr_centre(3) = xyzh(3,track_part)
else
apr_centre = tiny(apr_centre) ! this *might* be safe? Just want it to be irrelevant
apr_centre = tiny(apr_centre) ! this *might* be safe? Just want it to be irrelevant
endif

case default ! used for the test suite
case default ! used for the test suite
apr_centre(:) = 0.

end select
end select

end subroutine set_apr_centre

Expand All @@ -74,23 +74,23 @@ end subroutine set_apr_centre
!-----------------------------------------------------------------------

subroutine set_apr_regions(ref_dir,apr_max,apr_regions,apr_rad,apr_drad)
integer, intent(in) :: ref_dir,apr_max
real, intent(in) :: apr_rad,apr_drad
real, intent(inout) :: apr_regions(apr_max)
integer :: ii,kk
integer, intent(in) :: ref_dir,apr_max
real, intent(in) :: apr_rad,apr_drad
real, intent(inout) :: apr_regions(apr_max)
integer :: ii,kk

if (ref_dir == 1) then
if (ref_dir == 1) then
apr_regions(1) = huge(apr_regions(1)) ! this needs to be a number that encompasses the whole domain
do ii = 2,apr_max
kk = apr_max - ii + 2
apr_regions(kk) = apr_rad + (ii-1)*apr_drad
kk = apr_max - ii + 2
apr_regions(kk) = apr_rad + (ii-1)*apr_drad
enddo
else
else
apr_regions(apr_max) = huge(apr_regions(apr_max)) ! again this just needs to encompass the whole domain
do ii = 1,apr_max-1
apr_regions(ii) = apr_rad + (ii-1)*apr_drad
apr_regions(ii) = apr_rad + (ii-1)*apr_drad
enddo
endif
endif

end subroutine set_apr_regions

Expand Down
64 changes: 32 additions & 32 deletions src/main/centreofmass.f90
Original file line number Diff line number Diff line change
Expand Up @@ -113,17 +113,17 @@ subroutine get_centreofmass(xcom,vcom,npart,xyzh,vxyzu,nptmass,xyzmh_ptmass,vxyz
if (maxphase==maxp) then
itype = iamtype(iphase(i))
if (itype > 0) then ! avoid problems if called from ICs
if (use_apr) then
pmassi = aprmassoftype(itype,apr_level(i))
else
pmassi = massoftype(itype)
endif
if (use_apr) then
pmassi = aprmassoftype(itype,apr_level(i))
else
pmassi = massoftype(itype)
endif
else
if (use_apr) then
pmassi = aprmassoftype(igas,apr_level(i))
else
pmassi = massoftype(igas)
endif
if (use_apr) then
pmassi = aprmassoftype(igas,apr_level(i))
else
pmassi = massoftype(igas)
endif
endif
endif
totmass = totmass + pmassi
Expand Down Expand Up @@ -208,17 +208,17 @@ subroutine get_centreofmass_accel(acom,npart,xyzh,fxyzu,fext,nptmass,xyzmh_ptmas
hi = xyzh(4,i)
if (.not.isdead_or_accreted(hi)) then
if (maxphase==maxp) then
if (use_apr) then
pmassi = aprmassoftype(iamtype(iphase(i)),apr_level(i))
else
pmassi = massoftype(iamtype(iphase(i)))
endif
if (use_apr) then
pmassi = aprmassoftype(iamtype(iphase(i)),apr_level(i))
else
pmassi = massoftype(iamtype(iphase(i)))
endif
else
if (use_apr) then
pmassi = aprmassoftype(igas,apr_level(i))
else
pmassi = massoftype(igas)
endif
if (use_apr) then
pmassi = aprmassoftype(igas,apr_level(i))
else
pmassi = massoftype(igas)
endif
endif
totmass = totmass + pmassi
acom(1) = acom(1) + pmassi*(fxyzu(1,i) + fext(1,i))
Expand Down Expand Up @@ -296,17 +296,17 @@ subroutine correct_bulk_motion()
hi = xyzh(4,i)
if (.not.isdead_or_accreted(hi)) then
if (maxphase==maxp) then
if (use_apr) then
pmassi = aprmassoftype(iamtype(iphase(i)),apr_level(i))
else
pmassi = massoftype(iamtype(iphase(i)))
endif
if (use_apr) then
pmassi = aprmassoftype(iamtype(iphase(i)),apr_level(i))
else
pmassi = massoftype(iamtype(iphase(i)))
endif
else
if (use_apr) then
pmassi = aprmassoftype(igas,apr_level(i))
else
pmassi = massoftype(igas)
endif
if (use_apr) then
pmassi = aprmassoftype(igas,apr_level(i))
else
pmassi = massoftype(igas)
endif
endif
totmass = totmass + pmassi

Expand Down Expand Up @@ -418,9 +418,9 @@ subroutine get_total_angular_momentum(xyzh,vxyz,npart,L_tot,xyzmh_ptmass,vxyz_pt
if (.not.isdead_or_accreted(xyzh(4,ii))) then
itype = iamtype(iphase(ii))
if (use_apr) then
pmassi = aprmassoftype(itype,apr_level(ii))
pmassi = aprmassoftype(itype,apr_level(ii))
else
pmassi = massoftype(itype)
pmassi = massoftype(itype)
endif
call cross_product3D(xyzh(1:3,ii),vxyz(1:3,ii),temp)
L_tot = L_tot + temp*pmassi
Expand Down
24 changes: 12 additions & 12 deletions src/main/dens.F90
Original file line number Diff line number Diff line change
Expand Up @@ -741,11 +741,11 @@ pure subroutine get_density_sums(i,xpartveci,hi,hi1,hi21,iamtypei,iamgasi,iamdus
! adjust masses for apr
! this defaults to massoftype if apr_level=1
if (use_apr) then
pmassi = aprmassoftype(iamtypei,apri)
pmassj = aprmassoftype(iamtypej,apr_level(j))
pmassi = aprmassoftype(iamtypei,apri)
pmassj = aprmassoftype(iamtypej,apr_level(j))
else
pmassi = massoftype(iamtypei)
pmassj = massoftype(iamtypej)
pmassi = massoftype(iamtypei)
pmassj = massoftype(iamtypej)
endif

sametype: if (same_type) then
Expand Down Expand Up @@ -1258,9 +1258,9 @@ pure subroutine compute_cell(cell,listneigh,nneigh,getdv,getdB,Bevol,xyzh,vxyzu,
hi41 = hi21*hi21

if (use_apr) then
apri = cell%apr(i)
apri = cell%apr(i)
else
apri = 1
apri = 1
endif


Expand Down Expand Up @@ -1376,9 +1376,9 @@ subroutine start_cell(cell,iphase,xyzh,vxyzu,fxyzu,fext,Bevol,rad,apr_level)
if (do_radiation) cell%xpartvec(iradxii,cell%npcell) = rad(iradxi,i)

if (use_apr) then
cell%apr(cell%npcell) = apr_level(i)
cell%apr(cell%npcell) = apr_level(i)
else
cell%apr(cell%npcell) = 1
cell%apr(cell%npcell) = 1
endif

enddo over_parts
Expand Down Expand Up @@ -1422,9 +1422,9 @@ subroutine finish_cell(cell,cell_converged)

apri = cell%apr(i)
if (use_apr) then
pmassi = aprmassoftype(iamtypei,apri)
pmassi = aprmassoftype(iamtypei,apri)
else
pmassi = massoftype(iamtypei)
pmassi = massoftype(iamtypei)
endif

call finish_rhosum(rhosum,pmassi,hi,.true.,rhoi=rhoi,rhohi=rhohi,&
Expand Down Expand Up @@ -1588,9 +1588,9 @@ subroutine store_results(icall,cell,getdv,getdb,realviscosity,stressmax,xyzh,&

apri = cell%apr(i)
if (use_apr) then
pmassi = aprmassoftype(iamtypei,apri)
pmassi = aprmassoftype(iamtypei,apri)
else
pmassi = massoftype(iamtypei)
pmassi = massoftype(iamtypei)
endif

if (calculate_density) then
Expand Down
28 changes: 14 additions & 14 deletions src/main/force.F90
Original file line number Diff line number Diff line change
Expand Up @@ -675,9 +675,9 @@ subroutine force(icall,npart,xyzh,vxyzu,fxyzu,divcurlv,divcurlB,Bevol,dBevol,&
iamtypei = igas
endif
if (use_apr) then
pmassi = aprmassoftype(iamtypei,apr_level(i))
pmassi = aprmassoftype(iamtypei,apr_level(i))
else
pmassi = massoftype(iamtypei)
pmassi = massoftype(iamtypei)
endif
rhoi = rhoh(hi,pmassi)
if (rhoi > rho_crit) then
Expand Down Expand Up @@ -1320,9 +1320,9 @@ subroutine compute_forces(i,iamgasi,iamdusti,xpartveci,hi,hi1,hi21,hi41,gradhi,g
#endif
endif
if (use_apr) then
pmassj = aprmassoftype(iamtypej,apr_level(j))
pmassj = aprmassoftype(iamtypej,apr_level(j))
else
pmassj = massoftype(iamtypej)
pmassj = massoftype(iamtypej)
endif

fgrav = 0.5*(pmassj*fgravi + pmassi*fgravj)
Expand Down Expand Up @@ -1952,9 +1952,9 @@ subroutine compute_forces(i,iamgasi,iamdusti,xpartveci,hi,hi1,hi21,hi41,gradhi,g
iamtypej = iamtype(iphase(j))
endif
if (use_apr) then
pmassj = aprmassoftype(iamtypej,apr_level(j))
pmassj = aprmassoftype(iamtypej,apr_level(j))
else
pmassj = massoftype(iamtypej)
pmassj = massoftype(iamtypej)
endif
phii = -rij1
fgravj = fgrav*pmassj
Expand Down Expand Up @@ -2173,9 +2173,9 @@ subroutine start_cell(cell,iphase,xyzh,vxyzu,gradh,divcurlv,divcurlB,dvdx,Bevol,
endif

if (use_apr) then
pmassi = aprmassoftype(iamtypei,apr_level(i))
pmassi = aprmassoftype(iamtypei,apr_level(i))
else
pmassi = massoftype(iamtypei)
pmassi = massoftype(iamtypei)
endif

hi = xyzh(4,i)
Expand Down Expand Up @@ -2323,9 +2323,9 @@ subroutine start_cell(cell,iphase,xyzh,vxyzu,gradh,divcurlv,divcurlB,dvdx,Bevol,
endif
endif
if (use_apr) then
cell%apr(cell%npcell) = apr_level(i)
cell%apr(cell%npcell) = apr_level(i)
else
cell%apr(cell%npcell) = 1
cell%apr(cell%npcell) = 1
endif

alphai = alpha
Expand Down Expand Up @@ -2489,9 +2489,9 @@ subroutine compute_cell(cell,listneigh,nneigh,Bevol,xyzh,vxyzu,fxyzu, &
i = inodeparts(cell%arr_index(ip))

if (use_apr) then
pmassi = aprmassoftype(iamtypei,cell%apr(ip))
pmassi = aprmassoftype(iamtypei,cell%apr(ip))
else
pmassi = massoftype(iamtypei)
pmassi = massoftype(iamtypei)
endif

hi = cell%xpartvec(ihi,ip)
Expand Down Expand Up @@ -2673,9 +2673,9 @@ subroutine finish_cell_and_store_results(icall,cell,fxyzu,xyzh,vxyzu,poten,dt,dv
endif

if (use_apr) then
pmassi = aprmassoftype(iamtypei,cell%apr(ip))
pmassi = aprmassoftype(iamtypei,cell%apr(ip))
else
pmassi = massoftype(iamtypei)
pmassi = massoftype(iamtypei)
endif

i = inodeparts(cell%arr_index(ip))
Expand Down
4 changes: 2 additions & 2 deletions src/main/initial.F90
Original file line number Diff line number Diff line change
Expand Up @@ -372,9 +372,9 @@ subroutine startrun(infile,logfile,evfile,dumpfile,noread)

! initialise apr if it is being used
if (use_apr) then
call init_apr(apr_level,ierr)
call init_apr(apr_level,ierr)
else
apr_level(:) = 1
apr_level(:) = 1
endif

!
Expand Down
Loading

0 comments on commit 3759ed3

Please sign in to comment.