Tstar_v is now restored at different stages of cutbacking; we need this because preguess of state relies on consistent Tstar_v
This commit is contained in:
parent
ada92a9b74
commit
904ea78ac5
|
@ -13,50 +13,53 @@
|
||||||
|
|
||||||
MODULE crystallite
|
MODULE crystallite
|
||||||
|
|
||||||
use prec, only: pReal,pInt
|
use prec, only: pReal, pInt
|
||||||
implicit none
|
implicit none
|
||||||
!
|
!
|
||||||
! ****************************************************************
|
! ****************************************************************
|
||||||
! *** General variables for the crystallite calculation ***
|
! *** General variables for the crystallite calculation ***
|
||||||
! ****************************************************************
|
! ****************************************************************
|
||||||
integer(pInt), parameter :: crystallite_Nresults = 5_pInt ! phaseID, volume, Euler angles
|
integer(pInt), parameter :: crystallite_Nresults = 5_pInt ! phaseID, volume, Euler angles
|
||||||
|
|
||||||
real(pReal), dimension (:,:,:,:,:), allocatable :: crystallite_Fe, & ! current "elastic" def grad (end of converged time step)
|
real(pReal), dimension (:,:,:), allocatable :: crystallite_dt, & ! requested time increment of each grain
|
||||||
crystallite_Fp, & ! current plastic def grad (end of converged time step)
|
|
||||||
crystallite_Lp, & ! current plastic velocitiy grad (end of converged time step)
|
|
||||||
crystallite_F0, & ! def grad at start of FE inc
|
|
||||||
crystallite_Fp0, & ! plastic def grad at start of FE inc
|
|
||||||
crystallite_Lp0, & ! plastic velocitiy grad at start of FE inc
|
|
||||||
crystallite_partionedF, & ! def grad to be reached at end of homog inc
|
|
||||||
crystallite_partionedF0, & ! def grad at start of homog inc
|
|
||||||
crystallite_partionedFp0,& ! plastic def grad at start of homog inc
|
|
||||||
crystallite_partionedLp0,& ! plastic velocity grad at start of homog inc
|
|
||||||
crystallite_subF, & ! def grad to be reached at end of crystallite inc
|
|
||||||
crystallite_subF0, & ! def grad at start of crystallite inc
|
|
||||||
crystallite_subFp0,& ! plastic def grad at start of crystallite inc
|
|
||||||
crystallite_subLp0,& ! plastic velocity grad at start of crystallite inc
|
|
||||||
crystallite_P ! 1st Piola-Kirchhoff stress per grain
|
|
||||||
real(pReal), dimension (:,:,:,:), allocatable :: crystallite_Tstar_v ! 2nd Piola-Kirchhoff stress (vector) per grain
|
|
||||||
real(pReal), dimension (:,:,:,:,:,:,:),allocatable :: crystallite_dPdF, & ! individual dPdF per grain
|
|
||||||
crystallite_fallbackdPdF ! dPdF fallback for non-converged grains (elastic prediction)
|
|
||||||
real(pReal), dimension (:,:,:), allocatable :: crystallite_dt, & ! requested time increment of each grain
|
|
||||||
crystallite_subdt, & ! substepped time increment of each grain
|
crystallite_subdt, & ! substepped time increment of each grain
|
||||||
crystallite_subFrac, & ! already calculated fraction of increment
|
crystallite_subFrac, & ! already calculated fraction of increment
|
||||||
crystallite_subStep, & ! size of next integration step
|
crystallite_subStep, & ! size of next integration step
|
||||||
crystallite_Temperature ! Temp of each grain
|
crystallite_Temperature ! Temp of each grain
|
||||||
|
real(pReal), dimension (:,:,:,:), allocatable :: crystallite_Tstar_v, & ! current 2nd Piola-Kirchhoff stress vector (end of converged time step)
|
||||||
|
crystallite_Tstar0_v, & ! 2nd Piola-Kirchhoff stress vector at start of FE inc
|
||||||
|
crystallite_partionedTstar0_v, & ! 2nd Piola-Kirchhoff stress vector at start of homog inc
|
||||||
|
crystallite_subTstar0_v ! 2nd Piola-Kirchhoff stress vector at start of crystallite inc
|
||||||
|
real(pReal), dimension (:,:,:,:,:), allocatable :: 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_F0, & ! def grad at start of FE inc
|
||||||
|
crystallite_partionedF, & ! def grad to be reached at end of homog inc
|
||||||
|
crystallite_partionedF0, & ! def grad at start of homog inc
|
||||||
|
crystallite_subF, & ! def grad to be reached at end of crystallite inc
|
||||||
|
crystallite_subF0, & ! def grad at start of crystallite inc
|
||||||
|
crystallite_Lp, & ! current plastic velocitiy grad (end of converged time step)
|
||||||
|
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_P ! 1st Piola-Kirchhoff stress per grain
|
||||||
|
real(pReal), dimension (:,:,:,:,:,:,:), allocatable :: crystallite_dPdF, & ! individual dPdF per grain
|
||||||
|
crystallite_fallbackdPdF ! dPdF fallback for non-converged grains (elastic prediction)
|
||||||
|
|
||||||
logical, dimension (:,:,:), allocatable :: crystallite_localConstitution, & ! indicates this grain to have purely local constitutive law
|
logical, dimension (:,:,:), allocatable :: crystallite_localConstitution, & ! indicates this grain to have purely local constitutive law
|
||||||
crystallite_requested, & ! flag to request crystallite calculation
|
crystallite_requested, & ! flag to request crystallite calculation
|
||||||
crystallite_onTrack, & ! flag to indicate ongoing calculation
|
crystallite_onTrack, & ! flag to indicate ongoing calculation
|
||||||
crystallite_converged ! convergence flag
|
crystallite_converged ! convergence flag
|
||||||
|
|
||||||
|
|
||||||
CONTAINS
|
CONTAINS
|
||||||
|
|
||||||
!********************************************************************
|
!********************************************************************
|
||||||
! allocate and initialize per grain variables
|
! allocate and initialize per grain variables
|
||||||
!********************************************************************
|
!********************************************************************
|
||||||
subroutine crystallite_init()
|
subroutine crystallite_init()
|
||||||
|
|
||||||
!*** variables and functions from other modules ***!
|
!*** variables and functions from other modules ***!
|
||||||
use prec, only: pInt, &
|
use prec, only: pInt, &
|
||||||
|
@ -107,6 +110,9 @@ MODULE crystallite
|
||||||
! crystallite_subLp0
|
! crystallite_subLp0
|
||||||
! crystallite_P
|
! crystallite_P
|
||||||
! crystallite_Tstar_v
|
! crystallite_Tstar_v
|
||||||
|
! crystallite_Tstar0_v
|
||||||
|
! crystallite_partionedTstar0_v
|
||||||
|
! crystallite_subTstar0_v
|
||||||
! crystallite_dPdF
|
! crystallite_dPdF
|
||||||
! crystallite_fallbackdPdF
|
! crystallite_fallbackdPdF
|
||||||
! crystallite_dt
|
! crystallite_dt
|
||||||
|
@ -133,7 +139,7 @@ MODULE crystallite
|
||||||
allocate(crystallite_F0(3,3,gMax,iMax,eMax)); crystallite_F0 = 0.0_pReal
|
allocate(crystallite_F0(3,3,gMax,iMax,eMax)); crystallite_F0 = 0.0_pReal
|
||||||
allocate(crystallite_Fp0(3,3,gMax,iMax,eMax)); crystallite_Fp0 = 0.0_pReal
|
allocate(crystallite_Fp0(3,3,gMax,iMax,eMax)); crystallite_Fp0 = 0.0_pReal
|
||||||
allocate(crystallite_Lp0(3,3,gMax,iMax,eMax)); crystallite_Lp0 = 0.0_pReal
|
allocate(crystallite_Lp0(3,3,gMax,iMax,eMax)); crystallite_Lp0 = 0.0_pReal
|
||||||
allocate(crystallite_partionedF(3,3,gMax,iMax,eMax)); crystallite_partionedF0 = 0.0_pReal
|
allocate(crystallite_partionedF(3,3,gMax,iMax,eMax)); crystallite_partionedF = 0.0_pReal
|
||||||
allocate(crystallite_partionedF0(3,3,gMax,iMax,eMax)); crystallite_partionedF0 = 0.0_pReal
|
allocate(crystallite_partionedF0(3,3,gMax,iMax,eMax)); crystallite_partionedF0 = 0.0_pReal
|
||||||
allocate(crystallite_partionedFp0(3,3,gMax,iMax,eMax)); crystallite_partionedFp0 = 0.0_pReal
|
allocate(crystallite_partionedFp0(3,3,gMax,iMax,eMax)); crystallite_partionedFp0 = 0.0_pReal
|
||||||
allocate(crystallite_partionedLp0(3,3,gMax,iMax,eMax)); crystallite_partionedLp0 = 0.0_pReal
|
allocate(crystallite_partionedLp0(3,3,gMax,iMax,eMax)); crystallite_partionedLp0 = 0.0_pReal
|
||||||
|
@ -143,6 +149,9 @@ MODULE crystallite
|
||||||
allocate(crystallite_subLp0(3,3,gMax,iMax,eMax)); crystallite_subLp0 = 0.0_pReal
|
allocate(crystallite_subLp0(3,3,gMax,iMax,eMax)); crystallite_subLp0 = 0.0_pReal
|
||||||
allocate(crystallite_P(3,3,gMax,iMax,eMax)); crystallite_P = 0.0_pReal
|
allocate(crystallite_P(3,3,gMax,iMax,eMax)); crystallite_P = 0.0_pReal
|
||||||
allocate(crystallite_Tstar_v(6,gMax,iMax,eMax)); crystallite_Tstar_v = 0.0_pReal
|
allocate(crystallite_Tstar_v(6,gMax,iMax,eMax)); crystallite_Tstar_v = 0.0_pReal
|
||||||
|
allocate(crystallite_Tstar0_v(6,gMax,iMax,eMax)); crystallite_Tstar0_v = 0.0_pReal
|
||||||
|
allocate(crystallite_partionedTstar0_v(6,gMax,iMax,eMax)); crystallite_partionedTstar0_v = 0.0_pReal
|
||||||
|
allocate(crystallite_subTstar0_v(6,gMax,iMax,eMax)); crystallite_subTstar0_v = 0.0_pReal
|
||||||
allocate(crystallite_dPdF(3,3,3,3,gMax,iMax,eMax)); crystallite_dPdF = 0.0_pReal
|
allocate(crystallite_dPdF(3,3,3,3,gMax,iMax,eMax)); crystallite_dPdF = 0.0_pReal
|
||||||
allocate(crystallite_fallbackdPdF(3,3,3,3,gMax,iMax,eMax)); crystallite_fallbackdPdF = 0.0_pReal
|
allocate(crystallite_fallbackdPdF(3,3,3,3,gMax,iMax,eMax)); crystallite_fallbackdPdF = 0.0_pReal
|
||||||
allocate(crystallite_dt(gMax,iMax,eMax)); crystallite_dt = 0.0_pReal
|
allocate(crystallite_dt(gMax,iMax,eMax)); crystallite_dt = 0.0_pReal
|
||||||
|
@ -155,7 +164,7 @@ MODULE crystallite
|
||||||
allocate(crystallite_onTrack(gMax,iMax,eMax)); crystallite_onTrack = .false.
|
allocate(crystallite_onTrack(gMax,iMax,eMax)); crystallite_onTrack = .false.
|
||||||
allocate(crystallite_converged(gMax,iMax,eMax)); crystallite_converged = .true.
|
allocate(crystallite_converged(gMax,iMax,eMax)); crystallite_converged = .true.
|
||||||
|
|
||||||
!$OMP PARALLEL DO
|
!$OMP PARALLEL DO
|
||||||
do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over all cp elements
|
do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over all cp elements
|
||||||
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
||||||
do i = FEsolving_execIP(1,e),FEsolving_execIP(2,e) ! iterate over IPs of this element
|
do i = FEsolving_execIP(1,e),FEsolving_execIP(2,e) ! iterate over IPs of this element
|
||||||
|
@ -170,13 +179,13 @@ MODULE crystallite
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
!$OMPEND PARALLEL DO
|
!$OMPEND PARALLEL DO
|
||||||
|
|
||||||
call crystallite_stressAndItsTangent(.true.) ! request elastic answers
|
call crystallite_stressAndItsTangent(.true.) ! request elastic answers
|
||||||
crystallite_fallbackdPdF = crystallite_dPdF ! use initial elastic stiffness as fallback
|
crystallite_fallbackdPdF = crystallite_dPdF ! use initial elastic stiffness as fallback
|
||||||
|
|
||||||
! *** Output to MARC output file ***
|
! *** Output to MARC output file ***
|
||||||
!$OMP CRITICAL (write2out)
|
!$OMP CRITICAL (write2out)
|
||||||
write(6,*)
|
write(6,*)
|
||||||
write(6,*) '<<<+- crystallite init -+>>>'
|
write(6,*) '<<<+- crystallite init -+>>>'
|
||||||
write(6,*)
|
write(6,*)
|
||||||
|
@ -197,6 +206,9 @@ MODULE crystallite
|
||||||
write(6,'(a32,x,7(i5,x))') 'crystallite_subLp0: ', shape(crystallite_subLp0)
|
write(6,'(a32,x,7(i5,x))') 'crystallite_subLp0: ', shape(crystallite_subLp0)
|
||||||
write(6,'(a32,x,7(i5,x))') 'crystallite_P: ', shape(crystallite_P)
|
write(6,'(a32,x,7(i5,x))') 'crystallite_P: ', shape(crystallite_P)
|
||||||
write(6,'(a32,x,7(i5,x))') 'crystallite_Tstar_v: ', shape(crystallite_Tstar_v)
|
write(6,'(a32,x,7(i5,x))') 'crystallite_Tstar_v: ', shape(crystallite_Tstar_v)
|
||||||
|
write(6,'(a32,x,7(i5,x))') 'crystallite_Tstar0_v: ', shape(crystallite_Tstar0_v)
|
||||||
|
write(6,'(a32,x,7(i5,x))') 'crystallite_partionedTstar0_v: ', shape(crystallite_partionedTstar0_v)
|
||||||
|
write(6,'(a32,x,7(i5,x))') 'crystallite_subTstar0_v: ', shape(crystallite_subTstar0_v)
|
||||||
write(6,'(a32,x,7(i5,x))') 'crystallite_dPdF: ', shape(crystallite_dPdF)
|
write(6,'(a32,x,7(i5,x))') 'crystallite_dPdF: ', shape(crystallite_dPdF)
|
||||||
write(6,'(a32,x,7(i5,x))') 'crystallite_fallbackdPdF: ', shape(crystallite_fallbackdPdF)
|
write(6,'(a32,x,7(i5,x))') 'crystallite_fallbackdPdF: ', shape(crystallite_fallbackdPdF)
|
||||||
write(6,'(a32,x,7(i5,x))') 'crystallite_dt: ', shape(crystallite_dt)
|
write(6,'(a32,x,7(i5,x))') 'crystallite_dt: ', shape(crystallite_dt)
|
||||||
|
@ -211,14 +223,14 @@ MODULE crystallite
|
||||||
write(6,*)
|
write(6,*)
|
||||||
write(6,*) 'Number of non-local grains: ',count(.not. crystallite_localConstitution)
|
write(6,*) 'Number of non-local grains: ',count(.not. crystallite_localConstitution)
|
||||||
call flush(6)
|
call flush(6)
|
||||||
!$OMPEND CRITICAL (write2out)
|
!$OMPEND CRITICAL (write2out)
|
||||||
|
|
||||||
call debug_info()
|
call debug_info()
|
||||||
call debug_reset()
|
call debug_reset()
|
||||||
|
|
||||||
return
|
return
|
||||||
|
|
||||||
endsubroutine
|
endsubroutine
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
@ -256,6 +268,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
||||||
constitutive_subState0, &
|
constitutive_subState0, &
|
||||||
constitutive_partionedState0, &
|
constitutive_partionedState0, &
|
||||||
constitutive_homogenizedC
|
constitutive_homogenizedC
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
!*** input variables ***!
|
!*** input variables ***!
|
||||||
|
@ -272,6 +285,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
||||||
myFe, & ! local copy of the elastic deformation gradient
|
myFe, & ! local copy of the elastic deformation gradient
|
||||||
myLp, & ! local copy of the plastic velocity gradient
|
myLp, & ! local copy of the plastic velocity gradient
|
||||||
myP ! local copy of the 1st Piola-Kirchhoff stress tensor
|
myP ! local copy of the 1st Piola-Kirchhoff stress tensor
|
||||||
|
real(pReal), dimension(6) :: myTstar_v ! local copy of the 2nd Piola-Kirchhoff stress vector
|
||||||
real(pReal), dimension(constitutive_maxSizeState) :: myState ! local copy of the state
|
real(pReal), dimension(constitutive_maxSizeState) :: myState ! local copy of the state
|
||||||
integer(pInt) NiterationCrystallite, & ! number of iterations in crystallite loop
|
integer(pInt) NiterationCrystallite, & ! number of iterations in crystallite loop
|
||||||
NiterationState ! number of iterations in state loop
|
NiterationState ! number of iterations in state loop
|
||||||
|
@ -299,6 +313,9 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
||||||
! crystallite_subLp0
|
! crystallite_subLp0
|
||||||
! crystallite_P
|
! crystallite_P
|
||||||
! crystallite_Tstar_v
|
! crystallite_Tstar_v
|
||||||
|
! crystallite_Tstar0_v
|
||||||
|
! crystallite_partionedTstar0_v
|
||||||
|
! crystallite_subTstar0_v
|
||||||
! crystallite_dPdF
|
! crystallite_dPdF
|
||||||
! crystallite_fallbackdPdF
|
! crystallite_fallbackdPdF
|
||||||
! crystallite_dt
|
! crystallite_dt
|
||||||
|
@ -316,7 +333,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
||||||
! crystallite_updateState
|
! crystallite_updateState
|
||||||
|
|
||||||
|
|
||||||
! ------ initialize to starting condition ------
|
! ------ initialize to starting condition ------
|
||||||
|
|
||||||
write (6,*)
|
write (6,*)
|
||||||
write (6,*) 'Crystallite request from Materialpoint'
|
write (6,*) 'Crystallite request from Materialpoint'
|
||||||
|
@ -336,6 +353,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
||||||
crystallite_subFp0(:,:,g,i,e) = crystallite_partionedFp0(:,:,g,i,e) ! ...plastic def grad
|
crystallite_subFp0(:,:,g,i,e) = crystallite_partionedFp0(:,:,g,i,e) ! ...plastic def grad
|
||||||
crystallite_subLp0(:,:,g,i,e) = crystallite_partionedLp0(:,:,g,i,e) ! ...plastic velocity grad
|
crystallite_subLp0(:,:,g,i,e) = crystallite_partionedLp0(:,:,g,i,e) ! ...plastic velocity grad
|
||||||
crystallite_subF0(:,:,g,i,e) = crystallite_partionedF0(:,:,g,i,e) ! ...def grad
|
crystallite_subF0(:,:,g,i,e) = crystallite_partionedF0(:,:,g,i,e) ! ...def grad
|
||||||
|
crystallite_subTstar0_v(:,g,i,e) = crystallite_partionedTstar0_v(:,g,i,e) ! ...2nd PK stress
|
||||||
|
|
||||||
crystallite_subFrac(g,i,e) = 0.0_pReal
|
crystallite_subFrac(g,i,e) = 0.0_pReal
|
||||||
crystallite_subStep(g,i,e) = 2.0_pReal
|
crystallite_subStep(g,i,e) = 2.0_pReal
|
||||||
|
@ -375,6 +393,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
||||||
crystallite_subFp0(:,:,g,i,e) = crystallite_Fp(:,:,g,i,e) ! ...plastic def grad
|
crystallite_subFp0(:,:,g,i,e) = crystallite_Fp(:,:,g,i,e) ! ...plastic def grad
|
||||||
crystallite_subLp0(:,:,g,i,e) = crystallite_Lp(:,:,g,i,e) ! ...plastic velocity gradient
|
crystallite_subLp0(:,:,g,i,e) = crystallite_Lp(:,:,g,i,e) ! ...plastic velocity gradient
|
||||||
constitutive_subState0(g,i,e)%p = constitutive_state(g,i,e)%p ! ...microstructure
|
constitutive_subState0(g,i,e)%p = constitutive_state(g,i,e)%p ! ...microstructure
|
||||||
|
crystallite_subTstar0_v(:,g,i,e) = crystallite_Tstar_v(:,g,i,e) ! ...2nd PK stress
|
||||||
endif
|
endif
|
||||||
if (debugger) then
|
if (debugger) then
|
||||||
!$OMP CRITICAL (write2out)
|
!$OMP CRITICAL (write2out)
|
||||||
|
@ -389,6 +408,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
||||||
crystallite_Fp(:,:,g,i,e) = crystallite_subFp0(:,:,g,i,e) ! ...plastic def grad
|
crystallite_Fp(:,:,g,i,e) = crystallite_subFp0(:,:,g,i,e) ! ...plastic def grad
|
||||||
crystallite_Lp(:,:,g,i,e) = crystallite_subLp0(:,:,g,i,e) ! ...plastic velocity grad
|
crystallite_Lp(:,:,g,i,e) = crystallite_subLp0(:,:,g,i,e) ! ...plastic velocity grad
|
||||||
constitutive_state(g,i,e)%p = constitutive_subState0(g,i,e)%p ! ...microstructure
|
constitutive_state(g,i,e)%p = constitutive_subState0(g,i,e)%p ! ...microstructure
|
||||||
|
crystallite_Tstar_v(:,g,i,e) = crystallite_subTstar0_v(:,g,i,e) ! ...2nd PK stress
|
||||||
if (debugger) then
|
if (debugger) then
|
||||||
!$OMP CRITICAL (write2out)
|
!$OMP CRITICAL (write2out)
|
||||||
write(6,'(a78,f6.4)') 'cutback step in crystallite_stressAndItsTangent with new crystallite_subStep: ',&
|
write(6,'(a78,f6.4)') 'cutback step in crystallite_stressAndItsTangent with new crystallite_subStep: ',&
|
||||||
|
@ -510,7 +530,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
||||||
enddo ! cutback loop
|
enddo ! cutback loop
|
||||||
|
|
||||||
|
|
||||||
! ------ check for non-converged crystallites ------
|
! ------ check for non-converged crystallites ------
|
||||||
|
|
||||||
!$OMP PARALLEL DO
|
!$OMP PARALLEL DO
|
||||||
do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over elements to be processed
|
do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over elements to be processed
|
||||||
|
@ -533,7 +553,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
||||||
enddo
|
enddo
|
||||||
!$OMPEND PARALLEL DO
|
!$OMPEND PARALLEL DO
|
||||||
|
|
||||||
! --+>> stiffness calculation <<+--
|
! --+>> stiffness calculation <<+--
|
||||||
|
|
||||||
if(updateJaco) then ! Jacobian required
|
if(updateJaco) then ! Jacobian required
|
||||||
if (debugger) write (6,*) 'Stiffness calculation started'
|
if (debugger) write (6,*) 'Stiffness calculation started'
|
||||||
|
@ -550,6 +570,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
||||||
myFp = crystallite_Fp(:,:,g,i,e)
|
myFp = crystallite_Fp(:,:,g,i,e)
|
||||||
myFe = crystallite_Fe(:,:,g,i,e)
|
myFe = crystallite_Fe(:,:,g,i,e)
|
||||||
myLp = crystallite_Lp(:,:,g,i,e)
|
myLp = crystallite_Lp(:,:,g,i,e)
|
||||||
|
myTstar_v = crystallite_Tstar_v(:,g,i,e)
|
||||||
myP = crystallite_P(:,:,g,i,e)
|
myP = crystallite_P(:,:,g,i,e)
|
||||||
if (debugger) then
|
if (debugger) then
|
||||||
write (6,*) '#############'
|
write (6,*) '#############'
|
||||||
|
@ -593,6 +614,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
||||||
crystallite_Fp(:,:,g,i,e) = myFp ! ... and kinematics
|
crystallite_Fp(:,:,g,i,e) = myFp ! ... and kinematics
|
||||||
crystallite_Fe(:,:,g,i,e) = myFe
|
crystallite_Fe(:,:,g,i,e) = myFe
|
||||||
crystallite_Lp(:,:,g,i,e) = myLp
|
crystallite_Lp(:,:,g,i,e) = myLp
|
||||||
|
crystallite_Tstar_v(:,g,i,e) = myTstar_v
|
||||||
crystallite_P(:,:,g,i,e) = myP
|
crystallite_P(:,:,g,i,e) = myP
|
||||||
!$OMP CRITICAL (out)
|
!$OMP CRITICAL (out)
|
||||||
debug_StiffnessStateLoopDistribution(NiterationState) = &
|
debug_StiffnessStateLoopDistribution(NiterationState) = &
|
||||||
|
|
|
@ -43,7 +43,8 @@ MODULE homogenization
|
||||||
logical, dimension(:,:), allocatable :: materialpoint_requested, &
|
logical, dimension(:,:), allocatable :: materialpoint_requested, &
|
||||||
materialpoint_converged
|
materialpoint_converged
|
||||||
logical, dimension(:,:,:), allocatable :: materialpoint_doneAndHappy
|
logical, dimension(:,:,:), allocatable :: materialpoint_doneAndHappy
|
||||||
integer(pInt) homogenization_maxSizeState,homogenization_maxSizePostResults
|
integer(pInt) homogenization_maxSizeState, &
|
||||||
|
homogenization_maxSizePostResults
|
||||||
|
|
||||||
CONTAINS
|
CONTAINS
|
||||||
|
|
||||||
|
@ -179,7 +180,22 @@ subroutine materialpoint_stressAndItsTangent(&
|
||||||
use constitutive, only: constitutive_state0, &
|
use constitutive, only: constitutive_state0, &
|
||||||
constitutive_partionedState0, &
|
constitutive_partionedState0, &
|
||||||
constitutive_state
|
constitutive_state
|
||||||
use crystallite
|
use crystallite, only: crystallite_F0, &
|
||||||
|
crystallite_Fp0, &
|
||||||
|
crystallite_Fp, &
|
||||||
|
crystallite_Lp0, &
|
||||||
|
crystallite_Lp, &
|
||||||
|
crystallite_Tstar0_v, &
|
||||||
|
crystallite_Tstar_v, &
|
||||||
|
crystallite_partionedF0, &
|
||||||
|
crystallite_partionedF, &
|
||||||
|
crystallite_partionedFp0, &
|
||||||
|
crystallite_partionedLp0, &
|
||||||
|
crystallite_partionedTstar0_v, &
|
||||||
|
crystallite_dt, &
|
||||||
|
crystallite_requested, &
|
||||||
|
crystallite_stressAndItsTangent
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
real(pReal), intent(in) :: dt
|
real(pReal), intent(in) :: dt
|
||||||
|
@ -200,14 +216,17 @@ subroutine materialpoint_stressAndItsTangent(&
|
||||||
do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over elements to be processed
|
do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over elements to be processed
|
||||||
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
||||||
do i = FEsolving_execIP(1,e),FEsolving_execIP(2,e) ! iterate over IPs of this element to be processed
|
do i = FEsolving_execIP(1,e),FEsolving_execIP(2,e) ! iterate over IPs of this element to be processed
|
||||||
|
|
||||||
! initialize restoration points of grain...
|
! initialize restoration points of grain...
|
||||||
forall (g = 1:myNgrains) constitutive_partionedState0(g,i,e)%p = constitutive_state0(g,i,e)%p ! ...microstructures
|
forall (g = 1:myNgrains) constitutive_partionedState0(g,i,e)%p = constitutive_state0(g,i,e)%p ! ...microstructures
|
||||||
crystallite_partionedFp0(:,:,1:myNgrains,i,e) = crystallite_Fp0(:,:,1:myNgrains,i,e) ! ...plastic def grads
|
crystallite_partionedFp0(:,:,1:myNgrains,i,e) = crystallite_Fp0(:,:,1:myNgrains,i,e) ! ...plastic def grads
|
||||||
crystallite_partionedLp0(:,:,1:myNgrains,i,e) = crystallite_Lp0(:,:,1:myNgrains,i,e) ! ...plastic velocity grads
|
crystallite_partionedLp0(:,:,1:myNgrains,i,e) = crystallite_Lp0(:,:,1:myNgrains,i,e) ! ...plastic velocity grads
|
||||||
crystallite_partionedF0(:,:,1:myNgrains,i,e) = crystallite_F0(:,:,1:myNgrains,i,e) ! ...def grads
|
crystallite_partionedF0(:,:,1:myNgrains,i,e) = crystallite_F0(:,:,1:myNgrains,i,e) ! ...def grads
|
||||||
|
crystallite_partionedTstar0_v(:,1:myNgrains,i,e)= crystallite_Tstar0_v(:,1:myNgrains,i,e) ! ...2nd PK stress
|
||||||
|
|
||||||
! initialize restoration points of ...
|
! initialize restoration points of ...
|
||||||
if (homogenization_sizeState(i,e) > 0_pInt) &
|
if (homogenization_sizeState(i,e) > 0_pInt) &
|
||||||
homogenization_subState0(i,e)%p = homogenization_state0(i,e)%p ! ...internal homogenizaiton state
|
homogenization_subState0(i,e)%p = homogenization_state0(i,e)%p ! ...internal homogenization state
|
||||||
materialpoint_subF0(:,:,i,e) = materialpoint_F0(:,:,i,e) ! ...def grad
|
materialpoint_subF0(:,:,i,e) = materialpoint_F0(:,:,i,e) ! ...def grad
|
||||||
|
|
||||||
materialpoint_subFrac(i,e) = 0.0_pReal
|
materialpoint_subFrac(i,e) = 0.0_pReal
|
||||||
|
@ -227,29 +246,42 @@ subroutine materialpoint_stressAndItsTangent(&
|
||||||
do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over elements to be processed
|
do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over elements to be processed
|
||||||
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
||||||
do i = FEsolving_execIP(1,e),FEsolving_execIP(2,e) ! iterate over IPs of this element to be processed
|
do i = FEsolving_execIP(1,e),FEsolving_execIP(2,e) ! iterate over IPs of this element to be processed
|
||||||
|
|
||||||
|
! if our materialpoint converged then we are either finished or have to wind forward
|
||||||
if (materialpoint_converged(i,e)) then
|
if (materialpoint_converged(i,e)) then
|
||||||
|
|
||||||
|
! calculate new subStep and new subFrac
|
||||||
materialpoint_subFrac(i,e) = materialpoint_subFrac(i,e) + materialpoint_subStep(i,e)
|
materialpoint_subFrac(i,e) = materialpoint_subFrac(i,e) + materialpoint_subStep(i,e)
|
||||||
materialpoint_subStep(i,e) = min(1.0_pReal-materialpoint_subFrac(i,e), 2.0_pReal * materialpoint_subStep(i,e))
|
materialpoint_subStep(i,e) = min(1.0_pReal-materialpoint_subFrac(i,e), 2.0_pReal * materialpoint_subStep(i,e))
|
||||||
if (materialpoint_subStep(i,e) > subStepMin) then ! still stepping needed
|
|
||||||
|
! still stepping needed
|
||||||
|
if (materialpoint_subStep(i,e) > subStepMin) then
|
||||||
|
|
||||||
! wind forward grain starting point of...
|
! wind forward grain starting point of...
|
||||||
crystallite_partionedF0(:,:,1:myNgrains,i,e) = crystallite_partionedF(:,:,1:myNgrains,i,e) ! ...def grads
|
crystallite_partionedF0(:,:,1:myNgrains,i,e) = crystallite_partionedF(:,:,1:myNgrains,i,e) ! ...def grads
|
||||||
crystallite_partionedFp0(:,:,1:myNgrains,i,e) = crystallite_Fp(:,:,1:myNgrains,i,e) ! ...plastic def grads
|
crystallite_partionedFp0(:,:,1:myNgrains,i,e) = crystallite_Fp(:,:,1:myNgrains,i,e) ! ...plastic def grads
|
||||||
crystallite_partionedLp0(:,:,1:myNgrains,i,e) = crystallite_Lp(:,:,1:myNgrains,i,e) ! ...plastic velocity grads
|
crystallite_partionedLp0(:,:,1:myNgrains,i,e) = crystallite_Lp(:,:,1:myNgrains,i,e) ! ...plastic velocity grads
|
||||||
|
crystallite_partionedTstar0_v(:,1:myNgrains,i,e) = crystallite_Tstar_v(:,1:myNgrains,i,e) ! ...2nd PK stress
|
||||||
forall (g = 1:myNgrains) constitutive_partionedState0(g,i,e)%p = constitutive_state(g,i,e)%p ! ...microstructures
|
forall (g = 1:myNgrains) constitutive_partionedState0(g,i,e)%p = constitutive_state(g,i,e)%p ! ...microstructures
|
||||||
if (homogenization_sizeState(i,e) > 0_pInt) &
|
if (homogenization_sizeState(i,e) > 0_pInt) &
|
||||||
homogenization_subState0(i,e)%p = homogenization_state(i,e)%p ! ...internal state of homog scheme
|
homogenization_subState0(i,e)%p = homogenization_state(i,e)%p ! ...internal state of homog scheme
|
||||||
materialpoint_subF0(:,:,i,e) = materialpoint_subF(:,:,i,e) ! ...def grad
|
materialpoint_subF0(:,:,i,e) = materialpoint_subF(:,:,i,e) ! ...def grad
|
||||||
|
|
||||||
endif
|
endif
|
||||||
|
|
||||||
|
! materialpoint didn't converge, so we need a cutback here
|
||||||
else
|
else
|
||||||
materialpoint_subStep(i,e) = 0.5_pReal * materialpoint_subStep(i,e) ! cut step in half and restore...
|
|
||||||
|
|
||||||
! ####### why not resetting F0 ?!?!?
|
materialpoint_subStep(i,e) = 0.5_pReal * materialpoint_subStep(i,e)
|
||||||
|
|
||||||
|
! restore...
|
||||||
crystallite_Fp(:,:,1:myNgrains,i,e) = crystallite_partionedFp0(:,:,1:myNgrains,i,e) ! ...plastic def grads
|
crystallite_Fp(:,:,1:myNgrains,i,e) = crystallite_partionedFp0(:,:,1:myNgrains,i,e) ! ...plastic def grads
|
||||||
crystallite_Lp(:,:,1:myNgrains,i,e) = crystallite_partionedLp0(:,:,1:myNgrains,i,e) ! ...plastic velocity grads
|
crystallite_Lp(:,:,1:myNgrains,i,e) = crystallite_partionedLp0(:,:,1:myNgrains,i,e) ! ...plastic velocity grads
|
||||||
|
crystallite_Tstar_v(:,1:myNgrains,i,e) = crystallite_partionedTstar0_v(:,1:myNgrains,i,e) ! ...2nd PK stress
|
||||||
forall (g = 1:myNgrains) constitutive_state(g,i,e)%p = constitutive_partionedState0(g,i,e)%p ! ...microstructures
|
forall (g = 1:myNgrains) constitutive_state(g,i,e)%p = constitutive_partionedState0(g,i,e)%p ! ...microstructures
|
||||||
if (homogenization_sizeState(i,e) > 0_pInt) &
|
if (homogenization_sizeState(i,e) > 0_pInt) &
|
||||||
homogenization_state(i,e)%p = homogenization_subState0(i,e)%p ! ...internal state of homog scheme
|
homogenization_state(i,e)%p = homogenization_subState0(i,e)%p ! ...internal state of homog scheme
|
||||||
|
|
||||||
endif
|
endif
|
||||||
|
|
||||||
materialpoint_requested(i,e) = materialpoint_subStep(i,e) > subStepMin
|
materialpoint_requested(i,e) = materialpoint_subStep(i,e) > subStepMin
|
||||||
|
@ -403,7 +435,9 @@ subroutine homogenization_partitionDeformation(&
|
||||||
call homogenization_isostrain_partitionDeformation(crystallite_partionedF(:,:,:,ip,el), &
|
call homogenization_isostrain_partitionDeformation(crystallite_partionedF(:,:,:,ip,el), &
|
||||||
crystallite_partionedF0(:,:,:,ip,el),&
|
crystallite_partionedF0(:,:,:,ip,el),&
|
||||||
materialpoint_subF(:,:,ip,el),&
|
materialpoint_subF(:,:,ip,el),&
|
||||||
homogenization_state(ip,el),ip,el)
|
homogenization_state(ip,el), &
|
||||||
|
ip, &
|
||||||
|
el)
|
||||||
end select
|
end select
|
||||||
|
|
||||||
endsubroutine
|
endsubroutine
|
||||||
|
@ -430,9 +464,11 @@ function homogenization_updateState(&
|
||||||
|
|
||||||
select case(homogenization_type(mesh_element(3,el)))
|
select case(homogenization_type(mesh_element(3,el)))
|
||||||
case (homogenization_isostrain_label)
|
case (homogenization_isostrain_label)
|
||||||
homogenization_updateState = &
|
homogenization_updateState = homogenization_isostrain_updateState( homogenization_state(ip,el), &
|
||||||
homogenization_isostrain_updateState(homogenization_state(ip,el), &
|
crystallite_P(:,:,:,ip,el), &
|
||||||
crystallite_P(:,:,:,ip,el),crystallite_dPdF(:,:,:,:,:,ip,el),ip,el)
|
crystallite_dPdF(:,:,:,:,:,ip,el), &
|
||||||
|
ip, &
|
||||||
|
el)
|
||||||
end select
|
end select
|
||||||
|
|
||||||
return
|
return
|
||||||
|
@ -459,8 +495,12 @@ subroutine homogenization_averageStressAndItsTangent(&
|
||||||
|
|
||||||
select case(homogenization_type(mesh_element(3,el)))
|
select case(homogenization_type(mesh_element(3,el)))
|
||||||
case (homogenization_isostrain_label)
|
case (homogenization_isostrain_label)
|
||||||
call homogenization_isostrain_averageStressAndItsTangent(materialpoint_P(:,:,ip,el), materialpoint_dPdF(:,:,:,:,ip,el),&
|
call homogenization_isostrain_averageStressAndItsTangent( materialpoint_P(:,:,ip,el), &
|
||||||
crystallite_P(:,:,:,ip,el),crystallite_dPdF(:,:,:,:,:,ip,el),ip,el)
|
materialpoint_dPdF(:,:,:,:,ip,el),&
|
||||||
|
crystallite_P(:,:,:,ip,el), &
|
||||||
|
crystallite_dPdF(:,:,:,:,:,ip,el), &
|
||||||
|
ip, &
|
||||||
|
el)
|
||||||
end select
|
end select
|
||||||
|
|
||||||
return
|
return
|
||||||
|
|
Loading…
Reference in New Issue