Represents a generic \(\mathrm{ID}\) for \(\texttt{SPHINCS_BSSN}\) (binary neutron star, rotating star, etc.)
Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
logical, | private | :: | cold_system |
|
|||
type(timer), | public | :: | construction_timer |
Timer that times the construction of the appropriate object |
|||
logical, | private | :: | estimate_length_scale |
|
|||
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. |
||
integer, | private | :: | n_matter | = | 0 |
Number of matter objects belonging the physical system. For example, n_matter= 2 for a binary system of stars, and n_matter= 1 for a single star or for a binary system of a black hole and a star. |
|
logical, | private | :: | one_lapse |
Logical variable that determines if the lapse function , i.e., if the geodesic gauge is to be used |
|||
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 |
||
logical, | private | :: | zero_shift |
Logical variable that determines if the shift |
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 a TYPE that extends idbase
Construct 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 |
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
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 n_matter, the number of matter objects in the physical system
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 |
Initialize the \(\mathrm{ID}\); for example, set up the lattices around the stars for the \(\mathrm{BNS}\) produced with \(\texttt{FUKA}\).
Initialize the \(\mathrm{ID}\); for example, set up the lattices around the stars for the \(\mathrm{BNS}\) produced with \(\texttt{FUKA}\).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | 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 |
Prints a summary of the physical properties the system to the standard output and, optionally, to a formatted file whose name is given as optional argument
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(idbase), | intent(in) | :: | this | |||
character(len=*), | intent(inout), | optional | :: | filename |
Name of the formatted file to print the summary to |
Reads the full \(\mathrm{ID}\)
INTERFACE or the SUBROUTINE reading the full \(\mathrm{ID}\)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(inout) | :: | this |
idbase 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 |
Reads the hydro \(\mathrm{ID}\) needed to compute the constraints on the refined mesh
INTERFACE or the SUBROUTINE reading the the hydro \(\mathrm{ID}\) needed to compute the constraints on the refined mesh
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(inout) | :: | this |
idbase 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 |
Reads the components of the extrinsic curvature
INTERFACE or the SUBROUTINE reading the components of the extrinsic curvature
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(inout) | :: | this |
idbase 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 |
Reads the hydro \(\mathrm{ID}\) needed to compute the baryon mass
INTERFACE or the SUBROUTINE reading the hydro \(\mathrm{ID}\) needed to compute the baryon mass
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) | :: | 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 |
Reads the hydro \(\mathrm{ID}\) needed to compute the SPH \(\mathrm{ID}\)
INTERFACE or the SUBROUTINE reading the hydro \(\mathrm{ID}\) needed to compute the SPH \(\mathrm{ID}\)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(inout) | :: | this |
idbase 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 |
Reads the spacetime \(\mathrm{ID}\) needed to compute the BSSN variables and constraints
INTERFACE or the SUBROUTINE reading the spacetime \(\mathrm{ID}\)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(inout) | :: | this |
idbase 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 baryon mass density from the \(\mathrm{ID}\) at the given point
INTERFACE for a PROCEDURE that returns a DOUBLE PRECISION at a given position
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(in) | :: | this |
Object of class idbase 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 |
Real number at
Returns the pressure from te \(\mathrm{ID}\) at the given point
INTERFACE for a PROCEDURE that returns a DOUBLE PRECISION at a given position
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(in) | :: | this |
Object of class idbase 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 |
Real number at
Returns the ADM mass of the system
INTERFACE for a PROCEDURE that returns a DOUBLE PRECISION
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(in) | :: | this |
Real number
Returns the barycenters (centers of mass) of the matter objects.
INTERFACE for a PROCEDURE that returns a DOUBLE PRECISION
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(in) | :: | this | |||
integer, | intent(in) | :: | i_matter |
Index of the matter object whose parameter is to return |
Centers of the matter objects. The first index runs over the matter objects, the second index over .
Returns the centers of the matter objects.
INTERFACE for a PROCEDURE that returns a DOUBLE PRECISION
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(in) | :: | this | |||
integer, | intent(in) | :: | i_matter |
Index of the matter object whose parameter is to return |
Centers of the matter objects. The first index runs over the matter objects, the second index over .
Returns the name of the \(\mathrm{EOS}\) of the matter objects.
INTERFACE for a PROCEDURE that returns a CHARACTER(LEN=:)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(in) | :: | this |
idbase object which this PROCEDURE is a member of |
||
integer, | intent(in) | :: | i_matter |
Index of the matter object whose string is to return |
Returns the identification number of the \(\mathrm{EOS}\) of the matter objects.
Set up a convention for the identification number
INTERFACE for a PROCEDURE that returns an array containing the parametersf the \(\mathrm{EOS}\) for the matter objects
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(in) | :: | this | |||
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 |
Returns the masses of the matter objects.
INTERFACE for a PROCEDURE that returns a DOUBLE PRECISION
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(in) | :: | this | |||
integer, | intent(in) | :: | i_matter |
Index of the matter object whose parameter is to return |
Real number. Parameter of the i_matter
-th matter object
Returns the spatial extent of the matter objects, returning the array of 6 numbers
INTERFACE to the SUBROUTINE that detects the spatial extent of the matter objects, 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 |
||
integer, | intent(in) | :: | i_matter |
Index of the matter object whose string is to return |
6-dimensional array containing the coordinates of a box containing the physical system.
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 position has physically acceptable properties,
.FALSE.
otherwise
INTERFACE for a PROCEDURE that returns a LOGICAL at a given position
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(idbase), | intent(in) | :: | this |
Object of class idbase 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 |
Logical at
TYPE, ABSTRACT:: idbase
!# Represents a generic |id| for |sphincsbssn| (binary neutron star, rotating
! star, etc.)
PRIVATE
INTEGER:: n_matter= 0
!# Number of matter objects belonging the physical system.
! For example, n_matter= 2 for a binary system of stars, and n_matter= 1
! for a single star or for a binary system of a black hole and a star.
TYPE(surface), PUBLIC, DIMENSION(:), ALLOCATABLE:: surfaces
!# Array containing, for each matter object, a set of coordinates of some
! points modelling the surfaces.
! @todo TODO: make PRIVATE
TYPE(tabu_eos), PUBLIC, DIMENSION(:), ALLOCATABLE:: tab_eos
!# Array containing a tabulated |eos| for each matter object, when used.
! @todo TODO: make PRIVATE
LOGICAL:: one_lapse
!# Logical variable that determines if the lapse function \(\alpha=1\),
! i.e., if the geodesic gauge is to be used
LOGICAL:: zero_shift
!! Logical variable that determines if the shift \(\beta^i=0\)
LOGICAL:: cold_system
!# `.TRUE.` if the system is at zero temperature (no thermal component);
! `.FALSE.` otherwise
LOGICAL:: estimate_length_scale
!# `.TRUE.` if a typical length scale equal to the ratio of a field over
! its gradient should be computed (usually, the field is the pressure);
! `.FALSE.` otherwise
TYPE(timer), PUBLIC:: construction_timer
!! Timer that times the construction of the appropriate object
PROCEDURE(), POINTER, NOPASS, PUBLIC:: finalize_sph_id_ptr
!# Pointer to a procedure that finalize the |sph| |id|; for example,
! correct for the residual ADM linear momentum.
CONTAINS
!---------------------------!
!-- DEFERRED PROCEDURES --!
!---------------------------!
!
!-- PROCEDURES to read the value of a field at a point
!
PROCEDURE(read_double_at_pos), DEFERRED:: read_mass_density
!# Returns the baryon mass density from the |id| at the given point
PROCEDURE(read_double_at_pos), DEFERRED:: read_pressure
!# Returns the pressure from te |id| at the given point
PROCEDURE(read_logical_at_pos), DEFERRED:: test_position
!# Returns `.TRUE.` if the position has physically acceptable properties,
! `.FALSE.` otherwise
!
!-- PROCEDURES to read the value of several fields at several points
!
PROCEDURE(read_id_full_int), DEFERRED:: read_id_full
!# Reads the full |id|
PROCEDURE(read_id_particles_int), DEFERRED:: read_id_particles
!! Reads the hydro |id| needed to compute the SPH |id|
PROCEDURE(read_id_mass_b_int), DEFERRED:: read_id_mass_b
!! Reads the hydro |id| needed to compute the baryon mass
PROCEDURE(read_id_spacetime_int), DEFERRED:: read_id_spacetime
!# Reads the spacetime |id| needed to compute
! the BSSN variables and constraints
PROCEDURE(read_id_hydro_int), DEFERRED:: read_id_hydro
!# Reads the hydro |id| needed to compute the constraints on the refined
! mesh
PROCEDURE(read_id_k_int), DEFERRED:: read_id_k
!! Reads the components of the extrinsic curvature
!
!-- PROCEDURES returning the values of some parameters of a matter object
!
PROCEDURE(return_spatial_extent_int), DEFERRED:: return_spatial_extent
!# Returns the spatial extent of the matter objects,
! returning the array of 6 numbers
!\(x_{\rm min},x_{\rm max},y_{\rm min},y_{\rm max},z_{\rm min},z_{\rm max}\)
PROCEDURE(return_double_at_object), DEFERRED:: return_mass
!! Returns the masses of the matter objects.
PROCEDURE(return_double), DEFERRED:: return_adm_mass
!! Returns the ADM mass of the system
PROCEDURE(return_position), DEFERRED:: return_center
!! Returns the centers of the matter objects.
PROCEDURE(return_position), DEFERRED:: return_barycenter
!! Returns the barycenters (centers of mass) of the matter objects.
PROCEDURE(return_eos_parameters_int), DEFERRED:: return_eos_parameters
!# Returns the identification number of the |eos| of the matter objects.
! @todo Set up a convention for the identification number
PROCEDURE(return_string_parameter), DEFERRED:: return_eos_name
!! Returns the name of the |eos| of the matter objects.
PROCEDURE(initialize_id_int), DEFERRED:: initialize_id
!# Initialize the |id|; for example, set up the lattices around the
! stars for the |bns| produced with |fuka|.
!
!-- PROCEDURE that prints a summary of the physical properties the system
!-- to the standard output and, optionally, to a formatted file
!
PROCEDURE(print_summary_int), DEFERRED:: print_summary
!# Prints a summary of the physical properties the system
! to the standard output and, optionally, to a formatted file whose name
! is given as optional argument
!
!-- Constructors and destructors of derived types
!
PROCEDURE(derived_type_constructor_int), DEFERRED:: derived_type_constructor
!# Constructs a TYPE that extends [[idbase]]
!-------------------------------!
!-- NON-DEFERRED PROCEDURES --!
!-------------------------------!
PROCEDURE, NON_OVERRIDABLE:: sanity_check
!# Checks that [[idbase:n_matter]] and the sizes returned by
! [[idbase:return_spatial_extent]] and [[idbase:get_total_spatial_extent]]
! are acceptable. It is called by initialize, after the constructor of the
! derived type.
PROCEDURE, NON_OVERRIDABLE:: initialize
!# This PROCEDURE calls the constructor of the [[idbase]]-extended type
! and the SUBROUTINE [[idbase: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, NON_OVERRIDABLE:: get_total_spatial_extent
!# Returns the spatial extent of the physical system considered,
! as the array of 6 numbers
!\(x_{\rm min},x_{\rm max},y_{\rm min},y_{\rm max},z_{\rm min},z_{\rm max}\)
PROCEDURE, NON_OVERRIDABLE:: set_n_matter
!# Sets [[idbase:n_matter]], the number of matter objects in the
! physical system, to a value
PROCEDURE, NON_OVERRIDABLE:: get_n_matter
!# Returns [[idbase:n_matter]], the number of matter objects in the
! physical system
PROCEDURE, NON_OVERRIDABLE:: set_one_lapse
!# Sets [[idbase:one_lapse]], the `LOGICAL` variable that determines if
! the lapse \(\alpha=1\), i.e., if the geodesic gauge is to be used
PROCEDURE, NON_OVERRIDABLE:: get_one_lapse
!# Returns [[idbase:one_lapse]], the `LOGICAL` variable that determines if
! the lapse function \(\alpha=1\), i.e., if the geodesic gauge is to be used
PROCEDURE, NON_OVERRIDABLE:: set_zero_shift
!# Sets [[idbase:zero_shift]], the `LOGICAL` variable that determines if
! the shift \(\beta^i=0\)
PROCEDURE, NON_OVERRIDABLE:: get_zero_shift
!# Returns [[idbase:zero_shift]], the `LOGICAL` variable that determines if
! the shift \(\beta^i=0\)
PROCEDURE, NON_OVERRIDABLE:: set_cold_system
!# Sets [[idbase:cold_system]], the `LOGICAL` variable that specifies if
! the system is cold (no thermal component)
PROCEDURE, NON_OVERRIDABLE:: get_cold_system
!# Returns [[idbase:cold_system]], the `LOGICAL` variable that specifies if
! the system is cold (no thermal component)
PROCEDURE, NON_OVERRIDABLE:: set_estimate_length_scale
!# Sets [[idbase: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, NON_OVERRIDABLE:: get_estimate_length_scale
!# Returns [[idbase: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, NON_OVERRIDABLE:: check_i_matter
!# Checks that the given index is between 1 and [[idbase:n_matter]],
! included. If not, it stops the execution of the program.
PROCEDURE:: integrate_baryon_mass_density
!# Integrates the baryon mass density over a matter object, using spherical
! coordinates, and computes its radial profile inside the star
PROCEDURE:: estimate_lengthscale_field
!# Estimate typical length scales, one per each matter object, by
! computing \(\dfrac{f}{\partial f}\), where \(f\) is a field given
! as input, and \(\partial\) represent a derivative of it.
! Presently, the derivatives are computed separately along each spatial
! dimension, as 1D derivatives.
END TYPE idbase