explicit instance mapping not needed
This commit is contained in:
parent
b3dde6d722
commit
775a51faa1
|
@ -6,9 +6,6 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
submodule (phase:damagee) anisobrittle
|
submodule (phase:damagee) anisobrittle
|
||||||
|
|
||||||
integer, dimension(:), allocatable :: &
|
|
||||||
source_damage_anisoBrittle_instance !< instance of source mechanism
|
|
||||||
|
|
||||||
type :: tParameters !< container type for internal constitutive parameters
|
type :: tParameters !< container type for internal constitutive parameters
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
dot_o, & !< opening rate of cleavage planes
|
dot_o, & !< opening rate of cleavage planes
|
||||||
|
@ -56,17 +53,16 @@ module function anisobrittle_init(source_length) result(mySources)
|
||||||
if(Ninstances == 0) return
|
if(Ninstances == 0) return
|
||||||
|
|
||||||
phases => config_material%get('phase')
|
phases => config_material%get('phase')
|
||||||
allocate(param(Ninstances))
|
allocate(param(phases%length))
|
||||||
allocate(source_damage_anisoBrittle_instance(phases%length), source=0)
|
|
||||||
|
|
||||||
do p = 1, phases%length
|
do p = 1, phases%length
|
||||||
phase => phases%get(p)
|
phase => phases%get(p)
|
||||||
if(any(mySources(:,p))) source_damage_anisoBrittle_instance(p) = count(mySources(:,1:p))
|
|
||||||
if(count(mySources(:,p)) == 0) cycle
|
if(count(mySources(:,p)) == 0) cycle
|
||||||
sources => phase%get('damage')
|
sources => phase%get('damage')
|
||||||
do sourceOffset = 1, sources%length
|
do sourceOffset = 1, sources%length
|
||||||
if(mySources(sourceOffset,p)) then
|
if(mySources(sourceOffset,p)) then
|
||||||
associate(prm => param(source_damage_anisoBrittle_instance(p)))
|
associate(prm => param(p))
|
||||||
src => sources%get(sourceOffset)
|
src => sources%get(sourceOffset)
|
||||||
|
|
||||||
N_cl = src%get_asInts('N_cl',defaultVal=emptyIntArray)
|
N_cl = src%get_asInts('N_cl',defaultVal=emptyIntArray)
|
||||||
|
@ -141,22 +137,21 @@ module subroutine anisobrittle_dotState(S, co, ip, el)
|
||||||
me = material_phasememberAt(co,ip,el)
|
me = material_phasememberAt(co,ip,el)
|
||||||
|
|
||||||
|
|
||||||
associate(prm => param(source_damage_anisoBrittle_instance(ph)))
|
associate(prm => param(ph))
|
||||||
damageState(ph)%dotState(1,me) = 0.0_pReal
|
damageState(ph)%dotState(1,me) = 0.0_pReal
|
||||||
do i = 1, prm%sum_N_cl
|
do i = 1, prm%sum_N_cl
|
||||||
traction_d = math_tensordot(S,prm%cleavage_systems(1:3,1:3,1,i))
|
traction_d = math_tensordot(S,prm%cleavage_systems(1:3,1:3,1,i))
|
||||||
traction_t = math_tensordot(S,prm%cleavage_systems(1:3,1:3,2,i))
|
traction_t = math_tensordot(S,prm%cleavage_systems(1:3,1:3,2,i))
|
||||||
traction_n = math_tensordot(S,prm%cleavage_systems(1:3,1:3,3,i))
|
traction_n = math_tensordot(S,prm%cleavage_systems(1:3,1:3,3,i))
|
||||||
|
|
||||||
traction_crit = prm%g_crit(i)*phase_damage_get_phi(co,ip,el)**2.0_pReal
|
traction_crit = prm%g_crit(i)*phase_damage_get_phi(co,ip,el)**2.0_pReal
|
||||||
|
|
||||||
damageState(ph)%dotState(1,me) &
|
damageState(ph)%dotState(1,me) = damageState(ph)%dotState(1,me) &
|
||||||
= damageState(ph)%dotState(1,me) &
|
+ prm%dot_o / prm%s_crit(i) &
|
||||||
+ prm%dot_o / prm%s_crit(i) &
|
* ((max(0.0_pReal, abs(traction_d) - traction_crit)/traction_crit)**prm%q + &
|
||||||
* ((max(0.0_pReal, abs(traction_d) - traction_crit)/traction_crit)**prm%q + &
|
(max(0.0_pReal, abs(traction_t) - traction_crit)/traction_crit)**prm%q + &
|
||||||
(max(0.0_pReal, abs(traction_t) - traction_crit)/traction_crit)**prm%q + &
|
(max(0.0_pReal, abs(traction_n) - traction_crit)/traction_crit)**prm%q)
|
||||||
(max(0.0_pReal, abs(traction_n) - traction_crit)/traction_crit)**prm%q)
|
enddo
|
||||||
enddo
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
end subroutine anisobrittle_dotState
|
end subroutine anisobrittle_dotState
|
||||||
|
@ -195,14 +190,13 @@ module subroutine anisobrittle_results(phase,group)
|
||||||
|
|
||||||
integer :: o
|
integer :: o
|
||||||
|
|
||||||
associate(prm => param(source_damage_anisoBrittle_instance(phase)), &
|
associate(prm => param(phase), stt => damageState(phase)%state)
|
||||||
stt => damageState(phase)%state)
|
outputsLoop: do o = 1,size(prm%output)
|
||||||
outputsLoop: do o = 1,size(prm%output)
|
select case(trim(prm%output(o)))
|
||||||
select case(trim(prm%output(o)))
|
case ('f_phi')
|
||||||
case ('f_phi')
|
call results_writeDataset(group,stt,trim(prm%output(o)),'driving force','J/m³')
|
||||||
call results_writeDataset(group,stt,trim(prm%output(o)),'driving force','J/m³')
|
end select
|
||||||
end select
|
enddo outputsLoop
|
||||||
enddo outputsLoop
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
end subroutine anisobrittle_results
|
end subroutine anisobrittle_results
|
||||||
|
|
|
@ -6,9 +6,6 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
submodule(phase:damagee) anisoductile
|
submodule(phase:damagee) anisoductile
|
||||||
|
|
||||||
integer, dimension(:), allocatable :: &
|
|
||||||
source_damage_anisoDuctile_instance !< instance of damage source mechanism
|
|
||||||
|
|
||||||
type :: tParameters !< container type for internal constitutive parameters
|
type :: tParameters !< container type for internal constitutive parameters
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
q !< damage rate sensitivity
|
q !< damage rate sensitivity
|
||||||
|
@ -18,7 +15,7 @@ submodule(phase:damagee) anisoductile
|
||||||
output
|
output
|
||||||
end type tParameters
|
end type tParameters
|
||||||
|
|
||||||
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstances)
|
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters
|
||||||
|
|
||||||
contains
|
contains
|
||||||
|
|
||||||
|
@ -51,19 +48,17 @@ module function anisoductile_init(source_length) result(mySources)
|
||||||
if(Ninstances == 0) return
|
if(Ninstances == 0) return
|
||||||
|
|
||||||
phases => config_material%get('phase')
|
phases => config_material%get('phase')
|
||||||
allocate(param(Ninstances))
|
allocate(param(phases%length))
|
||||||
allocate(source_damage_anisoDuctile_instance(phases%length), source=0)
|
|
||||||
|
|
||||||
do p = 1, phases%length
|
do p = 1, phases%length
|
||||||
phase => phases%get(p)
|
phase => phases%get(p)
|
||||||
if(any(mySources(:,p))) source_damage_anisoDuctile_instance(p) = count(mySources(:,1:p))
|
|
||||||
if(count(mySources(:,p)) == 0) cycle
|
if(count(mySources(:,p)) == 0) cycle
|
||||||
mech => phase%get('mechanics')
|
mech => phase%get('mechanics')
|
||||||
pl => mech%get('plasticity')
|
pl => mech%get('plasticity')
|
||||||
sources => phase%get('source')
|
sources => phase%get('source')
|
||||||
do sourceOffset = 1, sources%length
|
do sourceOffset = 1, sources%length
|
||||||
if(mySources(sourceOffset,p)) then
|
if(mySources(sourceOffset,p)) then
|
||||||
associate(prm => param(source_damage_anisoDuctile_instance(p)))
|
associate(prm => param(p))
|
||||||
src => sources%get(sourceOffset)
|
src => sources%get(sourceOffset)
|
||||||
|
|
||||||
N_sl = pl%get_asInts('N_sl',defaultVal=emptyIntArray)
|
N_sl = pl%get_asInts('N_sl',defaultVal=emptyIntArray)
|
||||||
|
@ -119,8 +114,8 @@ module subroutine anisoductile_dotState(co, ip, el)
|
||||||
me = material_phasememberAt(co,ip,el)
|
me = material_phasememberAt(co,ip,el)
|
||||||
|
|
||||||
|
|
||||||
associate(prm => param(source_damage_anisoDuctile_instance(ph)))
|
associate(prm => param(ph))
|
||||||
damageState(ph)%dotState(1,me) = sum(plasticState(ph)%slipRate(:,me)/(phase_damage_get_phi(co,ip,el)**prm%q)/prm%gamma_crit)
|
damageState(ph)%dotState(1,me) = sum(plasticState(ph)%slipRate(:,me)/(damage_phi(ph,me)**prm%q)/prm%gamma_crit)
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
end subroutine anisoductile_dotState
|
end subroutine anisoductile_dotState
|
||||||
|
@ -159,14 +154,14 @@ module subroutine anisoductile_results(phase,group)
|
||||||
|
|
||||||
integer :: o
|
integer :: o
|
||||||
|
|
||||||
associate(prm => param(source_damage_anisoDuctile_instance(phase)), &
|
associate(prm => param(phase), &
|
||||||
stt => damageState(phase)%state)
|
stt => damageState(phase)%state)
|
||||||
outputsLoop: do o = 1,size(prm%output)
|
outputsLoop: do o = 1,size(prm%output)
|
||||||
select case(trim(prm%output(o)))
|
select case(trim(prm%output(o)))
|
||||||
case ('f_phi')
|
case ('f_phi')
|
||||||
call results_writeDataset(group,stt,trim(prm%output(o)),'driving force','J/m³')
|
call results_writeDataset(group,stt,trim(prm%output(o)),'driving force','J/m³')
|
||||||
end select
|
end select
|
||||||
enddo outputsLoop
|
enddo outputsLoop
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
end subroutine anisoductile_results
|
end subroutine anisoductile_results
|
||||||
|
|
|
@ -6,9 +6,6 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
submodule(phase:damagee) isobrittle
|
submodule(phase:damagee) isobrittle
|
||||||
|
|
||||||
integer, dimension(:), allocatable :: &
|
|
||||||
source_damage_isoBrittle_instance
|
|
||||||
|
|
||||||
type :: tParameters !< container type for internal constitutive parameters
|
type :: tParameters !< container type for internal constitutive parameters
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
W_crit !< critical elastic strain energy
|
W_crit !< critical elastic strain energy
|
||||||
|
@ -46,17 +43,15 @@ module function isobrittle_init(source_length) result(mySources)
|
||||||
if(Ninstances == 0) return
|
if(Ninstances == 0) return
|
||||||
|
|
||||||
phases => config_material%get('phase')
|
phases => config_material%get('phase')
|
||||||
allocate(param(Ninstances))
|
allocate(param(phases%length))
|
||||||
allocate(source_damage_isoBrittle_instance(phases%length), source=0)
|
|
||||||
|
|
||||||
do p = 1, phases%length
|
do p = 1, phases%length
|
||||||
phase => phases%get(p)
|
phase => phases%get(p)
|
||||||
if(any(mySources(:,p))) source_damage_isoBrittle_instance(p) = count(mySources(:,1:p))
|
|
||||||
if(count(mySources(:,p)) == 0) cycle
|
if(count(mySources(:,p)) == 0) cycle
|
||||||
sources => phase%get('damage')
|
sources => phase%get('damage')
|
||||||
do sourceOffset = 1, sources%length
|
do sourceOffset = 1, sources%length
|
||||||
if(mySources(sourceOffset,p)) then
|
if(mySources(sourceOffset,p)) then
|
||||||
associate(prm => param(source_damage_isoBrittle_instance(p)))
|
associate(prm => param(p))
|
||||||
src => sources%get(sourceOffset)
|
src => sources%get(sourceOffset)
|
||||||
|
|
||||||
prm%W_crit = src%get_asFloat('W_crit')
|
prm%W_crit = src%get_asFloat('W_crit')
|
||||||
|
@ -107,9 +102,9 @@ module subroutine source_damage_isoBrittle_deltaState(C, Fe, ph,me)
|
||||||
|
|
||||||
strain = 0.5_pReal*math_sym33to6(matmul(transpose(Fe),Fe)-math_I3)
|
strain = 0.5_pReal*math_sym33to6(matmul(transpose(Fe),Fe)-math_I3)
|
||||||
|
|
||||||
associate(prm => param(source_damage_isoBrittle_instance(ph)))
|
associate(prm => param(ph))
|
||||||
strainenergy = 2.0_pReal*sum(strain*matmul(C,strain))/prm%W_crit
|
strainenergy = 2.0_pReal*sum(strain*matmul(C,strain))/prm%W_crit
|
||||||
! ToDo: check strainenergy = 2.0_pReal*dot_product(strain,matmul(C,strain))/prm%W_crit
|
! ToDo: check strainenergy = 2.0_pReal*dot_product(strain,matmul(C,strain))/prm%W_crit
|
||||||
|
|
||||||
if (strainenergy > damageState(ph)%subState0(1,me)) then
|
if (strainenergy > damageState(ph)%subState0(1,me)) then
|
||||||
damageState(ph)%deltaState(1,me) = strainenergy - damageState(ph)%state(1,me)
|
damageState(ph)%deltaState(1,me) = strainenergy - damageState(ph)%state(1,me)
|
||||||
|
@ -136,7 +131,7 @@ module subroutine source_damage_isoBrittle_getRateAndItsTangent(localphiDot, dLo
|
||||||
dLocalphiDot_dPhi
|
dLocalphiDot_dPhi
|
||||||
|
|
||||||
|
|
||||||
associate(prm => param(source_damage_isoBrittle_instance(phase)))
|
associate(prm => param(phase))
|
||||||
localphiDot = 1.0_pReal &
|
localphiDot = 1.0_pReal &
|
||||||
- phi*damageState(phase)%state(1,constituent)
|
- phi*damageState(phase)%state(1,constituent)
|
||||||
dLocalphiDot_dPhi = - damageState(phase)%state(1,constituent)
|
dLocalphiDot_dPhi = - damageState(phase)%state(1,constituent)
|
||||||
|
@ -155,14 +150,15 @@ module subroutine isobrittle_results(phase,group)
|
||||||
|
|
||||||
integer :: o
|
integer :: o
|
||||||
|
|
||||||
associate(prm => param(source_damage_isoBrittle_instance(phase)), &
|
|
||||||
|
associate(prm => param(phase), &
|
||||||
stt => damageState(phase)%state)
|
stt => damageState(phase)%state)
|
||||||
outputsLoop: do o = 1,size(prm%output)
|
outputsLoop: do o = 1,size(prm%output)
|
||||||
select case(trim(prm%output(o)))
|
select case(trim(prm%output(o)))
|
||||||
case ('f_phi')
|
case ('f_phi')
|
||||||
call results_writeDataset(group,stt,trim(prm%output(o)),'driving force','J/m³')
|
call results_writeDataset(group,stt,trim(prm%output(o)),'driving force','J/m³')
|
||||||
end select
|
end select
|
||||||
enddo outputsLoop
|
enddo outputsLoop
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
end subroutine isobrittle_results
|
end subroutine isobrittle_results
|
||||||
|
|
|
@ -6,9 +6,6 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
submodule(phase:damagee) isoductile
|
submodule(phase:damagee) isoductile
|
||||||
|
|
||||||
integer, dimension(:), allocatable :: &
|
|
||||||
source_damage_isoDuctile_instance !< instance of damage source mechanism
|
|
||||||
|
|
||||||
type:: tParameters !< container type for internal constitutive parameters
|
type:: tParameters !< container type for internal constitutive parameters
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
gamma_crit, & !< critical plastic strain
|
gamma_crit, & !< critical plastic strain
|
||||||
|
@ -48,17 +45,15 @@ module function isoductile_init(source_length) result(mySources)
|
||||||
if(Ninstances == 0) return
|
if(Ninstances == 0) return
|
||||||
|
|
||||||
phases => config_material%get('phase')
|
phases => config_material%get('phase')
|
||||||
allocate(param(Ninstances))
|
allocate(param(phases%length))
|
||||||
allocate(source_damage_isoDuctile_instance(phases%length), source=0)
|
|
||||||
|
|
||||||
do p = 1, phases%length
|
do p = 1, phases%length
|
||||||
phase => phases%get(p)
|
phase => phases%get(p)
|
||||||
if(count(mySources(:,p)) == 0) cycle
|
if(count(mySources(:,p)) == 0) cycle
|
||||||
if(any(mySources(:,p))) source_damage_isoDuctile_instance(p) = count(mySources(:,1:p))
|
|
||||||
sources => phase%get('damage')
|
sources => phase%get('damage')
|
||||||
do sourceOffset = 1, sources%length
|
do sourceOffset = 1, sources%length
|
||||||
if(mySources(sourceOffset,p)) then
|
if(mySources(sourceOffset,p)) then
|
||||||
associate(prm => param(source_damage_isoDuctile_instance(p)))
|
associate(prm => param(p))
|
||||||
src => sources%get(sourceOffset)
|
src => sources%get(sourceOffset)
|
||||||
|
|
||||||
prm%q = src%get_asFloat('q')
|
prm%q = src%get_asFloat('q')
|
||||||
|
@ -110,8 +105,8 @@ module subroutine isoductile_dotState(co, ip, el)
|
||||||
me = material_phasememberAt(co,ip,el)
|
me = material_phasememberAt(co,ip,el)
|
||||||
|
|
||||||
|
|
||||||
associate(prm => param(source_damage_isoDuctile_instance(ph)))
|
associate(prm => param(ph))
|
||||||
damageState(ph)%dotState(1,me) = sum(plasticState(ph)%slipRate(:,me))/(phase_damage_get_phi(co,ip,el)**prm%q)/prm%gamma_crit
|
damageState(ph)%dotState(1,me) = sum(plasticState(ph)%slipRate(:,me))/(damage_phi(ph,me)**prm%q)/prm%gamma_crit
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
end subroutine isoductile_dotState
|
end subroutine isoductile_dotState
|
||||||
|
@ -150,14 +145,13 @@ module subroutine isoductile_results(phase,group)
|
||||||
|
|
||||||
integer :: o
|
integer :: o
|
||||||
|
|
||||||
associate(prm => param(source_damage_isoDuctile_instance(phase)), &
|
associate(prm => param(phase), stt => damageState(phase)%state)
|
||||||
stt => damageState(phase)%state)
|
outputsLoop: do o = 1,size(prm%output)
|
||||||
outputsLoop: do o = 1,size(prm%output)
|
select case(trim(prm%output(o)))
|
||||||
select case(trim(prm%output(o)))
|
case ('f_phi')
|
||||||
case ('f_phi')
|
call results_writeDataset(group,stt,trim(prm%output(o)),'driving force','J/m³')
|
||||||
call results_writeDataset(group,stt,trim(prm%output(o)),'driving force','J/m³')
|
end select
|
||||||
end select
|
enddo outputsLoop
|
||||||
enddo outputsLoop
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
end subroutine isoductile_results
|
end subroutine isoductile_results
|
||||||
|
|
Loading…
Reference in New Issue