Merge branch 'development' of magit1.mpie.de:damask/DAMASK into development
This commit is contained in:
commit
3128297301
|
@ -15,7 +15,6 @@ module discretization
|
|||
discretization_nElem
|
||||
|
||||
integer, public, protected, dimension(:), allocatable :: &
|
||||
discretization_homogenizationAt, &
|
||||
discretization_microstructureAt
|
||||
|
||||
real(pReal), public, protected, dimension(:,:), allocatable :: &
|
||||
|
@ -38,12 +37,11 @@ contains
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief stores the relevant information in globally accesible variables
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine discretization_init(homogenizationAt,microstructureAt,&
|
||||
subroutine discretization_init(microstructureAt,&
|
||||
IPcoords0,NodeCoords0,&
|
||||
sharedNodesBegin)
|
||||
|
||||
integer, dimension(:), intent(in) :: &
|
||||
homogenizationAt, &
|
||||
microstructureAt
|
||||
real(pReal), dimension(:,:), intent(in) :: &
|
||||
IPcoords0, &
|
||||
|
@ -56,7 +54,6 @@ subroutine discretization_init(homogenizationAt,microstructureAt,&
|
|||
discretization_nElem = size(microstructureAt,1)
|
||||
discretization_nIP = size(IPcoords0,2)/discretization_nElem
|
||||
|
||||
discretization_homogenizationAt = homogenizationAt
|
||||
discretization_microstructureAt = microstructureAt
|
||||
|
||||
discretization_IPcoords0 = IPcoords0
|
||||
|
|
|
@ -53,8 +53,7 @@ subroutine discretization_grid_init(restart)
|
|||
myGrid !< domain grid of this process
|
||||
|
||||
integer, dimension(:), allocatable :: &
|
||||
microstructureAt, &
|
||||
homogenizationAt
|
||||
microstructureAt
|
||||
|
||||
integer :: &
|
||||
j, &
|
||||
|
@ -65,7 +64,7 @@ subroutine discretization_grid_init(restart)
|
|||
|
||||
write(6,'(/,a)') ' <<<+- discretization_grid init -+>>>'; flush(6)
|
||||
|
||||
call readGeom(grid,geomSize,origin,microstructureAt,homogenizationAt)
|
||||
call readGeom(grid,geomSize,origin,microstructureAt)
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! grid solver specific quantities
|
||||
|
@ -94,10 +93,8 @@ subroutine discretization_grid_init(restart)
|
|||
! general discretization
|
||||
microstructureAt = microstructureAt(product(grid(1:2))*grid3Offset+1: &
|
||||
product(grid(1:2))*(grid3Offset+grid3)) ! reallocate/shrink in case of MPI
|
||||
homogenizationAt = homogenizationAt(product(grid(1:2))*grid3Offset+1: &
|
||||
product(grid(1:2))*(grid3Offset+grid3)) ! reallocate/shrink in case of MPI
|
||||
|
||||
call discretization_init(homogenizationAt,microstructureAt, &
|
||||
call discretization_init(microstructureAt, &
|
||||
IPcoordinates0(myGrid,mySize,grid3Offset), &
|
||||
Nodes0(myGrid,mySize,grid3Offset),&
|
||||
merge((grid(1)+1) * (grid(2)+1) * (grid3+1),& ! write bottom layer
|
||||
|
@ -139,7 +136,7 @@ end subroutine discretization_grid_init
|
|||
!> @details important variables have an implicit "save" attribute. Therefore, this function is
|
||||
! supposed to be called only once!
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine readGeom(grid,geomSize,origin,microstructure,homogenization)
|
||||
subroutine readGeom(grid,geomSize,origin,microstructure)
|
||||
|
||||
integer, dimension(3), intent(out) :: &
|
||||
grid ! grid (for all processes!)
|
||||
|
@ -147,8 +144,7 @@ subroutine readGeom(grid,geomSize,origin,microstructure,homogenization)
|
|||
geomSize, & ! size (for all processes!)
|
||||
origin ! origin (for all processes!)
|
||||
integer, dimension(:), intent(out), allocatable :: &
|
||||
microstructure, &
|
||||
homogenization
|
||||
microstructure
|
||||
|
||||
character(len=:), allocatable :: rawData
|
||||
character(len=65536) :: line
|
||||
|
@ -249,24 +245,18 @@ subroutine readGeom(grid,geomSize,origin,microstructure,homogenization)
|
|||
enddo
|
||||
endif
|
||||
|
||||
case ('homogenization')
|
||||
if (chunkPos(1) > 1) h = IO_intValue(line,chunkPos,2)
|
||||
|
||||
end select
|
||||
|
||||
enddo
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! sanity checks
|
||||
if(h < 1) &
|
||||
call IO_error(error_ID = 842, ext_msg='homogenization (readGeom)')
|
||||
if(any(grid < 1)) &
|
||||
call IO_error(error_ID = 842, ext_msg='grid (readGeom)')
|
||||
if(any(geomSize < 0.0_pReal)) &
|
||||
call IO_error(error_ID = 842, ext_msg='size (readGeom)')
|
||||
|
||||
allocate(microstructure(product(grid)), source = -1) ! too large in case of MPI (shrink later, not very elegant)
|
||||
allocate(homogenization(product(grid)), source = h) ! too large in case of MPI (shrink later, not very elegant)
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! read and interpret content
|
||||
|
|
|
@ -52,8 +52,7 @@ subroutine discretization_marc_init
|
|||
type(tElement) :: elem
|
||||
|
||||
integer, dimension(:), allocatable :: &
|
||||
microstructureAt, &
|
||||
homogenizationAt
|
||||
microstructureAt
|
||||
integer:: &
|
||||
Nnodes, & !< total number of nodes in the mesh
|
||||
Nelems, & !< total number of elements in the mesh
|
||||
|
@ -84,7 +83,7 @@ subroutine discretization_marc_init
|
|||
mesh_unitlength = num_commercialFEM%get_asFloat('unitlength',defaultVal=1.0_pReal) ! set physical extent of a length unit in mesh
|
||||
if (mesh_unitlength <= 0.0_pReal) call IO_error(301,ext_msg='unitlength')
|
||||
|
||||
call inputRead(elem,node0_elem,connectivity_elem,microstructureAt,homogenizationAt)
|
||||
call inputRead(elem,node0_elem,connectivity_elem,microstructureAt)
|
||||
nElems = size(connectivity_elem,2)
|
||||
|
||||
if (debug_e < 1 .or. debug_e > nElems) call IO_error(602,ext_msg='element')
|
||||
|
@ -104,7 +103,7 @@ subroutine discretization_marc_init
|
|||
call buildIPcoordinates(IP_reshaped,reshape(connectivity_cell,[elem%NcellNodesPerCell,&
|
||||
elem%nIPs*nElems]),node0_cell)
|
||||
|
||||
call discretization_init(microstructureAt,homogenizationAt,&
|
||||
call discretization_init(microstructureAt,&
|
||||
IP_reshaped,&
|
||||
node0_cell)
|
||||
|
||||
|
@ -173,7 +172,7 @@ end subroutine writeGeometry
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief Read mesh from marc input file
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine inputRead(elem,node0_elem,connectivity_elem,microstructureAt,homogenizationAt)
|
||||
subroutine inputRead(elem,node0_elem,connectivity_elem,microstructureAt)
|
||||
|
||||
type(tElement), intent(out) :: elem
|
||||
real(pReal), dimension(:,:), allocatable, intent(out) :: &
|
||||
|
@ -181,8 +180,7 @@ subroutine inputRead(elem,node0_elem,connectivity_elem,microstructureAt,homogeni
|
|||
integer, dimension(:,:), allocatable, intent(out) :: &
|
||||
connectivity_elem
|
||||
integer, dimension(:), allocatable, intent(out) :: &
|
||||
microstructureAt, &
|
||||
homogenizationAt
|
||||
microstructureAt
|
||||
|
||||
integer :: &
|
||||
fileFormatVersion, &
|
||||
|
@ -228,9 +226,9 @@ subroutine inputRead(elem,node0_elem,connectivity_elem,microstructureAt,homogeni
|
|||
|
||||
connectivity_elem = inputRead_connectivityElem(nElems,elem%nNodes,inputFile)
|
||||
|
||||
call inputRead_microstructureAndHomogenization(microstructureAt,homogenizationAt, &
|
||||
nElems,elem%nNodes,nameElemSet,mapElemSet,&
|
||||
initialcondTableStyle,inputFile)
|
||||
call inputRead_microstructure(microstructureAt, &
|
||||
nElems,elem%nNodes,nameElemSet,mapElemSet,&
|
||||
initialcondTableStyle,inputFile)
|
||||
end subroutine inputRead
|
||||
|
||||
|
||||
|
@ -677,14 +675,13 @@ end function inputRead_connectivityElem
|
|||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief Stores homogenization and microstructure ID
|
||||
!> @brief Store microstructure ID
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine inputRead_microstructureAndHomogenization(microstructureAt,homogenizationAt, &
|
||||
subroutine inputRead_microstructure(microstructureAt,&
|
||||
nElem,nNodes,nameElemSet,mapElemSet,initialcondTableStyle,fileContent)
|
||||
|
||||
integer, dimension(:), allocatable, intent(out) :: &
|
||||
microstructureAt, &
|
||||
homogenizationAt
|
||||
microstructureAt
|
||||
integer, intent(in) :: &
|
||||
nElem, &
|
||||
nNodes, & !< number of nodes per element
|
||||
|
@ -700,7 +697,6 @@ subroutine inputRead_microstructureAndHomogenization(microstructureAt,homogeniza
|
|||
|
||||
|
||||
allocate(microstructureAt(nElem),source=0)
|
||||
allocate(homogenizationAt(nElem),source=0)
|
||||
|
||||
do l = 1, size(fileContent)
|
||||
chunkPos = IO_stringPos(fileContent(l))
|
||||
|
@ -719,8 +715,7 @@ subroutine inputRead_microstructureAndHomogenization(microstructureAt,homogeniza
|
|||
contInts = continuousIntValues(fileContent(l+k+m+1:),nElem,nameElemSet,mapElemSet,size(nameElemSet)) ! get affected elements
|
||||
do i = 1,contInts(1)
|
||||
e = mesh_FEM2DAMASK_elem(contInts(1+i))
|
||||
if (sv == 2) microstructureAt(e) = myVal
|
||||
if (sv == 3) homogenizationAt(e) = myVal
|
||||
if (sv == 3) microstructureAt(e) = myVal
|
||||
enddo
|
||||
if (initialcondTableStyle == 0) m = m + 1
|
||||
enddo
|
||||
|
@ -728,7 +723,7 @@ subroutine inputRead_microstructureAndHomogenization(microstructureAt,homogeniza
|
|||
endif
|
||||
enddo
|
||||
|
||||
end subroutine inputRead_microstructureAndHomogenization
|
||||
end subroutine inputRead_microstructure
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
|
|
@ -80,7 +80,7 @@ module material
|
|||
damage_initialPhi !< initial damage per each homogenization
|
||||
|
||||
integer, dimension(:), allocatable, public, protected :: & ! (elem)
|
||||
material_homogenizationAt !< homogenization ID of each element (copy of discretization_homogenizationAt)
|
||||
material_homogenizationAt !< homogenization ID of each element
|
||||
integer, dimension(:,:), allocatable, public, target :: & ! (ip,elem) ToDo: ugly target for mapping hack
|
||||
material_homogenizationMemberAt !< position of the element within its homogenization instance
|
||||
integer, dimension(:,:), allocatable, public, protected :: & ! (constituent,elem)
|
||||
|
@ -241,7 +241,6 @@ subroutine material_parseHomogenization
|
|||
homogDamage
|
||||
|
||||
integer :: h
|
||||
logical, dimension(:), allocatable :: homogenization_active
|
||||
|
||||
material_homogenization => material_root%get('homogenization')
|
||||
material_Nhomogenization = material_homogenization%length
|
||||
|
@ -253,13 +252,9 @@ subroutine material_parseHomogenization
|
|||
allocate(thermal_typeInstance(material_Nhomogenization), source=0)
|
||||
allocate(damage_typeInstance(material_Nhomogenization), source=0)
|
||||
allocate(homogenization_Ngrains(material_Nhomogenization), source=0)
|
||||
allocate(homogenization_active(material_Nhomogenization), source=.false.) !!!!!!!!!!!!!!!
|
||||
allocate(thermal_initialT(material_Nhomogenization), source=300.0_pReal)
|
||||
allocate(damage_initialPhi(material_Nhomogenization), source=1.0_pReal)
|
||||
|
||||
forall (h = 1:material_Nhomogenization) &
|
||||
homogenization_active(h) = any(discretization_homogenizationAt == h) !ToDo: SR: needed??
|
||||
|
||||
do h=1, material_Nhomogenization
|
||||
homog => material_homogenization%get(h)
|
||||
homogMech => homog%get('mech')
|
||||
|
@ -317,7 +312,7 @@ subroutine material_parseHomogenization
|
|||
damage_typeInstance(h) = count(damage_type (1:h) == damage_type (h))
|
||||
enddo
|
||||
|
||||
homogenization_maxNgrains = maxval(homogenization_Ngrains,homogenization_active)
|
||||
homogenization_maxNgrains = maxval(homogenization_Ngrains)
|
||||
|
||||
|
||||
end subroutine material_parseHomogenization
|
||||
|
|
|
@ -77,7 +77,6 @@ subroutine discretization_mesh_init(restart)
|
|||
IS :: faceSetIS
|
||||
PetscErrorCode :: ierr
|
||||
integer, dimension(:), allocatable :: &
|
||||
homogenizationAt, &
|
||||
microstructureAt
|
||||
class(tNode), pointer :: &
|
||||
num_mesh
|
||||
|
@ -165,7 +164,6 @@ subroutine discretization_mesh_init(restart)
|
|||
call mesh_FEM_build_ipVolumes(dimPlex)
|
||||
|
||||
allocate(microstructureAt(mesh_NcpElems))
|
||||
allocate(homogenizationAt(mesh_NcpElems),source=1)
|
||||
do j = 1, mesh_NcpElems
|
||||
call DMGetLabelValue(geomMesh,'material',j-1,microstructureAt(j),ierr)
|
||||
CHKERRQ(ierr)
|
||||
|
@ -179,7 +177,7 @@ subroutine discretization_mesh_init(restart)
|
|||
|
||||
allocate(mesh_node0(3,mesh_Nnodes),source=0.0_pReal)
|
||||
|
||||
call discretization_init(microstructureAt,homogenizationAt,&
|
||||
call discretization_init(microstructureAt,&
|
||||
reshape(mesh_ipCoordinates,[3,mesh_maxNips*mesh_NcpElems]), &
|
||||
mesh_node0)
|
||||
|
||||
|
|
Loading…
Reference in New Issue