invert_sym3x3 Subroutine

public subroutine invert_sym3x3(A, iA)

Uses

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

Invert a symemtric matrix stored as a -vector

FT 25.04.2022


Arguments

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

The symmetric matrix, given as a -vector.

double precision, intent(out) :: iA(n_sym3x3)

Inverse of the symmetric matrix, given as input.


Calls

proc~~invert_sym3x3~~CallsGraph proc~invert_sym3x3 invert_sym3x3 invert_3x3_matrix invert_3x3_matrix proc~invert_sym3x3->invert_3x3_matrix proc~mat2vec_sym3x3 mat2vec_sym3x3 proc~invert_sym3x3->proc~mat2vec_sym3x3 proc~vec2mat_sym3x3 vec2mat_sym3x3 proc~invert_sym3x3->proc~vec2mat_sym3x3

Contents

Source Code


Variables

Type Visibility Attributes Name Initial
double precision, public :: Amat(3,3)

The symmetric matrix as a matrix

double precision, public :: iAmat(3,3)

The inverse of the symmetric matrix, as a matrix


Source Code

  SUBROUTINE invert_sym3x3( A, iA )

    !****************************************************************
    !
    !# Invert a \(3\times 3\) symemtric matrix stored as a \(6\)-vector
    !  @note The inverse (and the adjugate) of a symmetric matrix
    !        is symmetric
    !
    !  FT 25.04.2022
    !
    !****************************************************************

    USE tensor, ONLY: n_sym3x3
    USE matrix, ONLY: invert_3x3_matrix

    IMPLICIT NONE

    DOUBLE PRECISION, INTENT(IN):: A(:)
    !# The \(3\times 3\) symmetric matrix, given as a \(6\)-vector.
    DOUBLE PRECISION, INTENT(OUT):: iA(n_sym3x3)
    !# Inverse of the \(3\times 3\) symmetric matrix, given as input.

    DOUBLE PRECISION:: Amat(3,3)
    !! The \(3\times 3\) symmetric matrix as a matrix
    DOUBLE PRECISION:: iAmat(3,3)
    !! The inverse of the \(3\times 3\) symmetric matrix, as a matrix

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

    CALL vec2mat_sym3x3(A,Amat)

    CALL invert_3x3_matrix(Amat,iAmat)

    CALL mat2vec_sym3x3(iAmat,iA)

  END SUBROUTINE invert_sym3x3