handle_positions Submodule

This SUBMODULE contains the implementation of the PROCEDURES to handle particle positions.

FT 24.03.2022



Uses

  • module~~handle_positions~~UsesGraph module~handle_positions handle_positions module~sph_particles sph_particles module~handle_positions->module~sph_particles module~id_base id_base module~sph_particles->module~id_base module~utility utility module~sph_particles->module~utility timing timing module~sph_particles->timing module~id_base->module~utility module~id_base->timing constants constants module~utility->constants matrix matrix module~utility->matrix

Contents


Module Procedures

module procedure check_particle_position module function check_particle_position(npart, pos, pos_a) result(cnt)

Return the number of times that pos_a appears in the array pos

Read more…

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: npart
double precision, intent(in), DIMENSION(3,npart) :: pos
double precision, intent(in), DIMENSION(3) :: pos_a

Return Value integer

module procedure check_particle_positions module subroutine check_particle_positions(npart, pos, debug)

Check that the particles are not at the same positions

Read more…

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: npart

Number of particles

double precision, intent(in), DIMENSION(3,npart) :: pos

Array of particle positions

logical, intent(in), optional :: debug

TRUE to debug the SUBROUTINE, FALSE otherwise

module procedure correct_center_of_mass module subroutine correct_center_of_mass(npart, pos, nu, get_density, validate_pos, com_star, verbose)

Translate the particles so that their center of mass coincides with the center of mass of the star, given by \(\mathrm{ID}\)

Read more…

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: npart
double precision, intent(inout), DIMENSION(3,npart) :: pos
double precision, intent(inout), DIMENSION(npart) :: nu
function get_density(x, y, z) result(density)
Arguments
Type IntentOptional Attributes Name
double precision, intent(in) :: x
double precision, intent(in) :: y
double precision, intent(in) :: z
Return Value double precision
function validate_pos(x, y, z) result(answer)
Arguments
Type IntentOptional Attributes Name
double precision, intent(in) :: x
double precision, intent(in) :: y
double precision, intent(in) :: z
Return Value logical
double precision, intent(in), DIMENSION(3) :: com_star
logical, intent(in), optional :: verbose

module procedure find_particles_above_xy_plane module subroutine find_particles_above_xy_plane(npart, pos, npart_above_xy, above_xy_plane_a)

Find the particles above the plane

Read more…

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: npart
double precision, intent(in), DIMENSION(3,npart) :: pos
integer, intent(out) :: npart_above_xy
integer, intent(out), DIMENSION(:), ALLOCATABLE :: above_xy_plane_a

module procedure get_neighbours_bf module subroutine get_neighbours_bf(ipart, npart, pos, h, dimensions, nnei, neilist)

just for test purposes: get neighbours of particle ipart in a "brute force" way; ipart is ALSO on the neighbour list; SKR 8.2.2010

Read more…

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: ipart
integer, intent(in) :: npart
double precision, intent(in) :: pos(dimensions,npart)
double precision, intent(in) :: h(npart)
integer, intent(in) :: dimensions
integer, intent(out) :: nnei
integer, intent(out) :: neilist(npart)

module procedure get_object_of_particle pure module function get_object_of_particle(this, a)

Returns the number of the matter object asociated with the particle number given as input. Example: give number as input; this particle number corresponds to a particle on matter object . This functions returns .

Read more…

Arguments

Type IntentOptional Attributes Name
class(particles), intent(in) :: this

particles object which this PROCEDURE is a member of

integer, intent(in) :: a

Particle number

Return Value integer

module procedure impose_equatorial_plane_symmetry module subroutine impose_equatorial_plane_symmetry(npart, pos, nu, com_star, verbose)

Mirror the particle with z>0 with respect to the xy plane, to impose the equatorial-plane symmetry

Read more…

Arguments

Type IntentOptional Attributes Name
integer, intent(inout) :: npart
double precision, intent(inout), DIMENSION(3,npart) :: pos
double precision, intent(inout), optional, DIMENSION(npart) :: nu
double precision, intent(in), optional :: com_star
logical, intent(in), optional :: verbose

module procedure reflect_particles_xy_plane module subroutine reflect_particles_xy_plane(npart, pos, pos_below, npart_above_xy, above_xy_plane_a, nu, nu_below)

Reflect the particle with z>0 with respect to the xy plane

Read more…

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: npart
double precision, intent(inout), DIMENSION(3,npart) :: pos
double precision, intent(out), DIMENSION(3,npart_above_xy) :: pos_below
integer, intent(inout) :: npart_above_xy
integer, intent(in), DIMENSION(npart_above_xy) :: above_xy_plane_a
double precision, intent(inout), optional, DIMENSION(npart) :: nu
double precision, intent(out), optional, DIMENSION(npart_above_xy) :: nu_below