mesh_element/theMesh deprecated

This commit is contained in:
Martin Diehl 2019-06-07 07:49:45 +02:00
parent c7703d7aaf
commit b77ce718cf
4 changed files with 21 additions and 18 deletions

View File

@ -15,12 +15,11 @@ module CPFEM
use crystallite
use homogenization
use IO
use discretization
use DAMASK_interface
use numerics
#ifdef DAMASK_HDF5
use HDF5_utilities
use results
#endif
use lattice
use constitutive
@ -115,9 +114,9 @@ subroutine CPFEM_init
write(6,'(/,a)') ' <<<+- CPFEM init -+>>>'
flush(6)
allocate(CPFEM_cs( 6,theMesh%elem%nIPs,theMesh%Nelems), source= 0.0_pReal)
allocate(CPFEM_dcsdE( 6,6,theMesh%elem%nIPs,theMesh%Nelems), source= 0.0_pReal)
allocate(CPFEM_dcsdE_knownGood(6,6,theMesh%elem%nIPs,theMesh%Nelems), source= 0.0_pReal)
allocate(CPFEM_cs( 6,discretization_nIP,discretization_nElem), source= 0.0_pReal)
allocate(CPFEM_dcsdE( 6,6,discretization_nIP,discretization_nElem), source= 0.0_pReal)
allocate(CPFEM_dcsdE_knownGood(6,6,discretization_nIP,discretization_nElem), source= 0.0_pReal)
! *** restore the last converged values of each essential variable from the binary file
!if (restartRead) then
@ -260,7 +259,7 @@ subroutine CPFEM_general(mode, parallelExecution, ffn, ffn1, temperature_inp, dt
enddo; enddo
if (iand(debug_level(debug_CPFEM), debug_levelBasic) /= 0_pInt) then
write(6,'(a)') '<< CPFEM >> aging states'
if (debug_e <= theMesh%Nelems .and. debug_i <= theMesh%elem%nIPs) then
if (debug_e <= discretization_nElem .and. debug_i <=discretization_nIP) then
write(6,'(a,1x,i8,1x,i2,1x,i4,/,(12x,6(e20.8,1x)),/)') &
'<< CPFEM >> aged state of elFE ip grain',debug_e, debug_i, 1, &
plasticState(phaseAt(1,debug_i,debug_e))%state(:,phasememberAt(1,debug_i,debug_e))

View File

@ -14,6 +14,7 @@ module constitutive
use HDF5_utilities
use lattice
use mesh
use discretization
use plastic_none
use plastic_isotropic
use plastic_phenopowerlaw
@ -573,7 +574,7 @@ subroutine constitutive_collectDotState(S, FeArray, Fi, FpArray, subdt, ipc, ip,
el !< element
real(pReal), intent(in) :: &
subdt !< timestep
real(pReal), intent(in), dimension(3,3,homogenization_maxNgrains,theMesh%elem%nIPs,theMesh%Nelems) :: &
real(pReal), intent(in), dimension(3,3,homogenization_maxNgrains,discretization_nIP,discretization_nElem) :: &
FeArray, & !< elastic deformation gradient
FpArray !< plastic deformation gradient
real(pReal), intent(in), dimension(3,3) :: &

View File

@ -339,7 +339,7 @@ subroutine material_init
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! new mappings
allocate(material_homogenizationAt,source=theMesh%homogenizationAt)
allocate(material_homogenizationAt,source=discretization_homogenizationAt)
allocate(material_homogenizationMemberAt(discretization_nIP,discretization_nElem),source=0)
allocate(CounterHomogenization(size(config_homogenization)),source=0)
@ -388,7 +388,7 @@ subroutine material_init
do e = 1,discretization_nElem
myHomog = theMesh%homogenizationAt(e)
myHomog = discretization_homogenizationAt(e)
do i = 1, discretization_nIP
CounterHomogenization(myHomog) = CounterHomogenization(myHomog) + 1
mappingHomogenization(1:2,i,e) = [CounterHomogenization(myHomog),huge(1)]
@ -436,7 +436,7 @@ subroutine material_parseHomogenization
allocate(damage_initialPhi(size(config_homogenization)), source=1.0_pReal)
forall (h = 1:size(config_homogenization)) &
homogenization_active(h) = any(theMesh%homogenizationAt == h)
homogenization_active(h) = any(discretization_homogenizationAt == h)
do h=1, size(config_homogenization)
@ -522,11 +522,11 @@ subroutine material_parseMicrostructure
allocate(microstructure_Nconstituents(size(config_microstructure)), source=0)
allocate(microstructure_active(size(config_microstructure)), source=.false.)
if(any(theMesh%microstructureAt > size(config_microstructure))) &
if(any(discretization_microstructureAt > size(config_microstructure))) &
call IO_error(155,ext_msg='More microstructures in geometry than sections in material.config')
forall (e = 1:discretization_nElem) &
microstructure_active(theMesh%microstructureAt(e)) = .true. ! current microstructure used in model? Elementwise view, maximum N operations for N elements
microstructure_active(discretization_microstructureAt(e)) = .true. ! current microstructure used in model? Elementwise view, maximum N operations for N elements
do m=1, size(config_microstructure)
microstructure_Nconstituents(m) = config_microstructure(m)%countKeys('(constituent)')
@ -879,8 +879,8 @@ subroutine material_populateGrains
do e = 1, discretization_nElem
do i = 1, discretization_nIP
homog = theMesh%homogenizationAt(e)
micro = theMesh%microstructureAt(e)
homog = discretization_homogenizationAt(e)
micro = discretization_microstructureAt(e)
do c = 1, homogenization_Ngrains(homog)
material_phase(c,i,e) = microstructure_phase(c,micro)
material_texture(c,i,e) = microstructure_texture(c,micro)

View File

@ -24,7 +24,7 @@ module mesh
implicit none
private
integer(pInt), public, protected :: &
integer(pInt) :: &
mesh_Nnodes
integer(pInt), dimension(:), allocatable :: &
@ -32,7 +32,7 @@ module mesh
integer(pInt), dimension(:), allocatable :: &
mesh_homogenizationAt
integer(pInt), dimension(:,:), allocatable, public, protected :: &
integer(pInt), dimension(:,:), allocatable :: &
mesh_element !< entryCount and list of elements containing node
real(pReal), public, protected :: &
@ -57,11 +57,14 @@ module mesh
logical, dimension(3), public, parameter :: mesh_periodicSurface = .true. !< flag indicating periodic outer surfaces (used for fluxes)
integer(pInt) :: &
mesh_NcpElemsGlobal !< total number of CP elements in global mesh
! grid specific
integer(pInt), dimension(3), public, protected :: &
grid !< (global) grid
integer(pInt), public, protected :: &
mesh_NcpElemsGlobal, & !< total number of CP elements in global mesh
integer(pInt), public, protected :: & !< total number of CP elements in global mesh
grid3, & !< (local) grid in 3rd direction
grid3Offset !< (local) grid offset in 3rd direction
real(pReal), dimension(3), public, protected :: &