spacetime_vector_norm_sym4x4 Subroutine

public subroutine spacetime_vector_norm_sym4x4(g4, v, norm)

Uses

    • tensor
  • proc~~spacetime_vector_norm_sym4x4~~UsesGraph proc~spacetime_vector_norm_sym4x4 spacetime_vector_norm_sym4x4 tensor tensor proc~spacetime_vector_norm_sym4x4->tensor

Compute the spacetime squared norm of a vector, using the metric given as an array of 10 components

FT 07.02.2022


Arguments

Type IntentOptional Attributes Name
double precision, intent(in) :: g4(itt:izz)

The spacetime metric, given as a 10-vector.

double precision, intent(in) :: v(it:iz)

The -vector whose norm has to be computed.

double precision, intent(out) :: norm

Spacetime norm of the vector v.


Called by

proc~~spacetime_vector_norm_sym4x4~~CalledByGraph proc~spacetime_vector_norm_sym4x4 spacetime_vector_norm_sym4x4 proc~compute_and_print_sph_variables compute_and_print_sph_variables proc~compute_and_print_sph_variables->proc~spacetime_vector_norm_sym4x4 proc~construct_particles_bin construct_particles_bin proc~construct_particles_bin->proc~spacetime_vector_norm_sym4x4 program~construct_newtonian_binary construct_newtonian_binary program~construct_newtonian_binary->proc~spacetime_vector_norm_sym4x4 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~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

  SUBROUTINE spacetime_vector_norm_sym4x4( g4, v, norm )

    !****************************************************************
    !
    !# Compute the spacetime squared norm of a vector, using the
    !  metric given as an array of 10 components
    !
    !  FT 07.02.2022
    !
    !****************************************************************

    USE tensor,    ONLY: itt, itx, ity, itz, ixx, ixy, ixz, iyy, iyz, izz, &
                         it, ix, iy, iz, n_sym4x4

    IMPLICIT NONE

    DOUBLE PRECISION, INTENT(IN):: g4(itt:izz)
    !# The \(4\times 4\) spacetime metric, given as a 10-vector.
    DOUBLE PRECISION, INTENT(IN):: v(it:iz)
    !# The \(4\)-vector whose norm has to be computed.
    DOUBLE PRECISION, INTENT(OUT):: norm
    !! Spacetime norm of the vector v.

    IF( SIZE(g4) /= n_sym4x4 )THEN
      PRINT *, "** ERROR in spacetime_vector_norm_sym4x4 in MODULE utility.", &
               " This subroutine needs a symmetric matrix with 10 components,",&
               " and a ", SIZE(g4), "component matrix was given instead."
      STOP
    ENDIF

    norm= g4(itt)*v(it)*v(it)     + two*g4(itx)*v(it)*v(ix) &
        + two*g4(ity)*v(it)*v(iy) + two*g4(itz)*v(it)*v(iz) &
        + g4(ixx)*v(ix)*v(ix)     + two*g4(ixy)*v(ix)*v(iy) &
        + two*g4(ixz)*v(ix)*v(iz) + g4(iyy)*v(iy)*v(iy)     &
        + two*g4(iyz)*v(iy)*v(iz) + g4(izz)*v(iz)*v(iz)

  END SUBROUTINE spacetime_vector_norm_sym4x4