cleaning
This commit is contained in:
parent
fcaa319f56
commit
50a7caa61a
|
@ -1,7 +1,7 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief elasticity, plasticity, internal microstructure state
|
||||
!> @brief elasticity, plasticity, damage & thermal internal microstructure state
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module constitutive
|
||||
use prec
|
||||
|
@ -81,8 +81,8 @@ module constitutive
|
|||
end subroutine plastic_disloUCLA_dotState
|
||||
|
||||
module subroutine plastic_nonlocal_dotState(Mp, F, Fp, Temperature,timestep, &
|
||||
instance,of,ip,el)
|
||||
real(pReal), dimension(3,3), intent(in) ::&
|
||||
instance,of,ip,el)
|
||||
real(pReal), dimension(3,3), intent(in) :: &
|
||||
Mp !< MandelStress
|
||||
real(pReal), dimension(3,3,homogenization_maxNgrains,discretization_nIP,discretization_nElem), intent(in) :: &
|
||||
F, & !< deformation gradient
|
||||
|
@ -99,7 +99,6 @@ module constitutive
|
|||
|
||||
|
||||
module subroutine source_damage_anisoBrittle_dotState(S, ipc, ip, el)
|
||||
|
||||
integer, intent(in) :: &
|
||||
ipc, & !< component-ID of integration point
|
||||
ip, & !< integration point
|
||||
|
@ -109,7 +108,6 @@ module constitutive
|
|||
end subroutine source_damage_anisoBrittle_dotState
|
||||
|
||||
module subroutine source_damage_anisoDuctile_dotState(ipc, ip, el)
|
||||
|
||||
integer, intent(in) :: &
|
||||
ipc, & !< component-ID of integration point
|
||||
ip, & !< integration point
|
||||
|
@ -117,7 +115,6 @@ module constitutive
|
|||
end subroutine source_damage_anisoDuctile_dotState
|
||||
|
||||
module subroutine source_damage_isoDuctile_dotState(ipc, ip, el)
|
||||
|
||||
integer, intent(in) :: &
|
||||
ipc, & !< component-ID of integration point
|
||||
ip, & !< integration point
|
||||
|
@ -125,12 +122,36 @@ module constitutive
|
|||
end subroutine source_damage_isoDuctile_dotState
|
||||
|
||||
module subroutine source_thermal_externalheat_dotState(phase, of)
|
||||
|
||||
integer, intent(in) :: &
|
||||
phase, &
|
||||
of
|
||||
end subroutine source_thermal_externalheat_dotState
|
||||
|
||||
module subroutine constitutive_damage_getRateAndItsTangents(phiDot, dPhiDot_dPhi, phi, ip, el)
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
phi !< damage parameter
|
||||
real(pReal), intent(inout) :: &
|
||||
phiDot, &
|
||||
dPhiDot_dPhi
|
||||
end subroutine constitutive_damage_getRateAndItsTangents
|
||||
|
||||
module subroutine constitutive_thermal_getRateAndItsTangents(TDot, dTDot_dT, T, S, Lp, ip, el)
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
T
|
||||
real(pReal), intent(in), dimension(:,:,:,:,:) :: &
|
||||
S, & !< current 2nd Piola Kitchoff stress vector
|
||||
Lp !< plastic velocity gradient
|
||||
real(pReal), intent(inout) :: &
|
||||
TDot, &
|
||||
dTDot_dT
|
||||
end subroutine constitutive_thermal_getRateAndItsTangents
|
||||
|
||||
module function plastic_dislotwin_homogenizedC(ipc,ip,el) result(homogenizedC)
|
||||
real(pReal), dimension(6,6) :: &
|
||||
homogenizedC
|
||||
|
@ -140,43 +161,13 @@ module constitutive
|
|||
el !< element
|
||||
end function plastic_dislotwin_homogenizedC
|
||||
|
||||
module subroutine constitutive_plastic_dependentState(F, Fp, ipc, ip, el)
|
||||
|
||||
integer, intent(in) :: &
|
||||
ipc, & !< component-ID of integration point
|
||||
ip, & !< integration point
|
||||
el !< element
|
||||
real(pReal), intent(in), dimension(3,3) :: &
|
||||
F, & !< elastic deformation gradient
|
||||
Fp !< plastic deformation gradient
|
||||
end subroutine constitutive_plastic_dependentState
|
||||
|
||||
module subroutine constitutive_plastic_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, &
|
||||
S, Fi, ipc, ip, el)
|
||||
integer, intent(in) :: &
|
||||
ipc, & !< component-ID of integration point
|
||||
ip, & !< integration point
|
||||
el !< element
|
||||
real(pReal), intent(in), dimension(3,3) :: &
|
||||
S, & !< 2nd Piola-Kirchhoff stress
|
||||
Fi !< intermediate deformation gradient
|
||||
real(pReal), intent(out), dimension(3,3) :: &
|
||||
Lp !< plastic velocity gradient
|
||||
real(pReal), intent(out), dimension(3,3,3,3) :: &
|
||||
dLp_dS, &
|
||||
dLp_dFi !< derivative of Lp with respect to Fi
|
||||
|
||||
end subroutine constitutive_plastic_LpAndItsTangents
|
||||
|
||||
pure module function kinematics_thermal_expansion_initialStrain(homog,phase,offset) result(initialStrain)
|
||||
|
||||
integer, intent(in) :: &
|
||||
phase, &
|
||||
homog, &
|
||||
offset
|
||||
real(pReal), dimension(3,3) :: &
|
||||
initialStrain
|
||||
|
||||
end function kinematics_thermal_expansion_initialStrain
|
||||
|
||||
module subroutine plastic_nonlocal_updateCompatibility(orientation,instance,i,e)
|
||||
|
@ -188,39 +179,11 @@ module constitutive
|
|||
orientation !< crystal orientation
|
||||
end subroutine plastic_nonlocal_updateCompatibility
|
||||
|
||||
module subroutine constitutive_damage_getRateAndItsTangents(phiDot, dPhiDot_dPhi, phi, ip, el)
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
phi
|
||||
real(pReal), intent(inout) :: &
|
||||
phiDot, &
|
||||
dPhiDot_dPhi
|
||||
|
||||
end subroutine constitutive_damage_getRateAndItsTangents
|
||||
|
||||
module subroutine constitutive_thermal_getRateAndItsTangents(TDot, dTDot_dT, T, Tstar, Lp, ip, el)
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
T
|
||||
real(pReal), intent(in), dimension(:,:,:,:,:) :: &
|
||||
Tstar, &
|
||||
Lp
|
||||
real(pReal), intent(inout) :: &
|
||||
TDot, &
|
||||
dTDot_dT
|
||||
end subroutine constitutive_thermal_getRateAndItsTangents
|
||||
|
||||
|
||||
module subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dMi,Mi,instance,of)
|
||||
real(pReal), dimension(3,3), intent(out) :: &
|
||||
Li !< inleastic velocity gradient
|
||||
real(pReal), dimension(3,3,3,3), intent(out) :: &
|
||||
dLi_dMi !< derivative of Li with respect to Mandel stress
|
||||
|
||||
real(pReal), dimension(3,3), intent(in) :: &
|
||||
Mi !< Mandel stress
|
||||
integer, intent(in) :: &
|
||||
|
@ -229,7 +192,6 @@ module constitutive
|
|||
end subroutine plastic_isotropic_LiAndItsTangent
|
||||
|
||||
module subroutine kinematics_cleavage_opening_LiAndItsTangent(Ld, dLd_dTstar, S, ipc, ip, el)
|
||||
|
||||
integer, intent(in) :: &
|
||||
ipc, & !< grain number
|
||||
ip, & !< integration point number
|
||||
|
@ -243,7 +205,6 @@ module constitutive
|
|||
end subroutine kinematics_cleavage_opening_LiAndItsTangent
|
||||
|
||||
module subroutine kinematics_slipplane_opening_LiAndItsTangent(Ld, dLd_dTstar, S, ipc, ip, el)
|
||||
|
||||
integer, intent(in) :: &
|
||||
ipc, & !< grain number
|
||||
ip, & !< integration point number
|
||||
|
@ -257,7 +218,6 @@ module constitutive
|
|||
end subroutine kinematics_slipplane_opening_LiAndItsTangent
|
||||
|
||||
module subroutine kinematics_thermal_expansion_LiAndItsTangent(Li, dLi_dTstar, ipc, ip, el)
|
||||
|
||||
integer, intent(in) :: &
|
||||
ipc, & !< grain number
|
||||
ip, & !< integration point number
|
||||
|
@ -307,17 +267,40 @@ module constitutive
|
|||
end interface
|
||||
|
||||
interface constitutive_LpAndItsTangents
|
||||
module procedure :: constitutive_plastic_LpAndItsTangents
|
||||
|
||||
module subroutine constitutive_plastic_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, &
|
||||
S, Fi, ipc, ip, el)
|
||||
integer, intent(in) :: &
|
||||
ipc, & !< component-ID of integration point
|
||||
ip, & !< integration point
|
||||
el !< element
|
||||
real(pReal), intent(in), dimension(3,3) :: &
|
||||
S, & !< 2nd Piola-Kirchhoff stress
|
||||
Fi !< intermediate deformation gradient
|
||||
real(pReal), intent(out), dimension(3,3) :: &
|
||||
Lp !< plastic velocity gradient
|
||||
real(pReal), intent(out), dimension(3,3,3,3) :: &
|
||||
dLp_dS, &
|
||||
dLp_dFi !< derivative of Lp with respect to Fi
|
||||
end subroutine constitutive_plastic_LpAndItsTangents
|
||||
|
||||
end interface constitutive_LpAndItsTangents
|
||||
|
||||
|
||||
interface constitutive_dependentState
|
||||
module procedure :: constitutive_plastic_dependentState
|
||||
|
||||
module subroutine constitutive_plastic_dependentState(F, Fp, ipc, ip, el)
|
||||
integer, intent(in) :: &
|
||||
ipc, & !< component-ID of integration point
|
||||
ip, & !< integration point
|
||||
el !< element
|
||||
real(pReal), intent(in), dimension(3,3) :: &
|
||||
F, & !< elastic deformation gradient
|
||||
Fp !< plastic deformation gradient
|
||||
end subroutine constitutive_plastic_dependentState
|
||||
|
||||
end interface constitutive_dependentState
|
||||
|
||||
interface constitutive_getRateAndItsTangents
|
||||
module procedure :: constitutive_damage_getRateAndItsTangents , &
|
||||
constitutive_thermal_getRateAndItsTangents
|
||||
end interface constitutive_getRateAndItsTangents
|
||||
|
||||
type :: tDebugOptions
|
||||
logical :: &
|
||||
|
@ -343,14 +326,15 @@ module constitutive
|
|||
constitutive_collectDotState, &
|
||||
constitutive_deltaState, &
|
||||
plastic_nonlocal_updateCompatibility, &
|
||||
constitutive_getRateAndItsTangents, &
|
||||
constitutive_damage_getRateAndItsTangents, &
|
||||
constitutive_thermal_getRateAndItsTangents, &
|
||||
constitutive_results
|
||||
|
||||
contains
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief allocates arrays pointing to array of the various constitutive modules
|
||||
!> @brief Initialze constitutive models for individual physics
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine constitutive_init
|
||||
|
||||
|
|
|
@ -1,3 +1,6 @@
|
|||
!----------------------------------------------------------------------------------------------------
|
||||
!> @brief internal microstructure state for all damage sources and kinematics constitutive models
|
||||
!----------------------------------------------------------------------------------------------------
|
||||
submodule(constitutive) constitutive_damage
|
||||
|
||||
interface
|
||||
|
@ -26,7 +29,7 @@ submodule(constitutive) constitutive_damage
|
|||
phase, & !< phase ID of element
|
||||
constituent !< position of element within its phase instance
|
||||
real(pReal), intent(in) :: &
|
||||
phi !< damage value
|
||||
phi !< damage parameter
|
||||
real(pReal), intent(out) :: &
|
||||
localphiDot, &
|
||||
dLocalphiDot_dPhi
|
||||
|
@ -34,10 +37,10 @@ submodule(constitutive) constitutive_damage
|
|||
|
||||
module subroutine source_damage_anisoDuctile_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, phase, constituent)
|
||||
integer, intent(in) :: &
|
||||
phase, &
|
||||
constituent
|
||||
phase, & !< phase ID of element
|
||||
constituent !< position of element within its phase instance
|
||||
real(pReal), intent(in) :: &
|
||||
phi
|
||||
phi !< damage parameter
|
||||
real(pReal), intent(out) :: &
|
||||
localphiDot, &
|
||||
dLocalphiDot_dPhi
|
||||
|
@ -45,10 +48,10 @@ submodule(constitutive) constitutive_damage
|
|||
|
||||
module subroutine source_damage_isoBrittle_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, phase, constituent)
|
||||
integer, intent(in) :: &
|
||||
phase, &
|
||||
constituent
|
||||
phase, & !< phase ID of element
|
||||
constituent !< position of element within its phase instance
|
||||
real(pReal), intent(in) :: &
|
||||
phi
|
||||
phi !< damage parameter
|
||||
real(pReal), intent(out) :: &
|
||||
localphiDot, &
|
||||
dLocalphiDot_dPhi
|
||||
|
@ -56,28 +59,15 @@ submodule(constitutive) constitutive_damage
|
|||
|
||||
module subroutine source_damage_isoDuctile_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, phase, constituent)
|
||||
integer, intent(in) :: &
|
||||
phase, &
|
||||
constituent
|
||||
phase, & !< phase ID of element
|
||||
constituent !< position of element within its phase instance
|
||||
real(pReal), intent(in) :: &
|
||||
phi
|
||||
phi !< damage parameter
|
||||
real(pReal), intent(out) :: &
|
||||
localphiDot, &
|
||||
dLocalphiDot_dPhi
|
||||
end subroutine source_damage_isoDuctile_getRateAndItsTangent
|
||||
|
||||
module subroutine source_thermal_dissipation_getRateAndItsTangent(TDot, dTDot_dT, Tstar, Lp, phase)
|
||||
integer, intent(in) :: &
|
||||
phase
|
||||
real(pReal), intent(in), dimension(3,3) :: &
|
||||
Tstar
|
||||
real(pReal), intent(in), dimension(3,3) :: &
|
||||
Lp
|
||||
|
||||
real(pReal), intent(out) :: &
|
||||
TDot, &
|
||||
dTDot_dT
|
||||
end subroutine source_thermal_dissipation_getRateAndItsTangent
|
||||
|
||||
module subroutine source_damage_anisoBrittle_results(phase,group)
|
||||
integer, intent(in) :: phase
|
||||
character(len=*), intent(in) :: group
|
||||
|
@ -108,10 +98,10 @@ contains
|
|||
module subroutine damage_init
|
||||
|
||||
! initialize source mechanisms
|
||||
if (any(phase_source == SOURCE_damage_isoBrittle_ID)) call source_damage_isoBrittle_init
|
||||
if (any(phase_source == SOURCE_damage_isoDuctile_ID)) call source_damage_isoDuctile_init
|
||||
if (any(phase_source == SOURCE_damage_anisoBrittle_ID)) call source_damage_anisoBrittle_init
|
||||
if (any(phase_source == SOURCE_damage_anisoDuctile_ID)) call source_damage_anisoDuctile_init
|
||||
if (any(phase_source == SOURCE_damage_isoBrittle_ID)) call source_damage_isoBrittle_init
|
||||
if (any(phase_source == SOURCE_damage_isoDuctile_ID)) call source_damage_isoDuctile_init
|
||||
if (any(phase_source == SOURCE_damage_anisoBrittle_ID)) call source_damage_anisoBrittle_init
|
||||
if (any(phase_source == SOURCE_damage_anisoDuctile_ID)) call source_damage_anisoDuctile_init
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! initialize kinematic mechanisms
|
||||
|
@ -127,10 +117,10 @@ end subroutine damage_init
|
|||
module subroutine constitutive_damage_getRateAndItsTangents(phiDot, dPhiDot_dPhi, phi, ip, el)
|
||||
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
phi
|
||||
phi !< damage parameter
|
||||
real(pReal), intent(inout) :: &
|
||||
phiDot, &
|
||||
dPhiDot_dPhi
|
||||
|
@ -209,4 +199,4 @@ module subroutine damage_results
|
|||
end subroutine damage_results
|
||||
|
||||
|
||||
end submodule
|
||||
end submodule constitutive_damage
|
||||
|
|
|
@ -1,3 +1,6 @@
|
|||
!----------------------------------------------------------------------------------------------------
|
||||
!> @brief internal microstructure state for all plasticity constitutive models
|
||||
!----------------------------------------------------------------------------------------------------
|
||||
submodule(constitutive) constitutive_plastic
|
||||
|
||||
interface
|
||||
|
@ -42,7 +45,6 @@ submodule(constitutive) constitutive_plastic
|
|||
Lp !< plastic velocity gradient
|
||||
real(pReal), dimension(3,3,3,3), intent(out) :: &
|
||||
dLp_dMp !< derivative of Lp with respect to the Mandel stress
|
||||
|
||||
real(pReal), dimension(3,3), intent(in) :: &
|
||||
Mp !< Mandel stress
|
||||
integer, intent(in) :: &
|
||||
|
@ -128,13 +130,13 @@ submodule(constitutive) constitutive_plastic
|
|||
|
||||
module subroutine plastic_nonlocal_dependentState(F, Fp, instance, of, ip, el)
|
||||
real(pReal), dimension(3,3), intent(in) :: &
|
||||
F, &
|
||||
Fp
|
||||
F, & !< deformation gradient
|
||||
Fp !< plastic deformation gradient
|
||||
integer, intent(in) :: &
|
||||
instance, &
|
||||
of, &
|
||||
ip, &
|
||||
el
|
||||
ip, & !< current integration point
|
||||
el !< current element number
|
||||
end subroutine plastic_nonlocal_dependentState
|
||||
|
||||
module subroutine plastic_isotropic_results(instance,group)
|
||||
|
|
|
@ -1,3 +1,6 @@
|
|||
!----------------------------------------------------------------------------------------------------
|
||||
!> @brief internal microstructure state for all thermal sources and kinematics constitutive models
|
||||
!----------------------------------------------------------------------------------------------------
|
||||
submodule(constitutive) constitutive_thermal
|
||||
|
||||
interface
|
||||
|
@ -13,29 +16,24 @@ submodule(constitutive) constitutive_thermal
|
|||
|
||||
|
||||
module subroutine source_thermal_dissipation_getRateAndItsTangent(TDot, dTDot_dT, Tstar, Lp, phase)
|
||||
|
||||
integer, intent(in) :: &
|
||||
phase
|
||||
phase !< phase ID of element
|
||||
real(pReal), intent(in), dimension(3,3) :: &
|
||||
Tstar
|
||||
Tstar !< 2nd Piola Kirchoff stress tensor for a given element
|
||||
real(pReal), intent(in), dimension(3,3) :: &
|
||||
Lp
|
||||
|
||||
Lp !< plastic velocuty gradient for a given element
|
||||
real(pReal), intent(out) :: &
|
||||
TDot, &
|
||||
dTDot_dT
|
||||
|
||||
end subroutine source_thermal_dissipation_getRateAndItsTangent
|
||||
|
||||
module subroutine source_thermal_externalheat_getRateAndItsTangent(TDot, dTDot_dT, phase, of)
|
||||
|
||||
integer, intent(in) :: &
|
||||
phase, &
|
||||
of
|
||||
real(pReal), intent(out) :: &
|
||||
TDot, &
|
||||
dTDot_dT
|
||||
|
||||
end subroutine source_thermal_externalheat_getRateAndItsTangent
|
||||
|
||||
end interface
|
||||
|
@ -61,15 +59,15 @@ end subroutine thermal_init
|
|||
!----------------------------------------------------------------------------------------------
|
||||
!< @brief calculates thermal dissipation rate
|
||||
!----------------------------------------------------------------------------------------------
|
||||
module subroutine constitutive_thermal_getRateAndItsTangents(TDot, dTDot_dT, T, Tstar, Lp, ip, el)
|
||||
module subroutine constitutive_thermal_getRateAndItsTangents(TDot, dTDot_dT, T, S, Lp, ip, el)
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
T
|
||||
real(pReal), intent(in), dimension(:,:,:,:,:) :: &
|
||||
Tstar, &
|
||||
Lp
|
||||
S, & !< current 2nd Piola Kirchoff stress
|
||||
Lp !< plastic velocity gradient
|
||||
real(pReal), intent(inout) :: &
|
||||
TDot, &
|
||||
dTDot_dT
|
||||
|
@ -95,7 +93,7 @@ module subroutine constitutive_thermal_getRateAndItsTangents(TDot, dTDot_dT, T,
|
|||
select case(phase_source(source,phase))
|
||||
case (SOURCE_thermal_dissipation_ID)
|
||||
call source_thermal_dissipation_getRateAndItsTangent(my_Tdot, my_dTdot_dT, &
|
||||
Tstar(1:3,1:3,grain,ip,el), &
|
||||
S(1:3,1:3,grain,ip,el), &
|
||||
Lp(1:3,1:3,grain,ip,el), &
|
||||
phase)
|
||||
|
||||
|
@ -114,4 +112,5 @@ module subroutine constitutive_thermal_getRateAndItsTangents(TDot, dTDot_dT, T,
|
|||
|
||||
end subroutine constitutive_thermal_getRateAndItsTangents
|
||||
|
||||
end submodule
|
||||
|
||||
end submodule constitutive_thermal
|
||||
|
|
|
@ -131,7 +131,7 @@ subroutine damage_local_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el
|
|||
phiDot = 0.0_pReal
|
||||
dPhiDot_dPhi = 0.0_pReal
|
||||
|
||||
call constitutive_getRateAndItsTangents(phiDot, dPhiDot_dPhi, phi, ip, el)
|
||||
call constitutive_damage_getRateAndItsTangents(phiDot, dPhiDot_dPhi, phi, ip, el)
|
||||
|
||||
phiDot = phiDot/real(homogenization_Ngrains(material_homogenizationAt(el)),pReal)
|
||||
dPhiDot_dPhi = dPhiDot_dPhi/real(homogenization_Ngrains(material_homogenizationAt(el)),pReal)
|
||||
|
|
|
@ -100,7 +100,7 @@ subroutine damage_nonlocal_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip,
|
|||
phiDot = 0.0_pReal
|
||||
dPhiDot_dPhi = 0.0_pReal
|
||||
|
||||
call constitutive_getRateAndItsTangents(phiDot, dPhiDot_dPhi, phi, ip, el)
|
||||
call constitutive_damage_getRateAndItsTangents(phiDot, dPhiDot_dPhi, phi, ip, el)
|
||||
phiDot = phiDot/real(homogenization_Ngrains(material_homogenizationAt(el)),pReal)
|
||||
dPhiDot_dPhi = dPhiDot_dPhi/real(homogenization_Ngrains(material_homogenizationAt(el)),pReal)
|
||||
|
||||
|
|
|
@ -131,7 +131,7 @@ subroutine thermal_adiabatic_getSourceAndItsTangent(Tdot, dTdot_dT, T, ip, el)
|
|||
dTdot_dT = 0.0_pReal
|
||||
|
||||
homog = material_homogenizationAt(el)
|
||||
call constitutive_getRateAndItsTangents(TDot, dTDot_dT, T, crystallite_S, crystallite_Lp, ip, el)
|
||||
call constitutive_thermal_getRateAndItsTangents(TDot, dTDot_dT, T, crystallite_S, crystallite_Lp, ip, el)
|
||||
|
||||
Tdot = Tdot/real(homogenization_Ngrains(homog),pReal)
|
||||
dTdot_dT = dTdot_dT/real(homogenization_Ngrains(homog),pReal)
|
||||
|
|
|
@ -90,7 +90,7 @@ subroutine thermal_conduction_getSourceAndItsTangent(Tdot, dTdot_dT, T, ip, el)
|
|||
dTdot_dT = 0.0_pReal
|
||||
|
||||
homog = material_homogenizationAt(el)
|
||||
call constitutive_getRateAndItsTangents(TDot, dTDot_dT, T, crystallite_S,crystallite_Lp ,ip, el)
|
||||
call constitutive_thermal_getRateAndItsTangents(TDot, dTDot_dT, T, crystallite_S,crystallite_Lp ,ip, el)
|
||||
|
||||
Tdot = Tdot/real(homogenization_Ngrains(homog),pReal)
|
||||
dTdot_dT = dTdot_dT/real(homogenization_Ngrains(homog),pReal)
|
||||
|
|
Loading…
Reference in New Issue