Merge branch '20-NewStyleDislotwin' into development

This commit is contained in:
Martin Diehl 2019-01-28 07:38:30 +01:00
commit e2582a8d06
4 changed files with 509 additions and 805 deletions

View File

@ -550,7 +550,7 @@ end function getString
!> @details for cumulative keys, "()", values from all occurrences are return. Otherwise only all !> @details for cumulative keys, "()", values from all occurrences are return. Otherwise only all
!! values from the last occurrence. If key is not found exits with error unless default is given. !! values from the last occurrence. If key is not found exits with error unless default is given.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function getFloats(this,key,defaultVal,requiredShape,requiredSize) function getFloats(this,key,defaultVal,requiredSize)
use IO, only: & use IO, only: &
IO_error, & IO_error, &
IO_stringValue, & IO_stringValue, &
@ -561,7 +561,6 @@ function getFloats(this,key,defaultVal,requiredShape,requiredSize)
class(tPartitionedStringList), target, intent(in) :: this class(tPartitionedStringList), target, intent(in) :: this
character(len=*), intent(in) :: key character(len=*), intent(in) :: key
real(pReal), dimension(:), intent(in), optional :: defaultVal real(pReal), dimension(:), intent(in), optional :: defaultVal
integer(pInt), dimension(:), intent(in), optional :: requiredShape ! not useful (is always 1D array)
integer(pInt), intent(in), optional :: requiredSize integer(pInt), intent(in), optional :: requiredSize
type(tPartitionedStringList), pointer :: item type(tPartitionedStringList), pointer :: item
integer(pInt) :: i integer(pInt) :: i
@ -601,7 +600,7 @@ end function getFloats
!> @details for cumulative keys, "()", values from all occurrences are return. Otherwise only all !> @details for cumulative keys, "()", values from all occurrences are return. Otherwise only all
!! values from the last occurrence. If key is not found exits with error unless default is given. !! values from the last occurrence. If key is not found exits with error unless default is given.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function getInts(this,key,defaultVal,requiredShape,requiredSize) function getInts(this,key,defaultVal,requiredSize)
use IO, only: & use IO, only: &
IO_error, & IO_error, &
IO_stringValue, & IO_stringValue, &
@ -611,8 +610,7 @@ function getInts(this,key,defaultVal,requiredShape,requiredSize)
integer(pInt), dimension(:), allocatable :: getInts integer(pInt), dimension(:), allocatable :: getInts
class(tPartitionedStringList), target, intent(in) :: this class(tPartitionedStringList), target, intent(in) :: this
character(len=*), intent(in) :: key character(len=*), intent(in) :: key
integer(pInt), dimension(:), intent(in), optional :: defaultVal, & integer(pInt), dimension(:), intent(in), optional :: defaultVal
requiredShape ! not useful (is always 1D array)
integer(pInt), intent(in), optional :: requiredSize integer(pInt), intent(in), optional :: requiredSize
type(tPartitionedStringList), pointer :: item type(tPartitionedStringList), pointer :: item
integer(pInt) :: i integer(pInt) :: i
@ -653,7 +651,7 @@ end function getInts
!! values from the last occurrence. If key is not found exits with error unless default is given. !! values from the last occurrence. If key is not found exits with error unless default is given.
!! If raw is true, the the complete string is returned, otherwise the individual chunks are returned !! If raw is true, the the complete string is returned, otherwise the individual chunks are returned
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function getStrings(this,key,defaultVal,requiredShape,raw) function getStrings(this,key,defaultVal,raw)
use IO, only: & use IO, only: &
IO_error, & IO_error, &
IO_StringValue IO_StringValue
@ -663,7 +661,6 @@ function getStrings(this,key,defaultVal,requiredShape,raw)
class(tPartitionedStringList), target, intent(in) :: this class(tPartitionedStringList), target, intent(in) :: this
character(len=*), intent(in) :: key character(len=*), intent(in) :: key
character(len=65536),dimension(:), intent(in), optional :: defaultVal character(len=65536),dimension(:), intent(in), optional :: defaultVal
integer(pInt), dimension(:), intent(in), optional :: requiredShape
logical, intent(in), optional :: raw logical, intent(in), optional :: raw
type(tPartitionedStringList), pointer :: item type(tPartitionedStringList), pointer :: item
character(len=65536) :: str character(len=65536) :: str

View File

@ -365,7 +365,7 @@ subroutine constitutive_microstructure(orientations, Fe, Fp, ipc, ip, el)
use plastic_nonlocal, only: & use plastic_nonlocal, only: &
plastic_nonlocal_microstructure plastic_nonlocal_microstructure
use plastic_dislotwin, only: & use plastic_dislotwin, only: &
plastic_dislotwin_microstructure plastic_dislotwin_dependentState
use plastic_disloUCLA, only: & use plastic_disloUCLA, only: &
plastic_disloUCLA_dependentState plastic_disloUCLA_dependentState
@ -389,7 +389,9 @@ subroutine constitutive_microstructure(orientations, Fe, Fp, ipc, ip, el)
plasticityType: select case (phase_plasticity(material_phase(ipc,ip,el))) plasticityType: select case (phase_plasticity(material_phase(ipc,ip,el)))
case (PLASTICITY_DISLOTWIN_ID) plasticityType case (PLASTICITY_DISLOTWIN_ID) plasticityType
call plastic_dislotwin_microstructure(temperature(ho)%p(tme),ipc,ip,el) of = phasememberAt(ipc,ip,el)
instance = phase_plasticityInstance(material_phase(ipc,ip,el))
call plastic_dislotwin_dependentState(temperature(ho)%p(tme),instance,of)
case (PLASTICITY_DISLOUCLA_ID) plasticityType case (PLASTICITY_DISLOUCLA_ID) plasticityType
of = phasememberAt(ipc,ip,el) of = phasememberAt(ipc,ip,el)
instance = phase_plasticityInstance(material_phase(ipc,ip,el)) instance = phase_plasticityInstance(material_phase(ipc,ip,el))
@ -409,9 +411,9 @@ subroutine constitutive_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, S6, Fi, ipc, ip, e
pReal pReal
use math, only: & use math, only: &
math_mul33x33, & math_mul33x33, &
math_Mandel6to33, & math_6toSym33, &
math_Mandel33to6, & math_sym33to6, &
math_Plain99to3333 math_99to3333
use material, only: & use material, only: &
phasememberAt, & phasememberAt, &
phase_plasticity, & phase_plasticity, &
@ -470,7 +472,7 @@ subroutine constitutive_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, S6, Fi, ipc, ip, e
ho = material_homogenizationAt(el) ho = material_homogenizationAt(el)
tme = thermalMapping(ho)%p(ip,el) tme = thermalMapping(ho)%p(ip,el)
S = math_Mandel6to33(S6) S = math_6toSym33(S6)
Mp = math_mul33x33(math_mul33x33(transpose(Fi),Fi),S) Mp = math_mul33x33(math_mul33x33(transpose(Fi),Fi),S)
plasticityType: select case (phase_plasticity(material_phase(ipc,ip,el))) plasticityType: select case (phase_plasticity(material_phase(ipc,ip,el)))
@ -495,9 +497,9 @@ subroutine constitutive_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, S6, Fi, ipc, ip, e
call plastic_kinehardening_LpAndItsTangent (Lp,dLp_dMp, Mp,instance,of) call plastic_kinehardening_LpAndItsTangent (Lp,dLp_dMp, Mp,instance,of)
case (PLASTICITY_NONLOCAL_ID) plasticityType case (PLASTICITY_NONLOCAL_ID) plasticityType
call plastic_nonlocal_LpAndItsTangent (Lp,dLp_dMp99, math_Mandel33to6(Mp), & call plastic_nonlocal_LpAndItsTangent (Lp,dLp_dMp99, math_sym33to6(Mp), &
temperature(ho)%p(tme),ip,el) temperature(ho)%p(tme),ip,el)
dLp_dMp = math_Plain99to3333(dLp_dMp99) ! ToDo: We revert here the last statement in plastic_xx_LpAndItsTanget dLp_dMp = math_99to3333(dLp_dMp99) ! ToDo: We revert here the last statement in plastic_xx_LpAndItsTanget
case (PLASTICITY_DISLOTWIN_ID) plasticityType case (PLASTICITY_DISLOTWIN_ID) plasticityType
of = phasememberAt(ipc,ip,el) of = phasememberAt(ipc,ip,el)
@ -540,7 +542,7 @@ subroutine constitutive_LiAndItsTangents(Li, dLi_dS, dLi_dFi, S6, Fi, ipc, ip, e
math_inv33, & math_inv33, &
math_det33, & math_det33, &
math_mul33x33, & math_mul33x33, &
math_Mandel6to33 math_6toSym33
use material, only: & use material, only: &
phasememberAt, & phasememberAt, &
phase_plasticity, & phase_plasticity, &
@ -597,7 +599,7 @@ subroutine constitutive_LiAndItsTangents(Li, dLi_dS, dLi_dFi, S6, Fi, ipc, ip, e
case (PLASTICITY_isotropic_ID) plasticityType case (PLASTICITY_isotropic_ID) plasticityType
of = phasememberAt(ipc,ip,el) of = phasememberAt(ipc,ip,el)
instance = phase_plasticityInstance(material_phase(ipc,ip,el)) instance = phase_plasticityInstance(material_phase(ipc,ip,el))
call plastic_isotropic_LiAndItsTangent(my_Li, my_dLi_dS, math_Mandel6to33(S6),instance,of) call plastic_isotropic_LiAndItsTangent(my_Li, my_dLi_dS, math_6toSym33(S6),instance,of)
case default plasticityType case default plasticityType
my_Li = 0.0_pReal my_Li = 0.0_pReal
my_dLi_dS = 0.0_pReal my_dLi_dS = 0.0_pReal
@ -716,7 +718,7 @@ subroutine constitutive_hooke_SandItsTangents(S, dS_dFe, dS_dFi, Fe, Fi, ipc, ip
use math, only : & use math, only : &
math_mul33x33, & math_mul33x33, &
math_mul3333xx33, & math_mul3333xx33, &
math_Mandel66to3333, & math_66toSym3333, &
math_I3 math_I3
use material, only: & use material, only: &
material_phase, & material_phase, &
@ -749,7 +751,7 @@ subroutine constitutive_hooke_SandItsTangents(S, dS_dFe, dS_dFi, Fe, Fi, ipc, ip
i, j i, j
ho = material_homogenizationAt(el) ho = material_homogenizationAt(el)
C = math_Mandel66to3333(constitutive_homogenizedC(ipc,ip,el)) C = math_66toSym3333(constitutive_homogenizedC(ipc,ip,el))
DegradationLoop: do d = 1_pInt, phase_NstiffnessDegradations(material_phase(ipc,ip,el)) DegradationLoop: do d = 1_pInt, phase_NstiffnessDegradations(material_phase(ipc,ip,el))
degradationType: select case(phase_stiffnessDegradation(d,material_phase(ipc,ip,el))) degradationType: select case(phase_stiffnessDegradation(d,material_phase(ipc,ip,el)))
@ -784,8 +786,8 @@ subroutine constitutive_collectDotState(S6, FeArray, Fi, FpArray, subdt, subfrac
debug_levelBasic debug_levelBasic
use math, only: & use math, only: &
math_mul33x33, & math_mul33x33, &
math_Mandel6to33, & math_6toSym33, &
math_Mandel33to6, & math_sym33to6, &
math_mul33x33 math_mul33x33
use mesh, only: & use mesh, only: &
mesh_NcpElems, & mesh_NcpElems, &
@ -860,7 +862,7 @@ subroutine constitutive_collectDotState(S6, FeArray, Fi, FpArray, subdt, subfrac
ho = material_homogenizationAt(el) ho = material_homogenizationAt(el)
tme = thermalMapping(ho)%p(ip,el) tme = thermalMapping(ho)%p(ip,el)
Mp = math_mul33x33(math_mul33x33(transpose(Fi),Fi),math_Mandel6to33(S6)) Mp = math_mul33x33(math_mul33x33(transpose(Fi),Fi),math_6toSym33(S6))
plasticityType: select case (phase_plasticity(material_phase(ipc,ip,el))) plasticityType: select case (phase_plasticity(material_phase(ipc,ip,el)))
@ -890,7 +892,7 @@ subroutine constitutive_collectDotState(S6, FeArray, Fi, FpArray, subdt, subfrac
call plastic_disloucla_dotState (Mp,temperature(ho)%p(tme),instance,of) call plastic_disloucla_dotState (Mp,temperature(ho)%p(tme),instance,of)
case (PLASTICITY_NONLOCAL_ID) plasticityType case (PLASTICITY_NONLOCAL_ID) plasticityType
call plastic_nonlocal_dotState (math_Mandel33to6(Mp),FeArray,FpArray,temperature(ho)%p(tme), & call plastic_nonlocal_dotState (math_sym33to6(Mp),FeArray,FpArray,temperature(ho)%p(tme), &
subdt,subfracArray,ip,el) subdt,subfracArray,ip,el)
end select plasticityType end select plasticityType
@ -999,7 +1001,7 @@ function constitutive_postResults(S6, Fi, FeArray, ipc, ip, el)
use prec, only: & use prec, only: &
pReal pReal
use math, only: & use math, only: &
math_Mandel6to33, & math_6toSym33, &
math_mul33x33 math_mul33x33
use mesh, only: & use mesh, only: &
mesh_NcpElems, & mesh_NcpElems, &
@ -1074,7 +1076,7 @@ function constitutive_postResults(S6, Fi, FeArray, ipc, ip, el)
constitutive_postResults = 0.0_pReal constitutive_postResults = 0.0_pReal
Mp = math_mul33x33(math_mul33x33(transpose(Fi),Fi),math_Mandel6to33(S6)) Mp = math_mul33x33(math_mul33x33(transpose(Fi),Fi),math_6toSym33(S6))
ho = material_homogenizationAt(el) ho = material_homogenizationAt(el)
tme = thermalMapping(ho)%p(ip,el) tme = thermalMapping(ho)%p(ip,el)

View File

@ -28,8 +28,7 @@ module plastic_disloUCLA
shearrate_ID, & shearrate_ID, &
accumulatedshear_ID, & accumulatedshear_ID, &
mfp_ID, & mfp_ID, &
thresholdstress_ID, & thresholdstress_ID
dipoledistance_ID
end enum end enum
type, private :: tParameters type, private :: tParameters
@ -73,7 +72,7 @@ module plastic_disloUCLA
integer(kind(undefined_ID)), allocatable, dimension(:) :: & integer(kind(undefined_ID)), allocatable, dimension(:) :: &
outputID !< ID of each post result output outputID !< ID of each post result output
logical :: & logical :: &
dipoleformation dipoleFormation !< flag indicating consideration of dipole formation
end type !< container type for internal constitutive parameters end type !< container type for internal constitutive parameters
type, private :: tDisloUCLAState type, private :: tDisloUCLAState
@ -127,7 +126,6 @@ subroutine plastic_disloUCLA_init()
debug_constitutive,& debug_constitutive,&
debug_levelBasic debug_levelBasic
use math, only: & use math, only: &
math_mul3x3, &
math_expand math_expand
use IO, only: & use IO, only: &
IO_error, & IO_error, &
@ -148,8 +146,6 @@ subroutine plastic_disloUCLA_init()
implicit none implicit none
integer(pInt) :: & integer(pInt) :: &
index_myFamily, index_otherFamily, &
f,j,k,o, &
Ninstance, & Ninstance, &
p, i, & p, i, &
NipcMyPhase, & NipcMyPhase, &
@ -222,9 +218,13 @@ subroutine plastic_disloUCLA_init()
prm%nonSchmid_pos = prm%Schmid prm%nonSchmid_pos = prm%Schmid
prm%nonSchmid_neg = prm%Schmid prm%nonSchmid_neg = prm%Schmid
endif endif
prm%interaction_SlipSlip = lattice_interaction_SlipSlip(prm%Nslip, & prm%interaction_SlipSlip = lattice_interaction_SlipSlip(prm%Nslip, &
config%getFloats('interaction_slipslip'), & config%getFloats('interaction_slipslip'), &
config%getString('lattice_structure')) config%getString('lattice_structure'))
prm%forestProjectionEdge = lattice_forestProjection(prm%Nslip,config%getString('lattice_structure'),&
config%getFloat('c/a',defaultVal=0.0_pReal))
prm%rho0 = config%getFloats('rhoedge0', requiredSize=size(prm%Nslip)) prm%rho0 = config%getFloats('rhoedge0', requiredSize=size(prm%Nslip))
prm%rhoDip0 = config%getFloats('rhoedgedip0', requiredSize=size(prm%Nslip)) prm%rhoDip0 = config%getFloats('rhoedgedip0', requiredSize=size(prm%Nslip))
prm%v0 = config%getFloats('v0', requiredSize=size(prm%Nslip)) prm%v0 = config%getFloats('v0', requiredSize=size(prm%Nslip))
@ -311,8 +311,6 @@ subroutine plastic_disloUCLA_init()
outputID = merge(mfp_ID,undefined_ID,prm%totalNslip>0_pInt) outputID = merge(mfp_ID,undefined_ID,prm%totalNslip>0_pInt)
case ('threshold_stress','threshold_stress_slip') case ('threshold_stress','threshold_stress_slip')
outputID = merge(thresholdstress_ID,undefined_ID,prm%totalNslip>0_pInt) outputID = merge(thresholdstress_ID,undefined_ID,prm%totalNslip>0_pInt)
case ('edge_dipole_distance')
outputID = merge(dipoleDistance_ID,undefined_ID,prm%totalNslip>0_pInt)
end select end select
@ -334,24 +332,6 @@ subroutine plastic_disloUCLA_init()
prm%totalNslip,0_pInt,0_pInt) prm%totalNslip,0_pInt,0_pInt)
plasticState(p)%sizePostResults = sum(plastic_disloUCLA_sizePostResult(:,phase_plasticityInstance(p))) plasticState(p)%sizePostResults = sum(plastic_disloUCLA_sizePostResult(:,phase_plasticityInstance(p)))
allocate(prm%forestProjectionEdge(prm%totalNslip,prm%totalNslip),source = 0.0_pReal)
i = 0_pInt
mySlipFamilies: do f = 1_pInt,size(prm%Nslip,1)
index_myFamily = sum(prm%Nslip(1:f-1_pInt))
slipSystemsLoop: do j = 1_pInt,prm%Nslip(f)
i = i + 1_pInt
do o = 1_pInt, size(prm%Nslip,1)
index_otherFamily = sum(prm%Nslip(1:o-1_pInt))
do k = 1_pInt,prm%Nslip(o) ! loop over (active) systems in other family (slip)
prm%forestProjectionEdge(index_myFamily+j,index_otherFamily+k) = &
abs(math_mul3x3(lattice_sn(:,sum(lattice_NslipSystem(1:f-1,p))+j,p), &
lattice_st(:,sum(lattice_NslipSystem(1:o-1,p))+k,p)))
enddo; enddo
enddo slipSystemsLoop
enddo mySlipFamilies
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! locally defined state aliases and initialization of state0 and aTolState ! locally defined state aliases and initialization of state0 and aTolState
startIndex = 1_pInt startIndex = 1_pInt
@ -372,7 +352,7 @@ subroutine plastic_disloUCLA_init()
endIndex = endIndex + prm%totalNslip endIndex = endIndex + prm%totalNslip
stt%accshear=>plasticState(p)%state(startIndex:endIndex,:) stt%accshear=>plasticState(p)%state(startIndex:endIndex,:)
dot%accshear=>plasticState(p)%dotState(startIndex:endIndex,:) dot%accshear=>plasticState(p)%dotState(startIndex:endIndex,:)
plasticState(p)%aTolState(startIndex:endIndex) = 1e6_pReal !ToDo: better make optional parameter plasticState(p)%aTolState(startIndex:endIndex) = 1.0e6_pReal !ToDo: better make optional parameter
! global alias ! global alias
plasticState(p)%slipRate => plasticState(p)%dotState(startIndex:endIndex,:) plasticState(p)%slipRate => plasticState(p)%dotState(startIndex:endIndex,:)
plasticState(p)%accumulatedSlip => plasticState(p)%state(startIndex:endIndex,:) plasticState(p)%accumulatedSlip => plasticState(p)%state(startIndex:endIndex,:)
@ -577,16 +557,6 @@ function plastic_disloUCLA_postResults(Mp,Temperature,instance,of) result(postRe
postResults(c+1_pInt:c+prm%totalNslip) = dst%mfp(1_pInt:prm%totalNslip, of) postResults(c+1_pInt:c+prm%totalNslip) = dst%mfp(1_pInt:prm%totalNslip, of)
case (thresholdstress_ID) case (thresholdstress_ID)
postResults(c+1_pInt:c+prm%totalNslip) = dst%threshold_stress(1_pInt:prm%totalNslip,of) postResults(c+1_pInt:c+prm%totalNslip) = dst%threshold_stress(1_pInt:prm%totalNslip,of)
case (dipoleDistance_ID) ! ToDo: Discuss required changes with Franz
do i = 1_pInt, prm%totalNslip
if (dNeq0(abs(math_mul33xx33(Mp,prm%nonSchmid_pos(1:3,1:3,i))))) then
postResults(c+i) = (3.0_pReal*prm%mu*prm%burgers(i)) &
/ (16.0_pReal*pi*abs(math_mul33xx33(Mp,prm%nonSchmid_pos(1:3,1:3,i))))
else
postResults(c+i) = huge(1.0_pReal)
endif
postResults(c+i)=min(postResults(c+i),dst%mfp(i,of))
enddo
end select end select

File diff suppressed because it is too large Load Diff