compute_g4 Subroutine

public pure subroutine compute_g4(lapse, shift, g3, g4)

Uses

    • tensor
  • proc~~compute_g4~~UsesGraph proc~compute_g4 compute_g4 tensor tensor proc~compute_g4->tensor

Computes the spacetime metric from lapse, shift and spatial metric

FT 27.11.2020

Generalized to not be bound to the mesh

FT 07.02.2022


Arguments

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

Lapse function

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

Contravariant shift vector

double precision, intent(in), DIMENSION(6) :: g3

Covariant spatial metric

double precision, intent(inout), DIMENSION(10) :: g4

Covariant spacetime metric


Called by

proc~~compute_g4~~CalledByGraph proc~compute_g4 compute_g4 none~compute_4velocity_eul compute_4velocity_eul none~compute_4velocity_eul->proc~compute_g4 proc~compute_and_print_sph_variables compute_and_print_sph_variables proc~compute_and_print_sph_variables->proc~compute_g4 proc~construct_particles_bin construct_particles_bin proc~construct_particles_bin->proc~compute_g4 proc~correct_adm_linear_momentum correct_adm_linear_momentum proc~correct_adm_linear_momentum->proc~compute_g4 proc~read_fuka_id_spacetime read_fuka_id_spacetime proc~read_fuka_id_spacetime->proc~compute_g4 proc~read_id_spacetime read_id_spacetime proc~read_id_spacetime->proc~compute_g4 proc~read_id_spacetime~2 read_id_spacetime proc~read_id_spacetime~2->proc~compute_g4 proc~test_recovery test_recovery proc~test_recovery->proc~compute_g4 interface~compute_and_print_sph_variables compute_and_print_sph_variables interface~compute_and_print_sph_variables->proc~compute_and_print_sph_variables interface~construct_particles_bin construct_particles_bin interface~construct_particles_bin->proc~construct_particles_bin interface~correct_adm_linear_momentum correct_adm_linear_momentum interface~correct_adm_linear_momentum->proc~correct_adm_linear_momentum interface~read_fuka_id_spacetime read_fuka_id_spacetime interface~read_fuka_id_spacetime->proc~read_fuka_id_spacetime interface~read_id_spacetime read_id_spacetime interface~read_id_spacetime->proc~read_id_spacetime interface~read_id_spacetime~2 read_id_spacetime interface~read_id_spacetime~2->proc~read_id_spacetime~2 interface~test_recovery test_recovery interface~test_recovery->proc~test_recovery proc~compute_and_print_bssn_constraints_grid compute_and_print_bssn_constraints_grid proc~compute_and_print_bssn_constraints_grid->none~compute_4velocity_eul interface~compute_and_print_bssn_constraints_grid compute_and_print_bssn_constraints_grid interface~compute_and_print_bssn_constraints_grid->proc~compute_and_print_bssn_constraints_grid interface~particles particles interface~particles->interface~construct_particles_bin program~convergence_test convergence_test program~convergence_test->interface~particles program~sphincs_id sphincs_id program~sphincs_id->interface~particles

Contents

Source Code


Source Code

  PURE SUBROUTINE compute_g4( lapse, shift, g3, g4 )

    !***********************************************
    !
    !# Computes the spacetime metric from lapse,
    !  shift and spatial metric
    !
    !  FT 27.11.2020
    !
    !  Generalized to not be bound to the mesh
    !
    !  FT 07.02.2022
    !
    !***********************************************

    USE tensor,     ONLY: itt, itx, ity, itz, ixx, ixy, &
                          ixz, iyy, iyz, izz, jxx, jxy, jxz, &
                          jyy, jyz, jzz, jx, jy, jz

    IMPLICIT NONE

    DOUBLE PRECISION,                INTENT(IN)   :: lapse
    !! Lapse function
    DOUBLE PRECISION, DIMENSION(3),  INTENT(IN)   :: shift
    !! Contravariant shift vector
    DOUBLE PRECISION, DIMENSION(6),  INTENT(IN)   :: g3
    !! Covariant spatial metric
    DOUBLE PRECISION, DIMENSION(10), INTENT(INOUT):: g4
    !! Covariant spacetime metric

    g4(itt)= - lapse*lapse + g3(jxx)*shift(jx)*shift(jx)     &
                           + g3(jxy)*shift(jx)*shift(jy)*two &
                           + g3(jxz)*shift(jx)*shift(jz)*two &
                           + g3(jyy)*shift(jy)*shift(jy)     &
                           + g3(jyz)*shift(jy)*shift(jz)*two &
                           + g3(jzz)*shift(jz)*shift(jz)

    g4(itx)= g3(jxx)*shift(jx) + g3(jxy)*shift(jy) + g3(jxz)*shift(jz)
    g4(ity)= g3(jxy)*shift(jx) + g3(jyy)*shift(jy) + g3(jyz)*shift(jz)
    g4(itz)= g3(jxz)*shift(jx) + g3(jyz)*shift(jy) + g3(jzz)*shift(jz)

    g4(ixx)= g3(jxx)
    g4(ixy)= g3(jxy)
    g4(ixz)= g3(jxz)
    g4(iyy)= g3(jyy)
    g4(iyz)= g3(jyz)
    g4(izz)= g3(jzz)

  END SUBROUTINE compute_g4