compute_tpo_metric Subroutine

public subroutine compute_tpo_metric(g4, lapse, shift, g3)

Uses

    • tensor
    • matrix
  • proc~~compute_tpo_metric~~UsesGraph proc~compute_tpo_metric compute_tpo_metric matrix matrix proc~compute_tpo_metric->matrix tensor tensor proc~compute_tpo_metric->tensor

Computes the lapse,shift and spatial metric from the covariant spacetime metric

FT 12.04.2022


Arguments

Type IntentOptional Attributes Name
double precision, intent(in), DIMENSION(n_sym4x4) :: g4

Covariant spacetime metric

double precision, intent(out) :: lapse

Lapse function

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

Contravariant shift vector

double precision, intent(out), DIMENSION(n_sym3x3) :: g3

Covariant spatial metric


Calls

proc~~compute_tpo_metric~~CallsGraph proc~compute_tpo_metric compute_tpo_metric invert_3x3_matrix invert_3x3_matrix proc~compute_tpo_metric->invert_3x3_matrix

Called by

proc~~compute_tpo_metric~~CalledByGraph proc~compute_tpo_metric compute_tpo_metric proc~compute_adm_momentum_fluid_m2p compute_adm_momentum_fluid_m2p proc~compute_adm_momentum_fluid_m2p->proc~compute_tpo_metric proc~read_boost_superimpose_tov_adm_id read_boost_superimpose_tov_adm_id proc~read_boost_superimpose_tov_adm_id->proc~compute_tpo_metric interface~compute_adm_momentum_fluid_m2p compute_adm_momentum_fluid_m2p interface~compute_adm_momentum_fluid_m2p->proc~compute_adm_momentum_fluid_m2p program~construct_newtonian_binary construct_newtonian_binary program~construct_newtonian_binary->proc~read_boost_superimpose_tov_adm_id

Contents

Source Code


Variables

Type Visibility Attributes Name Initial
double precision, public, DIMENSION(3,3) :: gmat
double precision, public, DIMENSION(3,3) :: gmat_inv

Source Code

  SUBROUTINE compute_tpo_metric( g4, lapse, shift, g3 )

    !***********************************************
    !
    !# Computes the lapse,shift and spatial metric
    !  from the covariant spacetime metric
    !
    !  FT 12.04.2022
    !
    !***********************************************

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

    IMPLICIT NONE

    DOUBLE PRECISION, DIMENSION(n_sym4x4),  INTENT(IN) :: g4
    !! Covariant spacetime metric
    DOUBLE PRECISION,                       INTENT(OUT):: lapse
    !! Lapse function
    DOUBLE PRECISION, DIMENSION(3),         INTENT(OUT):: shift
    !! Contravariant shift vector
    DOUBLE PRECISION, DIMENSION(n_sym3x3),  INTENT(OUT):: g3
    !! Covariant spatial metric

    DOUBLE PRECISION, DIMENSION(3,3):: gmat
    DOUBLE PRECISION, DIMENSION(3,3):: gmat_inv

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

    gmat(1,1)= g3(jxx)
    gmat(1,2)= g3(jxy)
    gmat(1,3)= g3(jxz)
    gmat(2,1)= g3(jxy)
    gmat(2,2)= g3(jyy)
    gmat(2,3)= g3(jyz)
    gmat(3,1)= g3(jxz)
    gmat(3,2)= g3(jyz)
    gmat(3,3)= g3(jzz)

    CALL invert_3x3_matrix( gmat, gmat_inv )

    shift(jx)= gmat_inv(jx,jx)*g4(itx) + gmat_inv(jx,jy)*g4(ity) &
             + gmat_inv(jx,jz)*g4(itz)
    shift(jy)= gmat_inv(jy,jx)*g4(itx) + gmat_inv(jy,jy)*g4(ity) &
             + gmat_inv(jy,jz)*g4(itz)
    shift(jz)= gmat_inv(jz,jx)*g4(itx) + gmat_inv(jz,jy)*g4(ity) &
             + gmat_inv(jz,jz)*g4(itz)

    lapse= SQRT( shift(jx)*g4(itx) + shift(jy)*g4(ity) + shift(jz)*g4(itz) &
                 - g4(itt) )

  END SUBROUTINE compute_tpo_metric