This module contains the definition of ABSTRACT TYPE tpo
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
double precision, | intent(in) | :: | lower_bound | |||
double precision, | intent(in) | :: | upper_bound | |||
double precision, | intent(in), | DIMENSION(:,:,:) | :: | constraint | ||
integer, | intent(in) | :: | l | |||
logical, | intent(in) | :: | export | |||
integer, | intent(in) | :: | unit_analysis | |||
integer, | intent(out) | :: | cnt |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
integer, | intent(in) | :: | l | |||
double precision, | intent(in), | DIMENSION(:,:,:) | :: | constraint | ||
character(len=*), | intent(in) | :: | name_constraint | |||
integer, | intent(in) | :: | unit_logfile | |||
character(len=*), | intent(in) | :: | name_analysis | |||
double precision, | intent(out) | :: | l2_norm | |||
double precision, | intent(out) | :: | loo_norm | |||
double precision, | intent(out) | :: | integral | |||
double precision, | intent(in), | optional, | DIMENSION(:,:,:) | :: | source |
Computes an estimate of the linear momentum of the fluid using the \(\mathrm{SPH}\) hydro fields, and the spacetime metric mapped from the mesh
add reference
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(in) | :: | this |
tpo object which this PROCEDURE is a member of |
||
class(particles), | intent(in) | :: | parts |
particles object used to map the metric from the mesh to the particles, and to call the recovery procedures |
||
double precision, | intent(out), | DIMENSION(3) | :: | adm_mom |
ADM linear momentum of the fluid computed using the metric mapped with the mesh-to-particle mapping |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
integer, | intent(in) | :: | i | |||
integer, | intent(in) | :: | j | |||
integer, | intent(in) | :: | k | |||
integer, | intent(in) | :: | l |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
integer, | intent(in) | :: | i | |||
integer, | intent(in) | :: | j | |||
integer, | intent(in) | :: | k | |||
integer, | intent(in) | :: | l |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
integer, | intent(in) | :: | i | |||
integer, | intent(in) | :: | j | |||
integer, | intent(in) | :: | k | |||
integer, | intent(in) | :: | l |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
integer, | intent(in) | :: | i | |||
integer, | intent(in) | :: | j | |||
integer, | intent(in) | :: | k | |||
integer, | intent(in) | :: | l |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
integer, | intent(in) | :: | l |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
integer, | intent(in) | :: | l |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
integer, | intent(in) | :: | l |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
integer, | intent(in) | :: | i | |||
integer, | intent(in) | :: | j | |||
integer, | intent(in) | :: | k | |||
integer, | intent(in) | :: | l |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
integer, | intent(in) | :: | l |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
integer, | intent(in) | :: | l |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
integer, | intent(in) | :: | l |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
integer, | intent(in) | :: | l |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
integer, | intent(in) | :: | l |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
integer, | intent(in) | :: | l |
Prints a summary of the properties of the refined mesh,
and optionally, to a formatted file whose name
is given as the optional argument filename
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this |
Name of the formatted file to print the summary to |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | tpof | |||
class(idbase), | intent(inout) | :: | id | |||
double precision, | intent(in), | optional | :: | dx | ||
double precision, | intent(in), | optional | :: | dy | ||
double precision, | intent(in), | optional | :: | dz |
Tests the recovery. Computes the conserved variables from the physical ones, and then the physical ones from the conserved ones. It then compares the variables computed with the recovery PROCEDURES, with those computed with \(\texttt{SPHINCS_ID}\). Uses the mesh-2-particle.
add reference for recovery
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(in) | :: | this |
tpo object which this PROCEDURE is a member of |
||
class(particles), | intent(in) | :: | parts |
particles object used to map the metric from the mesh to the particles, and to call the recovery procedures |
||
character(len=*), | intent(inout) | :: | namefile |
Name of the formatted file where the data is printed |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout), | TARGET | :: | this | ||
class(idbase), | intent(inout) | :: | id | |||
character(len=*), | intent(inout) | :: | namefile | |||
character(len=*), | intent(inout) | :: | name_logfile | |||
double precision, | intent(in), | optional, | DIMENSION(:,:,:,:), TARGET | :: | points |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout), | TARGET | :: | this | ||
class(particles), | intent(inout) | :: | parts_obj | |||
character(len=*), | intent(inout) | :: | namefile | |||
character(len=*), | intent(inout) | :: | name_logfile | |||
double precision, | intent(in), | optional, | DIMENSION(:,:,:,:), TARGET | :: | points |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
character(len=*), | intent(inout), | optional | :: | namefile |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(tpo), | intent(inout) | :: | this | |||
double precision, | intent(in), | optional, | DIMENSION(:,:,:,:) | :: | points | |
character(len=*), | intent(inout), | optional | :: | namefile |
ABSTRACT TYPE representing the standard formulation of the Einstein equations
Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
type(grid_function_scalar), | public | :: | HC |
Grid scalar function storing the Hamiltonian constraint (violations) computed using the ID on the mesh |
|||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | HC_int |
Integral the Hamiltonian constraint computed using the stress-energy tensor mapped from the particles |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | HC_l2 |
norm of the Hamiltonian constraint computed on the mesh |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | HC_loo |
norm of the Hamiltonian constraint computed on the mesh (i.e., its maximum) |
||
type(grid_function_scalar), | public | :: | HC_parts |
Grid scalar function storing the Hamiltonian constraint (violations) computed using the stress-energy tensor mapped from the particles to the mesh |
|||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | HC_parts_int |
Integral the Hamiltonian constraint computed on the mesh |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | HC_parts_l2 |
norm of the Hamiltonian constraint computed on the mesh, using the stress-energy tensor mapped from the particles |
||
double precision, | public, | DIMENSION(:), ALLOCATABLE | :: | HC_parts_loo |
norm of the Hamiltonian constraint computed on the mesh, using the stress-energy tensor mapped from the particles (i.e., its maximum) |
||
type(grid_function), | public | :: | K_phys3_ll |
Grid function storing the extrinsic curvature |
|||
type(grid_function), | public | :: | MC |
Grid function storing the momentum constraint (violations) computed using the ID on the mesh |
|||
double precision, | public, | DIMENSION(:,:), ALLOCATABLE | :: | MC_int |
Integral of the momentum constraint computed on the mesh |
||
double precision, | public, | DIMENSION(:,:), ALLOCATABLE | :: | MC_l2 |
norm of the momentum constraint computed on the mesh |
||
double precision, | public, | DIMENSION(:,:), ALLOCATABLE | :: | MC_loo |
norm of the momentum constraint computed on the mesh (i.e., its maximum) |
||
type(grid_function), | public | :: | MC_parts |
Grid function storing the momentum constraint (violations) computed using the stress-energy tensor mapped from the particles to the mesh |
|||
double precision, | public, | DIMENSION(:,:), ALLOCATABLE | :: | MC_parts_int |
Integral of the momentum constraint computed using the stress-energy tensor mapped from the particles |
||
double precision, | public, | DIMENSION(:,:), ALLOCATABLE | :: | MC_parts_l2 |
norm of the Hamiltonian constraint computed on the mesh, using the stress-energy tensor mapped from the particles |
||
double precision, | public, | DIMENSION(:,:), ALLOCATABLE | :: | MC_parts_loo |
norm of the momentum constraint computed on the mesh, using the stress-energy tensor mapped from the particles (i.e., its maximum) |
||
type(grid_function), | public | :: | S |
Grid function storing the matter source in the momentum constraint computed using the ID on the mesh, multiplied by |
|||
type(grid_function), | public | :: | S_parts |
Grid function storing the matter source in the momentum constraint computed using the stress-energy tensor mapped from the particles to the mesh, multiplied by |
|||
integer, | public | :: | cons_step |
Constraint violations are printed to file every cons_step-th grid point |
|||
type(grid_function), | public | :: | coords |
Grid function storing the Cartesian coordinates |
|||
logical, | public | :: | export_constraints |
|
|||
logical, | public | :: | export_constraints_details |
|
|||
logical, | public | :: | export_constraints_x |
|
|||
logical, | public | :: | export_constraints_xy |
|
|||
type(grid_function), | public | :: | g_phys3_ll |
Grid function storing the spatial metric |
|||
type(timer), | public | :: | grid_timer |
Timer that times how long it takes to set up the grid and allocate the grid functions |
|||
type(timer), | public | :: | importer_timer |
Timer that times how long it takes to import the \(\texttt{LORENE}\) ID on the mesh |
|||
type(grid_function_scalar), | public | :: | lapse |
Grid scalar function storing the lapse function |
|||
type(level), | public, | DIMENSION(:), ALLOCATABLE | :: | levels |
Array containing the information on each refinement level |
||
integer, | public | :: | n_matter |
Number of matter objects in the physical system |
|||
integer, | public | :: | nlevels |
Number of refinement levels |
|||
integer, | public, | DIMENSION(:), ALLOCATABLE | :: | npoints_xaxis |
Array containing the number of mesh points of the highest-resolution refinement level across the x-axis-size of the matter objects |
||
type(grid_function_scalar), | public | :: | rad_coord |
Grid scalar function storing the radial coordinates of each grid point |
|||
type(grid_function_scalar), | public | :: | rho |
Grid scalar function storing the matter source in the Hamiltonian constraint computed using the ID on the mesh, multiplied by |
|||
type(grid_function_scalar), | public | :: | rho_parts |
Grid scalar function storing the matter source in the Hamiltonian constraint computed using the stress-energy tensor mapped from the particles to the mesh, multiplied by |
|||
type(grid_function), | public | :: | shift_u |
Grid function storing the shift vector |
|||
integer, | public | :: | tpo_id_number |
Negative integer that identifies the tpo object |
procedure , public :: abs_values_in Interface | |
procedure , public , NON_OVERRIDABLE :: analyze_constraint Interface | Analyze a constraint (or an arbitrary scalar grid function) by examining its values at the refined mesh. Computes the number of mesh points at which the scalar grid function has values lying within predefined (hard-coded) intervals |
procedure , public , NON_OVERRIDABLE :: compute_adm_momentum_fluid_m2p Interface | Computes an estimate of the linear momentum of the fluid using the \(\mathrm{SPH}\) hydro fields, and the spacetime metric mapped from the mesh |
generic, public :: compute_and_print_tpo_constraints => compute_and_print_tpo_constraints_grid, compute_and_print_tpo_constraints_particles | Overloaded PROCEDURE to compute the constraints using only the \(\mathrm{ID}\) on the refined mesh, or the spacetime \(\mathrm{ID}\) on the refined mesh and the hydrodynamical \(\mathrm{ID}\) mapped from the particles to the refined mesh |
procedure (compute_and_print_tpo_constraints_grid_interface) , public :: compute_and_print_tpo_constraints_grid | Computes the constraints specific to the formulation identified by an EXTENDED TYPE, using the full \(\mathrm{ID}\) on the refined mesh |
procedure (compute_and_print_tpo_constraints_particles_interface) , public :: compute_and_print_tpo_constraints_particles | Computes the constraints specific to the formulation identified by an EXTENDED TYPE, using the \(\mathrm{BSSNOK}\) \(\mathrm{ID}\) on the refined mesh and the hydrodynamical \(\mathrm{ID}\) mapped from the particles to the mesh |
procedure (compute_and_print_tpo_variables_interface) , public :: compute_and_print_tpo_variables | Compute the fields specific to the formulation identified by an EXTENDED TYPE, starting from the standard 3+1 fields |
procedure (deallocate_fields_interface) , public :: deallocate_fields | Deallocates memory for the fields specific to the formulation identified by an EXTENDED TYPE |
procedure , public , NON_OVERRIDABLE :: deallocate_standard_tpo_variables Interface | Deallocates memory for the standard 3+1 fields |
procedure (define_allocate_fields_interface) , public :: define_allocate_fields | Allocates memory for the fields specific to the formulation identified by an EXTENDED TYPE |
procedure , public :: get_HC Interface | |
procedure , public :: get_HC_parts Interface | |
procedure , public :: get_MC Interface | |
procedure , public :: get_MC_parts Interface | |
procedure , public :: get_dx Interface | |
procedure , public :: get_dy Interface | |
procedure , public :: get_dz Interface | |
procedure , public :: get_grid_point Interface | |
procedure , public :: get_levels Interface | |
procedure , public :: get_ngrid_x Interface | |
procedure , public :: get_ngrid_y Interface | |
procedure , public :: get_ngrid_z Interface | |
procedure , public :: get_nlevels Interface | |
procedure , public :: get_xR Interface | |
procedure , public :: get_yR Interface | |
procedure , public :: get_zR Interface | |
procedure (print_formatted_id_tpo_variables_interface) , public :: print_formatted_id_tpo_variables | Prints the spacetime \(\mathrm{ID}\) to a formatted file |
procedure , public , NON_OVERRIDABLE :: print_summary Interface | Prints a summary about the features of the refined mesh |
procedure , public , NON_OVERRIDABLE :: setup_standard_tpo_variables Interface | Set up the refined mesh by reading the |
procedure , public , NON_OVERRIDABLE :: test_recovery_m2p Interface | Computes the conserved variables from the physical ones, and vice versa, to test that the recovered physical variables are the same to those computed from the \(\mathrm{ID}\). Uses the metric mapped from the grid to the particles. |