ejecta_generic Module

This MODULE contains the definition of TYPE ejecta, which is an ABSTRACT TYPE representing any possible type of initial data (\(\mathrm{ID}\)) on a Cartesian, uniform grid to be set up for \(\texttt{SPHINCS_BSSN}\).

PROCEDURES and variables shared by all the types of \(\mathrm{ID}\) on a Cartesian uniform grid should belong to TYPE ejecta.

FT xx.11.2021



Uses

  • module~~ejecta_generic~~UsesGraph module~ejecta_generic ejecta_generic module~id_base id_base module~ejecta_generic->module~id_base module~utility utility module~ejecta_generic->module~utility module~id_base->module~utility timing timing module~id_base->timing constants constants module~utility->constants matrix matrix module~utility->matrix

Used by

  • module~~ejecta_generic~~UsedByGraph module~ejecta_generic ejecta_generic module~access~8 access module~access~8->module~ejecta_generic module~constructor~5 constructor module~constructor~5->module~ejecta_generic module~interpolate~2 interpolate module~interpolate~2->module~ejecta_generic module~io~9 io module~io~9->module~ejecta_generic module~memory~6 memory module~memory~6->module~ejecta_generic module~sphincs_id_fuka sphincs_id_fuka module~sphincs_id_fuka->module~ejecta_generic module~sphincs_id_full sphincs_id_full module~sphincs_id_full->module~ejecta_generic module~sphincs_id_interpolate sphincs_id_interpolate module~sphincs_id_interpolate->module~ejecta_generic module~sphincs_id_lorene sphincs_id_lorene module~sphincs_id_lorene->module~ejecta_generic program~convergence_test convergence_test program~convergence_test->module~sphincs_id_fuka program~convergence_test->module~sphincs_id_full program~convergence_test->module~sphincs_id_interpolate program~convergence_test->module~sphincs_id_lorene program~sphincs_id sphincs_id program~sphincs_id->module~sphincs_id_fuka program~sphincs_id->module~sphincs_id_full program~sphincs_id->module~sphincs_id_interpolate program~sphincs_id->module~sphincs_id_lorene

Contents


Interfaces

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

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

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

interface

  • public module subroutine destruct_ejecta(this)

    Destruct a ejecta object

    Arguments

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

    ejecta object to be destructed

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

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

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)

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)

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

interface

  • public module function get_eos_id(this)

    Interface to get_eos_id

    Arguments

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

    ejecta object which this PROCEDURE is a member of

    Return Value integer

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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)

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

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

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

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

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

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

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

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

interface

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

    Returns the \(\texttt{LORENE}\) conformally flat spatial metric component 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

    at

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

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

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


Derived Types

type, public, extends(idbase) ::  ejecta

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

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.

Read more…
type(tabu_eos), public, DIMENSION(:), ALLOCATABLE :: tab_eos

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

Read more…
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}\)

Finalizations Procedures

final :: destruct_ejecta

Finalizer (Destructor) of a ejecta object

Type-Bound Procedures

procedure , public :: allocate_gridid_memory Interface

Allocates memory for the ejecta member arrays

procedure , public , NON_OVERRIDABLE :: check_i_matter Interface

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

procedure , public :: deallocate_gridid_memory Interface

Deallocates memory for the ejecta member arrays

procedure , public :: derived_type_constructor => construct_ejecta Interface
procedure , public :: estimate_lengthscale_field Interface

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.

procedure , public , NOPASS :: finalize Interface

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

procedure , public , NON_OVERRIDABLE :: get_cold_system Interface

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

procedure , public , NON_OVERRIDABLE :: get_estimate_length_scale Interface

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

procedure , public :: get_gamma Interface

Returns gamma

procedure , public :: get_gamma0 Interface

Returns gamma0

procedure , public :: get_gamma1 Interface

Returns gamma1

procedure , public :: get_gamma2 Interface

Returns gamma2

procedure , public :: get_gamma3 Interface

Returns gamma3

procedure , public :: get_kappa Interface

Returns kappa

procedure , public :: get_kappa0 Interface

Returns kappa0

procedure , public :: get_kappa1 Interface

Returns kappa1

procedure , public :: get_kappa2 Interface

Returns kappa2

procedure , public :: get_kappa3 Interface

Returns kappa3

procedure , public :: get_logP1 Interface

Returns logP1

procedure , public :: get_logRho0 Interface

Returns logRho0

procedure , public :: get_logRho1 Interface

Returns logRho1

procedure , public :: get_logRho2 Interface

Returns logRho2

procedure , public , NON_OVERRIDABLE :: get_n_matter Interface

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

procedure , public :: get_npeos Interface

Returns npeos

procedure , public , NON_OVERRIDABLE :: get_one_lapse Interface

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

procedure , public , NON_OVERRIDABLE :: get_total_spatial_extent Interface

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

procedure , public , NON_OVERRIDABLE :: get_zero_shift Interface

Returns zero_shift, the LOGICAL variable that determines if the shift

procedure , public , NON_OVERRIDABLE :: initialize Interface

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.

procedure , public :: initialize_id => nothing Interface
procedure , public :: integrate_baryon_mass_density Interface

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

procedure , public :: nothing Interface

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 , public :: print_summary => print_summary_ejecta Interface

Returns the identifier for the EOS

procedure , public :: read_id_full => interpolate_id_full Interface
procedure , public :: read_id_hydro => interpolate_id_hydro Interface
procedure , public :: read_id_k => interpolate_id_k Interface
procedure , public :: read_id_mass_b => interpolate_id_mass_b Interface
procedure , public :: read_id_particles => interpolate_id_particles Interface
procedure , public :: read_id_spacetime => interpolate_id_spacetime Interface
procedure , public :: read_mass_density => interpolate_mass_density Interface

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

procedure , public :: read_pressure => interpolate_pressure Interface

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

Read more…
procedure , public :: return_adm_mass => get_adm_mass Interface
procedure , public :: return_barycenter => get_barycenter Interface
procedure , public :: return_center => get_center Interface
procedure , public :: return_eos_name => get_eos Interface
procedure , public :: return_eos_parameters => get_eos_parameters Interface
procedure , public :: return_mass => get_mass Interface
procedure , public :: return_spatial_extent => get_radii Interface
procedure , public , NON_OVERRIDABLE :: sanity_check Interface

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.

procedure , public , NON_OVERRIDABLE :: set_cold_system Interface

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

procedure , public , NON_OVERRIDABLE :: set_estimate_length_scale Interface

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

procedure , public , NON_OVERRIDABLE :: set_n_matter Interface

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

procedure , public , NON_OVERRIDABLE :: set_one_lapse Interface

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

procedure , public , NON_OVERRIDABLE :: set_zero_shift Interface

Sets zero_shift, the LOGICAL variable that determines if the shift

procedure , public :: test_position => is_hydro_positive Interface

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