DAMASK_EICMD/src/geometry_plastic_nonlocal.f90

148 lines
6.4 KiB
Fortran
Raw Permalink Normal View History

!--------------------------------------------------------------------------------------------------
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @author Christoph Koords, Max-Planck-Institut für Eisenforschung GmbH
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @brief Geometric information about the IP cells needed for the nonlocal
! plasticity model
!--------------------------------------------------------------------------------------------------
module geometry_plastic_nonlocal
use prec
2023-01-19 22:07:45 +05:30
use result
implicit none(type,external)
2020-01-03 00:17:48 +05:30
public
2021-06-01 20:35:13 +05:30
2020-01-03 00:17:48 +05:30
integer, protected :: &
geometry_plastic_nonlocal_nIPneighbors
2021-06-01 20:35:13 +05:30
2020-01-03 00:17:48 +05:30
integer, dimension(:,:,:,:), allocatable, protected :: &
geometry_plastic_nonlocal_IPneighborhood !< 6 or less neighboring IPs as [element ID, IP ID, face ID that point to me]
real(pREAL), dimension(:,:), allocatable, protected :: &
2019-06-06 14:38:58 +05:30
geometry_plastic_nonlocal_IPvolume0 !< volume associated with IP (initially!)
2021-06-01 20:35:13 +05:30
real(pREAL), dimension(:,:,:), allocatable, protected :: &
2019-06-06 14:38:58 +05:30
geometry_plastic_nonlocal_IParea0 !< area of interface to neighboring IP (initially!)
2021-06-01 20:35:13 +05:30
real(pREAL), dimension(:,:,:,:), allocatable, protected :: &
2019-06-06 14:38:58 +05:30
geometry_plastic_nonlocal_IPareaNormal0 !< area normal of interface to neighboring IP (initially!)
2021-06-01 20:35:13 +05:30
contains
!---------------------------------------------------------------------------------------------------
!> @brief Set the integration point (IP) neighborhood
!> @details: The IP neighborhood for element ID (last index), IP ID (second but last index) and
! face ID (second index) gives the element ID (1 @ first index), IP ID (2 @ first index)
! and face ID (3 @ first index).
! A triangle (2D) has 3 faces, a quadrilateral (2D) had 4 faces, a tetrahedron (3D) has
! 4 faces, and a hexahedron (3D) has 6 faces.
!---------------------------------------------------------------------------------------------------
2019-06-07 13:50:56 +05:30
subroutine geometry_plastic_nonlocal_setIPneighborhood(IPneighborhood)
2019-05-14 15:22:28 +05:30
integer, dimension(:,:,:,:), intent(in) :: IPneighborhood
geometry_plastic_nonlocal_IPneighborhood = IPneighborhood
geometry_plastic_nonlocal_nIPneighbors = size(IPneighborhood,2)
2021-06-01 20:35:13 +05:30
2019-05-14 15:22:28 +05:30
2019-06-07 13:50:56 +05:30
end subroutine geometry_plastic_nonlocal_setIPneighborhood
2019-05-14 15:22:28 +05:30
!---------------------------------------------------------------------------------------------------
!> @brief Set the initial volume associated with an integration point
!---------------------------------------------------------------------------------------------------
2019-06-07 13:50:56 +05:30
subroutine geometry_plastic_nonlocal_setIPvolume(IPvolume)
2019-05-14 15:22:28 +05:30
real(pREAL), dimension(:,:), intent(in) :: IPvolume
2019-05-14 15:22:28 +05:30
2019-06-06 14:38:58 +05:30
geometry_plastic_nonlocal_IPvolume0 = IPvolume
2019-05-14 15:22:28 +05:30
2019-06-07 13:50:56 +05:30
end subroutine geometry_plastic_nonlocal_setIPvolume
2019-05-14 15:22:28 +05:30
!---------------------------------------------------------------------------------------------------
!> @brief Set the initial areas of the unit triangle/unit quadrilateral/tetrahedron/hexahedron
! encompassing an integration point
!---------------------------------------------------------------------------------------------------
2019-06-07 13:50:56 +05:30
subroutine geometry_plastic_nonlocal_setIParea(IParea)
real(pREAL), dimension(:,:,:), intent(in) :: IParea
geometry_plastic_nonlocal_IParea0 = IParea
2019-06-07 13:50:56 +05:30
end subroutine geometry_plastic_nonlocal_setIParea
!---------------------------------------------------------------------------------------------------
!> @brief Set the direction normal of the areas of the triangle/quadrilateral/tetrahedron/hexahedron
! encompassing an integration point
!---------------------------------------------------------------------------------------------------
2019-06-07 13:50:56 +05:30
subroutine geometry_plastic_nonlocal_setIPareaNormal(IPareaNormal)
real(pREAL), dimension(:,:,:,:), intent(in) :: IPareaNormal
geometry_plastic_nonlocal_IPareaNormal0 = IPareaNormal
2019-06-07 13:50:56 +05:30
end subroutine geometry_plastic_nonlocal_setIPareaNormal
2019-06-07 13:50:56 +05:30
!---------------------------------------------------------------------------------------------------
2020-01-03 00:17:48 +05:30
!> @brief Free memory used by variables only needed by plastic_nonlocal
2019-06-07 13:50:56 +05:30
!---------------------------------------------------------------------------------------------------
subroutine geometry_plastic_nonlocal_disable
2022-12-07 22:59:03 +05:30
if (allocated(geometry_plastic_nonlocal_IPneighborhood)) &
2019-06-07 13:50:56 +05:30
deallocate(geometry_plastic_nonlocal_IPneighborhood)
2021-06-01 20:35:13 +05:30
2022-12-07 22:59:03 +05:30
if (allocated(geometry_plastic_nonlocal_IPvolume0)) &
2019-06-07 13:50:56 +05:30
deallocate(geometry_plastic_nonlocal_IPvolume0)
2021-06-01 20:35:13 +05:30
2022-12-07 22:59:03 +05:30
if (allocated(geometry_plastic_nonlocal_IParea0)) &
2019-06-07 13:50:56 +05:30
deallocate(geometry_plastic_nonlocal_IParea0)
2021-06-01 20:35:13 +05:30
2022-12-07 22:59:03 +05:30
if (allocated(geometry_plastic_nonlocal_IPareaNormal0)) &
2019-06-07 13:50:56 +05:30
deallocate(geometry_plastic_nonlocal_IPareaNormal0)
2021-06-01 20:35:13 +05:30
2019-06-07 13:50:56 +05:30
end subroutine geometry_plastic_nonlocal_disable
!---------------------------------------------------------------------------------------------------
2020-01-03 00:17:48 +05:30
!> @brief Write geometry data to results file
!---------------------------------------------------------------------------------------------------
2023-01-19 22:07:45 +05:30
subroutine geometry_plastic_nonlocal_result()
2021-06-01 20:35:13 +05:30
2019-10-17 11:18:57 +05:30
integer, dimension(:), allocatable :: shp
call result_openJobFile()
2019-10-17 03:51:48 +05:30
writeVolume: block
real(pREAL), dimension(:), allocatable :: temp
2019-10-17 11:18:57 +05:30
shp = shape(geometry_plastic_nonlocal_IPvolume0)
temp = reshape(geometry_plastic_nonlocal_IPvolume0,[shp(1)*shp(2)])
2023-01-19 22:07:45 +05:30
call result_writeDataset(temp,'geometry','v_0',&
'initial cell volume','m³')
2019-10-17 03:51:48 +05:30
end block writeVolume
2019-10-17 11:18:57 +05:30
writeAreas: block
real(pREAL), dimension(:,:), allocatable :: temp
2019-10-17 11:18:57 +05:30
shp = shape(geometry_plastic_nonlocal_IParea0)
temp = reshape(geometry_plastic_nonlocal_IParea0,[shp(1),shp(2)*shp(3)])
2023-01-19 22:07:45 +05:30
call result_writeDataset(temp,'geometry','a_0',&
'initial cell face area','m²')
2019-10-17 11:18:57 +05:30
end block writeAreas
writeNormals: block
real(pREAL), dimension(:,:,:), allocatable :: temp
2019-10-17 11:18:57 +05:30
shp = shape(geometry_plastic_nonlocal_IPareaNormal0)
temp = reshape(geometry_plastic_nonlocal_IPareaNormal0,[shp(1),shp(2),shp(3)*shp(4)])
2023-01-19 22:07:45 +05:30
call result_writeDataset(temp,'geometry','n_0',&
'initial cell face normals','-',transposed=.false.)
2019-10-17 11:18:57 +05:30
end block writeNormals
call result_closeJobFile()
2021-06-01 20:35:13 +05:30
2023-01-19 22:07:45 +05:30
end subroutine geometry_plastic_nonlocal_result
end module geometry_plastic_nonlocal