TYPE for \(\mathrm{ID}\) for \(\texttt{SPHINCS_BSSN}\) prepared on a Cartesian, uniform grid
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. TodoTODO: make PRIVATE |
||
type(tabu_eos), | public, | DIMENSION(:), ALLOCATABLE | :: | tab_eos |
Array containing a tabulated \(\mathrm{EOS}\) for each matter object, when used. TodoTODO: make PRIVATE |
||
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}\) |
Finalizer (Destructor) of a ejecta object
Allocates memory for the ejecta member arrays
Allocates allocatable arrays member of a ejecta object
Type | Intent | Optional | 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 |
Checks that the given index is between 1 and n_matter, included. If not, it stops the execution of the program.
Checks that the given index i_matter
is between 1 and
n_matter, included. If not, it stops the execution of the
program.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(in) | :: | this | |||
integer, | intent(in) | :: | i_matter |
Value to be checked |
Deallocates memory for the ejecta member arrays
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
Type | Intent | Optional | 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 |
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.
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.
Type | Intent | Optional | 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
Return Value double precisionValue of the field at |
||||||||||||||||||||||||||||||||||
integer, | intent(in) | :: | n_mat |
Array of the minimum over the lattices that surround each matter object
Corrects the \(\mathrm{SPH}\) \(\mathrm{ID}\) so that the linear momentum is zero
Post-process the \(\mathrm{SPH}\) \(\mathrm{ID}\); for example, correct for the residual ADM linear momentum.
Type | Intent | Optional | 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 |
Returns cold_system, the LOGICAL
variable that specifies if
the system is cold (no thermal component)
Returns cold_system, the LOGICAL
variable at specifies if
the system is cold (no thermal component)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(in) | :: | 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
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
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(in) | :: | this |
Returns gamma
Returns gamma0
Interface to get_gamma0
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(ejecta), | intent(in) | :: | this |
ejecta object which this PROCEDURE is a member of |
Returns gamma1
Interface to get_gamma1
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(ejecta), | intent(in) | :: | this |
ejecta object which this PROCEDURE is a member of |
Returns gamma2
Interface to get_gamma2
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(ejecta), | intent(in) | :: | this |
ejecta object which this PROCEDURE is a member of |
Returns gamma3
Interface to get_gamma3
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(ejecta), | intent(in) | :: | this |
ejecta object which this PROCEDURE is a member of |
Returns kappa
Returns kappa0
Interface to get_kappa0
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(ejecta), | intent(in) | :: | this |
ejecta object which this PROCEDURE is a member of |
Returns kappa1
Interface to get_kappa1
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(ejecta), | intent(in) | :: | this |
ejecta object which this PROCEDURE is a member of |
Returns kappa2
Interface to get_kappa2
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(ejecta), | intent(in) | :: | this |
ejecta object which this PROCEDURE is a member of |
Returns kappa3
Interface to get_kappa3
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(ejecta), | intent(in) | :: | this |
ejecta object which this PROCEDURE is a member of |
Returns logP1
Returns logRho0
Interface to get_logRho0
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(ejecta), | intent(in) | :: | this |
ejecta object which this PROCEDURE is a member of |
Returns logRho1
Interface to get_logRho1
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(ejecta), | intent(in) | :: | this |
ejecta object which this PROCEDURE is a member of |
Returns logRho2
Interface to get_logRho2
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(ejecta), | intent(in) | :: | this |
ejecta object which this PROCEDURE is a member of |
Returns n_matter, the number of matter objects in the physical system
Returns npeos
Returns one_lapse, the LOGICAL
variable that determines if
the lapse function , i.e., if the geodesic gauge is to be used
Returns the spatial extent of the physical system considered, as the array of 6 numbers
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.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(in) | :: | this |
Object of class idbase which this PROCEDURE is a member of |
6-dimensional array containing the coordinates of a box containing the physical system.
Returns zero_shift, the LOGICAL
variable that determines if
the shift
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.
Initialize the DERIVED TYPE that extends idbase
Type | Intent | Optional | 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 |
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.
Type | Intent | Optional | 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 |
Integrates the baryon mass density over a matter object, using spherical coordinates, and computes its radial profile inside the star
INTERFACE to the SUBROUTINE integrating the baryon mass density to compute the radial mass profile of a single star.
Type | Intent | Optional | 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
|
|
double precision, | intent(in), | optional, | DIMENSION(2) | :: | radii | |
type(surface), | intent(in), | optional | :: | surf |
Surface of the matter object |
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 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.
Type | Intent | Optional | 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 |
Returns the identifier for the EOS
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
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(ejecta), | intent(in) | :: | this | |||
character(len=*), | intent(inout), | optional | :: | filename |
Name of the formatted file to print the summary to |
Stores the ID in non ejecta-member arrays with the same shape as the ejecta member arrays
Type | Intent | Optional | 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 |
Stores the hydro ID in the arrays needed to compute the constraints on the refined mesh
Type | Intent | Optional | 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 |
Stores the components of the extrinsic curvature in arrays
Type | Intent | Optional | 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 |
Stores the hydro ID in the arrays needed to compute the baryon mass
Type | Intent | Optional | 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 |
Stores the hydro ID in the arrays needed to compute the SPH ID
Type | Intent | Optional | 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 |
Stores the spacetime ID in multi-dimensional arrays needed to compute the BSSN variables and constraints
Type | Intent | Optional | 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 |
Returns the \(\texttt{LORENE}\)'s mass density at the given point
Returns the \(\texttt{LORENE}\) baryon mass density at a point
Type | Intent | Optional | 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 |
Baryon mass density at
Returns the \(\texttt{LORENE}\)'s mass density at the given point
Returns the \(\texttt{LORENE}\)'s conformally flat spatial ADM metric
Returns the \(\texttt{LORENE}\) baryon mass density at a point
Type | Intent | Optional | 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 |
Pressure at
Type | Intent | Optional | 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 |
Type | Intent | Optional | 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 |
Interface to get_eos
Type | Intent | Optional | 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 |
Interface to get_eos_parameters
Type | Intent | Optional | 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 |
Type | Intent | Optional | 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 |
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.
Sets cold_system, the LOGICAL
variable that specifies if
the system is cold (no thermal component)
Sets cold_system, the LOGICAL
variable at specifies if
the system is cold (no thermal component)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(inout) | :: | this | |||
logical, | intent(in) | :: | value |
Value to set cold_system to |
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
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
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(inout) | :: | this | |||
logical, | intent(in) | :: | value |
Value to set cold_system to |
Sets n_matter, the number of matter objects in the physical system, to a value
Sets one_lapse, the LOGICAL
variable that determines if
the lapse , i.e., if the geodesic gauge is to be used
Sets zero_shift, the LOGICAL
variable that determines if
the shift
Returns 1 if the energy density or the specific energy or the pressure are negative
Returns .TRUE.
if the energy density or the specific energy or the
pressure are positivee, .FALSE.
otherwise
Type | Intent | Optional | 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 |
.FALSE.
if the energy density or the specific energy or the pressure
are negative, .TRUE.
otherwise
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