rho_forest is a dependent state

This commit is contained in:
Martin Diehl 2023-12-22 22:37:47 +01:00
parent af5bbed003
commit 696cccaa66
No known key found for this signature in database
GPG Key ID: 1FD50837275A0A9B
1 changed files with 18 additions and 19 deletions

View File

@ -124,7 +124,8 @@ submodule(phase:plastic) nonlocal
type :: tNonlocalDependentState
real(pREAL), allocatable, dimension(:,:) :: &
tau_pass, &
tau_back
tau_back, &
rho_forest
real(pREAL), allocatable, dimension(:,:,:,:,:) :: &
compatibility
end type tNonlocalDependentState
@ -146,7 +147,6 @@ submodule(phase:plastic) nonlocal
rhoDip, &
rho_dip_edg, &
rho_dip_scr, &
rho_forest, &
gamma, &
v, &
v_edg_pos, &
@ -177,7 +177,7 @@ module function plastic_nonlocal_init() result(myPlasticity)
integer :: &
ph, &
Nmembers, &
sizeState, sizeDotState, sizeDependentState, sizeDeltaState, &
sizeState, sizeDotState, sizeDeltaState, &
s1, s2, &
s, t, l
real(pREAL), dimension(:,:), allocatable :: &
@ -389,8 +389,7 @@ module function plastic_nonlocal_init() result(myPlasticity)
'rhoSglScrewPosImmobile','rhoSglScrewNegImmobile', &
'rhoDipEdge ','rhoDipScrew ', &
'gamma ' ]) * prm%sum_N_sl !< "basic" microstructural state variables that are independent from other state variables
sizeDependentState = size([ 'rhoForest ']) * prm%sum_N_sl !< microstructural state variables that depend on other state variables
sizeState = sizeDotState + sizeDependentState &
sizeState = sizeDotState &
+ size([ 'velocityEdgePos ','velocityEdgeNeg ', &
'velocityScrewPos ','velocityScrewNeg ', &
'maxDipoleHeightEdge ','maxDipoleHeightScrew' ]) * prm%sum_N_sl !< other dependent state variables that are not updated by microstructure
@ -477,15 +476,15 @@ module function plastic_nonlocal_init() result(myPlasticity)
if (any(plasticState(ph)%atol(10*prm%sum_N_sl+1:11*prm%sum_N_sl) < 0.0_pREAL)) &
extmsg = trim(extmsg)//' atol_gamma'
stt%rho_forest => plasticState(ph)%state (11*prm%sum_N_sl + 1:12*prm%sum_N_sl,1:Nmembers)
stt%v => plasticState(ph)%state (12*prm%sum_N_sl + 1:16*prm%sum_N_sl,1:Nmembers)
stt%v_edg_pos => plasticState(ph)%state (12*prm%sum_N_sl + 1:13*prm%sum_N_sl,1:Nmembers)
stt%v_edg_neg => plasticState(ph)%state (13*prm%sum_N_sl + 1:14*prm%sum_N_sl,1:Nmembers)
stt%v_scr_pos => plasticState(ph)%state (14*prm%sum_N_sl + 1:15*prm%sum_N_sl,1:Nmembers)
stt%v_scr_neg => plasticState(ph)%state (15*prm%sum_N_sl + 1:16*prm%sum_N_sl,1:Nmembers)
stt%v => plasticState(ph)%state (11*prm%sum_N_sl + 1:15*prm%sum_N_sl,1:Nmembers)
stt%v_edg_pos => plasticState(ph)%state (11*prm%sum_N_sl + 1:12*prm%sum_N_sl,1:Nmembers)
stt%v_edg_neg => plasticState(ph)%state (12*prm%sum_N_sl + 1:13*prm%sum_N_sl,1:Nmembers)
stt%v_scr_pos => plasticState(ph)%state (13*prm%sum_N_sl + 1:14*prm%sum_N_sl,1:Nmembers)
stt%v_scr_neg => plasticState(ph)%state (14*prm%sum_N_sl + 1:15*prm%sum_N_sl,1:Nmembers)
allocate(dst%tau_pass(prm%sum_N_sl,Nmembers),source=0.0_pREAL)
allocate(dst%tau_back(prm%sum_N_sl,Nmembers),source=0.0_pREAL)
allocate(dst%rho_forest(prm%sum_N_sl,Nmembers),source=0.0_pREAL)
allocate(dst%compatibility(2,maxval(param%sum_N_sl),maxval(param%sum_N_sl),nIPneighbors,Nmembers),source=0.0_pREAL)
end associate
@ -518,7 +517,7 @@ module function plastic_nonlocal_init() result(myPlasticity)
iRhoU(s,t,ph) = l
end do
end do
l = l + (4+2+1+1)*param(ph)%sum_N_sl ! immobile(4), dipole(2), shear, forest
l = l + (4+2+1)*param(ph)%sum_N_sl ! immobile(4), dipole(2), shear
do t = 1,4
do s = 1,param(ph)%sum_N_sl
l = l + 1
@ -602,7 +601,7 @@ module subroutine nonlocal_dependentState(ph, en)
nu = elastic_nu(ph,en,prm%isotropic_bound)
rho = getRho(ph,en)
stt%rho_forest(:,en) = matmul(prm%forestProjection_Edge, sum(abs(rho(:,edg)),2)) &
dst%rho_forest(:,en) = matmul(prm%forestProjection_Edge, sum(abs(rho(:,edg)),2)) &
+ matmul(prm%forestProjection_Screw,sum(abs(rho(:,scr)),2))
@ -612,7 +611,7 @@ module subroutine nonlocal_dependentState(ph, en)
myInteractionMatrix = prm%h_sl_sl &
* spread(( 1.0_pREAL - prm%f_F &
+ prm%f_F &
* log(0.35_pREAL * prm%b_sl * sqrt(max(stt%rho_forest(:,en),prm%rho_significant))) &
* log(0.35_pREAL * prm%b_sl * sqrt(max(dst%rho_forest(:,en),prm%rho_significant))) &
/ log(0.35_pREAL * prm%b_sl * 1e6_pREAL))**2,2,prm%sum_N_sl)
else
myInteractionMatrix = prm%h_sl_sl
@ -1018,17 +1017,17 @@ module subroutine nonlocal_dotState(Mp,timestep, &
isBCC: if (phase_lattice(ph) == 'cI') then
forall (s = 1:prm%sum_N_sl, sum(abs(v(s,1:4))) > 0.0_pREAL)
rhoDotMultiplication(s,1:2) = sum(abs(dot_gamma(s,3:4))) / prm%b_sl(s) & ! assuming double-cross-slip of screws to be decisive for multiplication
* sqrt(stt%rho_forest(s,en)) / prm%i_sl(s) ! & ! mean free path
* sqrt(dst%rho_forest(s,en)) / prm%i_sl(s) ! & ! mean free path
! * 2.0_pREAL * sum(abs(v(s,3:4))) / sum(abs(v(s,1:4))) ! ratio of screw to overall velocity determines edge generation
rhoDotMultiplication(s,3:4) = sum(abs(dot_gamma(s,3:4))) /prm%b_sl(s) & ! assuming double-cross-slip of screws to be decisive for multiplication
* sqrt(stt%rho_forest(s,en)) / prm%i_sl(s) ! & ! mean free path
* sqrt(dst%rho_forest(s,en)) / prm%i_sl(s) ! & ! mean free path
! * 2.0_pREAL * sum(abs(v(s,1:2))) / sum(abs(v(s,1:4))) ! ratio of edge to overall velocity determines screw generation
endforall
else isBCC
rhoDotMultiplication(:,1:4) = spread( &
(sum(abs(dot_gamma(:,1:2)),2) * prm%f_ed_mult + sum(abs(dot_gamma(:,3:4)),2)) &
* sqrt(stt%rho_forest(:,en)) / prm%i_sl / prm%b_sl, 2, 4) ! eq. 3.26
* sqrt(dst%rho_forest(:,en)) / prm%i_sl / prm%b_sl, 2, 4) ! eq. 3.26
end if isBCC
forall (s = 1:prm%sum_N_sl, t = 1:4) v0(s,t) = plasticState(ph)%state0(iV(s,t,ph),en)
@ -1074,7 +1073,7 @@ module subroutine nonlocal_dotState(Mp,timestep, &
if (phase_lattice(ph) == 'cF') &
forall (s = 1:prm%sum_N_sl, prm%colinearSystem(s) > 0) &
rhoDotAthermalAnnihilation(prm%colinearSystem(s),1:2) = - rhoDotAthermalAnnihilation(s,10) &
* 0.25_pREAL * sqrt(stt%rho_forest(s,en)) * (dUpper(s,2) + dLower(s,2)) * prm%f_ed
* 0.25_pREAL * sqrt(dst%rho_forest(s,en)) * (dUpper(s,2) + dLower(s,2)) * prm%f_ed
! thermally activated annihilation of edge dipoles by climb
@ -1486,7 +1485,7 @@ module subroutine plastic_nonlocal_result(ph,group)
call result_writeDataset(stt%rho_dip_scr,group,trim(prm%output(ou)), &
'screw dipole density','1/m²', prm%systems_sl)
case('rho_f')
call result_writeDataset(stt%rho_forest,group,trim(prm%output(ou)), &
call result_writeDataset(dst%rho_forest,group,trim(prm%output(ou)), &
'forest density','1/m²', prm%systems_sl)
case('v_ed_pos')
call result_writeDataset(stt%v_edg_pos,group,trim(prm%output(ou)), &