place_particles_ellipsoidal_surfaces Module Procedure

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)

Uses

    • matrix
    • utility
    • APM
    • numerics
    • constants
    • NR
  • proc~~place_particles_ellipsoidal_surfaces~~UsesGraph proc~place_particles_ellipsoidal_surfaces place_particles_ellipsoidal_surfaces APM APM proc~place_particles_ellipsoidal_surfaces->APM NR NR proc~place_particles_ellipsoidal_surfaces->NR constants constants proc~place_particles_ellipsoidal_surfaces->constants matrix matrix proc~place_particles_ellipsoidal_surfaces->matrix module~utility utility proc~place_particles_ellipsoidal_surfaces->module~utility numerics numerics proc~place_particles_ellipsoidal_surfaces->numerics module~utility->constants module~utility->matrix

Places particles on spherical surfaces inside a star

FT 19.04.2021

Upgraded to ellipsoidal surfaces. The user can choose to place prticles on ellipsoidal or spherical surfaces

FT 15.11.2022


rho_to_be_resolved= 1.138065390333111E-004

PRINT , "average rho_id on the outer layers for 1.3 MPA1=", & 1.363246651849556D+53amu/umass !=1.138065390333111E-004

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


Calls

proc~~place_particles_ellipsoidal_surfaces~~CallsGraph proc~place_particles_ellipsoidal_surfaces place_particles_ellipsoidal_surfaces bilinear_interpolation bilinear_interpolation proc~place_particles_ellipsoidal_surfaces->bilinear_interpolation none~allocate_surface_memory allocate_surface_memory proc~place_particles_ellipsoidal_surfaces->none~allocate_surface_memory none~initialize_surfaces initialize_surfaces proc~place_particles_ellipsoidal_surfaces->none~initialize_surfaces none~validate_position_final~2 validate_position_final proc~place_particles_ellipsoidal_surfaces->none~validate_position_final~2 proc~assign_surfaces_mass assign_surfaces_mass proc~place_particles_ellipsoidal_surfaces->proc~assign_surfaces_mass proc~cartesian_from_spherical cartesian_from_spherical proc~place_particles_ellipsoidal_surfaces->proc~cartesian_from_spherical proc~compute_colatitudes_uniformly_in compute_colatitudes_uniformly_in proc~place_particles_ellipsoidal_surfaces->proc~compute_colatitudes_uniformly_in proc~is_finite_number is_finite_number proc~place_particles_ellipsoidal_surfaces->proc~is_finite_number proc~number_surfaces number_surfaces proc~place_particles_ellipsoidal_surfaces->proc~number_surfaces proc~particle_volume particle_volume proc~place_particles_ellipsoidal_surfaces->proc~particle_volume proc~place_surfaces place_surfaces proc~place_particles_ellipsoidal_surfaces->proc~place_surfaces proc~print_mass_profile_surface_radii print_mass_profile_surface_radii proc~place_particles_ellipsoidal_surfaces->proc~print_mass_profile_surface_radii proc~reallocate_array_1d reallocate_array_1d proc~place_particles_ellipsoidal_surfaces->proc~reallocate_array_1d proc~reallocate_array_2d reallocate_array_2d proc~place_particles_ellipsoidal_surfaces->proc~reallocate_array_2d nu nu none~initialize_surfaces->nu pos pos none~initialize_surfaces->pos pvol pvol none~initialize_surfaces->pvol validate_position validate_position none~validate_position_final~2->validate_position proc~compute_colatitudes_uniformly_in->proc~is_finite_number proc~number_surfaces->proc~is_finite_number

Called by

proc~~place_particles_ellipsoidal_surfaces~~CalledByGraph proc~place_particles_ellipsoidal_surfaces place_particles_ellipsoidal_surfaces interface~place_particles_ellipsoidal_surfaces place_particles_ellipsoidal_surfaces interface~place_particles_ellipsoidal_surfaces->proc~place_particles_ellipsoidal_surfaces

Contents


Variables

Type Visibility Attributes Name Initial
double precision, private :: a_x
double precision, private :: a_y
double precision, private :: a_z
double precision, private, DIMENSION(:), ALLOCATABLE :: alpha
double precision, private, DIMENSION(:,:), ALLOCATABLE :: bar_density_tmp
integer, private :: cnt
integer, private :: cnt2
double precision, private :: col
double precision, private :: col_tmp
type(colatitude_pos_shell), private, DIMENSION(:), ALLOCATABLE :: colatitude_pos
logical, private, parameter :: debug = .FALSE.
double precision, private :: delta_r
integer, private :: dim_seed
double precision, private :: dphi
double precision, private :: dphi_shells
double precision, private :: dr
double precision, private :: dr_shells
double precision, private :: dth
double precision, private :: dth_shells
logical, private :: exist
character(len=:), private, ALLOCATABLE :: finalnamefile
character(len=:), private, ALLOCATABLE :: finalnamefile2
integer, private :: first_r
double precision, private, DIMENSION(:,:), ALLOCATABLE :: gam_euler_tmp
logical, private :: high_mass
double precision, private, parameter :: huge_real = 1.0D30
integer, private :: i_shell
integer, private :: itr2
logical, private :: kept_all
double precision, private :: long
logical, private :: low_mass
double precision, private :: lower_bound_tmp
double precision, private :: m_p
double precision, private, DIMENSION(:), ALLOCATABLE :: m_parts
double precision, private :: mass
double precision, private, DIMENSION(:,:), ALLOCATABLE :: mass_profile
integer, private, DIMENSION(:), ALLOCATABLE :: mass_profile_idx
double precision, private, DIMENSION(:), ALLOCATABLE :: mass_surface
double precision, private, DIMENSION(:), ALLOCATABLE :: mass_surface2
double precision, private :: mass_test
double precision, private :: mass_test2
double precision, private :: max_center
double precision, private :: max_radius
integer, private :: n_surfaces
integer, private :: npart_discard
integer, private, DIMENSION(:,:), ALLOCATABLE :: npart_discarded
integer, private, DIMENSION(:), ALLOCATABLE :: npart_shell
integer, private :: npart_shell_cnt
double precision, private :: npart_shell_kept
integer, private :: npart_shell_tmp
integer, private, DIMENSION(:), ALLOCATABLE :: npart_shelleq
integer, private, DIMENSION(:,:), ALLOCATABLE :: npart_surface_tmp
integer, private :: npart_test
double precision, private :: phase
double precision, private :: phase_th
integer, private :: phi
double precision, private, DIMENSION(:,:,:), ALLOCATABLE :: pos_shell_tmp
type(pos_on_surfaces), private, DIMENSION(:), ALLOCATABLE :: pos_surfaces
integer, private :: prev_shell
double precision, private :: proper_volume
double precision, private :: proper_volume_test
double precision, private, DIMENSION(:,:), ALLOCATABLE :: pvol_tmp
integer, private :: r
integer, private :: r_cnt
double precision, private :: rad
double precision, private :: rand_num
double precision, private :: rand_num2
integer, private :: rel_sign
integer, private, DIMENSION(:), ALLOCATABLE :: seed
double precision, private, DIMENSION(:), ALLOCATABLE :: shell_scales
double precision, private :: shell_thickness
integer, private :: size_pos_shell
double precision, private, DIMENSION(:,:), ALLOCATABLE :: sqdetg_tmp
double precision, private, DIMENSION(:), ALLOCATABLE :: surface_masses
double precision, private, DIMENSION(:), ALLOCATABLE :: surface_radii
character(len=:), private, ALLOCATABLE :: surface_type
double precision, private, DIMENSION(:), ALLOCATABLE :: surface_vol
double precision, private, DIMENSION(:), ALLOCATABLE :: surface_vol2
integer, private :: th
double precision, private :: upper_bound_tmp
double precision, private :: xtemp
double precision, private :: ytemp
double precision, private :: ztemp

Derived Types

type ::  colatitude_pos_shell

Components

Type Visibility Attributes Name Initial
double precision, public, DIMENSION(:), ALLOCATABLE :: colatitudes

type ::  pos_on_surfaces

Components

Type Visibility Attributes Name Initial
double precision, public, DIMENSION(:), ALLOCATABLE :: baryon_density
double precision, public, DIMENSION(:), ALLOCATABLE :: gamma_euler
double precision, public, DIMENSION(:), ALLOCATABLE :: pos_phi
double precision, public, DIMENSION(:,:), ALLOCATABLE :: pos_shell
double precision, public, DIMENSION(:), ALLOCATABLE :: pos_th
double precision, public, DIMENSION(:), ALLOCATABLE :: psurface_vol
double precision, public, DIMENSION(:), ALLOCATABLE :: psurface_vol2
double precision, public, DIMENSION(:), ALLOCATABLE :: sqdetg

Functions

function validate_position_final(x, y, z) result(answer)

Returns validate_position( x, y, z ) if the latter is present, .TRUE. otherwise

FT 22.09.2021


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 logical

validate_position( x, y, z ) if the latter is present, .TRUE. otherwise


Subroutines

subroutine allocate_surface_memory()

Allocates memory for the surfaces

FT 21.04.2022


Arguments

None

subroutine initialize_surfaces()

Initializes the fields before the iteration over the surfaces

FT 21.04.2022


Arguments

None