cleaner
This commit is contained in:
parent
fd7110ce45
commit
957c51fb07
|
@ -137,24 +137,8 @@ end subroutine damage_init
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief contains the constitutive equation for calculating the rate of change of microstructure
|
!> @brief contains the constitutive equation for calculating the rate of change of microstructure
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module function damage_dotState(S, FArray, Fi, FpArray, subdt, ipc, ip, el,phase,of) result(broken_damage)
|
module procedure damage_dotState
|
||||||
|
|
||||||
integer, intent(in) :: &
|
|
||||||
ipc, & !< component-ID of integration point
|
|
||||||
ip, & !< integration point
|
|
||||||
el, & !< element
|
|
||||||
phase, &
|
|
||||||
of
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
subdt !< timestep
|
|
||||||
real(pReal), intent(in), dimension(3,3,homogenization_maxNgrains,discretization_nIP,discretization_nElem) :: &
|
|
||||||
FArray, & !< elastic deformation gradient
|
|
||||||
FpArray !< plastic deformation gradient
|
|
||||||
real(pReal), intent(in), dimension(3,3) :: &
|
|
||||||
Fi !< intermediate deformation gradient
|
|
||||||
real(pReal), intent(in), dimension(3,3) :: &
|
|
||||||
S !< 2nd Piola Kirchhoff stress (vector notation)
|
|
||||||
logical :: broken_damage
|
|
||||||
integer :: i
|
integer :: i
|
||||||
|
|
||||||
SourceLoop: do i = 1, phase_Nsources(phase)
|
SourceLoop: do i = 1, phase_Nsources(phase)
|
||||||
|
@ -176,19 +160,10 @@ module function damage_dotState(S, FArray, Fi, FpArray, subdt, ipc, ip, el,phase
|
||||||
|
|
||||||
broken_damage = any(IEEE_is_NaN(sourceState(phase)%p(i)%dotState(:,of)))
|
broken_damage = any(IEEE_is_NaN(sourceState(phase)%p(i)%dotState(:,of)))
|
||||||
|
|
||||||
end function damage_dotState
|
end procedure damage_dotState
|
||||||
|
|
||||||
|
|
||||||
module subroutine damage_source_getRateAndItsTangents(phiDot, dPhiDot_dPhi, phi, ip, el)
|
module procedure damage_source_getRateAndItsTangents
|
||||||
|
|
||||||
integer, intent(in) :: &
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
phi
|
|
||||||
real(pReal), intent(inout) :: &
|
|
||||||
phiDot, &
|
|
||||||
dPhiDot_dPhi
|
|
||||||
|
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
localphiDot, &
|
localphiDot, &
|
||||||
|
@ -229,6 +204,6 @@ module subroutine damage_source_getRateAndItsTangents(phiDot, dPhiDot_dPhi, phi,
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end subroutine damage_source_getRateAndItsTangents
|
end procedure damage_source_getRateAndItsTangents
|
||||||
|
|
||||||
end submodule
|
end submodule
|
||||||
|
|
|
@ -239,32 +239,14 @@ end subroutine plastic_init
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief contains the constitutive equation for calculating the rate of change of microstructure
|
!> @brief contains the constitutive equation for calculating the rate of change of microstructure
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module function plastic_dotState(S, FArray, Fi, FpArray, subdt, ipc, ip, el,phase,of) result(broken_plastic)
|
module procedure plastic_dotState
|
||||||
|
|
||||||
integer, intent(in) :: &
|
|
||||||
ipc, & !< component-ID of integration point
|
|
||||||
ip, & !< integration point
|
|
||||||
el, & !< element
|
|
||||||
phase, &
|
|
||||||
of
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
subdt !< timestep
|
|
||||||
real(pReal), intent(in), dimension(3,3,homogenization_maxNgrains,discretization_nIP,discretization_nElem) :: &
|
|
||||||
FArray, & !< elastic deformation gradient
|
|
||||||
FpArray !< plastic deformation gradient
|
|
||||||
real(pReal), intent(in), dimension(3,3) :: &
|
|
||||||
Fi !< intermediate deformation gradient
|
|
||||||
real(pReal), intent(in), dimension(3,3) :: &
|
|
||||||
S !< 2nd Piola Kirchhoff stress (vector notation)
|
|
||||||
real(pReal), dimension(3,3) :: &
|
real(pReal), dimension(3,3) :: &
|
||||||
Mp
|
Mp
|
||||||
integer :: &
|
integer :: &
|
||||||
ho, & !< homogenization
|
ho, & !< homogenization
|
||||||
tme, & !< thermal member position
|
tme, & !< thermal member position
|
||||||
i, & !< counter in source loop
|
|
||||||
instance
|
instance
|
||||||
logical :: broken_plastic
|
|
||||||
|
|
||||||
|
|
||||||
ho = material_homogenizationAt(el)
|
ho = material_homogenizationAt(el)
|
||||||
tme = thermalMapping(ho)%p(ip,el)
|
tme = thermalMapping(ho)%p(ip,el)
|
||||||
|
@ -295,20 +277,14 @@ module function plastic_dotState(S, FArray, Fi, FpArray, subdt, ipc, ip, el,phas
|
||||||
end select plasticityType
|
end select plasticityType
|
||||||
broken_plastic = any(IEEE_is_NaN(plasticState(phase)%dotState(:,of)))
|
broken_plastic = any(IEEE_is_NaN(plasticState(phase)%dotState(:,of)))
|
||||||
|
|
||||||
end function plastic_dotState
|
end procedure plastic_dotState
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief returns the homogenize elasticity matrix
|
!> @brief returns the homogenize elasticity matrix
|
||||||
!> ToDo: homogenizedC66 would be more consistent
|
!> ToDo: homogenizedC66 would be more consistent
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module function plastic_homogenizedC(ipc,ip,el) result(homogenizedC)
|
module procedure plastic_homogenizedC
|
||||||
|
|
||||||
real(pReal), dimension(6,6) :: homogenizedC
|
|
||||||
integer, intent(in) :: &
|
|
||||||
ipc, & !< component-ID of integration point
|
|
||||||
ip, & !< integration point
|
|
||||||
el !< element
|
|
||||||
|
|
||||||
plasticityType: select case (phase_plasticity(material_phaseAt(ipc,el)))
|
plasticityType: select case (phase_plasticity(material_phaseAt(ipc,el)))
|
||||||
case (PLASTICITY_DISLOTWIN_ID) plasticityType
|
case (PLASTICITY_DISLOTWIN_ID) plasticityType
|
||||||
|
@ -317,21 +293,14 @@ module function plastic_homogenizedC(ipc,ip,el) result(homogenizedC)
|
||||||
homogenizedC = lattice_C66(1:6,1:6,material_phaseAt(ipc,el))
|
homogenizedC = lattice_C66(1:6,1:6,material_phaseAt(ipc,el))
|
||||||
end select plasticityType
|
end select plasticityType
|
||||||
|
|
||||||
end function plastic_homogenizedC
|
end procedure plastic_homogenizedC
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief calls microstructure function of the different constitutive models
|
!> @brief calls microstructure function of the different constitutive models
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module subroutine plastic_dependentState(F, Fp, ipc, ip, el)
|
module procedure plastic_dependentState
|
||||||
|
|
||||||
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
|
|
||||||
integer :: &
|
integer :: &
|
||||||
ho, & !< homogenization
|
ho, & !< homogenization
|
||||||
tme, & !< thermal member position
|
tme, & !< thermal member position
|
||||||
|
@ -351,27 +320,15 @@ module subroutine plastic_dependentState(F, Fp, ipc, ip, el)
|
||||||
call plastic_nonlocal_dependentState (F,Fp,instance,of,ip,el)
|
call plastic_nonlocal_dependentState (F,Fp,instance,of,ip,el)
|
||||||
end select plasticityType
|
end select plasticityType
|
||||||
|
|
||||||
end subroutine plastic_dependentState
|
end procedure plastic_dependentState
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief contains the constitutive equation for calculating the velocity gradient
|
!> @brief contains the constitutive equation for calculating the velocity gradient
|
||||||
! ToDo: Discuss whether it makes sense if crystallite handles the configuration conversion, i.e.
|
! ToDo: Discuss whether it makes sense if crystallite handles the configuration conversion, i.e.
|
||||||
! Mp in, dLp_dMp out
|
! Mp in, dLp_dMp out
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module subroutine plastic_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, &
|
module procedure plastic_LpAndItsTangents
|
||||||
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
|
|
||||||
real(pReal), dimension(3,3,3,3) :: &
|
real(pReal), dimension(3,3,3,3) :: &
|
||||||
dLp_dMp !< derivative of Lp with respect to Mandel stress
|
dLp_dMp !< derivative of Lp with respect to Mandel stress
|
||||||
real(pReal), dimension(3,3) :: &
|
real(pReal), dimension(3,3) :: &
|
||||||
|
@ -421,7 +378,7 @@ module subroutine plastic_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, &
|
||||||
dLp_dS(i,j,1:3,1:3) = matmul(matmul(transpose(Fi),Fi),dLp_dMp(i,j,1:3,1:3)) ! ToDo: @PS: why not: dLp_dMp:(FiT Fi)
|
dLp_dS(i,j,1:3,1:3) = matmul(matmul(transpose(Fi),Fi),dLp_dMp(i,j,1:3,1:3)) ! ToDo: @PS: why not: dLp_dMp:(FiT Fi)
|
||||||
enddo; enddo
|
enddo; enddo
|
||||||
|
|
||||||
end subroutine plastic_LpAndItsTangents
|
end procedure plastic_LpAndItsTangents
|
||||||
|
|
||||||
end submodule constitutive_plastic
|
end submodule constitutive_plastic
|
||||||
|
|
||||||
|
|
|
@ -64,24 +64,8 @@ end subroutine thermal_init
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief contains the constitutive equation for calculating the rate of change of microstructure
|
!> @brief contains the constitutive equation for calculating the rate of change of microstructure
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module function thermal_dotState(S, FArray, Fi, FpArray, subdt, ipc, ip, el,phase,of) result(broken_thermal)
|
module procedure thermal_dotState
|
||||||
|
|
||||||
integer, intent(in) :: &
|
|
||||||
ipc, & !< component-ID of integration point
|
|
||||||
ip, & !< integration point
|
|
||||||
el, & !< element
|
|
||||||
phase, &
|
|
||||||
of
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
subdt !< timestep
|
|
||||||
real(pReal), intent(in), dimension(3,3,homogenization_maxNgrains,discretization_nIP,discretization_nElem) :: &
|
|
||||||
FArray, & !< elastic deformation gradient
|
|
||||||
FpArray !< plastic deformation gradient
|
|
||||||
real(pReal), intent(in), dimension(3,3) :: &
|
|
||||||
Fi !< intermediate deformation gradient
|
|
||||||
real(pReal), intent(in), dimension(3,3) :: &
|
|
||||||
S !< 2nd Piola Kirchhoff stress (vector notation)
|
|
||||||
logical :: broken_thermal
|
|
||||||
integer :: i
|
integer :: i
|
||||||
|
|
||||||
SourceLoop: do i = 1, phase_Nsources(phase)
|
SourceLoop: do i = 1, phase_Nsources(phase)
|
||||||
|
@ -93,26 +77,14 @@ module function thermal_dotState(S, FArray, Fi, FpArray, subdt, ipc, ip, el,phas
|
||||||
|
|
||||||
end select sourceType
|
end select sourceType
|
||||||
|
|
||||||
broken_thermal = any(IEEE_is_NaN(sourceState(phase)%p(i)%dotState(:,of)))
|
|
||||||
|
|
||||||
enddo sourceLoop
|
enddo sourceLoop
|
||||||
|
|
||||||
end function thermal_dotState
|
broken_thermal = any(IEEE_is_NaN(sourceState(phase)%p(i)%dotState(:,of)))
|
||||||
|
|
||||||
|
end procedure thermal_dotState
|
||||||
|
|
||||||
|
|
||||||
module subroutine thermal_source_getRateAndItsTangents(Tdot, dTdot_dT, T, Tstar, Lp, ip, el)
|
module procedure thermal_source_getRateAndItsTangents
|
||||||
|
|
||||||
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
|
|
||||||
|
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
my_Tdot, &
|
my_Tdot, &
|
||||||
|
@ -152,6 +124,6 @@ module subroutine thermal_source_getRateAndItsTangents(Tdot, dTdot_dT, T, Tstar,
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end subroutine thermal_source_getRateAndItsTangents
|
end procedure thermal_source_getRateAndItsTangents
|
||||||
|
|
||||||
end submodule
|
end submodule
|
||||||
|
|
Loading…
Reference in New Issue