all nonlocal parts are fully explicit
i.e. they are based on converged (partioned0) states
This commit is contained in:
parent
f854dc27e9
commit
5d4d1dcf9a
|
@ -232,12 +232,12 @@ module constitutive
|
|||
of
|
||||
end subroutine plastic_disloUCLA_dependentState
|
||||
|
||||
module subroutine plastic_nonlocal_dependentState(Fe, Fp, ip, el)
|
||||
module subroutine plastic_nonlocal_dependentState(F, Fp, ip, el)
|
||||
integer, intent(in) :: &
|
||||
ip, &
|
||||
el
|
||||
real(pReal), dimension(3,3), intent(in) :: &
|
||||
Fe, &
|
||||
F, &
|
||||
Fp
|
||||
end subroutine plastic_nonlocal_dependentState
|
||||
|
||||
|
@ -412,14 +412,14 @@ end function constitutive_homogenizedC
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief calls microstructure function of the different constitutive models
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine constitutive_microstructure(Fe, Fp, ipc, ip, el)
|
||||
subroutine constitutive_microstructure(F, Fp, ipc, ip, el)
|
||||
|
||||
integer, intent(in) :: &
|
||||
ipc, & !< component-ID of integration point
|
||||
ip, & !< integration point
|
||||
el !< element
|
||||
real(pReal), intent(in), dimension(3,3) :: &
|
||||
Fe, & !< elastic deformation gradient
|
||||
F, & !< elastic deformation gradient
|
||||
Fp !< plastic deformation gradient
|
||||
integer :: &
|
||||
ho, & !< homogenization
|
||||
|
@ -439,7 +439,7 @@ subroutine constitutive_microstructure(Fe, Fp, ipc, ip, el)
|
|||
instance = phase_plasticityInstance(material_phaseAt(ipc,el))
|
||||
call plastic_disloUCLA_dependentState(instance,of)
|
||||
case (PLASTICITY_NONLOCAL_ID) plasticityType
|
||||
call plastic_nonlocal_dependentState (Fe,Fp,ip,el)
|
||||
call plastic_nonlocal_dependentState (F,Fp,ip,el)
|
||||
end select plasticityType
|
||||
|
||||
end subroutine constitutive_microstructure
|
||||
|
|
|
@ -716,13 +716,13 @@ end subroutine plastic_nonlocal_init
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief calculates quantities characterizing the microstructure
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module subroutine plastic_nonlocal_dependentState(Fe, Fp, ip, el)
|
||||
module subroutine plastic_nonlocal_dependentState(F, Fp, ip, el)
|
||||
|
||||
integer, intent(in) :: &
|
||||
ip, &
|
||||
el
|
||||
real(pReal), dimension(3,3), intent(in) :: &
|
||||
Fe, &
|
||||
F, &
|
||||
Fp
|
||||
|
||||
integer :: &
|
||||
|
@ -765,7 +765,8 @@ module subroutine plastic_nonlocal_dependentState(Fe, Fp, ip, el)
|
|||
rho_scr_delta
|
||||
real(pReal), dimension(totalNslip(phase_plasticityInstance(material_phaseAt(1,el))),10) :: &
|
||||
rho, &
|
||||
rho_neighbor
|
||||
rho0, &
|
||||
rho_neighbor0
|
||||
real(pReal), dimension(totalNslip(phase_plasticityInstance(material_phaseAt(1,el))), &
|
||||
totalNslip(phase_plasticityInstance(material_phaseAt(1,el)))) :: &
|
||||
myInteractionMatrix ! corrected slip interaction matrix
|
||||
|
@ -795,7 +796,7 @@ module subroutine plastic_nonlocal_dependentState(Fe, Fp, ip, el)
|
|||
|
||||
! coefficients are corrected for the line tension effect
|
||||
! (see Kubin,Devincre,Hoc; 2008; Modeling dislocation storage rates and mean free paths in face-centered cubic crystals)
|
||||
if (lattice_structure(ph) == LATTICE_bcc_ID .or. lattice_structure(ph) == LATTICE_fcc_ID) then ! only fcc and bcc
|
||||
if (lattice_structure(ph) == LATTICE_bcc_ID .or. lattice_structure(ph) == LATTICE_fcc_ID) then
|
||||
do s = 1,ns
|
||||
correction = ( 1.0_pReal - prm%linetensionEffect &
|
||||
+ prm%linetensionEffect &
|
||||
|
@ -819,13 +820,13 @@ module subroutine plastic_nonlocal_dependentState(Fe, Fp, ip, el)
|
|||
! ToDo: MD: this is most likely only correct for F_i = I
|
||||
!#################################################################################################
|
||||
|
||||
|
||||
rho0 = getRho0(instance,of,ip,el)
|
||||
if (.not. phase_localPlasticity(ph) .and. prm%shortRangeStressCorrection) then
|
||||
invFe = math_inv33(Fe)
|
||||
invFp = math_inv33(Fp)
|
||||
invFe = matmul(Fp,math_inv33(F))
|
||||
|
||||
rho_edg_delta = rho(:,mob_edg_pos) - rho(:,mob_edg_neg)
|
||||
rho_scr_delta = rho(:,mob_scr_pos) - rho(:,mob_scr_neg)
|
||||
rho_edg_delta = rho0(:,mob_edg_pos) - rho0(:,mob_edg_neg)
|
||||
rho_scr_delta = rho0(:,mob_scr_pos) - rho0(:,mob_scr_neg)
|
||||
|
||||
rhoExcess(1,1:ns) = rho_edg_delta
|
||||
rhoExcess(2,1:ns) = rho_scr_delta
|
||||
|
@ -845,13 +846,13 @@ module subroutine plastic_nonlocal_dependentState(Fe, Fp, ip, el)
|
|||
if (neighbor_instance == instance) then
|
||||
|
||||
nRealNeighbors = nRealNeighbors + 1.0_pReal
|
||||
rho_neighbor = getRho(instance,no,neighbor_ip,neighbor_el)
|
||||
rho_neighbor0 = getRho0(instance,no,neighbor_ip,neighbor_el)
|
||||
|
||||
rho_edg_delta_neighbor(:,n) = rho_neighbor(:,mob_edg_pos) - rho_neighbor(:,mob_edg_neg)
|
||||
rho_scr_delta_neighbor(:,n) = rho_neighbor(:,mob_scr_pos) - rho_neighbor(:,mob_scr_neg)
|
||||
rho_edg_delta_neighbor(:,n) = rho_neighbor0(:,mob_edg_pos) - rho_neighbor0(:,mob_edg_neg)
|
||||
rho_scr_delta_neighbor(:,n) = rho_neighbor0(:,mob_scr_pos) - rho_neighbor0(:,mob_scr_neg)
|
||||
|
||||
neighbor_rhoTotal(1,:,n) = sum(abs(rho_neighbor(:,edg)),2)
|
||||
neighbor_rhoTotal(2,:,n) = sum(abs(rho_neighbor(:,scr)),2)
|
||||
neighbor_rhoTotal(1,:,n) = sum(abs(rho_neighbor0(:,edg)),2)
|
||||
neighbor_rhoTotal(2,:,n) = sum(abs(rho_neighbor0(:,scr)),2)
|
||||
|
||||
connection_latticeConf(1:3,n) = matmul(invFe, discretization_IPcoords(1:3,neighbor_el+neighbor_ip-1) &
|
||||
- discretization_IPcoords(1:3,el+neighbor_ip-1))
|
||||
|
|
|
@ -264,8 +264,8 @@ subroutine crystallite_init
|
|||
do e = FEsolving_execElem(1),FEsolving_execElem(2)
|
||||
do i = FEsolving_execIP(1),FEsolving_execIP(2)
|
||||
do c = 1,homogenization_Ngrains(material_homogenizationAt(e))
|
||||
call constitutive_microstructure(crystallite_Fe(1:3,1:3,c,i,e), &
|
||||
crystallite_Fp(1:3,1:3,c,i,e), &
|
||||
call constitutive_microstructure(crystallite_partionedF0(1:3,1:3,c,i,e), &
|
||||
crystallite_partionedFp0(1:3,1:3,c,i,e), &
|
||||
c,i,e) ! update dependent state variables to be consistent with basic states
|
||||
enddo
|
||||
enddo
|
||||
|
|
Loading…
Reference in New Issue