TYPE representing a differentially rotating star (DRS)
Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
double precision, | public | :: | adm_mass |
ADM mass of the \(\mathrm{DRS}\) |
|||
double precision, | public | :: | angular_momentum | = | 0.0D0 |
Angular momentum of the \(\mathrm{DRS}\) |
|
double precision, | public | :: | area_radius |
Areal (or circumferential) radius of \(\mathrm{DRS}\) [Msun_geo] Note that these is the areal radius of the star in the binary system, which is different than that of an isolated star. The latter is used in the mass-radius diagrams, together with the gravitatonal mass |
|||
double precision, | public, | DIMENSION(3) | :: | barycenter |
Array containing the barycenters of the stars Todoadd details |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | baryon_density |
1-D array storing the baryon mass density in the fluid frame [kg m^{-3}] |
||
double precision, | public, | DIMENSION(3) | :: | center |
Array containing the centers of the stars Todoadd details |
||
type(timer), | public | :: | construction_timer |
Timer that times the construction of the appropriate object |
|||
integer, | private | :: | diffstar_identifier | = | 0 |
Identifier of the diffstarlorene object |
|
type(C_PTR), | private | :: | diffstar_ptr |
C pointer to the \(\texttt{LORENE}\)'s Etdiffrot object N.B. This variable is global. The pointer to the second \(\texttt{LORENE}\) Etdiffrot object will overwrite the first one, and so on. This variable stores the pointer to the last defined \(\texttt{LORENE}\) Etdiffrot object. That's why it is not freed in the destructor of a bns object. Presently, it has to be freed by the user at the end of the PROGRAM. See the last part of the PROGRAM in setup_diffstar.f90, for example. |
|||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | energy_density |
1-D array storing the energy density [kg c^2 m^{-3}] |
||
double precision, | public | :: | energy_density_center |
Central energy density |
|||
double precision, | public | :: | ent_center |
Central enthalpy |
|||
character(len=:), | public, | ALLOCATABLE | :: | eos |
Name of the equation of state (EoS) of star 1 |
||
character(len=max_length), | public, | DIMENSION(1) | :: | eos_filename |
Array of string containing the names of the files containing the \(\mathrm{EOS}\) to be used for each matter object. |
||
integer, | public | :: | eos_id |
\(\texttt{SPHINCS_ID}\) identifier for the \(\mathrm{EOS}\) of star 1 |
|||
integer, | private | :: | eos_loreneid |
\(\texttt{LORENE}\) identifier for the EoS |
|||
character(len=:), | public, | ALLOCATABLE | :: | eos_table |
String containing the path to the files containing the table of the \(\mathrm{EOS}\) |
||
double precision, | public | :: | f_isco |
Orbital frequency of the Innermost Stable Circular Orbit (ISCO) |
|||
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, | DIMENSION(:), ALLOCATABLE | :: | g_xx |
1-D array storing the xx component of the spatial metric [pure number] |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | g_xy |
1-D array storing the xy component of the spatial metric [pure number] |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | g_xz |
1-D array storing the xz component of the spatial metric [pure number] |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | g_yy |
1-D array storing the yy component of the spatial metric [pure number] |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | g_yz |
1-D array storing the yz component of the spatial metric [pure number] |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | g_zz |
1-D array storing the zz component of the spatial metric [pure number] |
||
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 | :: | grv2 |
Error on the virial identity . See Section 3.5 in Gourgoulhon et al, Astron.Astrophys.349:851,1999. |
|||
double precision, | public | :: | grv3 |
Error on the virial identity . See Section 3.5 in Gourgoulhon et al, Astron.Astrophys.349:851,1999 . The error is computed as the integral defined by Eq. (43) of Gourgoulhon and Bonazzola, Class. Quantum Grav. 11, 443 (1994) divided by the integral of the matter terms. |
|||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | k_xx |
1-D array storing the xx component of the extrinsic curvature [c/MSun_geo] |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | k_xy |
1-D array storing the xy component of the extrinsic curvature [c/MSun_geo] |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | k_xz |
1-D array storing the xz component of the extrinsic curvature [c/MSun_geo] |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | k_yy |
1-D array storing the yy component of the extrinsic curvature [c/MSun_geo] |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | k_yz |
1-D array storing the yz component of the extrinsic curvature [c/MSun_geo] |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | k_zz |
1-D array storing the zz component of the extrinsic curvature [c/MSun_geo] |
||
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, | DIMENSION(:), ALLOCATABLE | :: | lapse |
1-D array storing the lapse function |
||
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 | :: | mass |
Baryonic mass of \(\mathrm{DRS}\) |
|||
double precision, | public | :: | mass_grav |
Gravitational mass of \(\mathrm{DRS}\) |
|||
double precision, | public | :: | nbar_center |
Central baryon number density |
|||
integer, | public | :: | npeos |
Piecewise polytrope: Number of polytropic pieces |
|||
double precision, | public | :: | omega_c |
Central angular velocity |
|||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | pressure |
1-D array storing the pressure |
||
double precision, | public | :: | pressure_center |
Central pressure |
|||
double precision, | public | :: | r_circ |
Circumferential radius |
|||
double precision, | public | :: | r_eq |
Equatorial radius at |
|||
double precision, | public | :: | r_eq_3pi2 |
Equatorial radius at |
|||
double precision, | public | :: | r_eq_pi |
Equatorial radius at |
|||
double precision, | public | :: | r_eq_pi2 |
Equatorial radius at |
|||
double precision, | public | :: | r_isco |
Radius of the Innermost Stable Circular Orbit (ISCO) |
|||
double precision, | public | :: | r_mean |
Mean radius |
|||
double precision, | public | :: | r_pole |
Polar radius |
|||
double precision, | public | :: | r_ratio | ||||
double precision, | public, | DIMENSION(6) | :: | radii | |||
double precision, | public | :: | redshift_eqb |
Backward redshift factor at equator |
|||
double precision, | public | :: | redshift_eqf |
Forward redshift factor at equator |
|||
double precision, | public | :: | redshift_pole |
Redshift factor at North pole |
|||
double precision, | public | :: | rho_center |
Central baryon mass density |
|||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | shift_x |
1-D array storing the x component of the shift vector [c] |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | shift_y |
1-D array storing the y component of the shift vector [c] |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | shift_z |
1-D array storing the z component of the shift vector [c] |
||
double precision, | public | :: | specific_angular_momentum_isco |
Specific angular momentum of a test particle at the Innermost Stable Circular Orbit (ISCO) |
|||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | specific_energy |
1-D array storing the specific internal energy [c^2] |
||
double precision, | public | :: | specific_energy_center |
Central specific energy |
|||
double precision, | public | :: | specific_energy_isco |
Specific energy of a test particle at the Innermost Stable Circular Orbit (ISCO) |
|||
double precision, | public | :: | surface_area |
Surface area |
|||
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 | :: | tsw |
Ratio between the rotational kinetic and gravitatial potential energy . See Section 6 in Gourgoulhon et al, Astron.Astrophys.349:851,1999 For axisymmetric configurations as those considered here, the threshold for dynamical bar-mode instability is [Masaru Shibata et al 2000 ApJ 542 453]. See also Manca et al., Classical and Quantum Gravity, 24, 171, Sec.3.3 in Galeazzi et al., Astron Astrophys 541:A156, and Sec.5.1.3 in Paschalidis, V., Stergioulas, N., Rotating stars in relativity. Living Rev Relativ 20, 7 (2017). |
|||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | v_euler_x |
1-D array storing the x component of the fluid 3-velocity with respect to |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | v_euler_y |
1-D array storing the y component of the fluid 3-velocity with respect to |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | v_euler_z |
1-D array storing the z component of the fluid 3-velocity with respect to |
Finalizer (Destructor) of a diffstarlorene object
Allocates memory for the diffstarlorene member arrays
Allocates allocatable arrays member of a diffstarlorene object
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(inout) | :: | this |
diffstarlorene object which this PROCEDURE is a member of |
||
integer, | intent(in) | :: | d |
Dimension of the arrays |
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 |
Constructs the \(\texttt{LORENE}\) Etdiffrot object
Interface of the subroutine that constructs the \(\texttt{LORENE}\) Etdiffrot object
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(inout) | :: | this |
diffstarlorene object which this PROCEDURE is a member of |
||
character(kind=C_CHAR, len=*), | intent(in), | optional | :: | id_file |
\(\texttt{LORENE}\) binary file containing the spectral \(\mathrm{DRS}\) \(\mathrm{ID}\) |
|
character(kind=C_CHAR, len=*), | intent(in), | optional | :: | eos_filename |
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 |
Deallocates memory for the diffstarlorene member arrays
Deallocates allocatable arrays member of a diffstarlorene object
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(inout) | :: | this |
diffstarlorene object which this PROCEDURE is a member of |
Constructs a diffstarlorene 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(diffstarlorene), | intent(out) | :: | derived_type |
Constructed diffstarlorene object |
||
character(len=*), | intent(in), | optional | :: | filename |
\(\texttt{LORENE}\) binary file containing the spectral \(\mathrm{DRS}\) \(\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 |
Destructs the \(\texttt{LORENE}\) Etdiffrot object
Destructs a \(\texttt{LORENE}\) Etdiffrot object
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(inout) | :: | this |
diffstarlorene object which this PROCEDURE is a member of |
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 angular_momentum
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns area_radius
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
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 diffstar_identifier]
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(in) | :: | this |
diffstarlorene object which this PROCEDURE is a member of |
Returns energy_density_center
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns ent_center
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns the \(\texttt{LORENE}\) identifier for the EOS
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(in) | :: | this |
diffstarlorene object which this PROCEDURE is a member of |
Returns eos_loreneid
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(in) | :: | this |
diffstarlorene object which this PROCEDURE is a member of |
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 f_isco
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Access the diffstarlorene-member arrays
Returns the diffstarlorene member arrays named field
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(in) | :: | this |
diffstarlorene object which this PROCEDURE is a member of |
||
character(len=:), | intent(in), | ALLOCATABLE | :: | field |
Name of the desired diffstarlorene member array |
Desired diffstarlorene member array
GENERIC PROCEDURE, overloded to access the diffstarlorene-member variables as arrays and as values
Access the components of the diffstarlorene-member arrays
Returns the component n of the diffstarlorene member arrays named field
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(in) | :: | this |
diffstarlorene object which this PROCEDURE is a member of |
||
character(len=:), | intent(in), | ALLOCATABLE | :: | field |
Name of the desired diffstarlorene member array |
|
integer, | intent(in) | :: | n |
Component of the desired diffstarlorene member array |
Component n of the desired diffstarlorene member array
Returns gamma
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns gamma0
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns gamma1
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns gamma2
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns gamma3
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns grv2
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns grv3
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns kappa
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns kappa0
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns kappa1
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns kappa2
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns kappa3
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns logP1
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns logRho0
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns logRho1
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns logRho2
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns mass_grav
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns n_matter, the number of matter objects in the physical system
Returns nbar_center
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns npeos
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns omega_c
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns one_lapse, the LOGICAL
variable that determines if
the lapse function , i.e., if the geodesic gauge is to be used
Returns pressure_center
Returns eos
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns r_circ
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns r_eq
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns r_eq_3pi2
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns r_eq_pi
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns r_eq_pi2
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns r_isco
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns r_mean
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns r_pole
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns r_ratio
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns rho_center
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns specific_angular_momentum_isco
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns specific_energy_center
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns specific_energy_isco
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Returns surface_area
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
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 tsw
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
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 diffstarlorene. It also serves as a placeholder in case the idbase procedure will be needed in the future.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | 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 diffstarlorene. 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 diffstarlorene. It also serves as a placeholder in case the idbase procedure will be needed in the future.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(inout) | :: | this | |||
integer, | intent(in) | :: | flag |
Identifies what kind of initialization has to be done |
||
logical, | intent(in), | optional | :: | switch |
If |
Prints the parameters of the DRS to the standard output
Prints the DRS parameters to the standard output
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(inout) | :: | this |
diffstarlorene object which this PROCEDURE is a member of |
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(diffstarbase), | intent(in) | :: | this | |||
character(len=*), | intent(inout), | optional | :: | filename |
Name of the formatted file to print the summary to |
Imports the parameters of the DRS from \(\texttt{LORENE}\)
Imports the DRS parameters from \(\texttt{LORENE}\)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(inout) | :: | this |
diffstarlorene object which this PROCEDURE is a member of |
Stores the ID in non diffstarlorene-member arrays with the same shape as the diffstarlorene member arrays
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(inout) | :: | this |
diffstarlorene 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(diffstarlorene), | intent(inout) | :: | this |
diffstarlorene 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 ID in the diffstarlorene member arrays
Stores the ID in the diffstarlorene member arrays
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(inout) | :: | this |
diffstarlorene 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 |
Stores the components of the extrinsic curvature in arrays
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(inout) | :: | this |
diffstarlorene 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(diffstarlorene), | intent(inout) | :: | this |
diffstarlorene 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(diffstarlorene), | intent(inout) | :: | this |
diffstarlorene object which this PROCEDURE is a member of |
||
integer, | intent(in) | :: | n | |||
real(kind=C_DOUBLE), | intent(in), | DIMENSION(:) | :: | x | ||
real(kind=C_DOUBLE), | intent(in), | DIMENSION(:) | :: | y | ||
real(kind=C_DOUBLE), | 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(diffstarlorene), | intent(inout) | :: | this |
diffstarlorene 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(diffstarlorene), | intent(in) | :: | this |
diffstarlorene 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 pressure at the desired point
Returns the \(\texttt{LORENE}\) pressure at a point
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(in) | :: | this |
bnslorene 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
Returns the \(\texttt{LORENE}\)'s conformally flat spatial ADM metric
Returns the \(\texttt{LORENE}\) conformally flat spatial metric component at a point
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(in) | :: | this |
diffstarlorene object which this PROCEDURE is a member of |
||
real(kind=C_DOUBLE), | intent(in), | VALUE | :: | x |
coordinate of the desired point |
|
real(kind=C_DOUBLE), | intent(in), | VALUE | :: | y |
coordinate of the desired point |
|
real(kind=C_DOUBLE), | intent(in), | VALUE | :: | z |
coordinate of the desired point |
at
Returns 0 (the ADM mass is not necessarily known for this TYPE)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase 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(diffstarbase), | intent(in) | :: | this |
diffstarbase 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(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
||
integer, | intent(in) | :: | i_matter |
Index of the matter object whose string is to return |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(in) | :: | this |
diffstarlorene 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 |
Returns mass
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase object which this PROCEDURE is a member of |
||
integer, | intent(in) | :: | i_matter |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarbase), | intent(in) | :: | this |
diffstarbase 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 .TRUE.
if the energy density or the specific energy or the
pressure are positive
Returns .TRUE. if the energy density or the specific energy or the pressure are positive, .FALSE. otherwise
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(diffstarlorene), | intent(in) | :: | this |
diffstarlorene 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 |
1 if the energy density or the specific energy or the pressure are negative, 0 otherwise
TYPE, EXTENDS(diffstarbase):: diffstarlorene
!! TYPE representing a differentially rotating star (DRS)
PRIVATE
INTEGER:: diffstar_identifier= 0
!! Identifier of the diffstarlorene object
INTEGER:: eos_loreneid
!! |lorene| identifier for the EoS
!& C pointer to the |lorene|'s Etdiffrot object
! N.B. This variable is global. The pointer to the second |lorene| Etdiffrot
! object will overwrite the first one, and so on.
! This variable stores the pointer to the last defined |lorene| Etdiffrot
! object. That's why it is not freed in the destructor of a bns object.
! Presently, it has to be freed by the user at the end of the PROGRAM.
! See the last part of the PROGRAM in setup_diffstar.f90, for example.
TYPE(C_PTR):: diffstar_ptr
CONTAINS
!-------------------!
!-- SUBROUTINES --!
!-------------------!
PROCEDURE:: derived_type_constructor => construct_diffstarlorene
PROCEDURE:: construct_drs
!! Constructs the |lorene| Etdiffrot object
PROCEDURE:: destruct_drs
!! Destructs the |lorene| Etdiffrot object
PROCEDURE:: allocate_diffstar_memory
!! Allocates memory for the [[diffstarlorene]] member arrays
PROCEDURE:: deallocate_diffstar_memory
!! Deallocates memory for the [[diffstarlorene]] member arrays
PROCEDURE:: read_diffstar_properties
!! Imports the parameters of the DRS from |lorene|
PROCEDURE, PUBLIC:: print_diffstar_properties
!! Prints the parameters of the DRS to the standard output
PROCEDURE:: read_id_int
!! Stores the ID in the [[diffstarlorene]] member arrays
PROCEDURE:: read_id_full => read_id_full
PROCEDURE:: read_id_spacetime => read_id_spacetime
PROCEDURE:: read_id_particles => read_id_particles
PROCEDURE:: read_id_hydro => read_id_hydro
PROCEDURE:: read_id_mass_b => read_id_mass_b
PROCEDURE:: read_id_k => read_id_k
PROCEDURE:: nothing
!# Procedure that does nothing. It is used to instantiate a deferred
! idbase procedure which is not needed in TYPE [[diffstarlorene]].
! 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 => read_drslorene_mass_density
!! Returns the |lorene|'s mass density at the given point
PROCEDURE:: read_pressure => read_drslorene_pressure
!! Returns the |lorene|'s pressure at the desired point
PROCEDURE:: read_spatial_metric
!! Returns the |lorene|'s conformally flat spatial ADM metric
PROCEDURE:: test_position => is_hydro_positive
!# Returns `.TRUE.` if the energy density or the specific energy or the
! pressure are positive
!
!-- Overloaded FUNCTION to access the fields as arrays and as values
!
GENERIC, PUBLIC:: get_field => get_fa, get_fv
!# GENERIC PROCEDURE, overloded to access the [[diffstarlorene]]-member
! variables as arrays and as values
PROCEDURE:: get_fa => get_field_array
!! Access the [[diffstarlorene]]-member arrays
PROCEDURE:: get_fv => get_field_value
!! Access the components of the [[diffstarlorene]]-member arrays
!
!-- FUNCTIONS that access member variables
!
PROCEDURE:: get_eos_id => get_eos_loreneid
!! Returns the |lorene| identifier for the EOS
PROCEDURE:: return_eos_parameters => get_eos_parameters
PROCEDURE, PUBLIC:: get_eos_loreneid
!! Returns [[diffstarlorene:eos_loreneid]]
PROCEDURE, PUBLIC:: get_diffstar_identifier
!! Returns [[diffstarlorene:diffstar_identifier]]]
!PROCEDURE, PUBLIC:: get_diffstar_ptr
!PROCEDURE:: derived_type_destructor => destruct_diffstarlorene
FINAL:: destruct_diffstarlorene
!! Finalizer (Destructor) of a [[diffstarlorene]] object
PROCEDURE, NOPASS:: finalize
!# Corrects the |sph| |id| so that the linear \(\mathrm{ADM}\) momentum
! is zero
END TYPE diffstarlorene