DAMASK_EICMD/src/discretization.f90

119 lines
4.0 KiB
Fortran
Raw Normal View History

!--------------------------------------------------------------------------------------------------
!> @brief spatial discretization
2019-06-15 19:10:43 +05:30
!> @details serves as an abstraction layer between the different solvers and DAMASK
!--------------------------------------------------------------------------------------------------
module discretization
use prec
use results
implicit none
private
2019-06-07 02:19:17 +05:30
integer, public, protected :: &
discretization_nIP, &
discretization_nElem
2019-06-07 02:19:17 +05:30
integer, public, protected, dimension(:), allocatable :: &
discretization_microstructureAt
2019-06-07 02:19:17 +05:30
real(pReal), public, protected, dimension(:,:), allocatable :: &
discretization_IPcoords0, &
discretization_IPcoords, &
2020-01-27 01:45:21 +05:30
discretization_NodeCoords0, &
discretization_NodeCoords
integer :: &
2020-03-10 02:50:33 +05:30
discretization_sharedNodesBegin
public :: &
discretization_init, &
discretization_results, &
2019-09-28 02:37:34 +05:30
discretization_setIPcoords, &
discretization_setNodeCoords
contains
2019-06-15 19:10:43 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief stores the relevant information in globally accesible variables
!--------------------------------------------------------------------------------------------------
subroutine discretization_init(microstructureAt,&
IPcoords0,NodeCoords0,&
2020-03-10 02:50:33 +05:30
sharedNodesBegin)
2019-06-15 19:10:43 +05:30
integer, dimension(:), intent(in) :: &
microstructureAt
real(pReal), dimension(:,:), intent(in) :: &
IPcoords0, &
NodeCoords0
integer, optional, intent(in) :: &
2020-06-21 02:21:00 +05:30
sharedNodesBegin !< index of first node shared among different processes (MPI)
print'(/,a)', ' <<<+- discretization init -+>>>'; flush(6)
discretization_nElem = size(microstructureAt,1)
2019-06-07 02:30:06 +05:30
discretization_nIP = size(IPcoords0,2)/discretization_nElem
discretization_microstructureAt = microstructureAt
discretization_IPcoords0 = IPcoords0
discretization_IPcoords = IPcoords0
discretization_NodeCoords0 = NodeCoords0
discretization_NodeCoords = NodeCoords0
2020-03-10 02:50:33 +05:30
if(present(sharedNodesBegin)) then
discretization_sharedNodesBegin = sharedNodesBegin
else
2020-03-10 02:50:33 +05:30
discretization_sharedNodesBegin = size(discretization_NodeCoords0,2)
endif
end subroutine discretization_init
2019-06-15 19:10:43 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief write the displacements
!--------------------------------------------------------------------------------------------------
subroutine discretization_results
2019-12-19 00:35:51 +05:30
real(pReal), dimension(:,:), allocatable :: u
call results_closeGroup(results_addGroup('current/geometry'))
2020-03-10 02:50:33 +05:30
u = discretization_NodeCoords (1:3,:discretization_sharedNodesBegin) &
- discretization_NodeCoords0(1:3,:discretization_sharedNodesBegin)
call results_writeDataset('current/geometry',u,'u_n','displacements of the nodes','m')
u = discretization_IPcoords &
- discretization_IPcoords0
call results_writeDataset('current/geometry',u,'u_p','displacements of the materialpoints','m')
2019-12-19 00:35:51 +05:30
end subroutine discretization_results
2019-06-15 19:10:43 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief stores current IP coordinates
!--------------------------------------------------------------------------------------------------
subroutine discretization_setIPcoords(IPcoords)
real(pReal), dimension(:,:), intent(in) :: IPcoords
discretization_IPcoords = IPcoords
end subroutine discretization_setIPcoords
2019-09-28 02:37:34 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief stores current IP coordinates
!--------------------------------------------------------------------------------------------------
subroutine discretization_setNodeCoords(NodeCoords)
real(pReal), dimension(:,:), intent(in) :: NodeCoords
discretization_NodeCoords = NodeCoords
end subroutine discretization_setNodeCoords
end module discretization