keep variables local
This commit is contained in:
parent
9ce932a082
commit
9d09721689
|
@ -51,31 +51,6 @@ module constitutive
|
||||||
real(pReal), dimension(:,:,:), allocatable :: data
|
real(pReal), dimension(:,:,:), allocatable :: data
|
||||||
end type
|
end type
|
||||||
|
|
||||||
type(tTensorContainer), dimension(:), allocatable :: &
|
|
||||||
! current value
|
|
||||||
constitutive_mech_Fe, &
|
|
||||||
constitutive_mech_Fi, &
|
|
||||||
constitutive_mech_Fp, &
|
|
||||||
constitutive_mech_F, &
|
|
||||||
constitutive_mech_Li, &
|
|
||||||
constitutive_mech_Lp, &
|
|
||||||
constitutive_mech_S, &
|
|
||||||
! converged value at end of last solver increment
|
|
||||||
constitutive_mech_Fi0, &
|
|
||||||
constitutive_mech_Fp0, &
|
|
||||||
constitutive_mech_F0, &
|
|
||||||
constitutive_mech_Li0, &
|
|
||||||
constitutive_mech_Lp0, &
|
|
||||||
constitutive_mech_S0, &
|
|
||||||
! converged value at end of last homogenization increment (RGC only)
|
|
||||||
constitutive_mech_partitionedFi0, &
|
|
||||||
constitutive_mech_partitionedFp0, &
|
|
||||||
constitutive_mech_partitionedF0, &
|
|
||||||
constitutive_mech_partitionedLi0, &
|
|
||||||
constitutive_mech_partitionedLp0, &
|
|
||||||
constitutive_mech_partitionedS0
|
|
||||||
|
|
||||||
|
|
||||||
type :: tNumerics
|
type :: tNumerics
|
||||||
integer :: &
|
integer :: &
|
||||||
iJacoLpresiduum, & !< frequency of Jacobian update of residuum in Lp
|
iJacoLpresiduum, & !< frequency of Jacobian update of residuum in Lp
|
||||||
|
@ -198,6 +173,37 @@ module constitutive
|
||||||
integer, intent(in) :: ph
|
integer, intent(in) :: ph
|
||||||
end subroutine mech_restartRead
|
end subroutine mech_restartRead
|
||||||
|
|
||||||
|
|
||||||
|
module function constitutive_mech_getS(co,ip,el) result(S)
|
||||||
|
integer, intent(in) :: co, ip, el
|
||||||
|
real(pReal), dimension(3,3) :: S
|
||||||
|
end function constitutive_mech_getS
|
||||||
|
|
||||||
|
module function constitutive_mech_getLp(co,ip,el) result(Lp)
|
||||||
|
integer, intent(in) :: co, ip, el
|
||||||
|
real(pReal), dimension(3,3) :: Lp
|
||||||
|
end function constitutive_mech_getLp
|
||||||
|
|
||||||
|
module function constitutive_mech_getF(co,ip,el) result(F)
|
||||||
|
integer, intent(in) :: co, ip, el
|
||||||
|
real(pReal), dimension(3,3) :: F
|
||||||
|
end function constitutive_mech_getF
|
||||||
|
|
||||||
|
module function constitutive_mech_getF_e(co,ip,el) result(F_e)
|
||||||
|
integer, intent(in) :: co, ip, el
|
||||||
|
real(pReal), dimension(3,3) :: F_e
|
||||||
|
end function constitutive_mech_getF_e
|
||||||
|
|
||||||
|
module function constitutive_thermal_T(co,ip,el) result(T)
|
||||||
|
integer, intent(in) :: co, ip, el
|
||||||
|
real(pReal) :: T
|
||||||
|
end function constitutive_thermal_T
|
||||||
|
|
||||||
|
module subroutine constitutive_mech_setF(F,co,ip,el)
|
||||||
|
real(pReal), dimension(3,3), intent(in) :: F
|
||||||
|
integer, intent(in) :: co, ip, el
|
||||||
|
end subroutine constitutive_mech_setF
|
||||||
|
|
||||||
! == cleaned:end ===================================================================================
|
! == cleaned:end ===================================================================================
|
||||||
|
|
||||||
module function crystallite_stress(dt,co,ip,el) result(converged_)
|
module function crystallite_stress(dt,co,ip,el) result(converged_)
|
||||||
|
@ -1001,7 +1007,7 @@ subroutine crystallite_orientations(co,ip,el)
|
||||||
|
|
||||||
|
|
||||||
call crystallite_orientation(co,ip,el)%fromMatrix(transpose(math_rotationalPart(&
|
call crystallite_orientation(co,ip,el)%fromMatrix(transpose(math_rotationalPart(&
|
||||||
constitutive_mech_Fe(material_phaseAt(co,el))%data(1:3,1:3,material_phaseMemberAt(co,ip,el)))))
|
constitutive_mech_getF_e(co,ip,el))))
|
||||||
|
|
||||||
if (plasticState(material_phaseAt(1,el))%nonlocal) &
|
if (plasticState(material_phaseAt(1,el))%nonlocal) &
|
||||||
call plastic_nonlocal_updateCompatibility(crystallite_orientation, &
|
call plastic_nonlocal_updateCompatibility(crystallite_orientation, &
|
||||||
|
@ -1026,8 +1032,8 @@ function crystallite_push33ToRef(co,ip,el, tensor33)
|
||||||
real(pReal), dimension(3,3) :: T
|
real(pReal), dimension(3,3) :: T
|
||||||
|
|
||||||
|
|
||||||
T = matmul(material_orientation0(co,ip,el)%asMatrix(), & ! ToDo: initial orientation correct?
|
T = matmul(material_orientation0(co,ip,el)%asMatrix(),transpose(math_inv33(constitutive_mech_getF(co,ip,el)))) ! ToDo: initial orientation correct?
|
||||||
transpose(math_inv33(constitutive_mech_F(material_phaseAt(co,el))%data(1:3,1:3,material_phaseMemberAt(co,ip,el)))))
|
|
||||||
crystallite_push33ToRef = matmul(transpose(T),matmul(tensor33,T))
|
crystallite_push33ToRef = matmul(transpose(T),matmul(tensor33,T))
|
||||||
|
|
||||||
end function crystallite_push33ToRef
|
end function crystallite_push33ToRef
|
||||||
|
@ -1104,7 +1110,7 @@ function integrateSourceState(dt,co,ip,el) result(broken)
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
if(converged_) then
|
if(converged_) then
|
||||||
broken = constitutive_damage_deltaState(constitutive_mech_Fe(ph)%data(1:3,1:3,me),co,ip,el,ph,me)
|
broken = constitutive_damage_deltaState(constitutive_mech_getF_e(co,ip,el),co,ip,el,ph,me)
|
||||||
exit iteration
|
exit iteration
|
||||||
endif
|
endif
|
||||||
|
|
||||||
|
@ -1213,67 +1219,4 @@ subroutine constitutive_restartRead(fileHandle)
|
||||||
end subroutine constitutive_restartRead
|
end subroutine constitutive_restartRead
|
||||||
|
|
||||||
|
|
||||||
! getter for non-mech (e.g. thermal)
|
|
||||||
function constitutive_mech_getS(co,ip,el) result(S)
|
|
||||||
|
|
||||||
integer, intent(in) :: co, ip, el
|
|
||||||
real(pReal), dimension(3,3) :: S
|
|
||||||
|
|
||||||
|
|
||||||
S = constitutive_mech_S(material_phaseAt(co,el))%data(1:3,1:3,material_phaseMemberAt(co,ip,el))
|
|
||||||
|
|
||||||
end function constitutive_mech_getS
|
|
||||||
|
|
||||||
|
|
||||||
! getter for non-mech (e.g. thermal)
|
|
||||||
function constitutive_mech_getLp(co,ip,el) result(Lp)
|
|
||||||
|
|
||||||
integer, intent(in) :: co, ip, el
|
|
||||||
real(pReal), dimension(3,3) :: Lp
|
|
||||||
|
|
||||||
|
|
||||||
Lp = constitutive_mech_Lp(material_phaseAt(co,el))%data(1:3,1:3,material_phaseMemberAt(co,ip,el))
|
|
||||||
|
|
||||||
end function constitutive_mech_getLp
|
|
||||||
|
|
||||||
|
|
||||||
! getter for non-mech (e.g. thermal)
|
|
||||||
function constitutive_mech_getF(co,ip,el) result(F)
|
|
||||||
|
|
||||||
integer, intent(in) :: co, ip, el
|
|
||||||
real(pReal), dimension(3,3) :: F
|
|
||||||
|
|
||||||
|
|
||||||
F = constitutive_mech_F(material_phaseAt(co,el))%data(1:3,1:3,material_phaseMemberAt(co,ip,el))
|
|
||||||
|
|
||||||
end function constitutive_mech_getF
|
|
||||||
|
|
||||||
|
|
||||||
! getter for non-thermal (e.g. mech)
|
|
||||||
function constitutive_thermal_T(co,ip,el) result(T)
|
|
||||||
|
|
||||||
integer, intent(in) :: co, ip, el
|
|
||||||
real(pReal) :: T
|
|
||||||
|
|
||||||
integer :: ho, tme
|
|
||||||
|
|
||||||
ho = material_homogenizationAt(el)
|
|
||||||
tme = material_homogenizationMemberAt(ip,el)
|
|
||||||
|
|
||||||
T = temperature(ho)%p(tme)
|
|
||||||
|
|
||||||
end function constitutive_thermal_T
|
|
||||||
|
|
||||||
|
|
||||||
! setter for homogenization
|
|
||||||
subroutine constitutive_mech_setF(F,co,ip,el)
|
|
||||||
|
|
||||||
real(pReal), dimension(3,3), intent(in) :: F
|
|
||||||
integer, intent(in) :: co, ip, el
|
|
||||||
|
|
||||||
|
|
||||||
constitutive_mech_F(material_phaseAt(co,el))%data(1:3,1:3,material_phaseMemberAt(co,ip,el)) = F
|
|
||||||
|
|
||||||
end subroutine constitutive_mech_setF
|
|
||||||
|
|
||||||
end module constitutive
|
end module constitutive
|
||||||
|
|
|
@ -15,6 +15,30 @@ submodule(constitutive) constitutive_mech
|
||||||
integer(kind(SOURCE_undefined_ID)), dimension(:,:), allocatable :: &
|
integer(kind(SOURCE_undefined_ID)), dimension(:,:), allocatable :: &
|
||||||
phase_stiffnessDegradation !< active stiffness degradation mechanisms of each phase
|
phase_stiffnessDegradation !< active stiffness degradation mechanisms of each phase
|
||||||
|
|
||||||
|
type(tTensorContainer), dimension(:), allocatable :: &
|
||||||
|
! current value
|
||||||
|
constitutive_mech_Fe, &
|
||||||
|
constitutive_mech_Fi, &
|
||||||
|
constitutive_mech_Fp, &
|
||||||
|
constitutive_mech_F, &
|
||||||
|
constitutive_mech_Li, &
|
||||||
|
constitutive_mech_Lp, &
|
||||||
|
constitutive_mech_S, &
|
||||||
|
! converged value at end of last solver increment
|
||||||
|
constitutive_mech_Fi0, &
|
||||||
|
constitutive_mech_Fp0, &
|
||||||
|
constitutive_mech_F0, &
|
||||||
|
constitutive_mech_Li0, &
|
||||||
|
constitutive_mech_Lp0, &
|
||||||
|
constitutive_mech_S0, &
|
||||||
|
! converged value at end of last homogenization increment (RGC only)
|
||||||
|
constitutive_mech_partitionedFi0, &
|
||||||
|
constitutive_mech_partitionedFp0, &
|
||||||
|
constitutive_mech_partitionedF0, &
|
||||||
|
constitutive_mech_partitionedLi0, &
|
||||||
|
constitutive_mech_partitionedLp0, &
|
||||||
|
constitutive_mech_partitionedS0
|
||||||
|
|
||||||
|
|
||||||
interface
|
interface
|
||||||
|
|
||||||
|
@ -1845,5 +1869,65 @@ module subroutine mech_restartRead(groupHandle,ph)
|
||||||
|
|
||||||
end subroutine mech_restartRead
|
end subroutine mech_restartRead
|
||||||
|
|
||||||
|
|
||||||
|
! getter for non-mech (e.g. thermal)
|
||||||
|
module function constitutive_mech_getS(co,ip,el) result(S)
|
||||||
|
|
||||||
|
integer, intent(in) :: co, ip, el
|
||||||
|
real(pReal), dimension(3,3) :: S
|
||||||
|
|
||||||
|
|
||||||
|
S = constitutive_mech_S(material_phaseAt(co,el))%data(1:3,1:3,material_phaseMemberAt(co,ip,el))
|
||||||
|
|
||||||
|
end function constitutive_mech_getS
|
||||||
|
|
||||||
|
|
||||||
|
! getter for non-mech (e.g. thermal)
|
||||||
|
module function constitutive_mech_getLp(co,ip,el) result(Lp)
|
||||||
|
|
||||||
|
integer, intent(in) :: co, ip, el
|
||||||
|
real(pReal), dimension(3,3) :: Lp
|
||||||
|
|
||||||
|
|
||||||
|
Lp = constitutive_mech_Lp(material_phaseAt(co,el))%data(1:3,1:3,material_phaseMemberAt(co,ip,el))
|
||||||
|
|
||||||
|
end function constitutive_mech_getLp
|
||||||
|
|
||||||
|
|
||||||
|
! getter for non-mech (e.g. thermal)
|
||||||
|
module function constitutive_mech_getF(co,ip,el) result(F)
|
||||||
|
|
||||||
|
integer, intent(in) :: co, ip, el
|
||||||
|
real(pReal), dimension(3,3) :: F
|
||||||
|
|
||||||
|
|
||||||
|
F = constitutive_mech_F(material_phaseAt(co,el))%data(1:3,1:3,material_phaseMemberAt(co,ip,el))
|
||||||
|
|
||||||
|
end function constitutive_mech_getF
|
||||||
|
|
||||||
|
|
||||||
|
! getter for non-mech (e.g. thermal)
|
||||||
|
module function constitutive_mech_getF_e(co,ip,el) result(F_e)
|
||||||
|
|
||||||
|
integer, intent(in) :: co, ip, el
|
||||||
|
real(pReal), dimension(3,3) :: F_e
|
||||||
|
|
||||||
|
|
||||||
|
F_e = constitutive_mech_Fe(material_phaseAt(co,el))%data(1:3,1:3,material_phaseMemberAt(co,ip,el))
|
||||||
|
|
||||||
|
end function constitutive_mech_getF_e
|
||||||
|
|
||||||
|
|
||||||
|
! setter for homogenization
|
||||||
|
module subroutine constitutive_mech_setF(F,co,ip,el)
|
||||||
|
|
||||||
|
real(pReal), dimension(3,3), intent(in) :: F
|
||||||
|
integer, intent(in) :: co, ip, el
|
||||||
|
|
||||||
|
|
||||||
|
constitutive_mech_F(material_phaseAt(co,el))%data(1:3,1:3,material_phaseMemberAt(co,ip,el)) = F
|
||||||
|
|
||||||
|
end subroutine constitutive_mech_setF
|
||||||
|
|
||||||
end submodule constitutive_mech
|
end submodule constitutive_mech
|
||||||
|
|
||||||
|
|
|
@ -9,7 +9,7 @@ submodule(constitutive) constitutive_thermal
|
||||||
integer, intent(in) :: source_length
|
integer, intent(in) :: source_length
|
||||||
logical, dimension(:,:), allocatable :: mySources
|
logical, dimension(:,:), allocatable :: mySources
|
||||||
end function source_thermal_dissipation_init
|
end function source_thermal_dissipation_init
|
||||||
|
|
||||||
module function source_thermal_externalheat_init(source_length) result(mySources)
|
module function source_thermal_externalheat_init(source_length) result(mySources)
|
||||||
integer, intent(in) :: source_length
|
integer, intent(in) :: source_length
|
||||||
logical, dimension(:,:), allocatable :: mySources
|
logical, dimension(:,:), allocatable :: mySources
|
||||||
|
@ -55,8 +55,8 @@ module subroutine thermal_init
|
||||||
if(maxval(phase_Nsources) /= 0) then
|
if(maxval(phase_Nsources) /= 0) then
|
||||||
where(source_thermal_dissipation_init (maxval(phase_Nsources))) phase_source = SOURCE_thermal_dissipation_ID
|
where(source_thermal_dissipation_init (maxval(phase_Nsources))) phase_source = SOURCE_thermal_dissipation_ID
|
||||||
where(source_thermal_externalheat_init(maxval(phase_Nsources))) phase_source = SOURCE_thermal_externalheat_ID
|
where(source_thermal_externalheat_init(maxval(phase_Nsources))) phase_source = SOURCE_thermal_externalheat_ID
|
||||||
endif
|
endif
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!initialize kinematic mechanisms
|
!initialize kinematic mechanisms
|
||||||
if(maxval(phase_Nkinematics) /= 0) where(kinematics_thermal_expansion_init(maxval(phase_Nkinematics))) &
|
if(maxval(phase_Nkinematics) /= 0) where(kinematics_thermal_expansion_init(maxval(phase_Nkinematics))) &
|
||||||
|
@ -121,4 +121,22 @@ module subroutine constitutive_thermal_getRateAndItsTangents(TDot, dTDot_dT, T,
|
||||||
end subroutine constitutive_thermal_getRateAndItsTangents
|
end subroutine constitutive_thermal_getRateAndItsTangents
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
! getter for non-thermal (e.g. mech)
|
||||||
|
module function constitutive_thermal_T(co,ip,el) result(T)
|
||||||
|
|
||||||
|
integer, intent(in) :: co, ip, el
|
||||||
|
real(pReal) :: T
|
||||||
|
|
||||||
|
integer :: ho, tme
|
||||||
|
|
||||||
|
ho = material_homogenizationAt(el)
|
||||||
|
tme = material_homogenizationMemberAt(ip,el)
|
||||||
|
|
||||||
|
T = temperature(ho)%p(tme)
|
||||||
|
|
||||||
|
end function constitutive_thermal_T
|
||||||
|
|
||||||
|
|
||||||
end submodule constitutive_thermal
|
end submodule constitutive_thermal
|
||||||
|
|
Loading…
Reference in New Issue