idbase Derived Type

type, public, ABSTRACT :: idbase

Represents a generic \(\mathrm{ID}\) for \(\texttt{SPHINCS_BSSN}\) (binary neutron star, rotating star, etc.)


Inherits

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

Inherited by

type~~idbase~~InheritedByGraph type~idbase idbase type~bnsbase bnsbase type~bnsbase->type~idbase type~diffstarbase diffstarbase type~diffstarbase->type~idbase type~ejecta ejecta type~ejecta->type~idbase type~id id type~id->type~idbase idata type~bnsfuka bnsfuka type~bnsfuka->type~bnsbase type~bnslorene bnslorene type~bnslorene->type~bnsbase type~diffstarlorene diffstarlorene type~diffstarlorene->type~diffstarbase

Contents

Source Code


Components

Type Visibility Attributes Name Initial
logical, private :: cold_system

.TRUE. if the system is at zero temperature (no thermal component); .FALSE. otherwise

type(timer), public :: construction_timer

Timer that times the construction of the appropriate object

logical, private :: 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

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.

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

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

logical, private :: zero_shift

Logical variable that determines if the shift


Type-Bound Procedures

procedure, public, NON_OVERRIDABLE :: check_i_matter

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

  • interface

    public module subroutine check_i_matter(this, i_matter)

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

    Arguments

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

    Value to be checked

procedure(derived_type_constructor_int), public, deferred :: derived_type_constructor

Constructs a TYPE that extends idbase

  • subroutine derived_type_constructor_int(derived_type, filename, eos_filenames) Prototype

    Construct the DERIVED TYPE that extends idbase

    Arguments

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

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

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

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

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

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

procedure, public :: estimate_lengthscale_field

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

  • interface

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

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

    Arguments

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

    Returns the value of a field at the desired point

    Arguments
    Type IntentOptional Attributes Name
    double precision, intent(in) :: x

    coordinate of the desired point

    double precision, intent(in) :: y

    coordinate of the desired point

    double precision, intent(in) :: z

    coordinate of the desired point

    Return Value double precision

    Value of the field at

    integer, intent(in) :: n_mat

    Return Value double precision, DIMENSION(n_mat)

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

procedure, public, NON_OVERRIDABLE :: get_cold_system

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

  • interface

    public pure module function get_cold_system(this)

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

    Arguments

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

    Return Value logical

    cold_system

procedure, public, NON_OVERRIDABLE :: get_estimate_length_scale

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

  • interface

    public pure module function get_estimate_length_scale(this)

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

    Arguments

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

    Return Value logical

    estimate_length_scale

procedure, public, NON_OVERRIDABLE :: get_n_matter

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

  • interface

    public pure module function get_n_matter(this)

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

    Arguments

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

    Return Value integer

    n_matter, the number of matter objects in the

procedure, public, NON_OVERRIDABLE :: get_one_lapse

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

  • interface

    public pure module function get_one_lapse(this)

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

    Arguments

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

    Return Value logical

    n_matter, the number of matter objects in the

procedure, public, NON_OVERRIDABLE :: get_total_spatial_extent

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

  • interface

    public module function get_total_spatial_extent(this) result(box)

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

    Arguments

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

    Object of class idbase which this PROCEDURE is a member of

    Return Value double precision, DIMENSION(6)

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

procedure, public, NON_OVERRIDABLE :: get_zero_shift

Returns zero_shift, the LOGICAL variable that determines if the shift

  • interface

    public pure module function get_zero_shift(this)

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

    Arguments

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

    Return Value logical

    n_matter, the number of matter objects in the

procedure, public, NON_OVERRIDABLE :: initialize

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

  • interface

    public module subroutine initialize(derived_type, filename, eos_filenames)

    Initialize the DERIVED TYPE that extends idbase

    Arguments

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

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

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

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

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

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

procedure(initialize_id_int), public, deferred :: initialize_id

Initialize the \(\mathrm{ID}\); for example, set up the lattices around the stars for the \(\mathrm{BNS}\) produced with \(\texttt{FUKA}\).

  • subroutine initialize_id_int(this, flag, switch) Prototype

    Initialize the \(\mathrm{ID}\); for example, set up the lattices around the stars for the \(\mathrm{BNS}\) produced with \(\texttt{FUKA}\).

    Arguments

    Type IntentOptional 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 .TRUE., switch to a different initialization

procedure, public :: integrate_baryon_mass_density

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

  • interface

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

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

    Arguments

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

    Object of class idbase which this PROCEDURE is a member of

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

    Center of the star

    double precision, intent(in) :: radius

    Central density of the star

    double precision, intent(in) :: central_density

    Integration steps

    double precision, intent(in) :: dr

    Radius of the star

    double precision, intent(in) :: dth

    Radius of the star

    double precision, intent(in) :: dphi

    Radius of the star

    double precision, intent(inout) :: mass

    Integrated mass of the star

    double precision, intent(out), DIMENSION(3,0:NINT(radius/dr)) :: mass_profile

    Array storing the radial mass profile of the star

    integer, intent(out), DIMENSION(0:NINT(radius/dr)) :: mass_profile_idx

    Array to store the indices for array mass_profile, sorted so that mass_profile[mass_profile_idx] is in increasing order

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

    Surface of the matter object

procedure(print_summary_int), public, 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

  • subroutine print_summary_int(this, filename) Prototype

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

    Arguments

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

    Name of the formatted file to print the summary to

procedure(read_id_full_int), public, deferred :: read_id_full

Reads the full \(\mathrm{ID}\)

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

    INTERFACE or the SUBROUTINE reading the full \(\mathrm{ID}\)

    Arguments

    Type IntentOptional 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

procedure(read_id_hydro_int), public, deferred :: read_id_hydro

Reads the hydro \(\mathrm{ID}\) needed to compute the constraints on the refined mesh

  • subroutine read_id_hydro_int(this, nx, ny, nz, pos, baryon_density, energy_density, specific_energy, pressure, u_euler) Prototype

    INTERFACE or the SUBROUTINE reading the the hydro \(\mathrm{ID}\) needed to compute the constraints on the refined mesh

    Arguments

    Type IntentOptional 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

procedure(read_id_k_int), public, deferred :: read_id_k

Reads the components of the extrinsic curvature

  • subroutine read_id_k_int(this, n, x, y, z, k_xx, k_xy, k_xz, k_yy, k_yz, k_zz) Prototype

    INTERFACE or the SUBROUTINE reading the components of the extrinsic curvature

    Arguments

    Type IntentOptional 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

procedure(read_id_mass_b_int), public, deferred :: read_id_mass_b

Reads the hydro \(\mathrm{ID}\) needed to compute the baryon mass

  • subroutine read_id_mass_b_int(this, x, y, z, g, baryon_density, gamma_euler) Prototype

    INTERFACE or the SUBROUTINE reading the hydro \(\mathrm{ID}\) needed to compute the baryon mass

    Arguments

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

    Object of class idbase which this PROCEDURE is a member of

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

procedure(read_id_particles_int), public, deferred :: read_id_particles

Reads the hydro \(\mathrm{ID}\) needed to compute the SPH \(\mathrm{ID}\)

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

    INTERFACE or the SUBROUTINE reading the hydro \(\mathrm{ID}\) needed to compute the SPH \(\mathrm{ID}\)

    Arguments

    Type IntentOptional 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

procedure(read_id_spacetime_int), public, deferred :: read_id_spacetime

Reads the spacetime \(\mathrm{ID}\) needed to compute the BSSN variables and constraints

  • subroutine read_id_spacetime_int(this, nx, ny, nz, pos, lapse, shift, g, ek) Prototype

    INTERFACE or the SUBROUTINE reading the spacetime \(\mathrm{ID}\)

    Arguments

    Type IntentOptional 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

procedure(read_double_at_pos), public, deferred :: read_mass_density

Returns the baryon mass density from the \(\mathrm{ID}\) at the given point

  • function read_double_at_pos(this, x, y, z) result(res) Prototype

    INTERFACE for a PROCEDURE that returns a DOUBLE PRECISION at a given position

    Arguments

    Type IntentOptional 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

    Return Value double precision

    Real number at

procedure(read_double_at_pos), public, deferred :: read_pressure

Returns the pressure from te \(\mathrm{ID}\) at the given point

  • function read_double_at_pos(this, x, y, z) result(res) Prototype

    INTERFACE for a PROCEDURE that returns a DOUBLE PRECISION at a given position

    Arguments

    Type IntentOptional 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

    Return Value double precision

    Real number at

procedure(return_double), public, deferred :: return_adm_mass

Returns the ADM mass of the system

  • function return_double(this) result(res) Prototype

    INTERFACE for a PROCEDURE that returns a DOUBLE PRECISION

    Arguments

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

    Return Value double precision

    Real number

procedure(return_position), public, deferred :: return_barycenter

Returns the barycenters (centers of mass) of the matter objects.

  • function return_position(this, i_matter) result(res) Prototype

    INTERFACE for a PROCEDURE that returns a DOUBLE PRECISION

    Arguments

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

    Index of the matter object whose parameter is to return

    Return Value double precision, DIMENSION(3)

    Centers of the matter objects. The first index runs over the matter objects, the second index over .

procedure(return_position), public, deferred :: return_center

Returns the centers of the matter objects.

  • function return_position(this, i_matter) result(res) Prototype

    INTERFACE for a PROCEDURE that returns a DOUBLE PRECISION

    Arguments

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

    Index of the matter object whose parameter is to return

    Return Value double precision, DIMENSION(3)

    Centers of the matter objects. The first index runs over the matter objects, the second index over .

procedure(return_string_parameter), public, deferred :: return_eos_name

Returns the name of the \(\mathrm{EOS}\) of the matter objects.

  • function return_string_parameter(this, i_matter) result(string) Prototype

    INTERFACE for a PROCEDURE that returns a CHARACTER(LEN=:)

    Arguments

    Type IntentOptional 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

    Return Value character(len=:), ALLOCATABLE

procedure(return_eos_parameters_int), public, deferred :: return_eos_parameters

Returns the identification number of the \(\mathrm{EOS}\) of the matter objects.

  • subroutine return_eos_parameters_int(this, i_matter, eos_params) Prototype

    INTERFACE for a PROCEDURE that returns an array containing the parametersf the \(\mathrm{EOS}\) for the matter objects

    Arguments

    Type IntentOptional 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 i_matter-th matter object

procedure(return_double_at_object), public, deferred :: return_mass

Returns the masses of the matter objects.

  • function return_double_at_object(this, i_matter) result(res) Prototype

    INTERFACE for a PROCEDURE that returns a DOUBLE PRECISION

    Arguments

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

    Index of the matter object whose parameter is to return

    Return Value double precision

    Real number. Parameter of the i_matter-th matter object

procedure(return_spatial_extent_int), public, deferred :: return_spatial_extent

Returns the spatial extent of the matter objects, returning the array of 6 numbers

  • function return_spatial_extent_int(this, i_matter) result(box) Prototype

    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.

    Arguments

    Type IntentOptional 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

    Return Value double precision, DIMENSION(6)

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

procedure, public, NON_OVERRIDABLE :: sanity_check

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

  • interface

    public module subroutine sanity_check(derived_type)

    Check that the DERIVED TYPE that extends idbase is constructed consistently

    Arguments

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

    Object of DERIVED TYPE that extends idbase

procedure, public, NON_OVERRIDABLE :: set_cold_system

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

  • interface

    public module subroutine set_cold_system(this, value)

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

    Arguments

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

    Value to set cold_system to

procedure, public, NON_OVERRIDABLE :: set_estimate_length_scale

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

  • interface

    public module subroutine set_estimate_length_scale(this, value)

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

    Arguments

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

    Value to set cold_system to

procedure, public, NON_OVERRIDABLE :: set_n_matter

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

  • interface

    public pure module subroutine set_n_matter(this, value)

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

    Arguments

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

    Value to set n_matter to

procedure, public, NON_OVERRIDABLE :: set_one_lapse

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

  • interface

    public pure module subroutine set_one_lapse(this, logic)

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

    Arguments

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

    Value to set n_matter to

procedure, public, NON_OVERRIDABLE :: set_zero_shift

Sets zero_shift, the LOGICAL variable that determines if the shift

  • interface

    public pure module subroutine set_zero_shift(this, logic)

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

    Arguments

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

    Value to set n_matter to

procedure(read_logical_at_pos), public, deferred :: test_position

Returns .TRUE. if the position has physically acceptable properties, .FALSE. otherwise

  • function read_logical_at_pos(this, x, y, z) result(res) Prototype

    INTERFACE for a PROCEDURE that returns a LOGICAL at a given position

    Arguments

    Type IntentOptional 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

    Return Value logical

    Logical at

Source Code

  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