particles Derived Type

type, public :: particles

TYPE representing a \(\mathrm{SPH}\) particle distribution


Inherits

type~~particles~~InheritsGraph type~particles particles timer timer type~particles->timer placer_timer, same_particle_timer, apm_timers, importer_timer, sph_computer_timer type~eos eos type~particles->type~eos all_eos type~surface surface type~particles->type~surface surfaces

Contents

Source Code


Components

Type Visibility Attributes Name Initial
double precision, private, DIMENSION(:), ALLOCATABLE :: Theta

1-D array storing the generalized Lorentz factor

double precision, private, DIMENSION(:), ALLOCATABLE :: Ye

1-D array storing the electron fraction

double precision, private, DIMENSION(:), ALLOCATABLE :: Ye_table

Array storing the values of the electron fraction in the \(\mathrm{CompOSE}\) table

double precision, private, DIMENSION(3) :: adm_linear_momentum_fluid

Estimate of the linear momentum of the fluid computed from the canonical momentum per baryon on the particles

double precision, private, DIMENSION(:,:), ALLOCATABLE :: adm_linear_momentum_i

Estimate of the linear momentum of each matter object, computed from the canonical momentum per baryon on the particles

double precision, private :: adm_mass
type(eos), private, DIMENSION(:), ALLOCATABLE :: all_eos

Array of TYPE eos containing the \(\mathrm{EOS}\) information for all the matter objects

logical, private, DIMENSION(:), ALLOCATABLE :: apm_iterate

.TRUE. if the Artificial Pressure Method (APM) has to be applied to the particles, .FALSE. otherwise

type(timer), public, DIMENSION(:), ALLOCATABLE :: apm_timers

Timer that times how long it takes to perform the APM on the matter objects

double precision, private, DIMENSION(:,:), ALLOCATABLE :: barycenter

Array storing the centers of mass of the matter objects

double precision, private, DIMENSION(4) :: barycenter_system

Array storing the center of mass of the entire particle distribution

double precision, private, DIMENSION(:), ALLOCATABLE :: baryon_density

1-D array storing the baryon mass density in the fluid frame

integer, private, DIMENSION(:), ALLOCATABLE :: baryon_density_index

Array storing the indices to use with baryon_density to sort the elements of baryon_density in increasing order

integer, private :: call_flag = 0

Flag that is set different than 0 if the SUBROUTINE compute_and_print_sph_variables is called

logical, private :: cold_system

.TRUE. if the system is at zero temperature (no thermal component); .FALSE. otherwise

logical, private :: compose_eos

.TRUE. if the electron fraction should be read from the CompOSE table with extension.beta, .FALSE. otherwise

character(len=:), private, ALLOCATABLE :: compose_filename

String storing the subpath of compose_path to the CompOSE file with .beta extension

character(len=:), private, ALLOCATABLE :: compose_path

String storing the local path to the directory containing the CompOSE \(\mathrm{EOS}\)

logical, private :: correct_nu

.TRUE. if the baryon number per particle should be corrected to account for the total baryon masses of the stars, .FALSE. otherwise

integer, private :: distribution_id

Identification number for the particle distribution

logical, private :: empty_object

.TRUE. if the object is empty, .FALSE. if it's not empty

double precision, private, DIMENSION(:), ALLOCATABLE :: energy_density

1-D array storing the energy density

double precision, private, DIMENSION(:), ALLOCATABLE :: enthalpy

1-D array storing the enthalpy

logical, public :: export_bin

.TRUE. if the binary files for SPHINCS_BSSN are to be exported, .FALSE. otherwise

logical, public :: export_form_x

.TRUE. if the ID in the formatted files is to be on the x axis only, .FALSE. otherwise

logical, public :: export_form_xy

.TRUE. if the ID in the formatted files is to be on the xy plane only, .FALSE. otherwise

double precision, private, DIMENSION(:), ALLOCATABLE :: g_xx

Array storing the values of the xx component of the spatial metric on the particles

double precision, private, DIMENSION(:), ALLOCATABLE :: g_xy

Array storing the values of the xy component of the spatial metric on the particles

double precision, private, DIMENSION(:), ALLOCATABLE :: g_xz

Array storing the values of the xz component of the spatial metric on the particles

double precision, private, DIMENSION(:), ALLOCATABLE :: g_yy

Array storing the values of the xz component of the spatial metric on the particles

double precision, private, DIMENSION(:), ALLOCATABLE :: g_yz

Array storing the values of the yz component of the spatial metric on the particles

double precision, private, DIMENSION(:), ALLOCATABLE :: g_zz

Array storing the values of the zz component of the spatial metric on the particles

double precision, private, DIMENSION(:), ALLOCATABLE :: h

1-D array storing the smoothing length

type(timer), public :: importer_timer

Timer that times how long it takes to import the ID at the particle positions

double precision, private, DIMENSION(:), ALLOCATABLE :: lapse

Array storing the values of the lapse function on the particles

double precision, private, DIMENSION(:), ALLOCATABLE :: mass_fractions

Ratio between baryonic masses of the matter objects and the total baryonic mass of all the matter objects

double precision, private, DIMENSION(:), ALLOCATABLE :: mass_ratios

Ratio between baryonic masses of the matter objects and the maximum baryonic mass among them

double precision, private, DIMENSION(:), ALLOCATABLE :: masses

1-D array storing the particle masses

integer, private :: n_matter

Number of matter objects in the physical system

double precision, private, DIMENSION(:), ALLOCATABLE :: nb_table

Array storing the values of the baryon number density in the \(\mathrm{CompOSE}\) table.

double precision, private, DIMENSION(:), ALLOCATABLE :: nbar_i

Baryon numbers of the matter objects

double precision, private :: nbar_tot

Total baryon number

double precision, private, DIMENSION(:), ALLOCATABLE :: nlrf

1-D array storing baryon density in the local rest frame , computed directly from the \(\texttt{LORENE}\) density

double precision, private, DIMENSION(:), ALLOCATABLE :: nlrf_sph

1-D array storing baryon density in the local rest frame , computed from the kernel interpolated proper baryon number density nstar_sph

integer, private :: npart

Total particle number

integer, private, DIMENSION(:), ALLOCATABLE :: npart_fin

Array storing the index of the last particle for each matter objects

integer, private, DIMENSION(:), ALLOCATABLE :: npart_i

Array storing the particle numbers for the matter objects

double precision, private, DIMENSION(:), ALLOCATABLE :: nstar

1-D array storing the SPH estimate of the proper baryon number density

double precision, private, DIMENSION(:), ALLOCATABLE :: nstar_sph

1-D array storing the SPH estimate of the proper baryon number density, from kernel interpolation

double precision, private, DIMENSION(:), ALLOCATABLE :: nu

1-D array storing the baryon number per particle

double precision, private :: nu_ratio_des

Desired ratio between the max and min of the baryon number per particle, over all the matter objects. Only used when redistribute_nu is .TRUE.

double precision, private :: nuratio

Ratio between the max and min of the baryon number per particle, over all the matter objects

double precision, private, DIMENSION(:), ALLOCATABLE :: nuratio_i

Baryon number ratios on the matter objects

double precision, private, DIMENSION(:), ALLOCATABLE :: particle_density

1-D array storing the particle number density

double precision, private, DIMENSION(:), ALLOCATABLE :: particle_density_sph

1-D array storing the SPH estimate of the particle number density, from kernel interpolation

type(timer), public :: placer_timer

Timer that times how long it takes to place particles on the stars

double precision, private, DIMENSION(:,:), ALLOCATABLE :: pos

2-D array storing the particle positions

procedure, private, POINTER, NOPASS :: post_process_sph_id

Pointer to a procedure that post_process the \(\mathrm{SPH}\) \(\mathrm{ID}\); for example, correct for the residual ADM linear momentum.

double precision, private, DIMENSION(:), ALLOCATABLE :: pressure

1-D array storing the pressure

double precision, private, DIMENSION(:), ALLOCATABLE :: pressure_sph

1-D array storing the pressure in code units

double precision, private, DIMENSION(:), ALLOCATABLE :: pvol

1-D array storing the particle volumes

logical, private :: randomize_phi

.TRUE. if the particle positions on ellipsoidal surfaces are randomized in the direction, .FALSE. otherwise

logical, private :: randomize_r

.TRUE. if the particle positions on ellipsoidal surfaces are randomized in the direction, .FALSE. otherwise

logical, private :: randomize_theta

.TRUE. if the particle positions on ellipsoidal surfaces are randomized in the direction, .FALSE. otherwise

logical, private :: read_nu

.TRUE. if the baryon number per particle has to be read from the formatted file containing the particle positions, .FALSE. otherwise

logical, private :: redistribute_nu

.TRUE. if the baryon number per particle should be reassigned, trying to obtain a baryon number ratio no larger than nu_ratio, when placing particles on lattices; .FALSE. otherwise

logical, private :: reflect_particles_x

.TRUE. if the particles on star 2 should be the reflection of the particles on star 1 with respect to the plane, only if the baryon masses of the stars differe less than ; .FALSE. otherwise

type(timer), public :: same_particle_timer

Timer that times how long it takes to check if there are multiple particles at the same positions

double precision, private, DIMENSION(:), ALLOCATABLE :: shift_x

Array storing the values of the x component of the shift vector on the particles

double precision, private, DIMENSION(:), ALLOCATABLE :: shift_y

Array storing the values of the y component of the shift vector on the particles

double precision, private, DIMENSION(:), ALLOCATABLE :: shift_z

Array storing the values of the z component of the shift vector on the particles

double precision, private, DIMENSION(:), ALLOCATABLE :: specific_energy

1-D array storing the specific internal energy

type(timer), public :: sph_computer_timer

Timer that times how long it takes to compute the SPH variables at the particle positions

character(len=50), private :: sphincs_id_particles

String containing the name of the particles parameter file

type(surface), private, DIMENSION(:), ALLOCATABLE :: surfaces

1-D array storing the surfaces of the matter objects

double precision, private, DIMENSION(:), ALLOCATABLE :: u_sph

1-D array storing the specific internal energy computed using formula (9) in Read et al., Phys.Rev.D79:124032,2009, [arXiv:0812.2163][https://arxiv.org/abs/0812.2163]{:target="_blank"}

logical, private, DIMENSION(:), ALLOCATABLE :: use_atmosphere

.TRUE. to allow the particles to move where the density is 0 during the Artificial Pressure Method (APM) iteration. This can be useful when the system has an irregular geometry, as, for example, an ejecta .FALSE. otherwise

logical, private :: use_thres

.TRUE. if the threshold on the baryon mass density should e applied when placing particles on lattices, .FALSE. otherwise

double precision, private, DIMENSION(:,:), ALLOCATABLE :: v

2-D array storing the coordinate fluid 4-velocity

double precision, private, DIMENSION(:), ALLOCATABLE :: v_euler_x

1-D array storing the x component of the fluid 3-velocity wrt the Eulerian observer

double precision, private, DIMENSION(:), ALLOCATABLE :: v_euler_y

1-D array storing the y component of the fluid 3-velocity wrt the Eulerian observer

double precision, private, DIMENSION(:), ALLOCATABLE :: v_euler_z

1-D array storing the z component of the fluid 3-velocity wrt the Eulerian observer


Constructor

public interface particles

Interface of TYPE particles


Finalization Procedures

final :: destruct_particles

Finalizer (Destructor) of particles object


Type-Bound Procedures

procedure, public :: allocate_particles_memory

Allocates memory for the particles member arrays

  • interface

    public module subroutine allocate_particles_memory(this)

    Allocates allocatable arrays member of a particles object

    Arguments

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

    particles object which this PROCEDURE is a member of

procedure, public :: analyze_hydro

Scans the hydro fields taken from to look for negative or zero values

  • interface

    public module subroutine analyze_hydro(this, namefile)

    Scans the hydro fields taken from to look for negative or zero values

    Arguments

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

    particles object which this PROCEDURE is a member of

    character(len=*), intent(inout), optional :: namefile

    Name of the formatted file where the particle positions at which some of the hydro fields are negative or zero are printed to

procedure, public :: compute_Ye

Interpates linearly the electron fraction at the particle densities; that is, assigns at the particle positions

  • interface

    public module subroutine compute_Ye(this)

    Interpolates linearly the electron fraction at the particle densities; that is, assigns at the particle positions

    Arguments

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

    particles object which this PROCEDURE is a member of

procedure, public :: compute_and_print_sph_variables

Computes the SPH variables at the particle positions, and optionally prints them to a binary file to be read by and , and to a formatted file to be read by , by calling print_formatted_id_particles

  • interface

    public module subroutine compute_and_print_sph_variables(this, namefile)

    Computes the SPH variables at the particle positions, and optionally prints them to a binary file to be read by and , and to a formatted file to be read by , by calling print_formatted_id_particles

    Arguments

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

    particles object which this PROCEDURE is a member of

    character(len=*), intent(inout), optional :: namefile

    Name of the formatted file where the SPH ID is printed to

procedure, public :: compute_sph_hydro

Computes the hydro fields on a section of the particles specified as input. First, computes the \(\mathrm{SPH}\) pressure starting from the \(\mathrm{SPH}\) baryon mass density, and the specific internal energy. The pressure is computed differently for different \(\mathrm{EOS}\), and for cold and hot systems. Then computes the enthalpy and the sound speed accordingly.

  • interface

    public module subroutine compute_sph_hydro(this, npart_in, npart_fin, eqos, nlrf, u, Pr, enthalpy, cs, verbose)

    Computes the hydro fields on a section of the particles specified as input. First, computes the \(\mathrm{SPH}\) pressure starting from the \(\mathrm{SPH}\) baryon mass density, and the specific internal energy. The pressure is computed differently for different \(\mathrm{EOS}\), and for cold and hot systems. Then computes the enthalpy and the sound speed accordingly.

    Arguments

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

    particles object which this PROCEDURE is a member of

    integer, intent(in) :: npart_in

    First index of the desired section of the particles

    integer, intent(in) :: npart_fin

    Last index of the desired section of the particles

    class(eos), intent(in) :: eqos

    \(\mathrm{EOS}\) to be used

    double precision, intent(in), DIMENSION(npart_fin - npart_in + 1) :: nlrf

    Baryon mass density in the local rest frame

    double precision, intent(inout), DIMENSION(npart_fin - npart_in + 1) :: u

    Specific internal energy

    double precision, intent(inout), DIMENSION(npart_fin - npart_in + 1) :: Pr

    Pressure

    double precision, intent(inout), DIMENSION(npart_fin - npart_in + 1) :: enthalpy

    Enthalpy

    double precision, intent(inout), DIMENSION(npart_fin - npart_in + 1) :: cs

    Speed of sound

    logical, intent(in), optional :: verbose

procedure, public :: deallocate_particles_memory

Deallocates memory for the particles member arrays

  • interface

    public module subroutine deallocate_particles_memory(this)

    Deallocates allocatable arrays member of a particles object

    Arguments

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

    particles object which this PROCEDURE is a member of

procedure, public :: get_compose_eos

Returns compose_eos

  • interface

    public pure module function get_compose_eos(this) result(compose_eos)

    Returns compose_eos

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value logical

    (compose_eos)

procedure, public :: get_eos_id

Returns the \(\mathrm{EOS}\) identifier for matter object i_matter

  • interface

    public pure module function get_eos_id(this, i_matter) result(eos_id)

    Returns compose_eos

    Arguments

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

    particles object which this PROCEDURE is a member of

    integer, intent(in) :: i_matter

    Index of the matter object

    Return Value integer

    (compose_eos)

procedure, public :: get_g3

Returns (g_xx,g_xy,g_xz,g_yy,g_yz,g_zz)

  • interface

    public pure module function get_g3(this) result(g3)

    Returns the spatial metric on the particles

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(6,this% npart)

    (g_xx,g_xy,g_xz,g_yy,g_yz,g_zz)

procedure, public :: get_h

Returns h

  • interface

    public pure module function get_h(this) result(h)

    Returns h

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(:), ALLOCATABLE

    h

procedure, public :: get_lapse

Returns lapse

  • interface

    public pure module function get_lapse(this) result(lapse)

    Returns lapse

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(this% npart)

    lapse

procedure, public :: get_n_matter

Returns n_matter

  • interface

    public pure module function get_n_matter(this) result(n_matter)

    Returns n_matter

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value integer

    n_matter

procedure, public :: get_nlrf

Returns nlrf

  • interface

    public pure module function get_nlrf(this) result(nlrf)

    Returns nlrf

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(:), ALLOCATABLE

    nlrf

procedure, public :: get_nlrf_sph

Returns nlrf_sph

  • interface

    public pure module function get_nlrf_sph(this) result(nlrf_sph)

    Returns nlrf_sph

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(:), ALLOCATABLE

    nlrf_sph

procedure, public :: get_npart

Returns npart

  • interface

    public pure module function get_npart(this) result(n_part)

    Returns npart

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value integer

    npart

procedure, public :: get_npart_i

Returns the number of particles on the object i_matter

  • interface

    public pure module function get_npart_i(this, i_matter) result(n_part)

    Returns the number of particles on the object i_matter

    Arguments

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

    particles object which this PROCEDURE is a member of

    integer, intent(in) :: i_matter

    Index of the matter object

    Return Value integer

    Number of particles on the object i_matter

procedure, public :: get_nstar

Returns nstar

  • interface

    public pure module function get_nstar(this) result(nstar)

    Returns nstar

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(:), ALLOCATABLE

    nstar

procedure, public :: get_nstar_sph

Returns nstar_sph

  • interface

    public pure module function get_nstar_sph(this) result(nstar_sph)

    Returns nstar_sph

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(:), ALLOCATABLE

    nstar_sph

procedure, public :: get_nu

Returns nu

  • interface

    public pure module function get_nu(this) result(nu)

    Returns nu

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(:), ALLOCATABLE

    nu

procedure, public :: get_nuratio

Returns nuratio

  • interface

    public pure module function get_nuratio(this) result(nuratio)

    Returns nuratio

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value double precision

    nuratio

procedure, public :: get_nuratio_i

Returns the baryon number ratio on the object i_matter

  • interface

    public pure module function get_nuratio_i(this, i_matter) result(nuratio)

    Returns the baryon number ratio on the object i_matter

    Arguments

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

    particles object which this PROCEDURE is a member of

    integer, intent(in) :: i_matter

    Index of the matter object

    Return Value double precision

    Baryon number ratio on the object i_matter

procedure, public :: get_object_of_particle

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 .

  • interface

    public 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 .

    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

procedure, public :: get_pos

Returns pos

  • interface

    public pure module function get_pos(this) result(pos_u)

    Returns pos

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(:,:), ALLOCATABLE

    pos

procedure, public :: get_pressure

Returns pressure

  • interface

    public pure module function get_pressure(this) result(pressure)

    Returns pressure

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(:), ALLOCATABLE

    pressure

procedure, public :: get_pressure_sph

Returns pressure_sph

  • interface

    public pure module function get_pressure_sph(this) result(pressure_sph)

    Returns pressure_sph

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(:), ALLOCATABLE

    pressure_sph

procedure, public :: get_shift

Returns (shift_x,shift_y,shift_z)

  • interface

    public pure module function get_shift(this) result(shift)

    Returns

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(3,this% npart)

    (shift_x,shift_y,shift_z)

procedure, public :: get_theta

Returns Theta

  • interface

    public pure module function get_theta(this) result(theta)

    Returns Theta

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(:), ALLOCATABLE

    Theta

procedure, public :: get_u

Returns specific_energy

procedure, public :: get_u_sph

Returns u_sph

  • interface

    public pure module function get_u_sph(this) result(u_sph)

    Returns u_sph

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(:), ALLOCATABLE

    u_sph

procedure, public :: get_vel

Returns v

  • interface

    public pure module function get_vel(this) result(vel)

    Returns v

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(:,:), ALLOCATABLE

    v

procedure, public, NOPASS :: impose_equatorial_plane_symmetry

Reflects the positions of the particles on a matter object with respect to the plane

  • interface

    public 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

    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

procedure, public :: is_empty

Returns .TRUE if the particles object is empty, .FALSE otherwise

  • interface

    public module function is_empty(this) result(answer)

    Returns .TRUE if the particles object is empty, .FALSE otherwise

    Arguments

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

    particles object which this PROCEDURE is a member of

    Return Value logical

    .TRUE if the particles object is empty, .FALSE otherwise

procedure, public, NOPASS :: perform_apm

Performs the Artificial Pressure Method (APM) on one star's particles

  • interface

    public module subroutine perform_apm(get_density, get_nstar_id, get_pressure_id, compute_pressure, npart_output, pos_input, pvol, h_output, nu_output, center, com_star, mass, sizes, eqos, apm_max_it, max_inc, mass_it, correct_nu, nuratio_thres, nuratio_des, use_pressure, adapt_ghosts, move_away_ghosts, nx_gh, ny_gh, nz_gh, ghost_dist, use_atmosphere, remove_atmosphere, print_step, namefile_pos_id, namefile_pos, namefile_results, validate_position, surf)

    Performs the Artificial Pressure Method (APM)

    particles object which this PROCEDURE is a member of

    Arguments

    Type IntentOptional Attributes Name
    function get_density(x, y, z) result(density)

    Returns the baryon mass density at the desired point

    Arguments
    Type IntentOptional Attributes Name
    double precision, intent(in) :: x

    coordinate of the desired point

    double precision, intent(in) :: y

    coordinate of the desired point

    double precision, intent(in) :: z

    coordinate of the desired point

    Return Value double precision

    Baryon mass density at

    subroutine get_nstar_id(npart, x, y, z, nstar_sph, nstar_id, nlrf_sph, sqg)

    Computes the proper baryon number density at the particle positions

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

    Number of real particles (i.e., no ghost particles included here)

    double precision, intent(in) :: x(npart)

    Array of coordinates

    double precision, intent(in) :: y(npart)

    Array of coordinates

    double precision, intent(in) :: z(npart)

    Array of coordinates

    double precision, intent(in) :: nstar_sph(npart)

    \(\mathrm{SPH}\) proper baryon density

    double precision, intent(out) :: nstar_id(npart)

    Array to store the computed proper baryon number density

    double precision, intent(out) :: nlrf_sph(npart)

    Array to store the local rest frame baryon density computed from the \(\mathrm{SPH}\) proper baryon density

    double precision, intent(out) :: sqg(npart)

    Square root of minus the determinant of the spacetime metric

    function get_pressure_id(x, y, z) result(pressure)

    Returns the baryon mass density at the desired point

    Arguments
    Type IntentOptional Attributes Name
    double precision, intent(in) :: x

    coordinate of the desired point

    double precision, intent(in) :: y

    coordinate of the desired point

    double precision, intent(in) :: z

    coordinate of the desired point

    Return Value double precision

    Baryon mass density at

    subroutine compute_pressure(npart, x, y, z, nlrf, eqos, pressure, verbose)
    Arguments
    Type IntentOptional Attributes Name
    integer, intent(in) :: npart

    Returns the baryon mass density at the desired point

    double precision, intent(in) :: x(npart)

    coordinate of the desired point

    double precision, intent(in) :: y(npart)

    coordinate of the desired point

    double precision, intent(in) :: z(npart)

    coordinate of the desired point

    double precision, intent(in) :: nlrf(npart)

    Baryon mass density in the local rest frame

    type(eos), intent(in) :: eqos

    \(\mathrm{EOS}\) to use

    double precision, intent(inout) :: pressure(npart)

    Baryon mass density at

    logical, intent(in), optional :: verbose

    If .TRUE., print informative standard output about how the pressure is computed. Default is .TRUE.

    integer, intent(inout) :: npart_output

    Initial particle number

    double precision, intent(inout), DIMENSION(:,:), ALLOCATABLE :: pos_input

    Initial particle positions

    double precision, intent(inout), DIMENSION(:), ALLOCATABLE :: pvol

    Initial particle volume

    double precision, intent(inout), DIMENSION(:), ALLOCATABLE :: h_output

    Array to store the smoothing lengths computed at the end of the APM iteration

    double precision, intent(inout), DIMENSION(:), ALLOCATABLE :: nu_output

    Array to store the baryon number per particle computed at the end of the APM iteration

    double precision, intent(in), DIMENSION(3) :: center

    Center of the matter object, from the \(\mathrm{ID}\)

    double precision, intent(inout), DIMENSION(3) :: com_star

    Center of mass of the matter object, from the \(\mathrm{ID}\)

    double precision, intent(in) :: mass

    Mass of the matter object

    double precision, intent(in), DIMENSION(6) :: sizes

    Sizes of the matter object

    type(eos), intent(in) :: eqos

    \(\mathrm{EOS}\) to use when computing the pressure

    integer, intent(in) :: apm_max_it

    Maximum number of APM iterations, irrespective of the EXIT condition

    integer, intent(in) :: max_inc

    Sets the EXIT condition: If the average over all the particles of the relative error in the density estimate grows max_inc times, exit the iteration.

    logical, intent(in) :: mass_it

    If .TRUE. performs a second iteration after the APM one, without moving the particles, changing their mass in order to better match the star density. The mass ratio grows very fast in all the tried experiments, hence the suggested value is .FALSE.

    logical, intent(in) :: correct_nu

    If .TRUE., the baryon number per particle nu is corrected to include the total baryonic masses of the stars.

    double precision, intent(in) :: nuratio_thres

    Maximum mass ratio (equivalently baryon number ratio) to be used in the one-time-only final correction of the particle masses to match the star density even better (without moving the particles)

    double precision, intent(in) :: nuratio_des

    Sets the EXIT condition: If the baryon number ratio is within 2.5% of nuratio_des, exit the iteration Set nuratio_des to 0 to deactivate and exit the APM iteration using max_inc

    logical, intent(in) :: use_pressure

    If .TRUE., uses the physical pressure computed with the \(\mathrm{EOS}\) using the SPH estimate of the density nlrf_sph, to compute the artificial pressure. Otherwise, the density variable nstar_sph is used to compute the artificial pressure

    logical, intent(in) :: adapt_ghosts

    If .TRUE., the ghost particles will be placed and have a baryon number such to reproduce the density of the outermost layers (r > 99% of the minimum radius) of the object. If .TRUE., the arguments nx_gh, ny_gh, nz_gh, ghost_dist are ignored; if .FALSE., they are instead used to place the ghost particles

    logical, intent(in) :: move_away_ghosts

    If .TRUE., the ghost particles will slowly move away from the surface of the star during the iteration (depending on the EXIT condition chosen, this happens in slightly different ways), to allow for the real particles to get closer to the surface

    integer, intent(in) :: nx_gh

    Number of lattice points in the x direction for ghosts

    integer, intent(in) :: ny_gh

    Number of lattice points in the y direction for ghosts

    integer, intent(in) :: nz_gh

    Number of lattice points in the z direction for ghosts

    double precision, intent(inout) :: ghost_dist

    Distance between the ghost particles and the surface of the matter object considered (star, ejecta, etc...)

    logical, intent(inout) :: use_atmosphere

    If .TRUE., allows particles to move where the density is 0, and displace them using only the smoothing term. This can be useful when the system has an irregular geometry, as, for example, an ejecta; .FALSE. otherwise

    logical, intent(inout) :: remove_atmosphere

    If .TRUE., removes the particles placed where the density is 0, at the end of the APM iteration; .FALSE. otherwise

    integer, intent(inout) :: print_step

    Prints the particle positions to a formatted file every print_step steps

    character(len=*), intent(inout), optional :: namefile_pos_id

    Name for the formatted file where the initial particle positions and the ghost positions will be printed

    character(len=*), intent(inout), optional :: namefile_pos

    Name for the formatted file where the particle positions and the ghost positions will be printed every 15 iterations

    character(len=*), intent(inout), optional :: namefile_results

    Name for the formatted file where various quantities related to the particle distribution, the baryon number particle and the kernel estimate of the density will be printed at the end of the APM iteration

    procedure(validate_position_int), optional :: validate_position

    Returns 1 if the position is not valid, 0 otherwise

    type(surface), intent(in), optional :: surf

    Surface of the matter object

procedure, public :: place_particles_ellipsoidal_surfaces

Places particles on ellipsoidal surfaces on one star

  • interface

    public module subroutine place_particles_ellipsoidal_surfaces(this, mass_star, radius, center, central_density, npart_des, npart_out, pos, pvol, nu, h, last_r, upper_bound, lower_bound, upper_factor, lower_factor, max_steps, filename_mass_profile, filename_shells_radii, filename_shells_pos, get_density, integrate_density, get_id, validate_position, radii, surf)

    Places particles on ellipsoidal surfaces on one star

    Arguments

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

    particles object which this PROCEDURE is a member of

    double precision, intent(in) :: mass_star

    Baryonic mass of the star

    double precision, intent(in) :: radius

    Radius of the star in the x direction towards the companion

    double precision, intent(in), DIMENSION(3) :: center

    (x|) coordinate of the center of the star, i.e., of the point with highest density

    double precision, intent(in) :: central_density

    Central density of the star, i.e., highest density

    integer, intent(in) :: npart_des

    idbase object needed to access the BNS data

    integer, intent(out) :: npart_out

    Final number of particles on the star

    double precision, intent(inout), DIMENSION(:,:), ALLOCATABLE :: pos

    Array string the final positions

    double precision, intent(inout), DIMENSION(:), ALLOCATABLE :: pvol

    Array soring the inal particle volumes

    double precision, intent(inout), DIMENSION(:), ALLOCATABLE :: nu

    Array storing the final particle masses Array storing the particle baryon masses

    double precision, intent(inout), DIMENSION(:), ALLOCATABLE :: h

    Array storing the initial guess for the particle smoothing lengths

    double precision, intent(in) :: last_r

    Radius of the last ellipsoidal surface

    double precision, intent(inout) :: upper_bound

    Desired upper bound for the differences between particle masses on neighbouring ellipsoidal surfaces

    double precision, intent(inout) :: lower_bound

    Desired lower bound for the differences between particle masses on neighbouring ellipsoidal surfaces

    double precision, intent(in) :: upper_factor

    If, after max_steps, the iteration did not converge, multiply upper_bound by upper_factor, and lower_bound by lower_factor. upper_factor >= 1, usually an increase of 1% works

    double precision, intent(in) :: lower_factor

    If, after max_steps, the iteration did not converge, multiply upper_bound by upper_factor, and lower_bound by lower_factor. lower_factor <= 1, usually a decrease of 1% works

    integer, intent(in) :: max_steps

    If, after max_steps, the iteration did not converge, multiply upper_bound by upper_factor, and lower_bound by lower_factor. max_steps >= 10. 100 is a nice value

    character(len=*), intent(inout), optional :: filename_mass_profile
    character(len=*), intent(inout), optional :: filename_shells_radii

    Name of the file to store the surface radii

    character(len=*), intent(inout), optional :: filename_shells_pos

    Name of the file to store the final particle positions

    function get_density(x, y, z) result(density)

    Returns the baryon mass density at the desired point

    Arguments
    Type IntentOptional Attributes Name
    double precision, intent(in) :: x

    coordinate of the desired point

    double precision, intent(in) :: y

    coordinate of the desired point

    double precision, intent(in) :: z

    coordinate of the desired point

    Return Value double precision

    Baryon mass density at

    subroutine integrate_density(center, radius, central_density, dr, dth, dphi, mass, mass_profile, mass_profile_idx, radii, surf)
    Arguments
    Type IntentOptional Attributes Name
    double precision, intent(in), DIMENSION(3) :: center

    Center of the star

    double precision, intent(in) :: radius

    Radius of the star

    double precision, intent(in) :: central_density

    Central density of the star

    double precision, intent(in) :: dr

    Integration steps

    double precision, intent(in) :: dth

    Integration steps

    double precision, intent(in) :: dphi

    Integration steps

    double precision, intent(inout) :: mass

    Integrated mass of the star

    double precision, intent(out), DIMENSION(3,0:NINT(radius/dr)) :: mass_profile

    Array storing the radial mass profile of the star

    integer, intent(out), DIMENSION(0:NINT(radius/dr)) :: mass_profile_idx

    Array to store the indices for array mass_profile, sorted so that mass_profile[mass_profile_idx] is in increasing order INTEGER, DIMENSION(:), ALLOCATABLE, INTENT(INOUT)::mass_profile_idx

    double precision, intent(in), optional, DIMENSION(2) :: radii
    type(surface), intent(in), optional :: surf

    Surface of the matter object

    subroutine get_id(x, y, z, sqdetg, baryon_density, gamma_euler)

    Returns the baryon mass density at the desired point

    Arguments
    Type IntentOptional Attributes Name
    double precision, intent(in) :: x

    coordinate of the desired point

    double precision, intent(in) :: y

    coordinate of the desired point

    double precision, intent(in) :: z

    coordinate of the desired point

    double precision, intent(out) :: sqdetg
    double precision, intent(out) :: baryon_density
    double precision, intent(out) :: gamma_euler
    procedure(validate_position_int), optional :: validate_position

    Returns 1 if the position is not valid, 0 otherwise

    double precision, intent(in), optional, DIMENSION(2) :: radii
    type(surface), intent(in), optional :: surf

    Surface of the matter object

procedure, public :: place_particles_lattice

Places particles on a single lattice that surrounds both stars

  • interface

    public module subroutine place_particles_lattice(this, central_density, xmin, xmax, ymin, ymax, zmin, zmax, npart_des, npart_out, stretch, thres, pos, pvol, nu, h, get_density, get_id, validate_position)

    Places particles on a lattice containing a physical object

    Arguments

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

    particles object which this PROCEDURE is a member of

    double precision, intent(in) :: central_density

    Maximum baryon mass density of the system

    double precision, intent(in) :: xmin

    Left boundary of the lattice

    double precision, intent(in) :: xmax

    Right boundary of the lattice

    double precision, intent(in) :: ymin

    Left boundary of the lattice

    double precision, intent(in) :: ymax

    Right boundary of the lattice

    double precision, intent(in) :: zmin

    Left boundary of the lattice

    double precision, intent(in) :: zmax

    Right boundary of the lattice

    integer, intent(in) :: npart_des

    Desired particle number

    integer, intent(out) :: npart_out

    Real, output particle number

    double precision, intent(in) :: stretch

    Stretching factor fo the lattice. xmin to zmax are multiplied by it

    double precision, intent(in) :: thres

    (~rho_max)/thres is the minimum mass density considered when placing particles. Used only when redistribute_nu is .FALSE. . When redistribute_nu is .TRUE. thres= 100*nu_ratio

    double precision, intent(inout), DIMENSION(:,:), ALLOCATABLE :: pos
    double precision, intent(inout), DIMENSION(:), ALLOCATABLE :: pvol

    Array storing the particle positions Array storing the particle volumes

    double precision, intent(inout), DIMENSION(:), ALLOCATABLE :: nu

    Array storing the particle baryon masses

    double precision, intent(inout), DIMENSION(:), ALLOCATABLE :: h

    Array storing the initial guess for the particle smoothing lengths

    function get_density(x, y, z) result(density)

    Returns the baryon mass density at the desired point

    Arguments
    Type IntentOptional Attributes Name
    double precision, intent(in) :: x

    coordinate of the desired point

    double precision, intent(in) :: y

    coordinate of the desired point

    double precision, intent(in) :: z

    coordinate of the desired point

    Return Value double precision

    Baryon mass density at

    subroutine get_id(x, y, z, sqdetg, baryon_density, gamma_euler)

    Returns the baryon mass density at the desired point

    Arguments
    Type IntentOptional Attributes Name
    double precision, intent(in) :: x

    coordinate of the desired point

    double precision, intent(in) :: y

    coordinate of the desired point

    double precision, intent(in) :: z

    coordinate of the desired point

    double precision, intent(out) :: sqdetg
    double precision, intent(out) :: baryon_density
    double precision, intent(out) :: gamma_euler
    procedure(validate_position_int), optional :: validate_position

    Returns 1 if the position is not valid, 0 otherwise

procedure, public :: print_formatted_id_particles

Prints the \(\mathrm{SPH}\) \(\mathrm{ID}\) to a formatted file

  • interface

    public module subroutine print_formatted_id_particles(this, namefile)

    Prints the SPH ID to a formatted file

    Arguments

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

    particles object which this PROCEDURE is a member of

    character(len=*), intent(inout), optional :: namefile

    Name of the formatted output file

procedure, public :: print_summary

Prints the SPH ID to a formatted file

  • interface

    public module subroutine print_summary(this)

    Prints a summary of the properties of the \(\mathrm{SPH}\) particle distribution, optionally, to a formatted file whose name is given as the optional argument filename

    Arguments

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

    Name of the formatted file to print the summary to

procedure, public :: read_compose_composition

Reads the table in the CompOSE file with extension .beta

  • interface

    public module subroutine read_compose_composition(this, namefile)

    Reads the table in the CompOSE file with extension .beta

    Arguments

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

    particles object which this PROCEDURE is a member of

    character(len=*), intent(inout), optional :: namefile

    To read the file great_eos.beta in directory compose_path/GREAT_EoS, namefile="GREAT_EoS/great_eos"

procedure, public :: read_particles_formatted_file

Read particle positions and nu from a formatted file with the following format:

  1. The first line must contain the integer number of objects for the system, and the particle numbers on each object; each column separated by one tab.
  2. The other lines must contain at least 3 columns with the x, y, z coordinates of the particle positions. An optional 4th column can contain the values of nu on the particles. If the 4th column is not present, nu will be roughly estimated using the density read from the ID and the average volume per particle; the latter is computed by computing the average particle separation along the z direction.
  • interface

    public module subroutine read_particles_formatted_file(this, parts_pos_unit, nline_in, nline_fin, xmin, xmax, ymin, ymax, zmin, zmax, pos, pvol, nu, h)

    Read particle positions and nu from a formatted file with the following format:

    1. The first line must contain the integer number of objects for the system, and the particle numbers on each object; each column separated by one tab.
    2. The other lines must contain at least 3 columns with the x, y, z coordinates of the particle positions. An optional 4th column can contain the values of nu on the particles. If the 4th column is not present, nu will be roughly estimated using the density read from the ID and the average volume per particle; the latter is computed by computing the average particle separation along the z direction.

    Arguments

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

    particles object which this PROCEDURE is a member of

    String containing the name of the formatted file containing the particle positions and, optionally, nu

    integer :: parts_pos_unit

    Unit number of the formatted file containing the particle positions and, optionally, nu

    integer :: nline_in

    First line containing the relevant data

    integer :: nline_fin

    Last line containing the relevant data

    double precision, intent(in) :: xmin

    Left boundary of the lattice

    double precision, intent(in) :: xmax

    Right boundary of the lattice

    double precision, intent(in) :: ymin

    Left boundary of the lattice

    double precision, intent(in) :: ymax

    Right boundary of the lattice

    double precision, intent(in) :: zmin

    Left boundary of the lattice

    double precision, intent(in) :: zmax

    Right boundary of the lattice

    double precision, intent(inout), DIMENSION(:,:), ALLOCATABLE :: pos
    double precision, intent(inout), DIMENSION(:), ALLOCATABLE :: pvol

    Array storing the particle positions Array storing the particle volumes

    double precision, intent(inout), DIMENSION(:), ALLOCATABLE :: nu

    Array storing the particle baryon masses

    double precision, intent(inout), DIMENSION(:), ALLOCATABLE :: h

    Array storing the initial guess for the particle smoothing lengths

procedure, public :: read_sphincs_dump_print_formatted

Reads the binary ID file printed by compute_and_print_sph_variables, and prints it to a formatted file.

  • interface

    public module subroutine read_sphincs_dump_print_formatted(this, namefile_bin, namefile, save_data)

    Reads the binary ID file printed by compute_and_print_sph_variables and prints the data stored in it to a formatted file

    Arguments

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

    particles object which this PROCEDURE is a member of

    character(len=*), intent(inout), optional :: namefile_bin

    Name of the binary file to be read

    character(len=*), intent(inout), optional :: namefile

    Name of the formatted file to be printed

    logical, intent(in), optional :: save_data

    If .TRUE., saves the read data into the TYPE member variables

procedure, public :: test_recovery

Computes the conserved variables from the physical ones, and vice versa, to test that the recovered physical variables are the same to those computed from the \(\mathrm{ID}\).

Computes an estimate of the linear momentum using the canonical momentum per baryon on the particles

  • interface

    public module subroutine test_recovery(this, npart, pos, nlrf, u, pr, vel_u, theta, nstar)

    Tests the recovery. Computes the conserved variables from the physical ones, and then the physical ones from the conserved ones. It then compares the variables computed with the recovery PROCEDURES, with those computed with \(\texttt{SPHINCS_ID}\).

    Arguments

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

    particles object which this PROCEDURE is a member of

    integer, intent(in) :: npart

    Particle number

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

    Particle positions

    double precision, intent(in), DIMENSION(npart) :: nlrf

    Baryon density in the local rest frame on the particles

    double precision, intent(in), DIMENSION(npart) :: u

    Specific internal energy on the particles

    double precision, intent(in), DIMENSION(npart) :: pr

    Pressure on the particles

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

    Spatial velocity in the computing frame on the particles

    double precision, intent(in), DIMENSION(npart) :: theta

    Generalized Lorentz factor on the particles

    double precision, intent(in), DIMENSION(npart) :: nstar

    Proper baryon density in the local rest frame on the particles

    Canonical momentum on the particles

    Canonical energy on the particles

    Name of the formatted file where the data is printed

Source Code

  TYPE:: particles
  !! TYPE representing a |sph| particle distribution


    PRIVATE


    INTEGER:: npart
    !! Total particle number
    INTEGER:: n_matter
    !! Number of matter objects in the physical system
    INTEGER, DIMENSION(:), ALLOCATABLE:: npart_i
    !! Array storing the particle numbers for the matter objects
    INTEGER, DIMENSION(:), ALLOCATABLE:: npart_fin
    !! Array storing the index of the last particle for each matter objects
    INTEGER:: distribution_id
    !! Identification number for the particle distribution
    INTEGER:: call_flag= 0
    !# Flag that is set different than 0 if the SUBROUTINE
    !  compute_and_print_sph_variables is called
    LOGICAL:: cold_system
    !# `.TRUE.` if the system is at zero temperature (no thermal component);
    !  `.FALSE.` otherwise
    DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE:: barycenter
    !# Array storing the centers of mass of the matter objects
    DOUBLE PRECISION, DIMENSION(4):: barycenter_system
    !# Array storing the center of mass of the **entire particle distribution**

    INTEGER, DIMENSION(:), ALLOCATABLE:: baryon_density_index
    !# Array storing the indices to use with [[particles:baryon_density]]
    !  to sort the elements of [[particles:baryon_density]] in increasing
    !  order

    !
    !-- Hydro variables on the particles
    !

    !> 2-D array storing the particle positions
    DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE:: pos
    !& 1-D array storing the baryon mass density in the fluid frame
    !  \([\mathrm{kg}\,\mathrm{m}^{-3}]\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: baryon_density
    !> 1-D array storing the energy density
    !  \([\mathrm{kg}\,c^2\,\mathrm{m}^{-3}]\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: energy_density
    !> 1-D array storing the specific internal energy \([c^2]\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: specific_energy
    !& 1-D array storing the specific internal energy \([c^2]\) computed using
    !  formula (9) in Read et al., Phys.Rev.D79:124032,2009,
    !  [arXiv:0812.2163][https://arxiv.org/abs/0812.2163]{:target="_blank"}
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: u_sph
    !> 1-D array storing the pressure \([\mathrm{kg}\,c^2\,\mathrm{m}^{-3}]\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: pressure
    !& 1-D array storing the pressure in code units
    !  \([\mathrm{amu}\,c^2\,\mathrm{L_\odot}^{-3}]\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: pressure_sph
    !& 1-D array storing the x component of the fluid 3-velocity wrt
    !  the Eulerian observer \([c]\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: v_euler_x
    !& 1-D array storing the y component of the fluid 3-velocity wrt
    !  the Eulerian observer \([c]\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: v_euler_y
    !& 1-D array storing the z component of the fluid 3-velocity wrt
    !  the Eulerian observer \([c]\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: v_euler_z

    !
    !-- Arrays to store the electron fraction Ye as a function of the
    !-- baryon number density for beta-equilibrated EoS at T~0,
    !-- imported from the CompOSE database's and software's files
    !

    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: nb_table
    !# Array storing the values of the baryon number density in the |compose|
    !  table. @todo ADD UNITS
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: Ye_table
    !! Array storing the values of the electron fraction in the |compose| table

    !
    !-- Spacetime fields
    !

    !> Array storing the values of the lapse function on the particles
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: lapse
    !& Array storing the values of the x component of the shift vector
    !  on the particles
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: shift_x
    !& Array storing the values of the y component of the shift vector
    !  on the particles
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: shift_y
    !& Array storing the values of the z component of the shift vector
    !  on the particles
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: shift_z
    !& Array storing the values of the xx component of the spatial metric
    !  on the particles
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: g_xx
    !& Array storing the values of the xy component of the spatial metric
    !  on the particles
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: g_xy
    !& Array storing the values of the xz component of the spatial metric
    !  on the particles
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: g_xz
    !& Array storing the values of the xz component of the spatial metric
    !  on the particles
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: g_yy
    !& Array storing the values of the yz component of the spatial metric
    !  on the particles
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: g_yz
    !& Array storing the values of the zz component of the spatial metric
    !  on the particles
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: g_zz

    !
    !-- SPH fields
    !

    !& 1-D array storing baryon density in the local rest frame
    !  \([\mathrm{baryon}\, (L_\odot)^{-3}]\), computed directly from
    !  the |lorene| density
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: nlrf
    !& 1-D array storing baryon density in the local rest frame
    !  \([\mathrm{baryon}\, (L_\odot)^{-3}]\), computed from the kernel
    !  interpolated proper baryon number density [[particles:nstar_sph]]
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: nlrf_sph
    !> 1-D array storing the baryon number per particle
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: nu
    !& 1-D array storing the SPH estimate of the proper baryon number density
    !  \([\mathrm{baryon}\, (L_\odot)^{-3}]\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: nstar
    !& 1-D array storing the particle number density
    !  \([\mathrm{particle}\, (L_\odot)^{-3}]\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: particle_density
    !& 1-D array storing the SPH estimate of the proper baryon number density,
    !  from kernel interpolation \([\mathrm{baryon}\, (L_\odot)^{-3}]\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: nstar_sph
    !& 1-D array storing the SPH estimate of the particle number density, from
    !  kernel interpolation \([\mathrm{particle}\, (L_\odot)^{-3}]\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: particle_density_sph
    !> 1-D array storing the enthalpy \([??]\) @todo add units
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: enthalpy
    !> 2-D array storing the coordinate fluid 4-velocity \([c]\)
    DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE:: v
    !> 1-D array storing the generalized Lorentz factor
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: Theta
    !> 1-D array storing the electron fraction
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: Ye
    !> 1-D array storing the smoothing length \(L_\odot\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: h
    !> 1-D array storing the particle volumes \(L_\odot^3\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: pvol
    !> 1-D array storing the particle masses \(M_\odot\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: masses
    !> 1-D array storing the surfaces of the matter objects
    TYPE(surface),  DIMENSION(:), ALLOCATABLE:: surfaces
    !& Ratio between baryonic masses of the matter objects and the maximum
    !  baryonic mass among them @warning always \(< 1\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: mass_ratios
    !& Ratio between baryonic masses of the matter objects and the total
    !  baryonic mass of all the matter objects @warning always \(< 1\)
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: mass_fractions
    !> Total baryon number
    DOUBLE PRECISION:: nbar_tot
    !> Baryon numbers of the matter objects
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: nbar_i
    !& Ratio between the max and min of the baryon number per particle, over
    !  all the matter objects
    DOUBLE PRECISION:: nuratio
    !& Desired ratio between the max and min of the baryon number per particle,
    !  over all the matter objects. **Only used when redistribute_nu is .TRUE.**
    !  @warning Almost deprecated
    DOUBLE PRECISION:: nu_ratio_des
    !> Baryon number ratios on the matter objects
    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: nuratio_i

    DOUBLE PRECISION:: adm_mass
    DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE:: adm_linear_momentum_i
    !# Estimate of the \(\mathrm{ADM}\) linear momentum of each matter object,
    !  computed from the canonical momentum per baryon on the particles
    DOUBLE PRECISION, DIMENSION(3)               :: adm_linear_momentum_fluid
    !# Estimate of the \(\mathrm{ADM}\) linear momentum of the fluid computed
    !  from the canonical momentum per baryon on the particles

    !
    !-- Strings
    !

    CHARACTER(LEN= 50):: sphincs_id_particles
    !! String containing the name of the particles parameter file

    CHARACTER(LEN=:), ALLOCATABLE:: compose_path
    !# String storing the local path to the directory containing the
    !  CompOSE |eos|
    CHARACTER(LEN=:), ALLOCATABLE:: compose_filename
    !# String storing the subpath of compose_path to the CompOSE file with
    !  .beta extension

    !
    !-- Equations of state
    !

    TYPE(eos), DIMENSION(:), ALLOCATABLE:: all_eos
    !# Array of TYPE [[eos]] containing the |eos| information for all the
    !  matter objects

    !
    !-- Procedure pointers
    !

    !PROCEDURE(post_process_sph_id_int), POINTER, NOPASS:: post_process_sph_id
    PROCEDURE(), POINTER, NOPASS:: post_process_sph_id
    !# Pointer to a procedure that post_process the |sph| |id|; for example,
    !  correct for the residual ADM linear momentum.

    !
    !-- Steering variables
    !

    !> `.TRUE.` if the object is empty, `.FALSE.` if it's not empty
    LOGICAL:: empty_object
    !& `.TRUE.` if the binary files for SPHINCS_BSSN are to be exported,
    !  `.FALSE.` otherwise
    LOGICAL, PUBLIC:: export_bin
    !& `.TRUE.` if the ID in the formatted files is to be on the xy plane only,
    !  `.FALSE.` otherwise
    LOGICAL, PUBLIC:: export_form_xy
    !& `.TRUE.` if the ID in the formatted files is to be on the x axis only,
    !  `.FALSE.` otherwise
    LOGICAL, PUBLIC:: export_form_x
    !& `.TRUE.` if the threshold on the baryon mass density should e applied
    !  when placing particles on lattices, `.FALSE.` otherwise
    LOGICAL:: use_thres
    !& `.TRUE.` if the baryon number per particle should be reassigned, trying
    !  to obtain a baryon number ratio no larger than nu_ratio,
    !  when placing particles on lattices; `.FALSE.` otherwise
    LOGICAL:: redistribute_nu
    !& `.TRUE.` if the baryon number per particle should be corrected to account
    !  for the total baryon masses of the stars, `.FALSE.` otherwise
    LOGICAL:: correct_nu
    !& `.TRUE.` if the electron fraction \(Y_e\) should be read from the CompOSE
    !  table with extension.beta, `.FALSE.` otherwise
    !  @todo Chamge name of this variable to assign_Ye_compose. Check that
    !        the used EOS is indeed the one used to read \(Y_e\)
    LOGICAL:: compose_eos
    !& `.TRUE.` if the particle positions on ellipsoidal surfaces are randomized
    !  in the \(\phi\) direction, `.FALSE.` otherwise
    LOGICAL:: randomize_phi
    !& `.TRUE.` if the particle positions on ellipsoidal surfaces are randomized
    !  in the \(\theta\) direction, `.FALSE.` otherwise
    LOGICAL:: randomize_theta
    !& `.TRUE.` if the particle positions on ellipsoidal surfaces are randomized
    !  in the \(r\) direction, `.FALSE.` otherwise
    LOGICAL:: randomize_r
    !& `.TRUE.` if the Artificial Pressure Method (APM) has to be applied to the
    !  particles, `.FALSE.` otherwise
    LOGICAL, DIMENSION(:), ALLOCATABLE:: apm_iterate
    !& `.TRUE.` to allow the particles to move where the density is 0 during the
    !  Artificial Pressure Method (APM) iteration. This can be useful when the
    !  system has an irregular geometry, as, for example, an ejecta
    !  `.FALSE.` otherwise
    LOGICAL, DIMENSION(:), ALLOCATABLE:: use_atmosphere
    !& `.TRUE.` if the baryon number per particle \(\nu\) has to be read from
    !  the formatted file containing the particle positions, `.FALSE.` otherwise
    LOGICAL:: read_nu
    !& `.TRUE.` if the particles on star 2 should be the reflection of the
    !  particles on star 1 with respect to the \(yz\) plane, only if the baryon
    !  masses of the stars differe less than \(0.2\%\); `.FALSE.` otherwise
    LOGICAL:: reflect_particles_x

    !
    !-- Timers
    !

    !> Timer that times how long it takes to place particles on the stars
    TYPE(timer), PUBLIC:: placer_timer
    !& Timer that times how long it takes to check if there are multiple
    !  particles at the same positions
    TYPE(timer), PUBLIC:: same_particle_timer
    !& Timer that times how long it takes to perform the APM on the matter
    !  objects
    TYPE(timer), DIMENSION(:), ALLOCATABLE, PUBLIC:: apm_timers
    !& Timer that times how long it takes to import the \(\texttt{|lorene|}\) ID
    !  at the particle positions
    TYPE(timer), PUBLIC:: importer_timer
    !& Timer that times how long it takes to compute the SPH variables at the
    !  particle positions
    TYPE(timer), PUBLIC:: sph_computer_timer


    CONTAINS


    !-------------------!
    !--  SUBROUTINES  --!
    !-------------------!

    PROCEDURE:: read_particles_formatted_file
    !# Read particle positions and nu from a formatted file with the following
    !  format:
    !
    !   1. The first line must contain the integer number of objects for the
    !      system, and the particle numbers on each object;
    !      each column separated by one tab.
    !   2. The other lines must contain at least 3 columns with the x, y, z
    !      coordinates of the particle positions. An optional 4th column can
    !      contain the values of nu on the particles. If the 4th column is
    !      not present, nu will be roughly estimated using the density read
    !      from the ID and the average volume per particle; the latter is
    !      computed by computing the average particle separation along the
    !      z direction.

    PROCEDURE:: place_particles_lattice
    !! Places particles on a single lattice that surrounds both stars

    PROCEDURE:: place_particles_ellipsoidal_surfaces
    !! Places particles on ellipsoidal surfaces on one star

    PROCEDURE, NOPASS:: impose_equatorial_plane_symmetry
    !# Reflects the positions of the particles on a matter object with respect
    !  to the \(xy\) plane

    PROCEDURE:: get_object_of_particle
    !# Returns the number of the matter object asociated with the particle
    !  number given as input. Example: give number \(n\) as input; this
    !  particle number corresponds to a particle on matter object \(m\).
    !  This functions returns \(m\).

    PROCEDURE, NOPASS:: perform_apm
    !! Performs the Artificial Pressure Method (APM) on one star's particles

  !  GENERIC:: reshape_sph_field => reshape_sph_field_1d_ptr, &
  !                                 reshape_sph_field_2d_ptr
  !  !# GENERIC PROCEDURE, overloded to reallocate 1d and 2d arrays
  !  PROCEDURE:: reshape_sph_field_1d_ptr => reshape_sph_field_1d
  !  !! Reallocates a 1d array
  !  PROCEDURE:: reshape_sph_field_2d_ptr => reshape_sph_field_2d
  !  !! Reallocates a 2d array

    PROCEDURE:: allocate_particles_memory
    !! Allocates memory for the [[particles]] member arrays

    PROCEDURE:: deallocate_particles_memory
    !! Deallocates memory for the [[particles]] member arrays

    PROCEDURE:: compute_sph_hydro
    !# Computes the hydro fields on a section of the particles specified as
    !  input.
    !  First, computes the |sph| pressure starting from the |sph| baryon mass
    !  density, and the specific internal
    !  energy. The pressure is computed differently for different |eos|, and
    !  for cold and hot systems.
    !  Then computes the enthalpy and the sound speed accordingly.

    PROCEDURE:: read_compose_composition
    !! Reads the \(Y_e(n_b)\) table in the CompOSE file with extension .beta

    PROCEDURE:: compute_Ye
    !# Interpates linearly the electron fraction \(Y_e\) at the particle
    !  densities; that is, assigns \(Y_e\) at the particle positions

    PROCEDURE:: test_recovery
    !# Computes the conserved variables from the physical ones, and vice versa,
    !  to test that the recovered physical variables are the same to those
    !  computed from the |id|. @todo add reference for recovery

    !PROCEDURE:: compute_adm_momentum
    !# Computes an estimate of the \(\mathrm{ADM}\) linear momentum using
    !  the canonical momentum per baryon on the particles


    !
    !-- PUBLIC SUBROUTINES
    !

    PROCEDURE, PUBLIC:: analyze_hydro
    !# Scans the hydro fields taken from \(\texttt{|lorene|}\) to look
    !  for negative or zero values

    PROCEDURE, PUBLIC:: compute_and_print_sph_variables
    !# Computes the SPH variables at the particle positions, and optionally
    !  prints them to a binary file to be read by \(\texttt{SPHINCS_BSSN}\)
    !  and \(\texttt{splash}\), and to a formatted file to be read by
    !  \(\texttt{gnuplot}\), by calling
    !  [[particles:print_formatted_id_particles]]

    PROCEDURE, PUBLIC:: read_sphincs_dump_print_formatted
    !# Reads the binary ID file printed by
    !  [[particles:compute_and_print_sph_variables]], and prints it
    !  to a formatted file. @todo use this procedure in a second constructor

    PROCEDURE, PUBLIC:: print_formatted_id_particles
    !! Prints the |sph| |id| to a formatted file

    PROCEDURE, PUBLIC:: print_summary
    !! Prints the SPH ID to a formatted file

    PROCEDURE, PUBLIC:: is_empty
    !# Returns `.TRUE` if the [[particles]] object is empty, `.FALSE` otherwise
    !  @warning experimental, not actively used in the code yet

    !PROCEDURE, PUBLIC:: write_lorene_bns_id_dump

    !-----------------!
    !--  FUNCTIONS  --!
    !-----------------!

    PROCEDURE, PUBLIC:: get_npart
    !! Returns [[particles:npart]]
    PROCEDURE, PUBLIC:: get_npart_i
    !! Returns the number of particles on the object `i_matter`
    PROCEDURE, PUBLIC:: get_n_matter
    !! Returns [[particles:n_matter]]
    PROCEDURE, PUBLIC:: get_nuratio
    !! Returns [[particles:nuratio]]
    PROCEDURE, PUBLIC:: get_nuratio_i
    !! Returns the baryon number ratio on the object `i_matter`
    PROCEDURE, PUBLIC:: get_pos
    !! Returns [[particles:pos]]
    PROCEDURE, PUBLIC:: get_vel
    !! Returns [[particles:v]]
    PROCEDURE, PUBLIC:: get_nstar
    !! Returns [[particles:nstar]]
    PROCEDURE, PUBLIC:: get_nstar_sph
    !! Returns [[particles:nstar_sph]]
    PROCEDURE, PUBLIC:: get_nlrf
    !! Returns [[particles:nlrf]]
    PROCEDURE, PUBLIC:: get_nlrf_sph
    !! Returns [[particles:nlrf_sph]]
    PROCEDURE, PUBLIC:: get_nu
    !! Returns [[particles:nu]]
    PROCEDURE, PUBLIC:: get_u
    !! Returns [[particles:specific_energy]]
    PROCEDURE, PUBLIC:: get_u_sph
    !! Returns [[particles:u_sph]]
    PROCEDURE, PUBLIC:: get_pressure
    !! Returns [[particles:pressure]]
    PROCEDURE, PUBLIC:: get_pressure_sph
    !! Returns [[particles:pressure_sph]]
    PROCEDURE, PUBLIC:: get_theta
    !! Returns [[particles:theta]]
    PROCEDURE, PUBLIC:: get_h
    !! Returns [[particles:h]]
    PROCEDURE, PUBLIC:: get_lapse
    !! Returns [[particles:lapse]]
    PROCEDURE, PUBLIC:: get_shift
    !! Returns ([[particles:shift_x]],[[particles:shift_y]],[[particles:shift_z]])
    PROCEDURE, PUBLIC:: get_g3
    !! Returns ([[particles:g_xx]],[[particles:g_xy]],[[particles:g_xz]],[[particles:g_yy]],[[particles:g_yz]],[[particles:g_zz]])
    PROCEDURE, PUBLIC:: get_compose_eos
    !! Returns [[particles:compose_eos]]
    PROCEDURE, PUBLIC:: get_eos_id
    !! Returns the |eos| identifier for matter object `i_matter`

    FINAL:: destruct_particles
    !! Finalizer (Destructor) of [[particles]] object

  END TYPE particles