parent
6a0593bf9e
commit
1ad8464821
|
@ -1,7 +1,7 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief all DAMASK files without solver
|
||||
!> @details List of files needed by MSC.Marc, Abaqus/Explicit, and Abaqus/Standard
|
||||
!> @details List of files needed by MSC.Marc and Abaqus/Standard
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
#include "IO.f90"
|
||||
#include "numerics.f90"
|
||||
|
@ -15,7 +15,6 @@
|
|||
#include "rotations.f90"
|
||||
#include "FEsolving.f90"
|
||||
#include "element.f90"
|
||||
#include "mesh_base.f90"
|
||||
#include "HDF5_utilities.f90"
|
||||
#include "results.f90"
|
||||
#include "geometry_plastic_nonlocal.f90"
|
||||
|
|
|
@ -20,7 +20,6 @@ module mesh
|
|||
use FEsolving
|
||||
use FEM_Zoo
|
||||
use prec
|
||||
use mesh_base
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
@ -53,18 +52,6 @@ module mesh
|
|||
PetscInt, dimension(:), allocatable, public, protected :: &
|
||||
mesh_boundaries
|
||||
|
||||
|
||||
type, public, extends(tMesh) :: tMesh_FEM
|
||||
|
||||
|
||||
contains
|
||||
procedure, pass(self) :: tMesh_FEM_init
|
||||
generic, public :: init => tMesh_FEM_init
|
||||
end type tMesh_FEM
|
||||
|
||||
type(tMesh_FEM), public, protected :: theMesh
|
||||
|
||||
|
||||
public :: &
|
||||
mesh_init, &
|
||||
mesh_FEM_build_ipVolumes, &
|
||||
|
@ -72,24 +59,6 @@ module mesh
|
|||
|
||||
contains
|
||||
|
||||
subroutine tMesh_FEM_init(self,dimen,order,nodes)
|
||||
|
||||
integer, intent(in) :: dimen
|
||||
integer, intent(in) :: order
|
||||
real(pReal), intent(in), dimension(:,:) :: nodes
|
||||
class(tMesh_FEM) :: self
|
||||
|
||||
if (dimen == 2) then
|
||||
if (order == 1) call self%tMesh%init('mesh',1,nodes)
|
||||
if (order == 2) call self%tMesh%init('mesh',2,nodes)
|
||||
elseif(dimen == 3) then
|
||||
if (order == 1) call self%tMesh%init('mesh',6,nodes)
|
||||
if (order == 2) call self%tMesh%init('mesh',8,nodes)
|
||||
endif
|
||||
|
||||
end subroutine tMesh_FEM_init
|
||||
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief initializes the mesh by calling all necessary private routines the mesh module
|
||||
|
@ -217,8 +186,6 @@ subroutine mesh_init
|
|||
forall (j = 1:mesh_NcpElems) FEsolving_execIP(2,j) = FE_Nips(FE_geomtype(mesh_element(2,j))) ! ...up to own IP count for each element
|
||||
|
||||
allocate(mesh_node0(3,mesh_Nnodes),source=0.0_pReal)
|
||||
call theMesh%init(dimplex,integrationOrder,mesh_node0)
|
||||
call theMesh%setNelems(mesh_NcpElems)
|
||||
|
||||
call discretization_init(mesh_element(3,:),mesh_element(4,:),&
|
||||
reshape(mesh_ipCoordinates,[3,mesh_maxNips*mesh_NcpElems]), &
|
||||
|
|
|
@ -7,7 +7,6 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
module mesh
|
||||
use prec
|
||||
use mesh_base
|
||||
use geometry_plastic_nonlocal
|
||||
use discretization
|
||||
use math
|
||||
|
|
|
@ -1,74 +0,0 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @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 Sets up the mesh for the solvers MSC.Marc,FEM, Abaqus and the spectral solver
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module mesh_base
|
||||
|
||||
use prec
|
||||
use element
|
||||
|
||||
implicit none
|
||||
|
||||
!---------------------------------------------------------------------------------------------------
|
||||
!> Properties of a whole mesh (consisting of one type of elements)
|
||||
!---------------------------------------------------------------------------------------------------
|
||||
type, public :: tMesh
|
||||
type(tElement) :: &
|
||||
elem
|
||||
real(pReal), dimension(:,:), allocatable, public :: &
|
||||
ipVolume, & !< volume associated with each IP (initially!)
|
||||
node_0, & !< node x,y,z coordinates (initially)
|
||||
node !< node x,y,z coordinates (deformed)
|
||||
integer(pInt), dimension(:,:), allocatable, public :: &
|
||||
cellnodeParent !< cellnode's parent element ID, cellnode's intra-element ID
|
||||
character(pStringLen) :: type = "n/a"
|
||||
integer(pInt) :: &
|
||||
Nnodes, & !< total number of nodes in mesh
|
||||
Nelems = -1_pInt, &
|
||||
elemType, &
|
||||
Ncells, &
|
||||
nIPneighbors, &
|
||||
NcellNodes
|
||||
integer(pInt), dimension(:,:), allocatable, public :: &
|
||||
connectivity
|
||||
contains
|
||||
procedure, pass(self) :: tMesh_base_init
|
||||
procedure :: setNelems => tMesh_base_setNelems ! not needed once we compute the cells from the connectivity
|
||||
generic, public :: init => tMesh_base_init
|
||||
end type tMesh
|
||||
|
||||
contains
|
||||
|
||||
subroutine tMesh_base_init(self,meshType,elemType,nodes)
|
||||
|
||||
class(tMesh) :: self
|
||||
character(len=*), intent(in) :: meshType
|
||||
integer(pInt), intent(in) :: elemType
|
||||
real(pReal), dimension(:,:), intent(in) :: nodes
|
||||
|
||||
write(6,'(/,a)') ' <<<+- mesh_base_init -+>>>'
|
||||
|
||||
write(6,*)' mesh type ',meshType
|
||||
write(6,*)' # node ',size(nodes,2)
|
||||
|
||||
self%type = meshType
|
||||
call self%elem%init(elemType)
|
||||
self%node_0 = nodes
|
||||
self%nNodes = size(nodes,2)
|
||||
|
||||
end subroutine tMesh_base_init
|
||||
|
||||
|
||||
subroutine tMesh_base_setNelems(self,Nelems)
|
||||
|
||||
class(tMesh) :: self
|
||||
integer(pInt), intent(in) :: Nelems
|
||||
|
||||
self%Nelems = Nelems
|
||||
|
||||
end subroutine tMesh_base_setNelems
|
||||
|
||||
end module mesh_base
|
|
@ -9,7 +9,6 @@ module mesh
|
|||
use IO
|
||||
use prec
|
||||
use math
|
||||
use mesh_base
|
||||
use DAMASK_interface
|
||||
use IO
|
||||
use debug
|
||||
|
|
Loading…
Reference in New Issue