lorentz_boost Derived Type

type, public, extends(lorentz_transformation) :: lorentz_boost

TYPE representing a Lorentz boost


Inherits

type~~lorentz_boost~~InheritsGraph type~lorentz_boost lorentz_boost type~lorentz_transformation lorentz_transformation type~lorentz_boost->type~lorentz_transformation

Contents

Source Code


Components

Type Visibility Attributes Name Initial
double precision, private, DIMENSION(n_sym3x3) :: inv_lambda_s

Spatial part of the inverse Lorentz boost

double precision, private :: lambda

Lorentz factor

double precision, private, DIMENSION(n_sym3x3) :: lambda_s

Spatial part of the Lorentz boost

double precision, private, DIMENSION(3) :: p

Spatial vector equal to

double precision, private, DIMENSION(3) :: v

Spatial velocity that determines the boost

double precision, private :: v_speed

Euclidean norm of v (its speed)


Constructor

public interface lorentz_boost

  • public module function construct_boost(v) result(boost)

    Arguments

    Type IntentOptional Attributes Name
    double precision, intent(in), DIMENSION(3) :: v

    Spatial velocity that determines the boost

    Return Value type(lorentz_boost)

    lorentz_boost object to be constructed

  • public module function construct_boost_components(vx, vy, vz) result(boost)

    Arguments

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

    component of the spatial velocity that determines the boost

    double precision, intent(in) :: vy

    component of the spatial velocity that determines the boost

    double precision, intent(in) :: vz

    component of the spatial velocity that determines the boost

    Return Value type(lorentz_boost)

    lorentz_boost object to be constructed


Type-Bound Procedures

generic, public :: apply_as_congruence => apply_as_congruence_to_tensor, apply_as_congruence_to_symrank2_tensor

Generic procedure to apply the lorentz_transformation as a congruence

procedure, public, NON_OVERRIDABLE :: apply_as_congruence_to_symrank2_tensor

Action of the lorentz_transformation as a congruence on a -vector storing the components of a symmetric, purely covariant, tensor

  • interface

    public module function apply_as_congruence_to_symrank2_tensor(this, t) result(transformed_t)

    Action of the lorentz_transformation on a -vector

    Arguments

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

    lorentz_transformation object to apply

    double precision, intent(in), DIMENSION(n_sym4x4) :: t

    -vector storing the components of the symmetric tensor to be boosted

    Return Value double precision, DIMENSION(n_sym4x4)

    -vector storing the components of the boosted symmetric tensor

procedure, public, NON_OVERRIDABLE :: apply_as_congruence_to_tensor

Action of the lorentz_transformation as a congruence on a generic purely covariant tensor

  • interface

    public module function apply_as_congruence_to_tensor(this, t) result(transformed_t)

    Action of the lorentz_transformation on a -vector

    Arguments

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

    lorentz_transformation object to apply

    double precision, intent(in), DIMENSION(4,4) :: t(0:3,0:3)

    tensor to be boosted

    Return Value double precision, DIMENSION(4,4), (0:3,0:3)

    Boosted tensor

generic, public :: apply_as_similarity => apply_as_similarity_to_tensor, apply_as_similarity_to_symrank2_tensor

Generic procedure to apply the lorentz_transformation as a similarity

procedure, public, NON_OVERRIDABLE :: apply_as_similarity_to_symrank2_tensor

Action of the lorentz_transformation as a similarity on a -vector storing the components of a symmetric tensor

  • interface

    public module function apply_as_similarity_to_symrank2_tensor(this, t) result(transformed_t)

    Action of the lorentz_transformation on a -vector

    Arguments

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

    lorentz_transformation object to apply

    double precision, intent(in), DIMENSION(n_sym4x4) :: t

    -vector storing the components of the symmetric tensor to be boosted

    Return Value double precision, DIMENSION(n_sym4x4)

    -vector storing the components of the boosted symmetric tensor

procedure, public, NON_OVERRIDABLE :: apply_as_similarity_to_tensor

Action of the lorentz_transformation as a similarity on a generic tensor

  • interface

    public module function apply_as_similarity_to_tensor(this, t) result(transformed_t)

    Action of the lorentz_transformation on a -vector

    Arguments

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

    lorentz_transformation object to apply

    double precision, intent(in), DIMENSION(4,4) :: t(0:3,0:3)

    tensor to be boosted

    Return Value double precision, DIMENSION(4,4), (0:3,0:3)

    Boosted tensor

procedure, public, NON_OVERRIDABLE :: apply_to_vector

Action of the lorentz_transformation on a -vector

  • interface

    public module function apply_to_vector(this, u) result(transformed_u)

    Action of the lorentz_transformation on a -vector

    Arguments

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

    lorentz_transformation object to apply

    double precision, intent(in), DIMENSION(4) :: u(0:3)

    -vector to be boosted

    Return Value double precision, DIMENSION(4), (0:3)

    Boosted -vector

procedure, public :: compute_boost_matrices

Computes the spatial part of the matrix of the Lorentz boost, and its whole matrix, starting from the vector

  • interface

    public pure module subroutine compute_boost_matrices(this, p, lambda_s, matrix)

    Compute the matrices for the lorentz_boost

    Arguments

    Type IntentOptional Attributes Name
    class(lorentz_boost), intent(inout) :: this
    double precision, intent(in), DIMENSION(3) :: p

    lambdav

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

    Spatial part of the Lorentz boost

    double precision, intent(out), DIMENSION(4,4) :: matrix(0:3,0:3)

    matrix representing the Lorentz boost

procedure, public :: get_lambda

Returns the Lorentz factor lambda

  • interface

    public pure module function get_lambda(this) result(lambda)

    Returns the Lorentz factor lambda

    Arguments

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

    lorentz_boost object owning this FUNCTION

    Return Value double precision

    Lorentz factor lambda

Source Code

  TYPE, EXTENDS(lorentz_transformation):: lorentz_boost
  !! TYPE representing a Lorentz boost

    PRIVATE

    DOUBLE PRECISION, DIMENSION(3):: v
    !! Spatial velocity that determines the boost

    DOUBLE PRECISION:: v_speed
    !! Euclidean norm of [[lorentz_boost:v]] (its speed)

    DOUBLE PRECISION:: lambda
    !! Lorentz factor

    DOUBLE PRECISION, DIMENSION(3):: p
    !! Spatial vector equal to \(\lambda \,v\)

    DOUBLE PRECISION, DIMENSION(n_sym3x3):: lambda_s
    !! Spatial part of the Lorentz boost
    DOUBLE PRECISION, DIMENSION(n_sym3x3):: inv_lambda_s
    !! Spatial part of the inverse Lorentz boost


    CONTAINS


    PROCEDURE:: compute_boost_matrices
    !# Computes the spatial part of the matrix of the Lorentz
    !  boost, and its whole matrix, starting from the vector
    !  \(p\)

    PROCEDURE, PUBLIC:: get_lambda
    !! Returns the Lorentz factor [[lorentz_boost:lambda]]


  END TYPE lorentz_boost