Merge branch 'crystallite-private-data' into 'development'

Crystallite private data

See merge request damask/DAMASK!241
This commit is contained in:
Franz Roters 2020-09-29 16:32:45 +02:00
commit 63f2419e92
2 changed files with 144 additions and 119 deletions

View File

@ -35,35 +35,42 @@ module crystallite
crystallite_subStep !< size of next integration step
type(rotation), dimension(:,:,:), allocatable :: &
crystallite_orientation !< current orientation
real(pReal), dimension(:,:,:,:,:), allocatable, public, protected :: &
crystallite_Fe, & !< current "elastic" def grad (end of converged time step)
crystallite_P, & !< 1st Piola-Kirchhoff stress per grain
crystallite_S0, & !< 2nd Piola-Kirchhoff stress vector at start of FE inc
crystallite_Fp0, & !< plastic def grad at start of FE inc
crystallite_Fi0, & !< intermediate def grad at start of FE inc
real(pReal), dimension(:,:,:,:,:), allocatable :: &
crystallite_F0, & !< def grad at start of FE inc
crystallite_Lp0, & !< plastic velocitiy grad at start of FE inc
crystallite_Li0 !< intermediate velocitiy grad at start of FE inc
real(pReal), dimension(:,:,:,:,:), allocatable, public :: &
crystallite_S, & !< current 2nd Piola-Kirchhoff stress vector (end of converged time step)
crystallite_partionedS0, & !< 2nd Piola-Kirchhoff stress vector at start of homog inc
crystallite_Fp, & !< current plastic def grad (end of converged time step)
crystallite_partionedFp0,& !< plastic def grad at start of homog inc
crystallite_Fi, & !< current intermediate def grad (end of converged time step)
crystallite_partionedFi0,& !< intermediate def grad at start of homog inc
crystallite_partionedF, & !< def grad to be reached at end of homog inc
crystallite_partionedF0, & !< def grad at start of homog inc
crystallite_Lp, & !< current plastic velocitiy grad (end of converged time step)
crystallite_partionedLp0, & !< plastic velocity grad at start of homog inc
crystallite_Li, & !< current intermediate velocitiy grad (end of converged time step)
crystallite_partionedLi0 !< intermediate velocity grad at start of homog inc
real(pReal), dimension(:,:,:,:,:), allocatable :: &
crystallite_subFp0,& !< plastic def grad at start of crystallite inc
crystallite_subFi0,& !< intermediate def grad at start of crystallite inc
crystallite_subF, & !< def grad to be reached at end of crystallite inc
crystallite_subF0, & !< def grad at start of crystallite inc
!
crystallite_Fe, & !< current "elastic" def grad (end of converged time step)
!
crystallite_Fp, & !< current plastic def grad (end of converged time step)
crystallite_Fp0, & !< plastic def grad at start of FE inc
crystallite_partionedFp0,& !< plastic def grad at start of homog inc
crystallite_subFp0,& !< plastic def grad at start of crystallite inc
!
crystallite_Fi, & !< current intermediate def grad (end of converged time step)
crystallite_Fi0, & !< intermediate def grad at start of FE inc
crystallite_partionedFi0,& !< intermediate def grad at start of homog inc
crystallite_subFi0,& !< intermediate def grad at start of crystallite inc
!
crystallite_Lp0, & !< plastic velocitiy grad at start of FE inc
crystallite_partionedLp0, & !< plastic velocity grad at start of homog inc
crystallite_subLp0,& !< plastic velocity grad at start of crystallite inc
crystallite_subLi0 !< intermediate velocity grad at start of crystallite inc
!
crystallite_Li, & !< current intermediate velocitiy grad (end of converged time step)
crystallite_Li0, & !< intermediate velocitiy grad at start of FE inc
crystallite_partionedLi0, & !< intermediate velocity grad at start of homog inc
crystallite_subLi0, & !< intermediate velocity grad at start of crystallite inc
!
crystallite_S0, & !< 2nd Piola-Kirchhoff stress vector at start of FE inc
crystallite_partionedS0 !< 2nd Piola-Kirchhoff stress vector at start of homog inc
real(pReal), dimension(:,:,:,:,:), allocatable, public, protected :: &
crystallite_P, & !< 1st Piola-Kirchhoff stress per grain
crystallite_Lp, & !< current plastic velocitiy grad (end of converged time step)
crystallite_S, & !< current 2nd Piola-Kirchhoff stress vector (end of converged time step)
crystallite_partionedF0 !< def grad at start of homog inc
real(pReal), dimension(:,:,:,:,:), allocatable, public :: &
crystallite_partionedF !< def grad to be reached at end of homog inc
real(pReal), dimension(:,:,:,:,:,:,:), allocatable, public, protected :: &
crystallite_dPdF !< current individual dPdF per grain (end of converged time step)
logical, dimension(:,:,:), allocatable, public :: &
@ -119,7 +126,10 @@ module crystallite
crystallite_results, &
crystallite_restartWrite, &
crystallite_restartRead, &
crystallite_forward
crystallite_forward, &
crystallite_initializeRestorationPoints, &
crystallite_windForward, &
crystallite_restore
contains
@ -136,8 +146,8 @@ subroutine crystallite_init
e, & !< counter in element loop
cMax, & !< maximum number of integration point components
iMax, & !< maximum number of integration points
eMax, & !< maximum number of elements
myNcomponents !< number of components at current IP
eMax !< maximum number of elements
class(tNode), pointer :: &
num_crystallite, &
@ -237,7 +247,7 @@ subroutine crystallite_init
allocate(output_constituent(phases%length))
do c = 1, phases%length
phase => phases%get(c)
generic_param => phase%get('generic',defaultVal = emptyDict)
generic_param => phase%get('generic',defaultVal = emptyDict)
#if defined(__GFORTRAN__)
output_constituent(c)%label = output_asStrings(generic_param)
#else
@ -248,10 +258,9 @@ subroutine crystallite_init
!--------------------------------------------------------------------------------------------------
! initialize
!$OMP PARALLEL DO PRIVATE(myNcomponents,i,c)
!$OMP PARALLEL DO PRIVATE(i,c)
do e = FEsolving_execElem(1),FEsolving_execElem(2)
myNcomponents = homogenization_Ngrains(material_homogenizationAt(e))
do i = FEsolving_execIP(1), FEsolving_execIP(2); do c = 1, myNcomponents
do i = FEsolving_execIP(1), FEsolving_execIP(2); do c = 1, homogenization_Ngrains(material_homogenizationAt(e))
crystallite_Fp0(1:3,1:3,c,i,e) = material_orientation0(c,i,e)%asMatrix() ! Fp reflects initial orientation (see 10.1016/j.actamat.2006.01.005)
crystallite_Fp0(1:3,1:3,c,i,e) = crystallite_Fp0(1:3,1:3,c,i,e) &
/ math_det33(crystallite_Fp0(1:3,1:3,c,i,e))**(1.0_pReal/3.0_pReal)
@ -296,7 +305,6 @@ subroutine crystallite_init
print'(a42,1x,i10)', 'max # of constituents/integration point: ', cMax
flush(IO_STDOUT)
endif
#endif
end subroutine crystallite_init
@ -411,7 +419,6 @@ function crystallite_stress()
crystallite_subLi0(1:3,1:3,c,i,e) = crystallite_Li (1:3,1:3,c,i,e)
crystallite_subFp0(1:3,1:3,c,i,e) = crystallite_Fp (1:3,1:3,c,i,e)
crystallite_subFi0(1:3,1:3,c,i,e) = crystallite_Fi (1:3,1:3,c,i,e)
!if abbrevation, make c and p private in omp
plasticState( material_phaseAt(c,e))%subState0(:,material_phaseMemberAt(c,i,e)) &
= plasticState(material_phaseAt(c,e))%state( :,material_phaseMemberAt(c,i,e))
do s = 1, phase_Nsources(material_phaseAt(c,e))
@ -462,7 +469,7 @@ function crystallite_stress()
!--------------------------------------------------------------------------------------------------
! integrate --- requires fully defined state array (basic + dependent state)
if (any(todo)) call integrateState(todo) ! TODO: unroll into proper elementloop to avoid N^2 for single point evaluation
if (any(todo)) call integrateState(todo) ! TODO: unroll into proper elementloop to avoid N^2 for single point evaluation
where(.not. crystallite_converged .and. crystallite_subStep > num%subStepMinCryst) & ! do not try non-converged but fully cutbacked any further
todo = .true. ! TODO: again unroll this into proper elementloop to avoid N^2 for single point evaluation
@ -481,12 +488,108 @@ end function crystallite_stress
!--------------------------------------------------------------------------------------------------
!> @brief calculate tangent (dPdF)
!> @brief Backup data for homog cutback.
!--------------------------------------------------------------------------------------------------
subroutine crystallite_initializeRestorationPoints(i,e)
integer, intent(in) :: &
i, & !< integration point number
e !< element number
integer :: &
c, & !< constituent number
s
do c = 1,homogenization_Ngrains(material_homogenizationAt(e))
crystallite_partionedFp0(1:3,1:3,c,i,e) = crystallite_Fp0(1:3,1:3,c,i,e)
crystallite_partionedLp0(1:3,1:3,c,i,e) = crystallite_Lp0(1:3,1:3,c,i,e)
crystallite_partionedFi0(1:3,1:3,c,i,e) = crystallite_Fi0(1:3,1:3,c,i,e)
crystallite_partionedLi0(1:3,1:3,c,i,e) = crystallite_Li0(1:3,1:3,c,i,e)
crystallite_partionedF0(1:3,1:3,c,i,e) = crystallite_F0(1:3,1:3,c,i,e)
crystallite_partionedS0(1:3,1:3,c,i,e) = crystallite_S0(1:3,1:3,c,i,e)
plasticState(material_phaseAt(c,e))%partionedState0(:,material_phasememberAt(c,i,e)) = &
plasticState(material_phaseAt(c,e))%state0( :,material_phasememberAt(c,i,e))
do s = 1, phase_Nsources(material_phaseAt(c,e))
sourceState(material_phaseAt(c,e))%p(s)%partionedState0(:,material_phasememberAt(c,i,e)) = &
sourceState(material_phaseAt(c,e))%p(s)%state0( :,material_phasememberAt(c,i,e))
enddo
enddo
end subroutine crystallite_initializeRestorationPoints
!--------------------------------------------------------------------------------------------------
!> @brief Wind homog inc forward.
!--------------------------------------------------------------------------------------------------
subroutine crystallite_windForward(i,e)
integer, intent(in) :: &
i, & !< integration point number
e !< element number
integer :: &
c, & !< constituent number
s
do c = 1,homogenization_Ngrains(material_homogenizationAt(e))
crystallite_partionedF0 (1:3,1:3,c,i,e) = crystallite_partionedF(1:3,1:3,c,i,e)
crystallite_partionedFp0(1:3,1:3,c,i,e) = crystallite_Fp (1:3,1:3,c,i,e)
crystallite_partionedLp0(1:3,1:3,c,i,e) = crystallite_Lp (1:3,1:3,c,i,e)
crystallite_partionedFi0(1:3,1:3,c,i,e) = crystallite_Fi (1:3,1:3,c,i,e)
crystallite_partionedLi0(1:3,1:3,c,i,e) = crystallite_Li (1:3,1:3,c,i,e)
crystallite_partionedS0 (1:3,1:3,c,i,e) = crystallite_S (1:3,1:3,c,i,e)
plasticState (material_phaseAt(c,e))%partionedState0(:,material_phasememberAt(c,i,e)) = &
plasticState (material_phaseAt(c,e))%state (:,material_phasememberAt(c,i,e))
do s = 1, phase_Nsources(material_phaseAt(c,e))
sourceState(material_phaseAt(c,e))%p(s)%partionedState0(:,material_phasememberAt(c,i,e)) = &
sourceState(material_phaseAt(c,e))%p(s)%state (:,material_phasememberAt(c,i,e))
enddo
enddo
end subroutine crystallite_windForward
!--------------------------------------------------------------------------------------------------
!> @brief Restore data after homog cutback.
!--------------------------------------------------------------------------------------------------
subroutine crystallite_restore(i,e,includeL)
integer, intent(in) :: &
i, & !< integration point number
e !< element number
logical, intent(in) :: &
includeL !< protect agains fake cutback
integer :: &
c, & !< constituent number
s
do c = 1,homogenization_Ngrains(material_homogenizationAt(e))
if (includeL) then
crystallite_Lp(1:3,1:3,c,i,e) = crystallite_partionedLp0(1:3,1:3,c,i,e)
crystallite_Li(1:3,1:3,c,i,e) = crystallite_partionedLi0(1:3,1:3,c,i,e)
endif ! maybe protecting everything from overwriting makes more sense
crystallite_Fp(1:3,1:3,c,i,e) = crystallite_partionedFp0(1:3,1:3,c,i,e)
crystallite_Fi(1:3,1:3,c,i,e) = crystallite_partionedFi0(1:3,1:3,c,i,e)
crystallite_S (1:3,1:3,c,i,e) = crystallite_partionedS0 (1:3,1:3,c,i,e)
plasticState (material_phaseAt(c,e))%state( :,material_phasememberAt(c,i,e)) = &
plasticState (material_phaseAt(c,e))%partionedState0(:,material_phasememberAt(c,i,e))
do s = 1, phase_Nsources(material_phaseAt(c,e))
sourceState(material_phaseAt(c,e))%p(s)%state( :,material_phasememberAt(c,i,e)) = &
sourceState(material_phaseAt(c,e))%p(s)%partionedState0(:,material_phasememberAt(c,i,e))
enddo
enddo
end subroutine crystallite_restore
!--------------------------------------------------------------------------------------------------
!> @brief Calculate tangent (dPdF).
!--------------------------------------------------------------------------------------------------
subroutine crystallite_stressTangent
integer :: &
c, & !< counter in integration point component loop
c, & !< counter in constituent loop
i, & !< counter in integration point loop
e, & !< counter in element loop
o, &

View File

@ -211,10 +211,8 @@ subroutine materialpoint_stressAndItsTangent(updateJaco,dt)
integer :: &
NiterationHomog, &
NiterationMPstate, &
g, & !< grain number
i, & !< integration point number
e, & !< element number
mySource, &
myNgrains
real(pReal), dimension(discretization_nIP,discretization_nElem) :: &
subFrac, &
@ -225,40 +223,13 @@ subroutine materialpoint_stressAndItsTangent(updateJaco,dt)
logical, dimension(2,discretization_nIP,discretization_nElem) :: &
doneAndHappy
#ifdef DEBUG
if (debugHomog%basic) then
print'(/a,i5,1x,i2)', ' << HOMOG >> Material Point start at el ip ', debugHomog%element, debugHomog%ip
print'(a,/,3(12x,3(f14.9,1x)/))', ' << HOMOG >> F0', &
transpose(materialpoint_F0(1:3,1:3,debugHomog%ip,debugHomog%element))
print'(a,/,3(12x,3(f14.9,1x)/))', ' << HOMOG >> F', &
transpose(materialpoint_F(1:3,1:3,debugHomog%ip,debugHomog%element))
endif
#endif
!--------------------------------------------------------------------------------------------------
! initialize restoration points
do e = FEsolving_execElem(1),FEsolving_execElem(2)
myNgrains = homogenization_Ngrains(material_homogenizationAt(e))
do i = FEsolving_execIP(1),FEsolving_execIP(2);
do g = 1,myNgrains
plasticState (material_phaseAt(g,e))%partionedState0(:,material_phasememberAt(g,i,e)) = &
plasticState (material_phaseAt(g,e))%state0( :,material_phasememberAt(g,i,e))
do mySource = 1, phase_Nsources(material_phaseAt(g,e))
sourceState(material_phaseAt(g,e))%p(mySource)%partionedState0(:,material_phasememberAt(g,i,e)) = &
sourceState(material_phaseAt(g,e))%p(mySource)%state0( :,material_phasememberAt(g,i,e))
enddo
crystallite_partionedFp0(1:3,1:3,g,i,e) = crystallite_Fp0(1:3,1:3,g,i,e)
crystallite_partionedLp0(1:3,1:3,g,i,e) = crystallite_Lp0(1:3,1:3,g,i,e)
crystallite_partionedFi0(1:3,1:3,g,i,e) = crystallite_Fi0(1:3,1:3,g,i,e)
crystallite_partionedLi0(1:3,1:3,g,i,e) = crystallite_Li0(1:3,1:3,g,i,e)
crystallite_partionedF0(1:3,1:3,g,i,e) = crystallite_F0(1:3,1:3,g,i,e)
crystallite_partionedS0(1:3,1:3,g,i,e) = crystallite_S0(1:3,1:3,g,i,e)
enddo
call crystallite_initializeRestorationPoints(i,e)
subFrac(i,e) = 0.0_pReal
converged(i,e) = .false. ! pretend failed step ...
@ -285,44 +256,19 @@ subroutine materialpoint_stressAndItsTangent(updateJaco,dt)
any(subStep(FEsolving_execIP(1):FEsolving_execIP(2),&
FEsolving_execElem(1):FEsolving_execElem(2)) > num%subStepMinHomog))
!$OMP PARALLEL DO PRIVATE(myNgrains)
!$OMP PARALLEL DO
elementLooping1: do e = FEsolving_execElem(1),FEsolving_execElem(2)
myNgrains = homogenization_Ngrains(material_homogenizationAt(e))
IpLooping1: do i = FEsolving_execIP(1),FEsolving_execIP(2)
if (converged(i,e)) then
#ifdef DEBUG
if (debugHomog%extensive .and. ((e == debugHomog%element .and. i == debugHomog%ip) &
.or. .not. debugHomog%selective)) then
print'(a,f12.8,a,f12.8,a,i8,1x,i2/)', ' << HOMOG >> winding forward from ', &
subFrac(i,e), ' to current subFrac ', &
subFrac(i,e)+subStep(i,e),' in materialpoint_stressAndItsTangent at el ip ',e,i
endif
#endif
!---------------------------------------------------------------------------------------------------
! calculate new subStep and new subFrac
subFrac(i,e) = subFrac(i,e) + subStep(i,e)
subStep(i,e) = min(1.0_pReal-subFrac(i,e),num%stepIncreaseHomog*subStep(i,e)) ! introduce flexibility for step increase/acceleration
steppingNeeded: if (subStep(i,e) > num%subStepMinHomog) then
! wind forward grain starting point
crystallite_partionedF0 (1:3,1:3,1:myNgrains,i,e) = crystallite_partionedF(1:3,1:3,1:myNgrains,i,e)
crystallite_partionedFp0(1:3,1:3,1:myNgrains,i,e) = crystallite_Fp (1:3,1:3,1:myNgrains,i,e)
crystallite_partionedLp0(1:3,1:3,1:myNgrains,i,e) = crystallite_Lp (1:3,1:3,1:myNgrains,i,e)
crystallite_partionedFi0(1:3,1:3,1:myNgrains,i,e) = crystallite_Fi (1:3,1:3,1:myNgrains,i,e)
crystallite_partionedLi0(1:3,1:3,1:myNgrains,i,e) = crystallite_Li (1:3,1:3,1:myNgrains,i,e)
crystallite_partionedS0 (1:3,1:3,1:myNgrains,i,e) = crystallite_S (1:3,1:3,1:myNgrains,i,e)
do g = 1,myNgrains
plasticState (material_phaseAt(g,e))%partionedState0(:,material_phasememberAt(g,i,e)) = &
plasticState (material_phaseAt(g,e))%state (:,material_phasememberAt(g,i,e))
do mySource = 1, phase_Nsources(material_phaseAt(g,e))
sourceState(material_phaseAt(g,e))%p(mySource)%partionedState0(:,material_phasememberAt(g,i,e)) = &
sourceState(material_phaseAt(g,e))%p(mySource)%state (:,material_phasememberAt(g,i,e))
enddo
enddo
call crystallite_windForward(i,e)
if(homogState(material_homogenizationAt(e))%sizeState > 0) &
homogState(material_homogenizationAt(e))%subState0(:,material_homogenizationMemberAt(i,e)) = &
@ -347,32 +293,8 @@ subroutine materialpoint_stressAndItsTangent(updateJaco,dt)
else ! cutback makes sense
subStep(i,e) = num%subStepSizeHomog * subStep(i,e) ! crystallite had severe trouble, so do a significant cutback
#ifdef DEBUG
if (debugHomog%extensive .and. ((e == debugHomog%element .and. i == debugHomog%ip) &
.or. .not. debugHomog%selective)) then
print'(a,f12.8,a,i8,1x,i2/)', &
'<< HOMOG >> cutback step in materialpoint_stressAndItsTangent with new subStep: ',&
subStep(i,e),' at el ip',e,i
endif
#endif
call crystallite_restore(i,e,subStep(i,e) < 1.0_pReal)
!--------------------------------------------------------------------------------------------------
! restore
if (subStep(i,e) < 1.0_pReal) then ! protect against fake cutback from \Delta t = 2 to 1. Maybe that "trick" is not necessary anymore at all? I.e. start with \Delta t = 1
crystallite_Lp(1:3,1:3,1:myNgrains,i,e) = crystallite_partionedLp0(1:3,1:3,1:myNgrains,i,e)
crystallite_Li(1:3,1:3,1:myNgrains,i,e) = crystallite_partionedLi0(1:3,1:3,1:myNgrains,i,e)
endif ! maybe protecting everything from overwriting (not only L) makes even more sense
crystallite_Fp(1:3,1:3,1:myNgrains,i,e) = crystallite_partionedFp0(1:3,1:3,1:myNgrains,i,e)
crystallite_Fi(1:3,1:3,1:myNgrains,i,e) = crystallite_partionedFi0(1:3,1:3,1:myNgrains,i,e)
crystallite_S (1:3,1:3,1:myNgrains,i,e) = crystallite_partionedS0 (1:3,1:3,1:myNgrains,i,e)
do g = 1, myNgrains
plasticState (material_phaseAt(g,e))%state( :,material_phasememberAt(g,i,e)) = &
plasticState (material_phaseAt(g,e))%partionedState0(:,material_phasememberAt(g,i,e))
do mySource = 1, phase_Nsources(material_phaseAt(g,e))
sourceState(material_phaseAt(g,e))%p(mySource)%state( :,material_phasememberAt(g,i,e)) = &
sourceState(material_phaseAt(g,e))%p(mySource)%partionedState0(:,material_phasememberAt(g,i,e))
enddo
enddo
if(homogState(material_homogenizationAt(e))%sizeState > 0) &
homogState(material_homogenizationAt(e))%State( :,material_homogenizationMemberAt(i,e)) = &
homogState(material_homogenizationAt(e))%subState0(:,material_homogenizationMemberAt(i,e))