ellipsoidal_surfaces Submodule

This SUBMODULE contains the implementation of the method of TYPE particles that places particles on ellipsoidal surfaces inside a star

FT 19.04.2021



Uses

  • module~~ellipsoidal_surfaces~~UsesGraph module~ellipsoidal_surfaces ellipsoidal_surfaces module~sph_particles sph_particles module~ellipsoidal_surfaces->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


Functions

function number_surfaces(m_p, center, radius, get_dens) result(n_surfaces)

Compute the number of surfaces by integrating the linear particle density along the larger equatorial radius

Read more…

Arguments

Type IntentOptional Attributes Name
double precision, intent(in) :: m_p
double precision, intent(in) :: center
double precision, intent(in) :: radius
function get_dens(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

Return Value integer

function particle_volume(rad, col, dr_shells, dth_shells, dphi_shells, th, colatitudes, npart_equator) result(pvol)

Compute the geometrical particle volume not the proper particle volume.

Read more…

Arguments

Type IntentOptional Attributes Name
double precision, intent(in) :: rad
double precision, intent(in) :: col
double precision, intent(in) :: dr_shells
double precision, intent(inout) :: dth_shells
double precision, intent(in) :: dphi_shells
integer, intent(in) :: th
double precision, intent(in), DIMENSION(:) :: colatitudes
integer, intent(in) :: npart_equator

Return Value double precision


Subroutines

subroutine assign_surfaces_mass(surface_masses, surface_radii, radius, dr, n_surfaces, mass_profile_idx, mass_profile, mass_star)

Assign a mass to each surface, based on the radial mass profile of the star (computed along the larger equatorial radius)

Read more…

Arguments

Type IntentOptional Attributes Name
double precision, intent(inout), DIMENSION( n_surfaces ) :: surface_masses
double precision, intent(in), DIMENSION( n_surfaces ) :: surface_radii
double precision, intent(in) :: radius
double precision, intent(in) :: dr
integer, intent(in) :: n_surfaces
integer, intent(in), DIMENSION( : ) :: mass_profile_idx
double precision, intent(in), DIMENSION( :, : ) :: mass_profile
double precision, intent(in) :: mass_star

subroutine compute_colatitudes_uniformly_in(alpha, beta, colatitudes)

Compute the colatitudes according to a uniform distribution over a surface, between alpha and beta, with pi/2 < alpha < beta < pi. The values are stored in the array colatitudes See https://mathworld.wolfram.com/SpherePointPicking.html

Read more…

Arguments

Type IntentOptional Attributes Name
double precision, intent(in) :: alpha
double precision, intent(in) :: beta
double precision, intent(inout), DIMENSION(:) :: colatitudes

subroutine place_surfaces(central_dens, center, radius, m_p, n_surfaces, surface_radii, last_r, get_dens)

Place the surfaces, according to the baryon mass density of the star along the larger equatorial radius

Read more…

Arguments

Type IntentOptional Attributes Name
double precision, intent(in) :: central_dens
double precision, intent(in) :: center
double precision, intent(in) :: radius
double precision, intent(in) :: m_p
integer, intent(in) :: n_surfaces
double precision, intent(inout), DIMENSION( n_surfaces ) :: surface_radii
double precision, intent(in) :: last_r
function get_dens(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

subroutine print_mass_profile_surface_radii(mass_profile, mass_profile_idx, surface_radii, radius, dr, n_surfaces, filename_mass_profile, filename_shells_radii)

Print star's radial mass profile and radii of surfaces to different ASCII files

Read more…

Arguments

Type IntentOptional Attributes Name
double precision, intent(in), DIMENSION( :, : ) :: mass_profile
integer, intent(in), DIMENSION( : ) :: mass_profile_idx
double precision, intent(in), DIMENSION( n_surfaces ) :: surface_radii
double precision, intent(in) :: radius
double precision, intent(in) :: dr
integer, intent(in) :: n_surfaces
character(len=*), intent(in) :: filename_mass_profile
character(len=*), intent(in) :: filename_shells_radii

subroutine reallocate_array_1d(array, new_dim)

Reallocate a 1-dimensional array

Read more…

Arguments

Type IntentOptional Attributes Name
double precision, intent(inout), DIMENSION(:), ALLOCATABLE :: array
integer, intent(in) :: new_dim

subroutine reallocate_array_2d(array, new_dim, new_dim2)

Reallocate a 2-dimensional array

Read more…

Arguments

Type IntentOptional Attributes Name
double precision, intent(inout), DIMENSION(:,:), ALLOCATABLE :: array
integer, intent(in) :: new_dim
integer, intent(in) :: new_dim2

Module Procedures

module procedure place_particles_ellipsoidal_surfaces 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 spherical surfaces inside a star

Read more…

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

Read more…
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

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

Name of the file to store the final particle positions

Read more…
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