Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
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 |
List of values of each point
function tem_polygon_material_movement_multi(me, time, nPoint, coord) &
& result(res)
! ----------------------------------------------------------------------
type(tem_polygon_material_type), intent(in) :: me
!>velocity value
real(kind=rk), intent(in) :: time
!> number of points to get value for
integer, intent(in) :: nPoint
!> points
real(kind=rk), intent(in) :: coord(nPoint,3)
!> List of values of each point
real(kind=rk) :: res(nPoint*me%nComponents)
! ----------------------------------------------------------------------
integer :: iPoint, iPoly
integer :: iComp
type(tem_polygon_material_type) :: loc_polygon
! ----------------------------------------------------------------------
loc_polygon = me
select case(me%moving%movement_kind)
case ('lin_multi_body_2d','lin_multi_body_3d')
do iPoly = 1, me%nPoly
loc_polygon%poly_list(iPoly)%vertex(:,1) = &
& me%poly_list(iPoly)%vertex(:,1) + me%moving%lin_parameter(1) * time
loc_polygon%poly_list(iPoly)%vertex(:,2) = &
& me%poly_list(iPoly)%vertex(:,2) + me%moving%lin_parameter(2) * time
end do
case('sin_multi_body_2d', 'sin_multi_body_3d')
do ipoly = 1, me%nPoly
loc_polygon%poly_list(ipoly)%vertex(:,1) = &
& me%poly_list(ipoly)%vertex(:,1) + me%moving%sin_parameter(1) &
& *sin(2*PI*me%moving%sin_parameter(2)*time)
loc_polygon%poly_list(ipoly)%vertex(:,2) = &
& me%poly_list(ipoly)%vertex(:,2) + me%moving%sin_parameter(3) &
& *sin(2*PI*me%moving%sin_parameter(4)*time)
end do
case('rot_multi_body_2d', 'rot_multi_body_3d')
do ipoly = 1, me%nPoly
loc_polygon%poly_list(ipoly)%vertex(:,1) = &
& cos(me%moving%rot_parameter(3)*time) &
& *(me%poly_list(ipoly)%vertex(:,1) &
& - me%moving%rot_parameter(1)) &
& - sin(me%moving%rot_parameter(3)*time) &
& *(me%poly_list(ipoly)%vertex(:,2) &
& - me%moving%rot_parameter(2)) + me%moving%rot_parameter(1)
loc_polygon%poly_list(ipoly)%vertex(:,2) = &
& sin(me%moving%rot_parameter(3)*time) &
& *(me%poly_list(ipoly)%vertex(:,1) &
& - me%moving%rot_parameter(1)) &
& + cos(me%moving%rot_parameter(3)*time) &
& *(me%poly_list(ipoly)%vertex(:,2) &
& - me%moving%rot_parameter(2)) + me%moving%rot_parameter(2)
end do
case default
call tem_abort( 'ERROR in tem_polygon_material_module: UNKNOWN movement' &
& // 'for the polygon' )
end select
do icomp = 1, me%nComponents
res(iComp::me%nComponents) = me%outval(iComp)
end do
select case(me%moving%movement_kind)
case('lin_multi_body_2d', 'sin_multi_body_2d', 'rot_multi_body_2d')
do ipoly = 1, me%nPoly
do iPoint=1, nPoint
if (res((iPoint-1)*me%nComponents+1) .feq. me%outval(1) ) then
res((iPoint-1)*me%nComponents+1:iPoint*me%nComponents) &
& = tem_polygon_material_value( &
& me = loc_polygon%poly_list(iPoly), &
& nComponents = loc_polygon%nComponents, &
& inVal = loc_polygon%inVal, &
& outVal = loc_polygon%outVal, &
& point = coord(iPoint,:2) )
!else
! res = res((iPoint-1)*me%nComponents+1:iPoint*me%nComponents)=me%inval
end if
end do
end do
case('lin_multi_body_3d', 'sin_multi_body_3d', 'rot_multi_body_3d')
do ipoly = 1, me%nPoly
do iPoint=1, nPoint
if (res((iPoint-1)*me%nComponents+1) .feq. me%outval(1) ) then
if (coord(iPoint,3) >= me%zmin .and. coord(iPoint,3) <= me%zmax ) &
& then
res((iPoint-1)*me%nComponents+1:iPoint*me%nComponents) &
& = tem_polygon_material_value( &
& me = loc_polygon%poly_list(iPoly), &
& nComponents = loc_polygon%nComponents, &
& inVal = loc_polygon%inVal, &
& outVal = loc_polygon%outVal, &
& point = coord(iPoint,:2) )
else
res((iPoint-1)*me%nComponents+1:iPoint*me%nComponents) = me%outval
end if
end if
end do
end do
case default
call tem_abort( 'ERROR in tem_polygon_material_module: UNKNOWN movement' &
& // 'for the multi body polygon' )
end select
end function tem_polygon_material_movement_multi