simplified
This commit is contained in:
parent
d2855913b5
commit
fc4bdfb374
|
@ -623,7 +623,7 @@ module subroutine nonlocal_dependentState(ph, en, ip, el)
|
||||||
|
|
||||||
! coefficients are corrected for the line tension effect
|
! 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)
|
! (see Kubin,Devincre,Hoc; 2008; Modeling dislocation storage rates and mean free paths in face-centered cubic crystals)
|
||||||
if (any(lattice_structure(material_phaseAt(1,el)) == [LATTICE_bcc_ID,LATTICE_fcc_ID])) then
|
if (any(lattice_structure(ph) == [LATTICE_bcc_ID,LATTICE_fcc_ID])) then
|
||||||
myInteractionMatrix = prm%h_sl_sl &
|
myInteractionMatrix = prm%h_sl_sl &
|
||||||
* spread(( 1.0_pReal - prm%f_F &
|
* spread(( 1.0_pReal - prm%f_F &
|
||||||
+ prm%f_F &
|
+ prm%f_F &
|
||||||
|
@ -644,7 +644,7 @@ module subroutine nonlocal_dependentState(ph, en, ip, el)
|
||||||
!#################################################################################################
|
!#################################################################################################
|
||||||
|
|
||||||
rho0 = getRho0(ph,en)
|
rho0 = getRho0(ph,en)
|
||||||
if (.not. phase_localPlasticity(material_phaseAt(1,el)) .and. prm%shortRangeStressCorrection) then
|
if (.not. phase_localPlasticity(ph) .and. prm%shortRangeStressCorrection) then
|
||||||
invFp = math_inv33(phase_mechanical_Fp(ph)%data(1:3,1:3,en))
|
invFp = math_inv33(phase_mechanical_Fp(ph)%data(1:3,1:3,en))
|
||||||
invFe = math_inv33(phase_mechanical_Fe(ph)%data(1:3,1:3,en))
|
invFe = math_inv33(phase_mechanical_Fe(ph)%data(1:3,1:3,en))
|
||||||
|
|
||||||
|
@ -1238,7 +1238,7 @@ function rhoDotFlux(timestep,ph,en,ip,el)
|
||||||
!****************************************************************************
|
!****************************************************************************
|
||||||
!*** calculate dislocation fluxes (only for nonlocal plasticity)
|
!*** calculate dislocation fluxes (only for nonlocal plasticity)
|
||||||
rhoDotFlux = 0.0_pReal
|
rhoDotFlux = 0.0_pReal
|
||||||
if (.not. phase_localPlasticity(material_phaseAt(1,el))) then
|
if (.not. phase_localPlasticity(ph)) then
|
||||||
|
|
||||||
!*** check CFL (Courant-Friedrichs-Lewy) condition for flux
|
!*** check CFL (Courant-Friedrichs-Lewy) condition for flux
|
||||||
if (any( abs(gdot) > 0.0_pReal & ! any active slip system ...
|
if (any( abs(gdot) > 0.0_pReal & ! any active slip system ...
|
||||||
|
@ -1579,21 +1579,20 @@ end subroutine plastic_nonlocal_results
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief populates the initial dislocation density
|
!> @brief populates the initial dislocation density
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine stateInit(ini,phase,Nmembers)
|
subroutine stateInit(ini,phase,Nentries)
|
||||||
|
|
||||||
type(tInitialParameters) :: &
|
type(tInitialParameters) :: &
|
||||||
ini
|
ini
|
||||||
integer,intent(in) :: &
|
integer,intent(in) :: &
|
||||||
phase, &
|
phase, &
|
||||||
Nmembers
|
Nentries
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
i, &
|
|
||||||
e, &
|
e, &
|
||||||
f, &
|
f, &
|
||||||
from, &
|
from, &
|
||||||
upto, &
|
upto, &
|
||||||
s, &
|
s
|
||||||
phasemember
|
|
||||||
real(pReal), dimension(2) :: &
|
real(pReal), dimension(2) :: &
|
||||||
noise, &
|
noise, &
|
||||||
rnd
|
rnd
|
||||||
|
@ -1602,49 +1601,42 @@ subroutine stateInit(ini,phase,Nmembers)
|
||||||
totalVolume, &
|
totalVolume, &
|
||||||
densityBinning, &
|
densityBinning, &
|
||||||
minimumIpVolume
|
minimumIpVolume
|
||||||
real(pReal), dimension(Nmembers) :: &
|
|
||||||
volume
|
|
||||||
|
|
||||||
|
|
||||||
associate(stt => state(phase))
|
associate(stt => state(phase))
|
||||||
|
|
||||||
if (ini%random_rho_u > 0.0_pReal) then ! randomly distribute dislocation segments on random slip system and of random type in the volume
|
if (ini%random_rho_u > 0.0_pReal) then ! randomly distribute dislocation segments on random slip system and of random type in the volume
|
||||||
do e = 1,discretization_Nelems
|
totalVolume = sum(geom(phase)%V_0)
|
||||||
do i = 1,discretization_nIPs
|
minimumIPVolume = minval(geom(phase)%V_0)
|
||||||
if (material_phaseAt(1,e) == phase) volume(material_phasememberAt(1,i,e)) = IPvolume(i,e)
|
densityBinning = ini%random_rho_u_binning / minimumIpVolume ** (2.0_pReal / 3.0_pReal)
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
totalVolume = sum(volume)
|
|
||||||
minimumIPVolume = minval(volume)
|
|
||||||
densityBinning = ini%random_rho_u_binning / minimumIpVolume ** (2.0_pReal / 3.0_pReal)
|
|
||||||
|
|
||||||
! fill random material points with dislocation segments until the desired overall density is reached
|
! fill random material points with dislocation segments until the desired overall density is reached
|
||||||
meanDensity = 0.0_pReal
|
meanDensity = 0.0_pReal
|
||||||
do while(meanDensity < ini%random_rho_u)
|
do while(meanDensity < ini%random_rho_u)
|
||||||
call random_number(rnd)
|
call random_number(rnd)
|
||||||
phasemember = nint(rnd(1)*real(Nmembers,pReal) + 0.5_pReal)
|
e = nint(rnd(1)*real(Nentries,pReal) + 0.5_pReal)
|
||||||
s = nint(rnd(2)*real(sum(ini%N_sl),pReal)*4.0_pReal + 0.5_pReal)
|
s = nint(rnd(2)*real(sum(ini%N_sl),pReal)*4.0_pReal + 0.5_pReal)
|
||||||
meanDensity = meanDensity + densityBinning * volume(phasemember) / totalVolume
|
meanDensity = meanDensity + densityBinning * geom(phase)%V_0(e) / totalVolume
|
||||||
stt%rhoSglMobile(s,phasemember) = densityBinning
|
stt%rhoSglMobile(s,e) = densityBinning
|
||||||
enddo
|
|
||||||
else ! homogeneous distribution with noise
|
|
||||||
do e = 1, Nmembers
|
|
||||||
do f = 1,size(ini%N_sl,1)
|
|
||||||
from = 1 + sum(ini%N_sl(1:f-1))
|
|
||||||
upto = sum(ini%N_sl(1:f))
|
|
||||||
do s = from,upto
|
|
||||||
noise = [math_sampleGaussVar(0.0_pReal, ini%sigma_rho_u), &
|
|
||||||
math_sampleGaussVar(0.0_pReal, ini%sigma_rho_u)]
|
|
||||||
stt%rho_sgl_mob_edg_pos(s,e) = ini%rho_u_ed_pos_0(f) + noise(1)
|
|
||||||
stt%rho_sgl_mob_edg_neg(s,e) = ini%rho_u_ed_neg_0(f) + noise(1)
|
|
||||||
stt%rho_sgl_mob_scr_pos(s,e) = ini%rho_u_sc_pos_0(f) + noise(2)
|
|
||||||
stt%rho_sgl_mob_scr_neg(s,e) = ini%rho_u_sc_neg_0(f) + noise(2)
|
|
||||||
enddo
|
|
||||||
stt%rho_dip_edg(from:upto,e) = ini%rho_d_ed_0(f)
|
|
||||||
stt%rho_dip_scr(from:upto,e) = ini%rho_d_sc_0(f)
|
|
||||||
enddo
|
enddo
|
||||||
enddo
|
else ! homogeneous distribution with noise
|
||||||
endif
|
do e = 1, Nentries
|
||||||
|
do f = 1,size(ini%N_sl,1)
|
||||||
|
from = 1 + sum(ini%N_sl(1:f-1))
|
||||||
|
upto = sum(ini%N_sl(1:f))
|
||||||
|
do s = from,upto
|
||||||
|
noise = [math_sampleGaussVar(0.0_pReal, ini%sigma_rho_u), &
|
||||||
|
math_sampleGaussVar(0.0_pReal, ini%sigma_rho_u)]
|
||||||
|
stt%rho_sgl_mob_edg_pos(s,e) = ini%rho_u_ed_pos_0(f) + noise(1)
|
||||||
|
stt%rho_sgl_mob_edg_neg(s,e) = ini%rho_u_ed_neg_0(f) + noise(1)
|
||||||
|
stt%rho_sgl_mob_scr_pos(s,e) = ini%rho_u_sc_pos_0(f) + noise(2)
|
||||||
|
stt%rho_sgl_mob_scr_neg(s,e) = ini%rho_u_sc_neg_0(f) + noise(2)
|
||||||
|
enddo
|
||||||
|
stt%rho_dip_edg(from:upto,e) = ini%rho_d_ed_0(f)
|
||||||
|
stt%rho_dip_scr(from:upto,e) = ini%rho_d_sc_0(f)
|
||||||
|
enddo
|
||||||
|
enddo
|
||||||
|
endif
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue