all kinematics modules made consistent
This commit is contained in:
parent
190b90d3d4
commit
13cbd1c42e
|
@ -12,10 +12,10 @@ submodule(constitutive:constitutive_damage) kinematics_cleavage_opening
|
||||||
integer :: &
|
integer :: &
|
||||||
sum_N_cl !< total number of cleavage planes
|
sum_N_cl !< total number of cleavage planes
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
sdot0, & !< opening rate of cleavage planes
|
dot_o, & !< opening rate of cleavage planes
|
||||||
n !< damage rate sensitivity
|
q !< damage rate sensitivity
|
||||||
real(pReal), dimension(:), allocatable :: &
|
real(pReal), dimension(:), allocatable :: &
|
||||||
critLoad
|
g_crit
|
||||||
real(pReal), dimension(:,:,:,:), allocatable :: &
|
real(pReal), dimension(:,:,:,:), allocatable :: &
|
||||||
cleavage_systems
|
cleavage_systems
|
||||||
end type tParameters
|
end type tParameters
|
||||||
|
@ -70,21 +70,21 @@ module function kinematics_cleavage_opening_init(kinematics_length) result(myKin
|
||||||
N_cl = kinematic_type%get_asInts('N_cl')
|
N_cl = kinematic_type%get_asInts('N_cl')
|
||||||
prm%sum_N_cl = sum(abs(N_cl))
|
prm%sum_N_cl = sum(abs(N_cl))
|
||||||
|
|
||||||
prm%n = kinematic_type%get_asFloat('q')
|
prm%q = kinematic_type%get_asFloat('q')
|
||||||
prm%sdot0 = kinematic_type%get_asFloat('dot_o')
|
prm%dot_o = kinematic_type%get_asFloat('dot_o')
|
||||||
|
|
||||||
prm%critLoad = kinematic_type%get_asFloats('g_crit',requiredSize=size(N_cl))
|
prm%g_crit = kinematic_type%get_asFloats('g_crit',requiredSize=size(N_cl))
|
||||||
|
|
||||||
prm%cleavage_systems = lattice_SchmidMatrix_cleavage(N_cl,phase%get_asString('lattice'),&
|
prm%cleavage_systems = lattice_SchmidMatrix_cleavage(N_cl,phase%get_asString('lattice'),&
|
||||||
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
||||||
|
|
||||||
! expand: family => system
|
! expand: family => system
|
||||||
prm%critLoad = math_expand(prm%critLoad,N_cl)
|
prm%g_crit = math_expand(prm%g_crit,N_cl)
|
||||||
|
|
||||||
! sanity checks
|
! sanity checks
|
||||||
if (prm%n <= 0.0_pReal) extmsg = trim(extmsg)//' q'
|
if (prm%q <= 0.0_pReal) extmsg = trim(extmsg)//' q'
|
||||||
if (prm%sdot0 <= 0.0_pReal) extmsg = trim(extmsg)//' dot_o'
|
if (prm%dot_o <= 0.0_pReal) extmsg = trim(extmsg)//' dot_o'
|
||||||
if (any(prm%critLoad < 0.0_pReal)) extmsg = trim(extmsg)//' g_crit'
|
if (any(prm%g_crit < 0.0_pReal)) extmsg = trim(extmsg)//' g_crit'
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! exit if any parameter is out of range
|
! exit if any parameter is out of range
|
||||||
|
@ -128,13 +128,13 @@ module subroutine kinematics_cleavage_opening_LiAndItsTangent(Ld, dLd_dTstar, S,
|
||||||
dLd_dTstar = 0.0_pReal
|
dLd_dTstar = 0.0_pReal
|
||||||
associate(prm => param(kinematics_cleavage_opening_instance(material_phaseAt(ipc,el))))
|
associate(prm => param(kinematics_cleavage_opening_instance(material_phaseAt(ipc,el))))
|
||||||
do i = 1,prm%sum_N_cl
|
do i = 1,prm%sum_N_cl
|
||||||
traction_crit = prm%critLoad(i)* damage(homog)%p(damageOffset)**2.0_pReal
|
traction_crit = prm%g_crit(i)* damage(homog)%p(damageOffset)**2.0_pReal
|
||||||
|
|
||||||
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))
|
||||||
if (abs(traction_d) > traction_crit + tol_math_check) then
|
if (abs(traction_d) > traction_crit + tol_math_check) then
|
||||||
udotd = sign(1.0_pReal,traction_d)* prm%sdot0 * ((abs(traction_d) - traction_crit)/traction_crit)**prm%n
|
udotd = sign(1.0_pReal,traction_d)* prm%dot_o * ((abs(traction_d) - traction_crit)/traction_crit)**prm%q
|
||||||
Ld = Ld + udotd*prm%cleavage_systems(1:3,1:3,1,i)
|
Ld = Ld + udotd*prm%cleavage_systems(1:3,1:3,1,i)
|
||||||
dudotd_dt = sign(1.0_pReal,traction_d)*udotd*prm%n / (abs(traction_d) - traction_crit)
|
dudotd_dt = sign(1.0_pReal,traction_d)*udotd*prm%q / (abs(traction_d) - traction_crit)
|
||||||
forall (k=1:3,l=1:3,m=1:3,n=1:3) &
|
forall (k=1:3,l=1:3,m=1:3,n=1:3) &
|
||||||
dLd_dTstar(k,l,m,n) = dLd_dTstar(k,l,m,n) &
|
dLd_dTstar(k,l,m,n) = dLd_dTstar(k,l,m,n) &
|
||||||
+ dudotd_dt*prm%cleavage_systems(k,l,1,i) * prm%cleavage_systems(m,n,1,i)
|
+ dudotd_dt*prm%cleavage_systems(k,l,1,i) * prm%cleavage_systems(m,n,1,i)
|
||||||
|
@ -142,9 +142,9 @@ module subroutine kinematics_cleavage_opening_LiAndItsTangent(Ld, dLd_dTstar, S,
|
||||||
|
|
||||||
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))
|
||||||
if (abs(traction_t) > traction_crit + tol_math_check) then
|
if (abs(traction_t) > traction_crit + tol_math_check) then
|
||||||
udott = sign(1.0_pReal,traction_t)* prm%sdot0 * ((abs(traction_t) - traction_crit)/traction_crit)**prm%n
|
udott = sign(1.0_pReal,traction_t)* prm%dot_o * ((abs(traction_t) - traction_crit)/traction_crit)**prm%q
|
||||||
Ld = Ld + udott*prm%cleavage_systems(1:3,1:3,2,i)
|
Ld = Ld + udott*prm%cleavage_systems(1:3,1:3,2,i)
|
||||||
dudott_dt = sign(1.0_pReal,traction_t)*udott*prm%n / (abs(traction_t) - traction_crit)
|
dudott_dt = sign(1.0_pReal,traction_t)*udott*prm%q / (abs(traction_t) - traction_crit)
|
||||||
forall (k=1:3,l=1:3,m=1:3,n=1:3) &
|
forall (k=1:3,l=1:3,m=1:3,n=1:3) &
|
||||||
dLd_dTstar(k,l,m,n) = dLd_dTstar(k,l,m,n) &
|
dLd_dTstar(k,l,m,n) = dLd_dTstar(k,l,m,n) &
|
||||||
+ dudott_dt*prm%cleavage_systems(k,l,2,i) * prm%cleavage_systems(m,n,2,i)
|
+ dudott_dt*prm%cleavage_systems(k,l,2,i) * prm%cleavage_systems(m,n,2,i)
|
||||||
|
@ -152,9 +152,9 @@ module subroutine kinematics_cleavage_opening_LiAndItsTangent(Ld, dLd_dTstar, S,
|
||||||
|
|
||||||
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))
|
||||||
if (abs(traction_n) > traction_crit + tol_math_check) then
|
if (abs(traction_n) > traction_crit + tol_math_check) then
|
||||||
udotn = sign(1.0_pReal,traction_n)* prm%sdot0 * ((abs(traction_n) - traction_crit)/traction_crit)**prm%n
|
udotn = sign(1.0_pReal,traction_n)* prm%dot_o * ((abs(traction_n) - traction_crit)/traction_crit)**prm%q
|
||||||
Ld = Ld + udotn*prm%cleavage_systems(1:3,1:3,3,i)
|
Ld = Ld + udotn*prm%cleavage_systems(1:3,1:3,3,i)
|
||||||
dudotn_dt = sign(1.0_pReal,traction_n)*udotn*prm%n / (abs(traction_n) - traction_crit)
|
dudotn_dt = sign(1.0_pReal,traction_n)*udotn*prm%q / (abs(traction_n) - traction_crit)
|
||||||
forall (k=1:3,l=1:3,m=1:3,n=1:3) &
|
forall (k=1:3,l=1:3,m=1:3,n=1:3) &
|
||||||
dLd_dTstar(k,l,m,n) = dLd_dTstar(k,l,m,n) &
|
dLd_dTstar(k,l,m,n) = dLd_dTstar(k,l,m,n) &
|
||||||
+ dudotn_dt*prm%cleavage_systems(k,l,3,i) * prm%cleavage_systems(m,n,3,i)
|
+ dudotn_dt*prm%cleavage_systems(k,l,3,i) * prm%cleavage_systems(m,n,3,i)
|
||||||
|
|
|
@ -12,10 +12,10 @@ submodule(constitutive:constitutive_damage) kinematics_slipplane_opening
|
||||||
integer :: &
|
integer :: &
|
||||||
sum_N_sl !< total number of cleavage planes
|
sum_N_sl !< total number of cleavage planes
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
sdot0, & !< opening rate of cleavage planes
|
dot_o, & !< opening rate of cleavage planes
|
||||||
n !< damage rate sensitivity
|
q !< damage rate sensitivity
|
||||||
real(pReal), dimension(:), allocatable :: &
|
real(pReal), dimension(:), allocatable :: &
|
||||||
critLoad
|
g_crit
|
||||||
real(pReal), dimension(:,:,:), allocatable :: &
|
real(pReal), dimension(:,:,:), allocatable :: &
|
||||||
P_d, &
|
P_d, &
|
||||||
P_t, &
|
P_t, &
|
||||||
|
@ -70,8 +70,8 @@ module function kinematics_slipplane_opening_init(kinematics_length) result(myKi
|
||||||
associate(prm => param(kinematics_slipplane_opening_instance(p)))
|
associate(prm => param(kinematics_slipplane_opening_instance(p)))
|
||||||
kinematic_type => kinematics%get(k)
|
kinematic_type => kinematics%get(k)
|
||||||
|
|
||||||
prm%sdot0 = kinematic_type%get_asFloat('dot_o')
|
prm%dot_o = kinematic_type%get_asFloat('dot_o')
|
||||||
prm%n = kinematic_type%get_asFloat('q')
|
prm%q = kinematic_type%get_asFloat('q')
|
||||||
N_sl = pl%get_asInts('N_sl')
|
N_sl = pl%get_asInts('N_sl')
|
||||||
prm%sum_N_sl = sum(abs(N_sl))
|
prm%sum_N_sl = sum(abs(N_sl))
|
||||||
|
|
||||||
|
@ -89,15 +89,15 @@ module function kinematics_slipplane_opening_init(kinematics_length) result(myKi
|
||||||
prm%P_n(1:3,1:3,i) = math_outer(n(1:3,i), n(1:3,i))
|
prm%P_n(1:3,1:3,i) = math_outer(n(1:3,i), n(1:3,i))
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
prm%critLoad = kinematic_type%get_asFloats('g_crit',requiredSize=size(N_sl))
|
prm%g_crit = kinematic_type%get_asFloats('g_crit',requiredSize=size(N_sl))
|
||||||
|
|
||||||
! expand: family => system
|
! expand: family => system
|
||||||
prm%critLoad = math_expand(prm%critLoad,N_sl)
|
prm%g_crit = math_expand(prm%g_crit,N_sl)
|
||||||
|
|
||||||
! sanity checks
|
! sanity checks
|
||||||
if (prm%n <= 0.0_pReal) extmsg = trim(extmsg)//' anisoDuctile_n'
|
if (prm%q <= 0.0_pReal) extmsg = trim(extmsg)//' anisoDuctile_n'
|
||||||
if (prm%sdot0 <= 0.0_pReal) extmsg = trim(extmsg)//' anisoDuctile_sdot0'
|
if (prm%dot_o <= 0.0_pReal) extmsg = trim(extmsg)//' anisoDuctile_sdot0'
|
||||||
if (any(prm%critLoad < 0.0_pReal)) extmsg = trim(extmsg)//' anisoDuctile_critLoad'
|
if (any(prm%g_crit < 0.0_pReal)) extmsg = trim(extmsg)//' anisoDuctile_critLoad'
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! exit if any parameter is out of range
|
! exit if any parameter is out of range
|
||||||
|
@ -150,27 +150,27 @@ module subroutine kinematics_slipplane_opening_LiAndItsTangent(Ld, dLd_dTstar, S
|
||||||
traction_t = math_tensordot(S,prm%P_t(1:3,1:3,i))
|
traction_t = math_tensordot(S,prm%P_t(1:3,1:3,i))
|
||||||
traction_n = math_tensordot(S,prm%P_n(1:3,1:3,i))
|
traction_n = math_tensordot(S,prm%P_n(1:3,1:3,i))
|
||||||
|
|
||||||
traction_crit = prm%critLoad(i)* damage(homog)%p(damageOffset) ! degrading critical load carrying capacity by damage
|
traction_crit = prm%g_crit(i)* damage(homog)%p(damageOffset) ! degrading critical load carrying capacity by damage
|
||||||
|
|
||||||
udotd = sign(1.0_pReal,traction_d)* prm%sdot0* ( abs(traction_d)/traction_crit &
|
udotd = sign(1.0_pReal,traction_d)* prm%dot_o* ( abs(traction_d)/traction_crit &
|
||||||
- abs(traction_d)/prm%critLoad(i))**prm%n
|
- abs(traction_d)/prm%g_crit(i))**prm%q
|
||||||
udott = sign(1.0_pReal,traction_t)* prm%sdot0* ( abs(traction_t)/traction_crit &
|
udott = sign(1.0_pReal,traction_t)* prm%dot_o* ( abs(traction_t)/traction_crit &
|
||||||
- abs(traction_t)/prm%critLoad(i))**prm%n
|
- abs(traction_t)/prm%g_crit(i))**prm%q
|
||||||
udotn = prm%sdot0* ( max(0.0_pReal,traction_n)/traction_crit &
|
udotn = prm%dot_o* ( max(0.0_pReal,traction_n)/traction_crit &
|
||||||
- max(0.0_pReal,traction_n)/prm%critLoad(i))**prm%n
|
- max(0.0_pReal,traction_n)/prm%g_crit(i))**prm%q
|
||||||
|
|
||||||
if (dNeq0(traction_d)) then
|
if (dNeq0(traction_d)) then
|
||||||
dudotd_dt = udotd*prm%n/traction_d
|
dudotd_dt = udotd*prm%q/traction_d
|
||||||
else
|
else
|
||||||
dudotd_dt = 0.0_pReal
|
dudotd_dt = 0.0_pReal
|
||||||
endif
|
endif
|
||||||
if (dNeq0(traction_t)) then
|
if (dNeq0(traction_t)) then
|
||||||
dudott_dt = udott*prm%n/traction_t
|
dudott_dt = udott*prm%q/traction_t
|
||||||
else
|
else
|
||||||
dudott_dt = 0.0_pReal
|
dudott_dt = 0.0_pReal
|
||||||
endif
|
endif
|
||||||
if (dNeq0(traction_n)) then
|
if (dNeq0(traction_n)) then
|
||||||
dudotn_dt = udotn*prm%n/traction_n
|
dudotn_dt = udotn*prm%q/traction_n
|
||||||
else
|
else
|
||||||
dudotn_dt = 0.0_pReal
|
dudotn_dt = 0.0_pReal
|
||||||
endif
|
endif
|
||||||
|
|
|
@ -11,7 +11,7 @@ submodule(constitutive:constitutive_thermal) kinematics_thermal_expansion
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
T_ref
|
T_ref
|
||||||
real(pReal), dimension(3,3,3) :: &
|
real(pReal), dimension(3,3,3) :: &
|
||||||
expansion = 0.0_pReal
|
A = 0.0_pReal
|
||||||
end type tParameters
|
end type tParameters
|
||||||
|
|
||||||
type(tParameters), dimension(:), allocatable :: param
|
type(tParameters), dimension(:), allocatable :: param
|
||||||
|
@ -64,13 +64,13 @@ module function kinematics_thermal_expansion_init(kinematics_length) result(myKi
|
||||||
|
|
||||||
! read up to three parameters (constant, linear, quadratic with T)
|
! read up to three parameters (constant, linear, quadratic with T)
|
||||||
temp = kinematic_type%get_asFloats('A_11')
|
temp = kinematic_type%get_asFloats('A_11')
|
||||||
prm%expansion(1,1,1:size(temp)) = temp
|
prm%A(1,1,1:size(temp)) = temp
|
||||||
temp = kinematic_type%get_asFloats('A_22',defaultVal=[(0.0_pReal, i=1,size(temp))],requiredSize=size(temp))
|
temp = kinematic_type%get_asFloats('A_22',defaultVal=[(0.0_pReal, i=1,size(temp))],requiredSize=size(temp))
|
||||||
prm%expansion(2,2,1:size(temp)) = temp
|
prm%A(2,2,1:size(temp)) = temp
|
||||||
temp = kinematic_type%get_asFloats('A_33',defaultVal=[(0.0_pReal, i=1,size(temp))],requiredSize=size(temp))
|
temp = kinematic_type%get_asFloats('A_33',defaultVal=[(0.0_pReal, i=1,size(temp))],requiredSize=size(temp))
|
||||||
prm%expansion(3,3,1:size(temp)) = temp
|
prm%A(3,3,1:size(temp)) = temp
|
||||||
do i=1, size(prm%expansion,3)
|
do i=1, size(prm%A,3)
|
||||||
prm%expansion(1:3,1:3,i) = lattice_applyLatticeSymmetry33(prm%expansion(1:3,1:3,i),&
|
prm%A(1:3,1:3,i) = lattice_applyLatticeSymmetry33(prm%A(1:3,1:3,i),&
|
||||||
phase%get_asString('lattice'))
|
phase%get_asString('lattice'))
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
@ -94,13 +94,13 @@ pure module function kinematics_thermal_expansion_initialStrain(homog,phase,offs
|
||||||
offset
|
offset
|
||||||
|
|
||||||
real(pReal), dimension(3,3) :: &
|
real(pReal), dimension(3,3) :: &
|
||||||
initialStrain !< initial thermal strain (should be small strain, though)
|
initialStrain !< initial thermal strain (should be small strain, though)
|
||||||
|
|
||||||
associate(prm => param(kinematics_thermal_expansion_instance(phase)))
|
associate(prm => param(kinematics_thermal_expansion_instance(phase)))
|
||||||
initialStrain = &
|
initialStrain = &
|
||||||
(temperature(homog)%p(offset) - prm%T_ref)**1 / 1. * prm%expansion(1:3,1:3,1) + & ! constant coefficient
|
(temperature(homog)%p(offset) - prm%T_ref)**1 / 1. * prm%A(1:3,1:3,1) + & ! constant coefficient
|
||||||
(temperature(homog)%p(offset) - prm%T_ref)**2 / 2. * prm%expansion(1:3,1:3,2) + & ! linear coefficient
|
(temperature(homog)%p(offset) - prm%T_ref)**2 / 2. * prm%A(1:3,1:3,2) + & ! linear coefficient
|
||||||
(temperature(homog)%p(offset) - prm%T_ref)**3 / 3. * prm%expansion(1:3,1:3,3) ! quadratic coefficient
|
(temperature(homog)%p(offset) - prm%T_ref)**3 / 3. * prm%A(1:3,1:3,3) ! quadratic coefficient
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
end function kinematics_thermal_expansion_initialStrain
|
end function kinematics_thermal_expansion_initialStrain
|
||||||
|
@ -133,14 +133,14 @@ module subroutine kinematics_thermal_expansion_LiAndItsTangent(Li, dLi_dTstar, i
|
||||||
|
|
||||||
associate(prm => param(kinematics_thermal_expansion_instance(phase)))
|
associate(prm => param(kinematics_thermal_expansion_instance(phase)))
|
||||||
Li = TDot * ( &
|
Li = TDot * ( &
|
||||||
prm%expansion(1:3,1:3,1)*(T - prm%T_ref)**0 & ! constant coefficient
|
prm%A(1:3,1:3,1)*(T - prm%T_ref)**0 & ! constant coefficient
|
||||||
+ prm%expansion(1:3,1:3,2)*(T - prm%T_ref)**1 & ! linear coefficient
|
+ prm%A(1:3,1:3,2)*(T - prm%T_ref)**1 & ! linear coefficient
|
||||||
+ prm%expansion(1:3,1:3,3)*(T - prm%T_ref)**2 & ! quadratic coefficient
|
+ prm%A(1:3,1:3,3)*(T - prm%T_ref)**2 & ! quadratic coefficient
|
||||||
) / &
|
) / &
|
||||||
(1.0_pReal &
|
(1.0_pReal &
|
||||||
+ prm%expansion(1:3,1:3,1)*(T - prm%T_ref)**1 / 1. &
|
+ prm%A(1:3,1:3,1)*(T - prm%T_ref)**1 / 1. &
|
||||||
+ prm%expansion(1:3,1:3,2)*(T - prm%T_ref)**2 / 2. &
|
+ prm%A(1:3,1:3,2)*(T - prm%T_ref)**2 / 2. &
|
||||||
+ prm%expansion(1:3,1:3,3)*(T - prm%T_ref)**3 / 3. &
|
+ prm%A(1:3,1:3,3)*(T - prm%T_ref)**3 / 3. &
|
||||||
)
|
)
|
||||||
end associate
|
end associate
|
||||||
dLi_dTstar = 0.0_pReal
|
dLi_dTstar = 0.0_pReal
|
||||||
|
|
Loading…
Reference in New Issue