tem_coordinate_module Module


Uses

  • module~~tem_coordinate_module~~UsesGraph module~tem_coordinate_module tem_coordinate_module module~tem_logging_module tem_logging_module module~tem_coordinate_module->module~tem_logging_module module~tem_varsys_module tem_varSys_module module~tem_coordinate_module->module~tem_varsys_module module~env_module env_module module~tem_logging_module->module~env_module module~aot_table_module aot_table_module module~tem_logging_module->module~aot_table_module module~aotus_module aotus_module module~tem_logging_module->module~aotus_module module~tem_varsys_module->module~tem_logging_module module~tem_dyn_array_module tem_dyn_array_module module~tem_varsys_module->module~tem_dyn_array_module module~tem_aux_module tem_aux_module module~tem_varsys_module->module~tem_aux_module iso_c_binding iso_c_binding module~tem_varsys_module->iso_c_binding module~treelmesh_module treelmesh_module module~tem_varsys_module->module~treelmesh_module module~tem_varsys_module->module~env_module module~tem_time_module tem_time_module module~tem_varsys_module->module~tem_time_module module~tem_varsys_module->module~aot_table_module module~tem_varsys_module->module~aotus_module module~aot_out_module aot_out_module module~tem_varsys_module->module~aot_out_module module~tem_dyn_array_module->module~env_module module~tem_aux_module->module~tem_logging_module module~tem_aux_module->module~env_module module~tem_aux_module->module~aot_table_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~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~treelmesh_module->module~tem_logging_module module~treelmesh_module->module~tem_aux_module module~treelmesh_module->module~env_module module~treelmesh_module->module~aot_table_module module~treelmesh_module->module~aotus_module module~tem_global_module tem_global_module module~treelmesh_module->module~tem_global_module module~tem_sparta_module tem_Sparta_module module~treelmesh_module->module~tem_sparta_module module~tem_topology_module tem_topology_module module~treelmesh_module->module~tem_topology_module module~tem_property_module tem_property_module module~treelmesh_module->module~tem_property_module module~treelmesh_module->module~tem_tools_module module~treelmesh_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_time_module->module~env_module module~tem_time_module->module~aot_table_module module~tem_time_module->module~aotus_module module~tem_time_module->module~aot_out_module module~tem_time_module->mpi module~tem_global_module->module~tem_logging_module module~tem_global_module->module~tem_aux_module module~tem_global_module->module~env_module module~tem_global_module->module~aot_table_module module~tem_global_module->module~aotus_module module~tem_global_module->module~aot_out_module module~tem_global_module->mpi module~tem_prophead_module tem_prophead_module module~tem_global_module->module~tem_prophead_module module~tem_sparta_module->module~tem_logging_module module~tem_sparta_module->module~tem_aux_module module~tem_sparta_module->module~env_module module~tem_sparta_module->mpi module~tem_float_module tem_float_module module~tem_sparta_module->module~tem_float_module module~tem_topology_module->module~env_module module~tem_property_module->module~env_module module~tem_property_module->mpi module~tem_property_module->module~tem_prophead_module module~tem_comm_env_module->mpi module~tem_tools_module->module~env_module module~tem_lua_requires_module->iso_c_binding module~tem_lua_requires_module->module~env_module module~tem_lua_requires_module->module~aot_table_module module~tem_lua_requires_module->module~aotus_module module~tem_lua_requires_module->module~flu_binding

Contents


Variables

TypeVisibilityAttributesNameInitial
integer, public, parameter:: xToXAxes =1

Identity transformation

integer, public, parameter:: yToXAxes =2

Transformation to transform a y axis into an x axis

integer, public, parameter:: zToXAxes =3

Transformation to transform a z axis into an x axis

integer, private, parameter:: xDir =1

constant representing the x direction

integer, private, parameter:: yDir =2

constant representing the y direction

integer, private, parameter:: zDir =3

constant representing the z direction


Derived Types

type, public :: coordRotation_type

datatype to transform varibales given in one coordinate

Read more…

Components

TypeVisibilityAttributesNameInitial
integer, private :: rotationType

The type of the rotation, see parameters above.

integer, private, allocatable:: varTransformIndices(:)

Array of integers defining how to transform the variables of your state vector. Therefore the size of this array is the number of scalar variables of your equation system.

integer, private, allocatable:: derTransformIndices(:)

Array of integers defining how to transform the derivatives of your state vector. Therefore the size of this array is the total number of derivatives you store in your state vector.


Functions

public function dirToString(direction) result(dirAsChar)

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: direction

direction to convert

Return Value character(len=1)

direction as string

private function rotateVector3(coordTrans) result(rotationIndices)

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: coordTrans

The coordinate transformation you apply.

Return Value integer(3)

Rotation indices for the given transformation

private function rotateTensor3(coordTrans) result(rotationIndices)

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: coordTrans

The coordinate transformation you apply.

Return Value integer(9)

Rotation indices for the given transformation

private function rotateVector2(coordTrans) result(rotationIndices)

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: coordTrans

The coordinate transformation you apply.

Return Value integer(2)

Rotation indices for the given transformation

private function rotateScalar() result(rotationIndices)

Arguments

None

Return Value integer(1)

The coordinate transformation you apply. Rotation indices for the given transformation


Subroutines

public subroutine initCoordinateRotation(varSys, coordTrans, derivatives, rotation, dimen)

routine to specify a coordinate transformation for the state

Read more…

Arguments

TypeIntentOptionalAttributesName
type(tem_varSys_type), intent(in) :: varSys

The variables to build the permutations for.

integer, intent(in) :: coordTrans

The rotation you want to obtain. Please have a look at the parameters of this module to find a valid input argument.

integer, intent(in) :: derivatives

The number of derivatives (already multidimensional) you need for your equation. Zero means that we calculate cell values only, one means all first derivatives and so on.

type(coordRotation_type), intent(out) :: rotation

The coordinate rotation you want to initialize.

integer, intent(in) :: dimen

The spatial dimension of the system

private subroutine appendDerivative(derivatives, coordTrans, rotation, dimen)

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: derivatives

The number of derivatives of your equation (inclunding the zeroth order derivative).

integer, intent(in) :: coordTrans

The coordinate transformation you apply.

type(coordRotation_type), intent(inout) :: rotation

The coordinate rotation you want to initialize.

integer, intent(in) :: dimen

The spatial dimension of the system

private subroutine appendRotatedVariable(nComponents, prevScalarVars, coordTrans, rotation)

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: nComponents

nComponents of variable you want to append.

integer, intent(in) :: prevScalarVars

The number of scalar variable you append before you append this variable.

integer, intent(in) :: coordTrans

The coordinate transformation you apply.

type(coordRotation_type), intent(inout) :: rotation

The coordinate rotation you want to initialize.