tem_polygon_material_module Module

This module provides a spatial function to describe a 2D polygon.

The spatial function will provide different values for points within the polygon and those outside.

A polygon is defined in the configuration by the following definition:

   -- Vector to return inside the polygon
   inval = {1.0, 0.0, 2.0}

   -- It also can be a scalar, if none is provided a scalar 1 is assumed.
   inval = 1.0 -- This is the value to return for points inside the polygon
               -- defaults to 1.

   -- Vector to return outside the polygon
   outval = {0.0, 0.0, 0.0}
   -- Needs to conform to the definition of inval, that is, if inval is scalar
   -- or not given, outval needs to be a scalar.
   -- Defaults to all zero components for a vector of the length of inval.
   -- If inval is a scalar, outval has to be given as a scalar aswell:
   outval = 0.0 -- The value to return for points outside the polygon,
                -- defaults to 0.

   -- List of 2D Points to be used as vertices for the polygon.
   -- The polygon will be closed by going from the last point back to the
   -- first one.
   vertex = { { 1.0,  0.0},
              { 0.0, -1.0},
              {-1.0,  0.0},
              { 0.0,  1.0},
            }

Uses

  • module~~tem_polygon_material_module~~UsesGraph module~tem_polygon_material_module tem_polygon_material_module module~tem_float_module tem_float_module module~tem_polygon_material_module->module~tem_float_module module~tem_aux_module tem_aux_module module~tem_polygon_material_module->module~tem_aux_module module~env_module env_module module~tem_polygon_material_module->module~env_module module~tem_logging_module tem_logging_module module~tem_polygon_material_module->module~tem_logging_module module~aot_table_module aot_table_module module~tem_polygon_material_module->module~aot_table_module module~aotus_module aotus_module module~tem_polygon_material_module->module~aotus_module module~tem_float_module->module~env_module module~tem_aux_module->module~env_module module~tem_aux_module->module~tem_logging_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~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~aot_table_module module~tem_logging_module->module~aotus_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~aot_table_module module~tem_lua_requires_module->module~aotus_module module~tem_lua_requires_module->module~flu_binding iso_c_binding iso_c_binding module~tem_lua_requires_module->iso_c_binding

Used by

  • module~~tem_polygon_material_module~~UsedByGraph module~tem_polygon_material_module tem_polygon_material_module module~tem_spatial_module tem_spatial_module module~tem_spatial_module->module~tem_polygon_material_module module~tem_spacetime_fun_module tem_spacetime_fun_module module~tem_spacetime_fun_module->module~tem_polygon_material_module module~tem_spacetime_fun_module->module~tem_spatial_module program~tem_polygon_material_test tem_polygon_material_test program~tem_polygon_material_test->module~tem_polygon_material_module module~tem_derived_module tem_derived_module module~tem_derived_module->module~tem_spacetime_fun_module module~tem_spacetime_var_module tem_spacetime_var_module module~tem_derived_module->module~tem_spacetime_var_module module~tem_variable_module tem_variable_module module~tem_derived_module->module~tem_variable_module program~tem_varsys_stfunvar_test tem_varSys_stfunVar_test program~tem_varsys_stfunvar_test->module~tem_spacetime_fun_module program~tem_varsys_stfunvar_test->module~tem_derived_module program~tem_varsys_stfunvar_test->module~tem_variable_module program~tem_varsys_derivevar_test tem_varSys_deriveVar_test program~tem_varsys_derivevar_test->module~tem_spacetime_fun_module module~tem_spacetime_var_module->module~tem_spatial_module module~tem_spacetime_var_module->module~tem_spacetime_fun_module module~tem_spacetime_var_module->module~tem_variable_module program~tem_variable_evaltype_test tem_variable_evaltype_test program~tem_variable_evaltype_test->module~tem_spacetime_fun_module program~tem_variable_evaltype_test->module~tem_derived_module program~tem_variable_evaltype_test->module~tem_variable_module program~tem_varsys_test tem_varSys_test program~tem_varsys_test->module~tem_spacetime_fun_module program~tem_varsys_test->module~tem_spacetime_var_module program~tem_varsys_test->module~tem_variable_module module~tem_varmap_module tem_varMap_module module~tem_varmap_module->module~tem_spacetime_fun_module module~tem_varmap_module->module~tem_spacetime_var_module module~tem_surfacedata_module tem_surfaceData_module module~tem_surfacedata_module->module~tem_spacetime_fun_module program~tem_spacetime_fun_test tem_spacetime_fun_test program~tem_spacetime_fun_test->module~tem_spacetime_fun_module program~tem_logical_opertor_test tem_logical_opertor_test program~tem_logical_opertor_test->module~tem_spacetime_fun_module program~tem_logical_opertor_test->module~tem_derived_module program~tem_logical_opertor_test->module~tem_variable_module program~tem_variable_extract_test tem_variable_extract_test program~tem_variable_extract_test->module~tem_spacetime_fun_module program~tem_variable_extract_test->module~tem_derived_module program~tem_variable_extract_test->module~tem_variable_module program~tem_variable_combine_test tem_variable_combine_Test program~tem_variable_combine_test->module~tem_spacetime_fun_module program~tem_variable_combine_test->module~tem_derived_module program~tem_variable_combine_test->module~tem_variable_module module~tem_face_module tem_face_module module~tem_face_module->module~tem_spacetime_fun_module module~tem_ini_condition_module tem_ini_condition_module module~tem_ini_condition_module->module~tem_spatial_module module~tem_variable_module->module~tem_spacetime_fun_module module~tem_bc_module tem_bc_module module~tem_bc_module->module~tem_spacetime_fun_module module~tem_bc_module->module~tem_varmap_module program~tem_varsys_opvar_test tem_varSys_opVar_test program~tem_varsys_opvar_test->module~tem_spacetime_fun_module program~tem_varsys_opvar_test->module~tem_derived_module program~tem_varsys_opvar_test->module~tem_variable_module program~tem_face_test~3 tem_face_test program~tem_face_test~3->module~tem_face_module module~tem_depend_module tem_depend_module module~tem_depend_module->module~tem_varmap_module module~tem_restart_module tem_restart_module module~tem_restart_module->module~tem_varmap_module module~hvs_output_module hvs_output_module module~hvs_output_module->module~tem_varmap_module program~tem_face_test tem_face_test program~tem_face_test->module~tem_face_module program~tem_face_test~2 tem_face_test program~tem_face_test~2->module~tem_face_module module~tem_tracking_module tem_tracking_module module~tem_tracking_module->module~tem_varmap_module module~tem_operation_var_module tem_operation_var_module module~tem_operation_var_module->module~tem_varmap_module module~tem_operation_var_module->module~tem_variable_module module~tem_convergence_module tem_convergence_module module~tem_convergence_module->module~tem_varmap_module

Contents


Variables

TypeVisibilityAttributesNameInitial
real(kind=rk), private, parameter:: PI =2*asin(1.0_rk)

Definition of Pi

real(kind=rk), private, parameter:: tolp =(1.0_rk+epsilon(1.0_rk))

Overestimating tolerance factor for comparisons of reals

real(kind=rk), private, parameter:: tolm =(1.0_rk-epsilon(1.0_rk))

Underestimating tolerance factor for comparisons of reals


Derived Types

type, public :: tem_polygon_material_type

Description of a 2D closed polygon.

Components

TypeVisibilityAttributesNameInitial
type(tem_polygon_vertex_type), private, allocatable:: poly_list(:)

poly_list, we can have multiply of them

type(tem_polygon_movement_type), private :: moving

Movement of each polygon

integer, private :: nPoly

Number of poly_list

real(kind=rk), private :: zmin

Extrude in z direction

real(kind=rk), private :: zmax
integer, private :: nComponents

how many components inval/outval have, they are defined as vectors and might have more than 1 entries, defined by the user in the config file!

real(kind=rk), private, allocatable:: inval(:)

Value of Material inside the polygon.

real(kind=rk), private, allocatable:: outval(:)

Value of Material outside the polygon.

type, private :: tem_polygon_vertex_type

Type to store the vertices for the polygon

Components

TypeVisibilityAttributesNameInitial
integer, private :: nVertices

Number of vertices in the polygon.

real(kind=rk), private, allocatable:: vertex(:,:)

2D Coordinates of the vertices. First index runs over number of vertices, second from 1 to 2.

type, private :: tem_polygon_movement_type

Type to store information regarding the movement of the polygon

Components

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

Linear movement of the polygon Include the values for the velocity, the first entry is the velocity in X direction, de second in Y The third one is the Z component of the velocity

real(kind=rk), private, allocatable:: sin_parameter(:)

Move the polygon with a sine fuction First and second entry belong to X direction and are the amplitude and the frequency. The third and forth entry are the devoted to the Y direction, for amplitude and the frequency respectivly.

real(kind=rk), private, allocatable:: rot_parameter(:)

Rotation of the polygon the first two entries belong to the directions, the first entry is the rot pointX and the second entry the rot pointY ) the third one is the rot_speed omega

real(kind=rk), private, allocatable:: angle_parameter(:)

chaning the angle of attack for airfoild with a sinus the first entry is the phase shift (y), the second is the amplitude and the third one is the angular velocity (omega)

character(len=labellen), private :: movement_kind

Kind of movement


Functions

public function tem_eval_polygon_material(me, coord, n) result(res)

Evaluate a list of points, and return inval for each that is within me and outval for all other points.

Arguments

TypeIntentOptionalAttributesName
type(tem_polygon_material_type), intent(in) :: me

Description of the polygon to evaluate

real(kind=rk), intent(in) :: coord(n,3)

Coordinates for which the function should be evaluated.

integer, intent(in) :: n

Number of points to get a value for.

Return Value real(kind=rk)(n,me%nComponents)

Resulting value at each point.

public function tem_eval_polygon_material_3d(me, coord, n) result(res)

Evaluate a list of points, and return inval for each that is within me and outval for all other points.

Arguments

TypeIntentOptionalAttributesName
type(tem_polygon_material_type), intent(in) :: me

Description of the polygon to evaluate

real(kind=rk), intent(in) :: coord(n,3)

Coordinates for which the function should be evaluated.

integer, intent(in) :: n

Number of points to get a value for.

Return Value real(kind=rk)(n,me%nComponents)

Resulting value at each point.

public function tem_eval_polygon_material_scal(me, coord, n) result(res)

Evaluate a list of points, and return first component of inval for each that is within me and first component of outval for all other points.

Arguments

TypeIntentOptionalAttributesName
type(tem_polygon_material_type), intent(in) :: me

Description of the polygon to evaluate

real(kind=rk), intent(in) :: coord(n,3)

Coordinates for which the function should be evaluated.

integer, intent(in) :: n

Number of points to get a value for.

Return Value real(kind=rk)(n)

Resulting value at each point.

public function tem_eval_polygon_material_scal_3d(me, coord, n) result(res)

Evaluate a list of points, and return first component of inval for each that is within me and first component of outval for all other points.

Arguments

TypeIntentOptionalAttributesName
type(tem_polygon_material_type), intent(in) :: me

Description of the polygon to evaluate

real(kind=rk), intent(in) :: coord(n,3)

Coordinates for which the function should be evaluated.

integer, intent(in) :: n

Number of points to get a value for.

Return Value real(kind=rk)(n)

Resulting value at each point.

public function tem_polygon_material_value(me, nComponents, inVal, outVal, point) result(res)

Return the material value for point, based on the position in relation to the polygon.

Read more…

Arguments

TypeIntentOptionalAttributesName
type(tem_polygon_vertex_type), intent(in) :: me

Polygon to describe the material shape.

integer, intent(in) :: nComponents
real(kind=rk), intent(in) :: inVal(nComponents)
real(kind=rk), intent(in) :: outVal(nComponents)
real(kind=rk), intent(in) :: point(:)

Point to check against the polygon.

Return Value real(kind=rk)(nComponents)

Material value at point, as defined by the polygon.

public function tem_polygon_material_movement_single(me, time, nPoint, coord) result(res)

Arguments

TypeIntentOptionalAttributesName
type(tem_polygon_material_type), intent(in) :: me
real(kind=rk), intent(in) :: time

velocity value

integer, intent(in) :: nPoint

number of points to get value for

real(kind=rk), intent(in) :: coord(nPoint,3)

points

Return Value real(kind=rk)(nPoint*me%nComponents)

List of values of each point

public function tem_polygon_material_movement_multi(me, time, nPoint, coord) result(res)

Arguments

TypeIntentOptionalAttributesName
type(tem_polygon_material_type), intent(in) :: me
real(kind=rk), intent(in) :: time

velocity value

integer, intent(in) :: nPoint

number of points to get value for

real(kind=rk), intent(in) :: coord(nPoint,3)

points

Return Value real(kind=rk)(nPoint*me%nComponents)

List of values of each point

private elemental function angle_between(va_x, va_y, vb_x, vb_y) result(angle)

Compute the angle between to vectors (they should not both be the 0 vector).

Read more…

Arguments

TypeIntentOptionalAttributesName
real(kind=rk), intent(in) :: va_x

The first vector va

real(kind=rk), intent(in) :: va_y

The first vector va

real(kind=rk), intent(in) :: vb_x

The second vector vb

real(kind=rk), intent(in) :: vb_y

The second vector vb

Return Value real(kind=rk)

The angle betweend va and vb


Subroutines

public subroutine tem_polygon_material_load(me, conf, thandle)

read list of vertices

Arguments

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

Polygon data structure to fill with information provided by the user in config.

type(flu_state) :: conf

Handle to the Lua script containing the polygon definition

integer, intent(in), optional :: thandle

Handle for the table containing the polygon definition.

public subroutine tem_polygon_material_single_load(me, conf, thandle)

get the z component

Read more…

Arguments

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

Polygon data structure to fill with information provided by the user in config.

type(flu_state) :: conf

Handle to the Lua script containing the polygon definition

integer, intent(in), optional :: thandle

Handle for the table containing the polygon definition.

public subroutine tem_polygon_material_multi_load(me, conf, thandle)

get the z component

Read more…

Arguments

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

Polygon data structure to fill with information provided by the user in config.

type(flu_state) :: conf

Handle to the Lua script containing the polygon definition

integer, intent(in), optional :: thandle

Handle for the table containing the polygon definition.

public subroutine tem_polygon_material_test_value(success)

A subroutine to test the tem_polygon_material_value function in tem_polygon_material_test.

Read more…

Arguments

TypeIntentOptionalAttributesName
logical, intent(out) :: success

Indicator if all tests were computed correctly.

public subroutine tem_polygon_material_test_angle(success)

A subroutine to test the angle_between function in tem_polygon_material_test.

Read more…

Arguments

TypeIntentOptionalAttributesName
logical, intent(out) :: success

Indicator if all tests were computed correctly.