lorentz_transformation Derived Type

type, public, ABSTRACT :: lorentz_transformation

TYPE representing a 4D, proper, orthochronous Lorentz transformation


Inherited by

type~~lorentz_transformation~~InheritedByGraph type~lorentz_transformation lorentz_transformation type~lorentz_boost lorentz_boost type~lorentz_boost->type~lorentz_transformation type~spatial_rotation spatial_rotation type~spatial_rotation->type~lorentz_transformation

Contents


Components

Type Visibility Attributes Name Initial
double precision, private, DIMENSION(4,4) :: inv_matrix(0:3,0:3)

matrix representing the inverse Lorentz transformation

double precision, private, DIMENSION(4,4) :: matrix(0:3,0:3)

matrix representing the Lorentz transformation

double precision, private, DIMENSION(4,4) :: tr_matrix(0:3,0:3)

Transpose of the matrix representing the Lorentz transformation


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

Source Code

  TYPE, ABSTRACT:: lorentz_transformation
  !! TYPE representing a 4D, proper, orthochronous Lorentz transformation

    PRIVATE

    DOUBLE PRECISION, DIMENSION(4,4):: matrix(0:3,0:3)
    !! \(4\times 4\) matrix representing the Lorentz transformation
    DOUBLE PRECISION, DIMENSION(4,4):: inv_matrix(0:3,0:3)
    !! \(4\times 4\) matrix representing the inverse Lorentz transformation
    DOUBLE PRECISION, DIMENSION(4,4):: tr_matrix(0:3,0:3)
    !# Transpose of the \(4\times 4\) matrix representing the Lorentz
    !  transformation


    CONTAINS


    PROCEDURE, PUBLIC, NON_OVERRIDABLE:: apply_to_vector
    !! Action of the [[lorentz_transformation]] on a \(4\)-vector

    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, NON_OVERRIDABLE:: apply_as_similarity_to_tensor
    !# Action of the [[lorentz_transformation]] as a similarity on a generic
    !  tensor

    PROCEDURE, NON_OVERRIDABLE:: apply_as_similarity_to_symrank2_tensor
    !# Action of the [[lorentz_transformation]] as a similarity on a
    !  \(10\)-vector storing the components of a symmetric \(4\times 4\) tensor

    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, NON_OVERRIDABLE:: apply_as_congruence_to_tensor
    !# Action of the [[lorentz_transformation]] as a congruence on a generic
    !  purely covariant tensor

    PROCEDURE, NON_OVERRIDABLE:: apply_as_congruence_to_symrank2_tensor
    !# Action of the [[lorentz_transformation]] as a congruence on a
    !  \(10\)-vector storing the components of a symmetric, purely covariant,
    !  \(4\times 4\) tensor

  END TYPE lorentz_transformation