adapted nonlocal
This commit is contained in:
parent
7ac552ee49
commit
715bc1bb83
|
@ -116,8 +116,7 @@ submodule(phase:plastic) nonlocal
|
||||||
character(len=pSTRLEN), dimension(:), allocatable :: &
|
character(len=pSTRLEN), dimension(:), allocatable :: &
|
||||||
output
|
output
|
||||||
logical :: &
|
logical :: &
|
||||||
shortRangeStressCorrection, & !< use of short range stress correction by excess density gradient term
|
shortRangeStressCorrection !< use of short range stress correction by excess density gradient term
|
||||||
nonSchmidActive = .false.
|
|
||||||
character(len=:), allocatable, dimension(:) :: &
|
character(len=:), allocatable, dimension(:) :: &
|
||||||
systems_sl
|
systems_sl
|
||||||
end type tParameters
|
end type tParameters
|
||||||
|
@ -125,7 +124,7 @@ submodule(phase:plastic) nonlocal
|
||||||
type :: tNonlocalDependentState
|
type :: tNonlocalDependentState
|
||||||
real(pREAL), allocatable, dimension(:,:) :: &
|
real(pREAL), allocatable, dimension(:,:) :: &
|
||||||
tau_pass, &
|
tau_pass, &
|
||||||
tau_Back
|
tau_back
|
||||||
real(pREAL), allocatable, dimension(:,:,:,:,:) :: &
|
real(pREAL), allocatable, dimension(:,:,:,:,:) :: &
|
||||||
compatibility
|
compatibility
|
||||||
end type tNonlocalDependentState
|
end type tNonlocalDependentState
|
||||||
|
@ -150,10 +149,10 @@ submodule(phase:plastic) nonlocal
|
||||||
rho_forest, &
|
rho_forest, &
|
||||||
gamma, &
|
gamma, &
|
||||||
v, &
|
v, &
|
||||||
v_edg_pos, &
|
v_edg_pos, &
|
||||||
v_edg_neg, &
|
v_edg_neg, &
|
||||||
v_scr_pos, &
|
v_scr_pos, &
|
||||||
v_scr_neg
|
v_scr_neg
|
||||||
end type tNonlocalState
|
end type tNonlocalState
|
||||||
|
|
||||||
type(tNonlocalState), allocatable, dimension(:) :: &
|
type(tNonlocalState), allocatable, dimension(:) :: &
|
||||||
|
@ -176,14 +175,13 @@ module function plastic_nonlocal_init() result(myPlasticity)
|
||||||
|
|
||||||
logical, dimension(:), allocatable :: myPlasticity
|
logical, dimension(:), allocatable :: myPlasticity
|
||||||
integer :: &
|
integer :: &
|
||||||
Ninstances, &
|
|
||||||
ph, &
|
ph, &
|
||||||
Nmembers, &
|
Nmembers, &
|
||||||
sizeState, sizeDotState, sizeDependentState, sizeDeltaState, &
|
sizeState, sizeDotState, sizeDependentState, sizeDeltaState, &
|
||||||
s1, s2, &
|
s1, s2, &
|
||||||
s, t, l
|
s, t, l
|
||||||
real(pREAL), dimension(:), allocatable :: &
|
real(pREAL), dimension(:,:), allocatable :: &
|
||||||
a
|
a_nS !< non-Schmid coefficients
|
||||||
character(len=:), allocatable :: &
|
character(len=:), allocatable :: &
|
||||||
refs, &
|
refs, &
|
||||||
extmsg
|
extmsg
|
||||||
|
@ -196,8 +194,7 @@ module function plastic_nonlocal_init() result(myPlasticity)
|
||||||
pl
|
pl
|
||||||
|
|
||||||
myPlasticity = plastic_active('nonlocal')
|
myPlasticity = plastic_active('nonlocal')
|
||||||
Ninstances = count(myPlasticity)
|
if (count(myPlasticity) == 0) then
|
||||||
if (Ninstances == 0) then
|
|
||||||
call geometry_plastic_nonlocal_disable()
|
call geometry_plastic_nonlocal_disable()
|
||||||
return
|
return
|
||||||
end if
|
end if
|
||||||
|
@ -210,7 +207,7 @@ module function plastic_nonlocal_init() result(myPlasticity)
|
||||||
print'(/,1x,a)', 'C. Kords, Dissertation RWTH Aachen, 2014'
|
print'(/,1x,a)', 'C. Kords, Dissertation RWTH Aachen, 2014'
|
||||||
print'( 1x,a)', 'http://publications.rwth-aachen.de/record/229993'
|
print'( 1x,a)', 'http://publications.rwth-aachen.de/record/229993'
|
||||||
|
|
||||||
print'(/,1x,a,1x,i0)', '# phases:',Ninstances; flush(IO_STDOUT)
|
print'(/,1x,a,1x,i0)', '# phases:',count(myPlasticity); flush(IO_STDOUT)
|
||||||
|
|
||||||
phases => config_material%get_dict('phase')
|
phases => config_material%get_dict('phase')
|
||||||
allocate(geom(phases%length))
|
allocate(geom(phases%length))
|
||||||
|
@ -253,13 +250,13 @@ module function plastic_nonlocal_init() result(myPlasticity)
|
||||||
prm%P_sl = crystal_SchmidMatrix_slip(ini%N_sl,phase_lattice(ph), phase_cOverA(ph))
|
prm%P_sl = crystal_SchmidMatrix_slip(ini%N_sl,phase_lattice(ph), phase_cOverA(ph))
|
||||||
|
|
||||||
if (phase_lattice(ph) == 'cI') then
|
if (phase_lattice(ph) == 'cI') then
|
||||||
a = pl%get_as1dReal('a_nonSchmid_110',defaultVal = emptyRealArray)
|
allocate(a_nS(3,size(pl%get_as1dReal('a_nonSchmid_110',defaultVal=emptyRealArray))),source=0.0_pREAL) ! anticipating parameters for all three families
|
||||||
if (size(a) > 0) prm%nonSchmidActive = .true.
|
a_nS(1,:) = pl%get_as1dReal('a_nonSchmid_110',defaultVal=emptyRealArray)
|
||||||
prm%P_nS_pos = crystal_nonSchmidMatrix(ini%N_sl,a,+1)
|
prm%P_nS_pos = crystal_SchmidMatrix_slip(ini%N_sl,phase_lattice(ph),phase_cOverA(ph),nonSchmidCoefficients=a_nS,sense=+1)
|
||||||
prm%P_nS_neg = crystal_nonSchmidMatrix(ini%N_sl,a,-1)
|
prm%P_nS_neg = crystal_SchmidMatrix_slip(ini%N_sl,phase_lattice(ph),phase_cOverA(ph),nonSchmidCoefficients=a_nS,sense=-1)
|
||||||
else
|
else
|
||||||
prm%P_nS_pos = prm%P_sl
|
prm%P_nS_pos = +prm%P_sl
|
||||||
prm%P_nS_neg = prm%P_sl
|
prm%P_nS_neg = -prm%P_sl
|
||||||
end if
|
end if
|
||||||
|
|
||||||
prm%h_sl_sl = crystal_interaction_SlipBySlip(ini%N_sl,pl%get_as1dReal('h_sl-sl'), &
|
prm%h_sl_sl = crystal_interaction_SlipBySlip(ini%N_sl,pl%get_as1dReal('h_sl-sl'), &
|
||||||
|
@ -801,16 +798,10 @@ module subroutine nonlocal_LpAndItsTangent(Lp,dLp_dMp, &
|
||||||
dv_dtauNS(:,2) = dv_dtauNS(:,1)
|
dv_dtauNS(:,2) = dv_dtauNS(:,1)
|
||||||
|
|
||||||
!screws
|
!screws
|
||||||
if (prm%nonSchmidActive) then
|
do t = 3,4
|
||||||
do t = 3,4
|
call kinetics(v(:,t), dv_dtau(:,t), dv_dtauNS(:,t), &
|
||||||
call kinetics(v(:,t), dv_dtau(:,t), dv_dtauNS(:,t), &
|
tau, tauNS(:,t), dst%tau_pass(:,en),2,Temperature, ph)
|
||||||
tau, tauNS(:,t), dst%tau_pass(:,en),2,Temperature, ph)
|
end do
|
||||||
end do
|
|
||||||
else
|
|
||||||
v(:,3:4) = spread(v(:,1),2,2)
|
|
||||||
dv_dtau(:,3:4) = spread(dv_dtau(:,1),2,2)
|
|
||||||
dv_dtauNS(:,3:4) = spread(dv_dtauNS(:,1),2,2)
|
|
||||||
end if
|
|
||||||
|
|
||||||
stt%v(:,en) = pack(v,.true.)
|
stt%v(:,en) = pack(v,.true.)
|
||||||
|
|
||||||
|
@ -1592,12 +1583,12 @@ pure subroutine kinetics(v, dv_dtau, dv_dtauNS, tau, tauNS, tauThreshold, c, T,
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
c, & !< dislocation character (1:edge, 2:screw)
|
c, & !< dislocation character (1:edge, 2:screw)
|
||||||
ph
|
ph
|
||||||
real(pREAL), intent(in) :: &
|
|
||||||
T !< T
|
|
||||||
real(pREAL), dimension(param(ph)%sum_N_sl), intent(in) :: &
|
real(pREAL), dimension(param(ph)%sum_N_sl), intent(in) :: &
|
||||||
tau, & !< resolved external shear stress (without non Schmid effects)
|
tau, & !< resolved external shear stress (without non Schmid effects)
|
||||||
tauNS, & !< resolved external shear stress (including non Schmid effects)
|
tauNS, & !< resolved external shear stress (including non Schmid effects)
|
||||||
tauThreshold !< threshold shear stress
|
tauThreshold !< threshold shear stress
|
||||||
|
real(pREAL), intent(in) :: &
|
||||||
|
T !< T
|
||||||
real(pREAL), dimension(param(ph)%sum_N_sl), intent(out) :: &
|
real(pREAL), dimension(param(ph)%sum_N_sl), intent(out) :: &
|
||||||
v, & !< velocity
|
v, & !< velocity
|
||||||
dv_dtau, & !< velocity derivative with respect to resolved shear stress (without non Schmid contributions)
|
dv_dtau, & !< velocity derivative with respect to resolved shear stress (without non Schmid contributions)
|
||||||
|
@ -1634,7 +1625,7 @@ pure subroutine kinetics(v, dv_dtau, dv_dtauNS, tau, tauNS, tauThreshold, c, T,
|
||||||
!* Peierls contribution
|
!* Peierls contribution
|
||||||
tauEff = max(0.0_pREAL, abs(tauNS(s)) - tauThreshold(s))
|
tauEff = max(0.0_pREAL, abs(tauNS(s)) - tauThreshold(s))
|
||||||
lambda_P = prm%b_sl(s)
|
lambda_P = prm%b_sl(s)
|
||||||
activationVolume_P = prm%w *prm%b_sl(s)**3
|
activationVolume_P = prm%w * prm%b_sl(s)**3
|
||||||
criticalStress_P = prm%peierlsStress(s,c)
|
criticalStress_P = prm%peierlsStress(s,c)
|
||||||
activationEnergy_P = criticalStress_P * activationVolume_P
|
activationEnergy_P = criticalStress_P * activationVolume_P
|
||||||
tauRel_P = min(1.0_pREAL, tauEff / criticalStress_P)
|
tauRel_P = min(1.0_pREAL, tauEff / criticalStress_P)
|
||||||
|
|
Loading…
Reference in New Issue