ejecta Derived Type

type, public, extends(idbase) :: ejecta

TYPE for \(\mathrm{ID}\) for \(\texttt{SPHINCS_BSSN}\) prepared on a Cartesian, uniform grid


Inherits

type~~ejecta~~InheritsGraph type~ejecta ejecta type~idbase idbase type~ejecta->type~idbase timer timer type~idbase->timer construction_timer type~surface surface type~idbase->type~surface surfaces type~tabu_eos tabu_eos type~idbase->type~tabu_eos tab_eos

Contents

Source Code


Components

Type Visibility Attributes Name Initial
double precision, public :: adm_mass

ADM mass of the system

double precision, public, DIMENSION(:,:), ALLOCATABLE :: barycenters

Barycenters of the matter objects

double precision, public, DIMENSION(:,:,:), ALLOCATABLE :: baryon_mass_density

Array storing the baryon mass density at the grid points. The indices specify the grid point.

double precision, public, DIMENSION(:,:), ALLOCATABLE :: centers

Centers of the matter objects

type(timer), public :: construction_timer

Timer that times the construction of the appropriate object

double precision, public :: dx_grid

Spacing on the -axis for the grid containing the \(\mathrm{ID}\)

double precision, public :: dy_grid

Spacing on the -axis for the grid containing the \(\mathrm{ID}\)

double precision, public :: dz_grid

Spacing on the -axis for the grid containing the \(\mathrm{ID}\)

character(len=:), public, ALLOCATABLE :: eos

Name of the equation of state (EoS) of star 1

integer, public :: eos_id

\(\texttt{SPHINCS_ID}\) identifier for the \(\mathrm{EOS}\)

procedure, public, POINTER, NOPASS :: finalize_sph_id_ptr

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

double precision, public :: gamma

Single polytrope: polytropic index

double precision, public :: gamma0

Piecewise polytrope: polytropic index

double precision, public :: gamma1

Piecewise polytrope: polytropic index

double precision, public :: gamma2

Piecewise polytrope: polytropic index

double precision, public :: gamma3

Piecewise polytrope: polytropic index

double precision, public, DIMENSION(:,:,:,:), ALLOCATABLE :: grid

Array storing the Cartesian coordinates of the grid points. The first three indices specify the grid point; the last index specifies the coordinates

double precision, public :: kappa

Single polytrope: polytropic constant [pure number]

double precision, public :: kappa0

Piecewise polytrope: polytropic constant [pure number]

double precision, public :: kappa1

Piecewise polytrope: polytropic constant [pure number]

double precision, public :: kappa2

Piecewise polytrope: polytropic constant [pure number]

double precision, public :: kappa3

Piecewise polytrope: polytropic constant [pure number]

double precision, public :: logP1

Piecewise polytrope: Base 10 exponent of the pressure at the first fiducial density (between and )

double precision, public :: logRho0

Piecewise polytrope: Base 10 exponent of the first fiducial density (between and )

double precision, public :: logRho1

Piecewise polytrope: Base 10 exponent of the second fiducial density (between and )

double precision, public :: logRho2

Piecewise polytrope: Base 10 exponent of the third fiducial density (between and )

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

Masses of the matter objects

integer, public :: n_gridpoints

Total number of grid points for the grid containing the \(\mathrm{ID}\)

integer, public :: npeos

Piecewise polytrope: Number of polytropic pieces

integer, public :: nx_grid

Number of grid points in the direction for the grid containing the \(\mathrm{ID}\)

integer, public :: ny_grid

Number of grid points in the direction for the grid containing the \(\mathrm{ID}\)

integer, public :: nz_grid

Number of grid points in the direction for the grid containing the \(\mathrm{ID}\)

double precision, public, DIMENSION(:,:), ALLOCATABLE :: sizes

Sizes of the matter objects

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

Array storing the specific energy at the grid points. The indices specify the grid point.

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

Array containing, for each matter object, a set of coordinates of some points modelling the surfaces.

type(tabu_eos), public, DIMENSION(:), ALLOCATABLE :: tab_eos

Array containing a tabulated \(\mathrm{EOS}\) for each matter object, when used.

double precision, public, DIMENSION(:,:,:,:), ALLOCATABLE :: vel

Array storing the fluid velocity with respect to the Eulerian observer at the grid points. The first three indices specify the grid point; the last index specifies the components of the velocity.

double precision, public :: xL_grid

Minimum coordinate on the grid containing the \(\mathrm{ID}\)

double precision, public :: xR_grid

Maximum coordinate on the grid containing the \(\mathrm{ID}\)

double precision, public :: yL_grid

Minimum coordinate on the grid containing the \(\mathrm{ID}\)

double precision, public :: yR_grid

Maximum coordinate on the grid containing the \(\mathrm{ID}\)

double precision, public :: zL_grid

Minimum coordinate on the grid containing the \(\mathrm{ID}\)

double precision, public :: zR_grid

Maximum coordinate on the grid containing the \(\mathrm{ID}\)


Finalization Procedures

final :: destruct_ejecta

Finalizer (Destructor) of a ejecta object


Type-Bound Procedures

procedure, public :: allocate_gridid_memory

Allocates memory for the ejecta member arrays

  • interface

    public module subroutine allocate_gridid_memory(this, n_matter)

    Allocates allocatable arrays member of a ejecta object

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    integer, intent(in) :: n_matter

    Number of matter objects

procedure, public, NON_OVERRIDABLE :: check_i_matter

Checks that the given index is between 1 and n_matter, included. If not, it stops the execution of the program.

  • interface

    public module subroutine check_i_matter(this, i_matter)

    Checks that the given index i_matter is between 1 and n_matter, included. If not, it stops the execution of the program.

    Arguments

    Type IntentOptional Attributes Name
    class(idbase), intent(in) :: this
    integer, intent(in) :: i_matter

    Value to be checked

procedure, public :: deallocate_gridid_memory

Deallocates memory for the ejecta member arrays

  • interface

    public module subroutine deallocate_gridid_memory(this)

    Deallocates allocatable arrays member of a ejecta object

    Arguments

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

    ejecta object which this PROCEDURE is a member of

procedure, public :: derived_type_constructor => construct_ejecta

  • interface

    public module subroutine construct_ejecta(derived_type, filename, eos_filenames)

    Constructs a ejecta object Prints a summary of the physical properties the system to the standard output and, optionally, to a formatted file whose name is given as the optional argument filename

    Arguments

    Type IntentOptional Attributes Name
    class(ejecta), intent(out) :: derived_type

    Constructed ejecta object

    character(len=*), intent(in), optional :: filename

    \(\texttt{LORENE}\) binary file containing the spectral DRS ID

    character(len=*), intent(in), optional, DIMENSION(:) :: eos_filenames

    Array of strings containing the names of the files containing the \(\mathrm{EOS}\) to be used for each matter object. If not PRESENT, information from the file filename is used

procedure, public :: estimate_lengthscale_field

Estimate typical length scales, one per each matter object, by computing , where is a field given as input, and represent a derivative of it. Presently, the derivatives are computed separately along each spatial dimension, as 1D derivatives.

  • interface

    public module function estimate_lengthscale_field(this, get_field, n_mat) result(scales)

    Estimate typical length scales, one per each matter object, by computing , where is a field given as input, and represent a derivative of it. Presently, the derivatives are computed separately along each spatial dimension, as 1D derivatives.

    Arguments

    Type IntentOptional Attributes Name
    class(idbase), intent(inout) :: this
    function get_field(x, y, z) result(val)

    Returns the value of a field 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

    Value of the field at

    integer, intent(in) :: n_mat

    Return Value double precision, DIMENSION(n_mat)

    Array of the minimum over the lattices that surround each matter object

procedure, public, NOPASS :: finalize

Corrects the \(\mathrm{SPH}\) \(\mathrm{ID}\) so that the linear momentum is zero

  • interface

    public module subroutine finalize(npart, pos, nlrf, u, pr, vel_u, theta, nstar, nu)

    Post-process the \(\mathrm{SPH}\) \(\mathrm{ID}\); for example, correct for the residual ADM linear momentum.

    Arguments

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

    Particle number

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

    Particle positions

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

    Baryon density in the local rest frame on the particles

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

    Specific internal energy on the particles

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

    Pressure on the particles

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

    Spatial velocity in the computing frame on the particles

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

    Generalized Lorentz factor on the particles

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

    Proper baryon density in the local rest frame on the particles

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

    Baryon number per particle

procedure, public, NON_OVERRIDABLE :: get_cold_system

Returns cold_system, the LOGICAL variable that specifies if the system is cold (no thermal component)

  • interface

    public pure module function get_cold_system(this)

    Returns cold_system, the LOGICAL variable at specifies if the system is cold (no thermal component)

    Arguments

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

    Return Value logical

    cold_system

procedure, public, NON_OVERRIDABLE :: get_estimate_length_scale

Returns estimate_length_scale, the LOGICAL variable that specifies if a typical length scale, equal to the ratio of a field over its gradient, should be computed

  • interface

    public pure module function get_estimate_length_scale(this)

    Returns estimate_length_scale, the LOGICAL variable that specifies if a typical length scale, equal to the ratio of a field over its gradient, should be computed

    Arguments

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

    Return Value logical

    estimate_length_scale

procedure, public :: get_gamma

Returns gamma

  • interface

    public pure module function get_gamma(this)

    Interface to get_gamma

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value double precision

procedure, public :: get_gamma0

Returns gamma0

  • interface

    public pure module function get_gamma0(this)

    Interface to get_gamma0

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value double precision

procedure, public :: get_gamma1

Returns gamma1

  • interface

    public pure module function get_gamma1(this)

    Interface to get_gamma1

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value double precision

procedure, public :: get_gamma2

Returns gamma2

  • interface

    public pure module function get_gamma2(this)

    Interface to get_gamma2

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value double precision

procedure, public :: get_gamma3

Returns gamma3

  • interface

    public pure module function get_gamma3(this)

    Interface to get_gamma3

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value double precision

procedure, public :: get_kappa

Returns kappa

  • interface

    public pure module function get_kappa(this)

    Interface to get_kappa

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value double precision

procedure, public :: get_kappa0

Returns kappa0

  • interface

    public pure module function get_kappa0(this)

    Interface to get_kappa0

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value double precision

procedure, public :: get_kappa1

Returns kappa1

  • interface

    public pure module function get_kappa1(this)

    Interface to get_kappa1

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value double precision

procedure, public :: get_kappa2

Returns kappa2

  • interface

    public pure module function get_kappa2(this)

    Interface to get_kappa2

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value double precision

procedure, public :: get_kappa3

Returns kappa3

  • interface

    public pure module function get_kappa3(this)

    Interface to get_kappa3

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value double precision

procedure, public :: get_logP1

Returns logP1

  • interface

    public pure module function get_logP1(this)

    Interface to get_logP1

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value double precision

procedure, public :: get_logRho0

Returns logRho0

  • interface

    public pure module function get_logRho0(this)

    Interface to get_logRho0

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value double precision

procedure, public :: get_logRho1

Returns logRho1

  • interface

    public pure module function get_logRho1(this)

    Interface to get_logRho1

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value double precision

procedure, public :: get_logRho2

Returns logRho2

  • interface

    public pure module function get_logRho2(this)

    Interface to get_logRho2

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value double precision

procedure, public, NON_OVERRIDABLE :: get_n_matter

Returns n_matter, the number of matter objects in the physical system

  • interface

    public pure module function get_n_matter(this)

    Returns n_matter, the number of matter objects in the physical system

    Arguments

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

    Return Value integer

    n_matter, the number of matter objects in the

procedure, public :: get_npeos

Returns npeos

  • interface

    public pure module function get_npeos(this)

    Interface to get_npeos

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value integer

procedure, public, NON_OVERRIDABLE :: get_one_lapse

Returns one_lapse, the LOGICAL variable that determines if the lapse function , i.e., if the geodesic gauge is to be used

  • interface

    public pure module function get_one_lapse(this)

    Returns n_matter, the number of matter objects in the physical system

    Arguments

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

    Return Value logical

    n_matter, the number of matter objects in the

procedure, public, NON_OVERRIDABLE :: get_total_spatial_extent

Returns the spatial extent of the physical system considered, as the array of 6 numbers

  • interface

    public module function get_total_spatial_extent(this) result(box)

    INTERFACE to the SUBROUTINE that detects the spatial extent of the physical system considered, and returns a 6-dimensional array containing the coordinates of a box centered at the center of the object and containing the system.

    Arguments

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

    Object of class idbase which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(6)

    6-dimensional array containing the coordinates of a box containing the physical system.

procedure, public, NON_OVERRIDABLE :: get_zero_shift

Returns zero_shift, the LOGICAL variable that determines if the shift

  • interface

    public pure module function get_zero_shift(this)

    Returns n_matter, the number of matter objects in the physical system

    Arguments

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

    Return Value logical

    n_matter, the number of matter objects in the

procedure, public, NON_OVERRIDABLE :: initialize

This PROCEDURE calls the constructor of the idbase-extended type and the SUBROUTINE sanity_check afterwards. It is recommended to use this SUBROUTINE to construct objects of idbase-extended type since the sanity check is performed automatically.

  • interface

    public module subroutine initialize(derived_type, filename, eos_filenames)

    Initialize the DERIVED TYPE that extends idbase

    Arguments

    Type IntentOptional Attributes Name
    class(idbase), intent(out) :: derived_type

    Object of DERIVED TYPE that extends [[idbase], to be constructed

    character(len=*), intent(in), optional :: filename

    Name of the file containing the \(\mathrm{ID}\)

    character(len=*), intent(in), optional, DIMENSION(:) :: eos_filenames

    Array of strings containing the names of the files containing the \(\mathrm{EOS}\) to be used for each matter object. If not PRESENT, information from the file filename is used

procedure, public :: initialize_id => nothing

  • interface

    public module subroutine nothing(this, flag, switch)

    Procedure that does nothing. It is used to instantiate a deferred idbase procedure which is not needed in TYPE ejecta. It also serves as a placeholder in case the idbase procedure will be needed in the future.

    Arguments

    Type IntentOptional Attributes Name
    class(ejecta), intent(inout) :: this
    integer, intent(in) :: flag

    Identifies what kind of initialization has to be done

    logical, intent(in), optional :: switch

    If .TRUE., switch to a different initialization

procedure, public :: integrate_baryon_mass_density

Integrates the baryon mass density over a matter object, using spherical coordinates, and computes its radial profile inside the star

  • interface

    public module subroutine integrate_baryon_mass_density(this, center, radius, central_density, dr, dth, dphi, mass, mass_profile, mass_profile_idx, radii, surf)

    INTERFACE to the SUBROUTINE integrating the baryon mass density to compute the radial mass profile of a single star.

    Arguments

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

    Object of class idbase which this PROCEDURE is a member of

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

    Center of the star

    double precision, intent(in) :: radius

    Central density of the star

    double precision, intent(in) :: central_density

    Integration steps

    double precision, intent(in) :: dr

    Radius of the star

    double precision, intent(in) :: dth

    Radius of the star

    double precision, intent(in) :: dphi

    Radius of the star

    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

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

    Surface of the matter object

procedure, public :: nothing

Procedure that does nothing. It is used to instantiate a deferred idbase procedure which is not needed in TYPE ejecta. It also serves as a placeholder in case the idbase procedure will be needed in the future.

  • interface

    public module subroutine nothing(this, flag, switch)

    Procedure that does nothing. It is used to instantiate a deferred idbase procedure which is not needed in TYPE ejecta. It also serves as a placeholder in case the idbase procedure will be needed in the future.

    Arguments

    Type IntentOptional Attributes Name
    class(ejecta), intent(inout) :: this
    integer, intent(in) :: flag

    Identifies what kind of initialization has to be done

    logical, intent(in), optional :: switch

    If .TRUE., switch to a different initialization

procedure, public :: print_summary => print_summary_ejecta

Returns the identifier for the EOS

  • interface

    public module subroutine print_summary_ejecta(this, filename)

    Prints a summary of the physical properties the system to the standard output and, optionally, to a formatted file whose name is given as the optional argument filename

    Arguments

    Type IntentOptional Attributes Name
    class(ejecta), intent(in) :: this
    character(len=*), intent(inout), optional :: filename

    Name of the formatted file to print the summary to

procedure, public :: read_id_full => interpolate_id_full

  • interface

    public module subroutine interpolate_id_full(this, n, x, y, z, lapse, shift_x, shift_y, shift_z, g_xx, g_xy, g_xz, g_yy, g_yz, g_zz, k_xx, k_xy, k_xz, k_yy, k_yz, k_zz, baryon_density, energy_density, specific_energy, pressure, u_euler_x, u_euler_y, u_euler_z)

    Stores the ID in non ejecta-member arrays with the same shape as the ejecta member arrays

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    integer, intent(in) :: n
    double precision, intent(in), DIMENSION(:) :: x
    double precision, intent(in), DIMENSION(:) :: y
    double precision, intent(in), DIMENSION(:) :: z
    double precision, intent(inout), DIMENSION(:) :: lapse
    double precision, intent(inout), DIMENSION(:) :: shift_x
    double precision, intent(inout), DIMENSION(:) :: shift_y
    double precision, intent(inout), DIMENSION(:) :: shift_z
    double precision, intent(inout), DIMENSION(:) :: g_xx
    double precision, intent(inout), DIMENSION(:) :: g_xy
    double precision, intent(inout), DIMENSION(:) :: g_xz
    double precision, intent(inout), DIMENSION(:) :: g_yy
    double precision, intent(inout), DIMENSION(:) :: g_yz
    double precision, intent(inout), DIMENSION(:) :: g_zz
    double precision, intent(inout), DIMENSION(:) :: k_xx
    double precision, intent(inout), DIMENSION(:) :: k_xy
    double precision, intent(inout), DIMENSION(:) :: k_xz
    double precision, intent(inout), DIMENSION(:) :: k_yy
    double precision, intent(inout), DIMENSION(:) :: k_yz
    double precision, intent(inout), DIMENSION(:) :: k_zz
    double precision, intent(inout), DIMENSION(:) :: baryon_density
    double precision, intent(inout), DIMENSION(:) :: energy_density
    double precision, intent(inout), DIMENSION(:) :: specific_energy
    double precision, intent(inout), DIMENSION(:) :: pressure
    double precision, intent(inout), DIMENSION(:) :: u_euler_x
    double precision, intent(inout), DIMENSION(:) :: u_euler_y
    double precision, intent(inout), DIMENSION(:) :: u_euler_z

procedure, public :: read_id_hydro => interpolate_id_hydro

  • interface

    public module subroutine interpolate_id_hydro(this, nx, ny, nz, pos, baryon_density, energy_density, specific_energy, pressure, u_euler)

    Stores the hydro ID in the arrays needed to compute the constraints on the refined mesh

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    integer, intent(in) :: nx
    integer, intent(in) :: ny
    integer, intent(in) :: nz
    double precision, intent(in), DIMENSION(:,:,:,:) :: pos
    double precision, intent(inout), DIMENSION(:,:,:) :: baryon_density
    double precision, intent(inout), DIMENSION(:,:,:) :: energy_density
    double precision, intent(inout), DIMENSION(:,:,:) :: specific_energy
    double precision, intent(inout), DIMENSION(:,:,:) :: pressure
    double precision, intent(inout), DIMENSION(:,:,:,:) :: u_euler

procedure, public :: read_id_k => interpolate_id_k

  • interface

    public module subroutine interpolate_id_k(this, n, x, y, z, k_xx, k_xy, k_xz, k_yy, k_yz, k_zz)

    Stores the components of the extrinsic curvature in arrays

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    integer, intent(in) :: n
    double precision, intent(in), DIMENSION(:) :: x
    double precision, intent(in), DIMENSION(:) :: y
    double precision, intent(in), DIMENSION(:) :: z
    double precision, intent(inout), DIMENSION(:) :: k_xx
    double precision, intent(inout), DIMENSION(:) :: k_xy
    double precision, intent(inout), DIMENSION(:) :: k_xz
    double precision, intent(inout), DIMENSION(:) :: k_yy
    double precision, intent(inout), DIMENSION(:) :: k_yz
    double precision, intent(inout), DIMENSION(:) :: k_zz

procedure, public :: read_id_mass_b => interpolate_id_mass_b

  • interface

    public module subroutine interpolate_id_mass_b(this, x, y, z, g, baryon_density, gamma_euler)

    Stores the hydro ID in the arrays needed to compute the baryon mass

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    double precision, intent(in) :: x
    double precision, intent(in) :: y
    double precision, intent(in) :: z
    double precision, intent(out), DIMENSION(6) :: g
    double precision, intent(out) :: baryon_density
    double precision, intent(out) :: gamma_euler

procedure, public :: read_id_particles => interpolate_id_particles

  • interface

    public module subroutine interpolate_id_particles(this, n, x, y, z, lapse, shift_x, shift_y, shift_z, g_xx, g_xy, g_xz, g_yy, g_yz, g_zz, baryon_density, energy_density, specific_energy, pressure, u_euler_x, u_euler_y, u_euler_z)

    Stores the hydro ID in the arrays needed to compute the SPH ID

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    integer, intent(in) :: n
    double precision, intent(in), DIMENSION(:) :: x
    double precision, intent(in), DIMENSION(:) :: y
    double precision, intent(in), DIMENSION(:) :: z
    double precision, intent(inout), DIMENSION(:) :: lapse
    double precision, intent(inout), DIMENSION(:) :: shift_x
    double precision, intent(inout), DIMENSION(:) :: shift_y
    double precision, intent(inout), DIMENSION(:) :: shift_z
    double precision, intent(inout), DIMENSION(:) :: g_xx
    double precision, intent(inout), DIMENSION(:) :: g_xy
    double precision, intent(inout), DIMENSION(:) :: g_xz
    double precision, intent(inout), DIMENSION(:) :: g_yy
    double precision, intent(inout), DIMENSION(:) :: g_yz
    double precision, intent(inout), DIMENSION(:) :: g_zz
    double precision, intent(inout), DIMENSION(:) :: baryon_density
    double precision, intent(inout), DIMENSION(:) :: energy_density
    double precision, intent(inout), DIMENSION(:) :: specific_energy
    double precision, intent(inout), DIMENSION(:) :: pressure
    double precision, intent(inout), DIMENSION(:) :: u_euler_x
    double precision, intent(inout), DIMENSION(:) :: u_euler_y
    double precision, intent(inout), DIMENSION(:) :: u_euler_z

procedure, public :: read_id_spacetime => interpolate_id_spacetime

  • interface

    public module subroutine interpolate_id_spacetime(this, nx, ny, nz, pos, lapse, shift, g, ek)

    Stores the spacetime ID in multi-dimensional arrays needed to compute the BSSN variables and constraints

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    integer, intent(in) :: nx
    integer, intent(in) :: ny
    integer, intent(in) :: nz
    double precision, intent(in), DIMENSION(:,:,:,:) :: pos
    double precision, intent(inout), DIMENSION(:,:,:) :: lapse
    double precision, intent(inout), DIMENSION(:,:,:,:) :: shift
    double precision, intent(inout), DIMENSION(:,:,:,:) :: g
    double precision, intent(inout), DIMENSION(:,:,:,:) :: ek

procedure, public :: read_mass_density => interpolate_mass_density

Returns the \(\texttt{LORENE}\)'s mass density at the given point

  • interface

    public module function interpolate_mass_density(this, x, y, z) result(res)

    Returns the \(\texttt{LORENE}\) baryon mass density at a point

    Arguments

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

    ejecta object which this PROCEDURE is a member of

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

    coordinate of the desired point

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

    coordinate of the desired point

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

    coordinate of the desired point

    Return Value double precision

    Baryon mass density at

procedure, public :: read_pressure => interpolate_pressure

Returns the \(\texttt{LORENE}\)'s mass density at the given point

Returns the \(\texttt{LORENE}\)'s conformally flat spatial ADM metric

  • interface

    public module function interpolate_pressure(this, x, y, z) result(res)

    Returns the \(\texttt{LORENE}\) baryon mass density at a point

    Arguments

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

    ejecta object which this PROCEDURE is a member of

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

    coordinate of the desired point

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

    coordinate of the desired point

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

    coordinate of the desired point

    Return Value double precision

    Pressure at

procedure, public :: return_adm_mass => get_adm_mass

  • interface

    public module function get_adm_mass(this)

    Returns 0 (the ADM mass is not necessarily known for this TYPE)

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value double precision

procedure, public :: return_barycenter => get_barycenter

  • interface

    public module function get_barycenter(this, i_matter)

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    integer, intent(in) :: i_matter

    Index of the matter object whose parameter is to return

    Return Value double precision, DIMENSION(3)

procedure, public :: return_center => get_center

  • interface

    public module function get_center(this, i_matter)

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    integer, intent(in) :: i_matter

    Index of the matter object whose parameter is to return

    Return Value double precision, DIMENSION(3)

procedure, public :: return_eos_name => get_eos

  • interface

    public module function get_eos(this, i_matter)

    Interface to get_eos

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    integer, intent(in) :: i_matter

    Index of the matter object whose string is to return

    Return Value character(len=:), ALLOCATABLE

procedure, public :: return_eos_parameters => get_eos_parameters

  • interface

    public module subroutine get_eos_parameters(this, i_matter, eos_params)

    Interface to get_eos_parameters

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    integer, intent(in) :: i_matter

    Index of the matter object whose parameter is to return

    double precision, intent(out), DIMENSION(:), ALLOCATABLE :: eos_params

    Array containing the parameters of the \(\mathrm{EOS}\) for the DRS

procedure, public :: return_mass => get_mass

  • interface

    public module function get_mass(this, i_matter)

    Returns masses

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    integer, intent(in) :: i_matter

    Return Value double precision

procedure, public :: return_spatial_extent => get_radii

  • interface

    public module function get_radii(this, i_matter)

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    integer, intent(in) :: i_matter

    Index of the matter object whose string is to return

    Return Value double precision, DIMENSION(6)

procedure, public, NON_OVERRIDABLE :: sanity_check

Checks that n_matter and the sizes returned by return_spatial_extent and get_total_spatial_extent are acceptable. It is called by initialize, after the constructor of the derived type.

  • interface

    public module subroutine sanity_check(derived_type)

    Check that the DERIVED TYPE that extends idbase is constructed consistently

    Arguments

    Type IntentOptional Attributes Name
    class(idbase), intent(in) :: derived_type

    Object of DERIVED TYPE that extends idbase

procedure, public, NON_OVERRIDABLE :: set_cold_system

Sets cold_system, the LOGICAL variable that specifies if the system is cold (no thermal component)

  • interface

    public module subroutine set_cold_system(this, value)

    Sets cold_system, the LOGICAL variable at specifies if the system is cold (no thermal component)

    Arguments

    Type IntentOptional Attributes Name
    class(idbase), intent(inout) :: this
    logical, intent(in) :: value

    Value to set cold_system to

procedure, public, NON_OVERRIDABLE :: set_estimate_length_scale

Sets estimate_length_scale, the LOGICAL variable that specifies if a typical length scale, equal to the ratio of a field over its gradient, should be computed

  • interface

    public module subroutine set_estimate_length_scale(this, value)

    Sets estimate_length_scale, the LOGICAL variable that specifies if a typical length scale, equal to the ratio of a field over its gradient, should be computed

    Arguments

    Type IntentOptional Attributes Name
    class(idbase), intent(inout) :: this
    logical, intent(in) :: value

    Value to set cold_system to

procedure, public, NON_OVERRIDABLE :: set_n_matter

Sets n_matter, the number of matter objects in the physical system, to a value

  • interface

    public pure module subroutine set_n_matter(this, value)

    Sets n_matter, the number of matter objects in the physical system, to the given value

    Arguments

    Type IntentOptional Attributes Name
    class(idbase), intent(inout) :: this
    integer, intent(in) :: value

    Value to set n_matter to

procedure, public, NON_OVERRIDABLE :: set_one_lapse

Sets one_lapse, the LOGICAL variable that determines if the lapse , i.e., if the geodesic gauge is to be used

  • interface

    public pure module subroutine set_one_lapse(this, logic)

    Sets n_matter, the number of matter objects in the physical system, to the given value

    Arguments

    Type IntentOptional Attributes Name
    class(idbase), intent(inout) :: this
    logical, intent(in) :: logic

    Value to set n_matter to

procedure, public, NON_OVERRIDABLE :: set_zero_shift

Sets zero_shift, the LOGICAL variable that determines if the shift

  • interface

    public pure module subroutine set_zero_shift(this, logic)

    Sets n_matter, the number of matter objects in the physical system, to the given value

    Arguments

    Type IntentOptional Attributes Name
    class(idbase), intent(inout) :: this
    logical, intent(in) :: logic

    Value to set n_matter to

procedure, public :: test_position => is_hydro_positive

Returns 1 if the energy density or the specific energy or the pressure are negative

  • interface

    public module function is_hydro_positive(this, x, y, z) result(res)

    Returns .TRUE. if the energy density or the specific energy or the pressure are positivee, .FALSE. otherwise

    Arguments

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

    ejecta object which this PROCEDURE is a member of

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

    coordinate of the desired point

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

    coordinate of the desired point

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

    coordinate of the desired point

    Return Value logical

    .FALSE. if the energy density or the specific energy or the pressure are negative, .TRUE. otherwise

Source Code

  TYPE, EXTENDS(idbase):: ejecta
  !# TYPE for |id| for |sphincsbssn| prepared on a Cartesian, uniform grid

    INTEGER:: nx_grid
    !# Number of grid points in the \(x\) direction for the grid
    !  containing the |id|

    INTEGER:: ny_grid
    !# Number of grid points in the \(y\) direction for the grid
    !  containing the |id|

    INTEGER:: nz_grid
    !# Number of grid points in the \(z\) direction for the grid
    !  containing the |id|

    INTEGER:: n_gridpoints
    !! Total number of grid points for the grid containing the |id|

    DOUBLE PRECISION:: xL_grid
    !! Minimum \(x\) coordinate on the grid containing the |id|

    DOUBLE PRECISION:: yL_grid
    !! Minimum \(y\) coordinate on the grid containing the |id|

    DOUBLE PRECISION:: zL_grid
    !! Minimum \(z\) coordinate on the grid containing the |id|

    DOUBLE PRECISION:: xR_grid
    !! Maximum \(x\) coordinate on the grid containing the |id|

    DOUBLE PRECISION:: yR_grid
    !! Maximum \(y\) coordinate on the grid containing the |id|

    DOUBLE PRECISION:: zR_grid
    !! Maximum \(z\) coordinate on the grid containing the |id|

    DOUBLE PRECISION, PUBLIC:: dx_grid
    !! Spacing on the \(x\)-axis for the grid containing the |id|

    DOUBLE PRECISION:: dy_grid
    !! Spacing on the \(y\)-axis for the grid containing the |id|

    DOUBLE PRECISION:: dz_grid
    !! Spacing on the \(z\)-axis for the grid containing the |id|

    DOUBLE PRECISION, DIMENSION(:,:,:,:), ALLOCATABLE:: grid
    !# Array storing the Cartesian coordinates of the grid points.
    !  The first three indices specify the grid point; the last index
    !  specifies the \(x,y,z\) coordinates

    DOUBLE PRECISION, DIMENSION(:,:,:),   ALLOCATABLE:: baryon_mass_density
    !# Array storing the baryon mass density at the grid points.
    !  The indices specify the grid point.

    DOUBLE PRECISION, DIMENSION(:,:,:),   ALLOCATABLE:: specific_energy
    !# Array storing the specific energy at the grid points.
    !  The indices specify the grid point.

    DOUBLE PRECISION, DIMENSION(:,:,:,:), ALLOCATABLE:: vel
    !# Array storing the fluid velocity with respect to the Eulerian observer
    !  at the grid points.
    !  The first three indices specify the grid point; the last index
    !  specifies the \(x,y,z\) components of the velocity.

    DOUBLE PRECISION:: adm_mass
    !! ADM mass of the system \([M_\odot]\)

    DOUBLE PRECISION, DIMENSION(:),   ALLOCATABLE:: masses
    !! Masses of the matter objects

    DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE:: sizes
    !! Sizes of the matter objects

    DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE:: centers
    !! Centers of the matter objects

    DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE:: barycenters
    !! Barycenters of the matter objects

    !--------------------------------!
    !--  Parameters of the ejecta  --!
    !--------------------------------!

    CHARACTER(LEN=:), ALLOCATABLE:: eos
    !! Name of the equation of state (EoS) of star 1


    !
    !-- Parameters of single polytropic equations of state for the two NSs
    !

    DOUBLE PRECISION:: gamma
    !! Single polytrope: polytropic index

    DOUBLE PRECISION:: kappa
    !! Single polytrope: polytropic constant [pure number]

    !
    !-- Parameters of the piecewise polytropic equation of state for NS 1
    !

    INTEGER:: npeos
    !! Piecewise polytrope: Number of polytropic pieces

    DOUBLE PRECISION:: gamma0
    !! Piecewise polytrope: polytropic index \(\gamma_0\)

    DOUBLE PRECISION:: gamma1
    !! Piecewise polytrope: polytropic index \(\gamma_1\)

    DOUBLE PRECISION:: gamma2
    !! Piecewise polytrope: polytropic index \(\gamma_2\)

    DOUBLE PRECISION:: gamma3
    !! Piecewise polytrope: polytropic index \(\gamma_3\)

    DOUBLE PRECISION:: kappa0
    !# Piecewise polytrope: polytropic constant \(\kappa_0\)
    !  [pure number]

    DOUBLE PRECISION:: kappa1
    !# Piecewise polytrope: polytropic constant \(\kappa_1\)
    !  [pure number]

    DOUBLE PRECISION:: kappa2
    !# Piecewise polytrope: polytropic constant \(\kappa_2\)
    !  [pure number]

    DOUBLE PRECISION:: kappa3
    !# Piecewise polytrope: polytropic constant \(\kappa_3\)
    !  [pure number]

    DOUBLE PRECISION:: logP1
    !# Piecewise polytrope: Base 10 exponent of the pressure at the first
    !  fiducial density (between \(\gamma_0\) and \(\gamma_1\))
    !  \([{\rm dyne/cm^2}]\)

    DOUBLE PRECISION:: logRho0
    !# Piecewise polytrope: Base 10 exponent of the first fiducial density
    !  (between \(\gamma_0\) and \(\gamma_1\)) \([{\rm g/cm^3}]\)

    DOUBLE PRECISION:: logRho1
    !# Piecewise polytrope: Base 10 exponent of the second fiducial density
    !  (between \(\gamma_1\) and \(\gamma_2\)) \([{\rm g/cm^3}]\)

    DOUBLE PRECISION:: logRho2
    !# Piecewise polytrope: Base 10 exponent of the third fiducial density
    !  (between \(\gamma_2\) and \(\gamma_3\)) \([{\rm g/cm^3}]\)


    INTEGER:: eos_id
    !! |sphincsid| identifier for the |eos|


    CONTAINS


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

    PROCEDURE:: derived_type_constructor => construct_ejecta

    PROCEDURE:: allocate_gridid_memory
    !! Allocates memory for the [[ejecta]] member arrays

    PROCEDURE:: deallocate_gridid_memory
    !! Deallocates memory for the [[ejecta]] member arrays

    PROCEDURE:: read_id_full      => interpolate_id_full
    PROCEDURE:: read_id_spacetime => interpolate_id_spacetime
    PROCEDURE:: read_id_particles => interpolate_id_particles
    PROCEDURE:: read_id_hydro     => interpolate_id_hydro
    PROCEDURE:: read_id_mass_b    => interpolate_id_mass_b
    PROCEDURE:: read_id_k         => interpolate_id_k

    PROCEDURE, NOPASS:: finalize
    !# Corrects the |sph| |id| so that the linear \(\mathrm{ADM}\) momentum
    !  is zero

    PROCEDURE:: nothing
    !# Procedure that does nothing. It is used to instantiate a deferred
    !  idbase procedure which is not needed in TYPE [[ejecta]].
    !  It also serves as a placeholder in case the idbase procedure
    !  will be needed in the future.

    PROCEDURE:: initialize_id => nothing

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

    PROCEDURE:: read_mass_density => interpolate_mass_density
    !! Returns the |lorene|'s mass density at the given point

    PROCEDURE:: read_pressure => interpolate_pressure
    !! Returns the |lorene|'s mass density at the given point

    !PROCEDURE:: interpolate_spatial_metric
    !! Returns the |lorene|'s conformally flat spatial ADM metric

    PROCEDURE:: test_position => is_hydro_positive
    !# Returns 1 if the energy density or the specific energy or the pressure
    !  are negative


    !
    !-- FUNCTIONS that access PRIVATE member variables
    !

    PROCEDURE:: return_mass                 => get_mass
    PROCEDURE:: return_adm_mass             => get_adm_mass
    PROCEDURE:: return_center               => get_center
    PROCEDURE:: return_barycenter           => get_barycenter
    PROCEDURE:: return_eos_name             => get_eos
    PROCEDURE:: return_spatial_extent       => get_radii
    PROCEDURE:: print_summary               => print_summary_ejecta

    !PROCEDURE:: get_eos_id => get_eos_ejectaid
    !! Returns the identifier for the EOS

    PROCEDURE:: return_eos_parameters => get_eos_parameters

    !
    !-- PROCEDURES to be used for single polytropic EOS
    !
    PROCEDURE, PUBLIC:: get_gamma
    !! Returns [[ejecta:gamma]]
    PROCEDURE, PUBLIC:: get_kappa
    !! Returns [[ejecta:kappa]]

    !
    !-- PROCEDURES to be used for piecewise polytropic EOS
    !
    PROCEDURE, PUBLIC:: get_npeos
    !! Returns [[ejecta:npeos]]
    PROCEDURE, PUBLIC:: get_gamma0
    !! Returns [[ejecta:gamma0]]
    PROCEDURE, PUBLIC:: get_gamma1
    !! Returns [[ejecta:gamma1]]
    PROCEDURE, PUBLIC:: get_gamma2
    !! Returns [[ejecta:gamma2]]
    PROCEDURE, PUBLIC:: get_gamma3
    !! Returns [[ejecta:gamma3]]
    PROCEDURE, PUBLIC:: get_kappa0
    !! Returns [[ejecta:kappa0]]
    PROCEDURE, PUBLIC:: get_kappa1
    !! Returns [[ejecta:kappa1]]
    PROCEDURE, PUBLIC:: get_kappa2
    !! Returns [[ejecta:kappa2]]
    PROCEDURE, PUBLIC:: get_kappa3
    !! Returns [[ejecta:kappa3]]
    PROCEDURE, PUBLIC:: get_logP1
    !! Returns [[ejecta:logP1]]
    PROCEDURE, PUBLIC:: get_logRho0
    !! Returns [[ejecta:logRho0]]
    PROCEDURE, PUBLIC:: get_logRho1
    !! Returns [[ejecta:logRho1]]
    PROCEDURE, PUBLIC:: get_logRho2
    !! Returns [[ejecta:logRho2]]

    FINAL:: destruct_ejecta
    !! Finalizer (Destructor) of a [[ejecta]] object

  END TYPE ejecta