tem_matrix_module Module

Contains data_types and function for matrix operations


Uses

  • module~~tem_matrix_module~~UsesGraph module~tem_matrix_module tem_matrix_module module~tem_float_module tem_float_module module~tem_matrix_module->module~tem_float_module module~tem_dyn_array_module tem_dyn_array_module module~tem_matrix_module->module~tem_dyn_array_module module~tem_aux_module tem_aux_module module~tem_matrix_module->module~tem_aux_module module~env_module env_module module~tem_matrix_module->module~env_module module~tem_logging_module tem_logging_module module~tem_matrix_module->module~tem_logging_module module~tem_grow_array_module tem_grow_array_module module~tem_matrix_module->module~tem_grow_array_module module~tem_debug_module tem_debug_module module~tem_matrix_module->module~tem_debug_module module~tem_param_module tem_param_module module~tem_matrix_module->module~tem_param_module module~tem_float_module->module~env_module module~tem_dyn_array_module->module~env_module module~tem_aux_module->module~env_module module~tem_aux_module->module~tem_logging_module module~aotus_module aotus_module module~tem_aux_module->module~aotus_module module~tem_revision_module tem_revision_module module~tem_aux_module->module~tem_revision_module module~tem_comm_env_module tem_comm_env_module module~tem_aux_module->module~tem_comm_env_module module~flu_binding flu_binding module~tem_aux_module->module~flu_binding module~aot_table_module aot_table_module module~tem_aux_module->module~aot_table_module module~tem_tools_module tem_tools_module module~tem_aux_module->module~tem_tools_module module~tem_lua_requires_module tem_lua_requires_module module~tem_aux_module->module~tem_lua_requires_module mpi mpi module~tem_aux_module->mpi module~env_module->module~aotus_module module~env_module->module~flu_binding iso_fortran_env iso_fortran_env module~env_module->iso_fortran_env module~env_module->mpi module~tem_logging_module->module~env_module module~tem_logging_module->module~aotus_module module~tem_logging_module->module~aot_table_module module~tem_grow_array_module->module~env_module module~tem_debug_module->module~env_module module~tem_debug_module->module~tem_logging_module module~tem_debug_module->module~flu_binding module~tem_debug_module->module~aot_table_module module~tem_debug_module->module~tem_tools_module module~tem_param_module->module~env_module module~tem_comm_env_module->mpi module~tem_tools_module->module~env_module module~tem_lua_requires_module->module~env_module module~tem_lua_requires_module->module~aotus_module module~tem_lua_requires_module->module~flu_binding module~tem_lua_requires_module->module~aot_table_module iso_c_binding iso_c_binding module~tem_lua_requires_module->iso_c_binding

Used by

  • module~~tem_matrix_module~~UsedByGraph module~tem_matrix_module tem_matrix_module module~tem_math_module tem_math_module module~tem_math_module->module~tem_matrix_module module~tem_plane_module tem_plane_module module~tem_plane_module->module~tem_math_module module~tem_triangle_module tem_triangle_module module~tem_plane_module->module~tem_triangle_module module~tem_surfacedata_module tem_surfaceData_module module~tem_surfacedata_module->module~tem_math_module module~tem_stlb_io_module tem_stlb_io_module module~tem_surfacedata_module->module~tem_stlb_io_module module~tem_triangle_module->module~tem_math_module module~tem_line_module tem_line_module module~tem_line_module->module~tem_math_module module~tem_line_module->module~tem_triangle_module module~tem_stlb_io_module->module~tem_math_module module~tem_box_module tem_box_module module~tem_box_module->module~tem_plane_module module~tem_shape_module tem_shape_module module~tem_shape_module->module~tem_triangle_module module~tem_canonicalnd_module tem_canonicalND_module module~tem_shape_module->module~tem_canonicalnd_module module~tem_stl_module tem_stl_module module~tem_shape_module->module~tem_stl_module module~tem_cylinder_module tem_cylinder_module module~tem_shape_module->module~tem_cylinder_module module~tem_canonicalnd_module->module~tem_plane_module module~tem_canonicalnd_module->module~tem_line_module module~tem_canonicalnd_module->module~tem_box_module module~tem_stl_module->module~tem_triangle_module module~tem_stl_module->module~tem_stlb_io_module module~tem_cylinder_module->module~tem_line_module module~hvs_ascii_module hvs_ascii_module module~hvs_ascii_module->module~tem_shape_module module~hvs_output_module hvs_output_module module~hvs_output_module->module~tem_shape_module module~tem_spatial_module tem_spatial_module module~tem_spatial_module->module~tem_shape_module module~tem_spatial_module->module~tem_canonicalnd_module module~tem_tracking_module tem_tracking_module module~tem_tracking_module->module~tem_shape_module module~tem_subtree_module tem_subTree_module module~tem_subtree_module->module~tem_shape_module module~tem_spacetime_fun_module tem_spacetime_fun_module module~tem_spacetime_fun_module->module~tem_shape_module module~tem_convergence_module tem_convergence_module module~tem_convergence_module->module~tem_shape_module

Contents


Variables

TypeVisibilityAttributesNameInitial
integer, private, parameter:: maxIntp_order =2
integer, private, parameter, dimension(maxIntp_order):: nCoeffs_1D =(/2, 3/)

For 1D stencil, 2 unknown coeffs: p(x)=a0+a1 x for linear 1st order interpolation 3 unknown coeffs: p(x)=a0+a1 x+a2 x^2 for quadratic 2nd order interpolation

integer, private, parameter, dimension(maxIntp_order):: nCoeffs_2D =(/3, 6/)

For 2D stencil, 3 unknown coeffs for linear 1st order interpolation: p(x,y)=a0+a1 x+a2 y 6 unknown coeffs for quadratic 2nd order interpolation: p(x,y)=a0+a1 x+a2 y+a3 x^2+a4 y^2+ a5 xy

integer, private, parameter, dimension(maxIntp_order):: nCoeffs_3D =(/4, 10/)

For 3D stencil, 4 unknown coeffs for linear 1st order interpolation: p(x,y,z)=a0+a1 x+a2 y+a3 z 10 unknown coeffs for quadratic 2nd order interpolation: p(x,y,z)=a0+a1 x+a2 y+a3 z+a4 x^2+a5 y^2+ a6 z^2+ a7 xy + a8 yz + a9 zx


Interfaces

public interface init

initialize the dynamic array

  • private subroutine init_ga_matrix(me, length)

    Arguments

    TypeIntentOptionalAttributesName
    type(grw_matrixarray_type), intent(out) :: me
    integer, intent(in), optional :: length

public interface truncate

truncate the array, meaning cut off the trailing empty entries

public interface empty

empty the entries without changing arrays

public interface destroy

destroy the dynamic array

public interface placeat

insert an element at a given position

  • private subroutine placeat_ga_matrix(me, val, pos, length)

    adds the value to a given position inside the growing array.

    Read more…

    Arguments

    TypeIntentOptionalAttributesName
    type(grw_matrixarray_type) :: me
    type(tem_matrix_type), intent(in) :: val
    integer, intent(in) :: pos
    integer, intent(in), optional :: length

    optional length to expand the array

  • private subroutine placeat_ga_matrix_vec(me, val, pos, length)

    adds the values starting from a given position inside the growing array.

    Read more…

    Arguments

    TypeIntentOptionalAttributesName
    type(grw_matrixarray_type) :: me
    type(tem_matrix_type), intent(in) :: val(:)
    integer, intent(in) :: pos
    integer, intent(in), optional :: length

    optional length to expand the array

public interface append

append a value to the dynamic array and return its position.

private interface expand

increase the size of the container for the array.

  • private subroutine expand_ga_matrix(me, pos, length)

    Arguments

    TypeIntentOptionalAttributesName
    type(grw_matrixarray_type) :: me
    integer, intent(in), optional :: pos
    integer, intent(in), optional :: length

    optional length to expand the array

private interface init

  • private subroutine init_intpMatrixLSF(me, length, nDims, order)

    This routine initialize interpolation matrix for least square fit

    Arguments

    TypeIntentOptionalAttributesName
    type(tem_intpMatrixLSF_type), intent(out) :: me
    integer, intent(in) :: length
    integer, intent(in) :: nDims
    integer, intent(in) :: order

private interface append

  • private subroutine append_intpMatrixLSF(me, order, QQ, nDims, nSources, cxDirRK, neighDir, pos, success)

    This routine builds up the matrix for least square fit used in linear and quadratic interpolation.

    Read more…

    Arguments

    TypeIntentOptionalAttributesName
    type(tem_intpMatrixLSF_type), intent(inout) :: me

    intpMatrix for LSF fill

    integer, intent(inout) :: order

    interpolation order calculated for current element depending on nSources if quadratic LSF matrix is singular fall back to linear

    integer, intent(in) :: QQ

    Number of stencil directions

    integer, intent(in) :: nDims

    Number of dimensions

    integer, intent(in) :: nSources

    Number of sources from coarser found

    real(kind=rk), intent(in) :: cxDirRK(3,QQ)

    Stencil directions

    integer, intent(in) :: neighDir(nSources)

    direction in which sources are found

    integer, intent(out) :: pos

    Pointer to position of interpolation matrix in growing array of matrix

    logical, intent(out) :: success

    success if false if matrix is singular reduce interpolation order

private interface truncate

private interface destroy

private interface assignment(=)

  • private subroutine copy_matrix(left, right)

    This routine provides assignment operator of tem_matrix_type

    Arguments

    TypeIntentOptionalAttributesName
    type(tem_matrix_type), intent(out) :: left
    type(tem_matrix_type), intent(in) :: right

Derived Types

type, public :: tem_matrix_type

This derived type encapsulates the definition of the matrix

Components

TypeVisibilityAttributesNameInitial
real(kind=rk), private, allocatable:: A(:,:)

inverted matrix to solve linear system of equation

integer, private :: nEntries(2)

how many entries are in the 2d matrix?

type, public :: tem_intpMatrixLSF_type

This derived type encapsulates the definition of least square fit matrix for interpolation method which is required for every combination of available nSourceFromCoarser

Components

TypeVisibilityAttributesNameInitial
type(grw_matrixarray_type), private :: matArray
type(dyn_intarray_type), private :: ID

Unique hash ID to identify different combination of available nSourceFromCoarser

integer, private :: nCoeffs

nCoeffs required for least square fit. Depends on nDims and order of interpolation

type(grw_logicalarray_type), private :: isInvertible

For every matrix in matArray, store if its invertible or not to avoid rebuilding singular matrix

type, private :: grw_matrixarray_type

growing array type for type(tem_matrix_type)

Components

TypeVisibilityAttributesNameInitial
integer, private :: nvals =0
integer, private :: containersize =0
type(tem_matrix_type), private, allocatable:: val(:)

Functions

public function invert_matrix(A, errCode) result(Ainv)

Returns the inverse of a matrix calculated by finding the LU decomposition. Depends on LAPACK.

Arguments

TypeIntentOptionalAttributesName
real(kind=rk), intent(in), dimension(:,:):: A

Matrix to invert

integer, intent(out), optional :: errCode

If error code is present return error code and do not abort

Return Value real(kind=rk),dimension(size(A,1),size(A,2))

inverse of A

private pure function polyQuadratic_1D(cxDir) result(phi)

This function returns matrix entries for quadratic polynomial for 1D stencil

Arguments

TypeIntentOptionalAttributesName
real(kind=rk), intent(in) :: cxDir(3)

Return Value real(kind=rk)(3)

private pure function polyQuadratic_2D(cxDir) result(phi)

This function returns matrix entries for quadratic polynomial for 2D stencil

Arguments

TypeIntentOptionalAttributesName
real(kind=rk), intent(in) :: cxDir(3)

Return Value real(kind=rk)(6)

private pure function polyQuadratic_3D(cxDir) result(phi)

This function returns matrix entries for quadratic polynomial for 3D stencil

Arguments

TypeIntentOptionalAttributesName
real(kind=rk), intent(in) :: cxDir(3)

Return Value real(kind=rk)(10)

private pure function polyLinear_1D(cxDir) result(phi)

This function returns matrix entries for Linear polynomial for 1D stencil

Arguments

TypeIntentOptionalAttributesName
real(kind=rk), intent(in) :: cxDir(3)

Return Value real(kind=rk)(2)

private pure function polyLinear_2D(cxDir) result(phi)

This function returns matrix entries for Linear polynomial for 2D stencil

Arguments

TypeIntentOptionalAttributesName
real(kind=rk), intent(in) :: cxDir(3)

Return Value real(kind=rk)(3)

private pure function polyLinear_3D(cxDir) result(phi)

This function returns matrix entries for Linear polynomial for 3D stencil

Arguments

TypeIntentOptionalAttributesName
real(kind=rk), intent(in) :: cxDir(3)

Return Value real(kind=rk)(4)


Subroutines

public subroutine tem_matrix_dump(me, outUnit)

Arguments

TypeIntentOptionalAttributesName
type(tem_matrix_type), intent(in) :: me
integer, intent(in) :: outUnit

private subroutine init_ga_matrix(me, length)

Arguments

TypeIntentOptionalAttributesName
type(grw_matrixarray_type), intent(out) :: me
integer, intent(in), optional :: length

private subroutine destroy_ga_matrix(me)

Arguments

TypeIntentOptionalAttributesName
type(grw_matrixarray_type), intent(inout) :: me

private subroutine truncate_ga_matrix(me)

Arguments

TypeIntentOptionalAttributesName
type(grw_matrixarray_type) :: me

private subroutine empty_ga_matrix(me)

Arguments

TypeIntentOptionalAttributesName
type(grw_matrixarray_type) :: me

private subroutine placeat_ga_matrix(me, val, pos, length)

adds the value to a given position inside the growing array.

Read more…

Arguments

TypeIntentOptionalAttributesName
type(grw_matrixarray_type) :: me
type(tem_matrix_type), intent(in) :: val
integer, intent(in) :: pos
integer, intent(in), optional :: length

optional length to expand the array

private subroutine placeat_ga_matrix_vec(me, val, pos, length)

adds the values starting from a given position inside the growing array.

Read more…

Arguments

TypeIntentOptionalAttributesName
type(grw_matrixarray_type) :: me
type(tem_matrix_type), intent(in) :: val(:)
integer, intent(in) :: pos
integer, intent(in), optional :: length

optional length to expand the array

private subroutine append_ga_matrix(me, val, length)

Arguments

TypeIntentOptionalAttributesName
type(grw_matrixarray_type) :: me
type(tem_matrix_type), intent(in) :: val
integer, intent(in), optional :: length

optional length to expand the array

private subroutine append_ga_matrix_vec(me, val, length)

Arguments

TypeIntentOptionalAttributesName
type(grw_matrixarray_type) :: me
type(tem_matrix_type), intent(in) :: val(:)
integer, intent(in), optional :: length

optional length to expand the array

private subroutine expand_ga_matrix(me, pos, length)

Arguments

TypeIntentOptionalAttributesName
type(grw_matrixarray_type) :: me
integer, intent(in), optional :: pos
integer, intent(in), optional :: length

optional length to expand the array

private subroutine init_intpMatrixLSF(me, length, nDims, order)

This routine initialize interpolation matrix for least square fit

Arguments

TypeIntentOptionalAttributesName
type(tem_intpMatrixLSF_type), intent(out) :: me
integer, intent(in) :: length
integer, intent(in) :: nDims
integer, intent(in) :: order

private subroutine append_intpMatrixLSF(me, order, QQ, nDims, nSources, cxDirRK, neighDir, pos, success)

This routine builds up the matrix for least square fit used in linear and quadratic interpolation.

Read more…

Arguments

TypeIntentOptionalAttributesName
type(tem_intpMatrixLSF_type), intent(inout) :: me

intpMatrix for LSF fill

integer, intent(inout) :: order

interpolation order calculated for current element depending on nSources if quadratic LSF matrix is singular fall back to linear

integer, intent(in) :: QQ

Number of stencil directions

integer, intent(in) :: nDims

Number of dimensions

integer, intent(in) :: nSources

Number of sources from coarser found

real(kind=rk), intent(in) :: cxDirRK(3,QQ)

Stencil directions

integer, intent(in) :: neighDir(nSources)

direction in which sources are found

integer, intent(out) :: pos

Pointer to position of interpolation matrix in growing array of matrix

logical, intent(out) :: success

success if false if matrix is singular reduce interpolation order

private subroutine build_matrixLSF_quadIntp(me, QQ, nDims, nSources, cxDirRK, neighDir, nCoeffs, success)

This routine builds up the matrix for least square fit used in quadratic interpolation. We extract momentum information completely on the view of the source coordinate system Set the right hand side of the equation system Solve the problem, where b = rhs, x = coefficients Ax = b overdetermined, solve the least Square fit problem (A^T)Ax = (A^T)b x = ((A^T)A)^-1(A^T)b Solve linear system of equation with inverted matrix. Size of matrix: (nCoeffs, QQ) matrix_LSF = ((A^T)A)^-1(A^T)

Arguments

TypeIntentOptionalAttributesName
type(tem_matrix_type), intent(out) :: me

Matrix to fill

integer, intent(in) :: QQ

Number of stencil directions

integer, intent(in) :: nDims

Number of dimensions

integer, intent(in) :: nSources

Number of sources from coarser found

real(kind=rk), intent(in) :: cxDirRK(3,QQ)

Stencil directions

integer, intent(in) :: neighDir(nSources)

direction in which sources are found

integer, intent(in) :: nCoeffs

nUnknown coeffs

logical, intent(out) :: success

success if false if matrix is singular reduce interpolation order

private subroutine build_matrixLSF_linearIntp(me, QQ, nDims, nSources, cxDirRK, neighDir, nCoeffs, success)

This routine builds up the matrix for least square fit used in linear interpolation.

Arguments

TypeIntentOptionalAttributesName
type(tem_matrix_type), intent(out) :: me

Matrix to fill

integer, intent(in) :: QQ

Number of stencil directions

integer, intent(in) :: nDims

Number of dimensions

integer, intent(in) :: nSources

Number of sources from coarser found

real(kind=rk), intent(in) :: cxDirRK(3,QQ)

Stencil directions

integer, intent(in) :: neighDir(nSources)

direction in which sources are found

integer, intent(in) :: nCoeffs

nUnknown coeffs

logical, intent(out) :: success

success if false if matrix is singular reduce interpolation order

private subroutine truncate_intpMatrixLSF(me)

Arguments

TypeIntentOptionalAttributesName
type(tem_intpMatrixLSF_type), intent(inout) :: me

private subroutine destroy_intpMatrixLSF(me)

Arguments

TypeIntentOptionalAttributesName
type(tem_intpMatrixLSF_type), intent(inout) :: me

private subroutine copy_matrix(left, right)

This routine provides assignment operator of tem_matrix_type

Arguments

TypeIntentOptionalAttributesName
type(tem_matrix_type), intent(out) :: left
type(tem_matrix_type), intent(in) :: right

private subroutine alloc_matrix(me, dim1, dim2)

This routine allocates matrix with given dimentions

Arguments

TypeIntentOptionalAttributesName
type(tem_matrix_type) :: me
integer, intent(in) :: dim1
integer, intent(in) :: dim2