DAMASK_EICMD/src/phase_mechanical_plastic.f90

460 lines
18 KiB
Fortran
Raw Normal View History

2021-02-13 23:27:41 +05:30
submodule(phase:mechanical) plastic
2021-01-26 05:41:32 +05:30
interface
2021-01-26 13:09:17 +05:30
2021-01-27 05:02:44 +05:30
module function plastic_none_init() result(myPlasticity)
logical, dimension(:), allocatable :: &
myPlasticity
end function plastic_none_init
module function plastic_isotropic_init() result(myPlasticity)
logical, dimension(:), allocatable :: &
myPlasticity
end function plastic_isotropic_init
module function plastic_phenopowerlaw_init() result(myPlasticity)
logical, dimension(:), allocatable :: &
myPlasticity
end function plastic_phenopowerlaw_init
module function plastic_kinehardening_init() result(myPlasticity)
logical, dimension(:), allocatable :: &
myPlasticity
end function plastic_kinehardening_init
module function plastic_dislotwin_init() result(myPlasticity)
logical, dimension(:), allocatable :: &
myPlasticity
end function plastic_dislotwin_init
module function plastic_dislotungsten_init() result(myPlasticity)
logical, dimension(:), allocatable :: &
myPlasticity
end function plastic_dislotungsten_init
module function plastic_nonlocal_init() result(myPlasticity)
logical, dimension(:), allocatable :: &
myPlasticity
end function plastic_nonlocal_init
module subroutine isotropic_LpAndItsTangent(Lp,dLp_dMp,Mp,ph,me)
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3), intent(out) :: &
2021-01-26 13:09:17 +05:30
Lp
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3,3,3), intent(out) :: &
2021-01-26 13:09:17 +05:30
dLp_dMp
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3), intent(in) :: &
2021-01-26 13:09:17 +05:30
Mp
2021-01-26 05:41:32 +05:30
integer, intent(in) :: &
ph, &
2021-01-26 13:09:17 +05:30
me
2021-01-26 12:03:04 +05:30
end subroutine isotropic_LpAndItsTangent
2021-01-26 05:41:32 +05:30
pure module subroutine phenopowerlaw_LpAndItsTangent(Lp,dLp_dMp,Mp,ph,me)
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3), intent(out) :: &
2021-01-26 13:09:17 +05:30
Lp
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3,3,3), intent(out) :: &
2021-01-26 13:09:17 +05:30
dLp_dMp
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3), intent(in) :: &
2021-01-26 13:09:17 +05:30
Mp
2021-01-26 05:41:32 +05:30
integer, intent(in) :: &
ph, &
2021-01-26 13:09:17 +05:30
me
2021-01-26 12:03:04 +05:30
end subroutine phenopowerlaw_LpAndItsTangent
2021-01-26 05:41:32 +05:30
pure module subroutine kinehardening_LpAndItsTangent(Lp,dLp_dMp,Mp,ph,me)
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3), intent(out) :: &
2021-01-26 13:09:17 +05:30
Lp
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3,3,3), intent(out) :: &
2021-01-26 13:09:17 +05:30
dLp_dMp
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3), intent(in) :: &
2021-01-26 13:09:17 +05:30
Mp
2021-01-26 05:41:32 +05:30
integer, intent(in) :: &
ph, &
2021-01-26 13:09:17 +05:30
me
2021-01-26 12:03:04 +05:30
end subroutine kinehardening_LpAndItsTangent
2021-01-26 05:41:32 +05:30
module subroutine dislotwin_LpAndItsTangent(Lp,dLp_dMp,Mp,T,ph,me)
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3), intent(out) :: &
2021-01-26 13:09:17 +05:30
Lp
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3,3,3), intent(out) :: &
2021-01-26 13:09:17 +05:30
dLp_dMp
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3), intent(in) :: &
2021-01-26 13:09:17 +05:30
Mp
2021-01-26 05:41:32 +05:30
real(pReal), intent(in) :: &
T
integer, intent(in) :: &
ph, &
2021-01-26 13:09:17 +05:30
me
2021-01-26 12:03:04 +05:30
end subroutine dislotwin_LpAndItsTangent
2021-01-26 05:41:32 +05:30
pure module subroutine dislotungsten_LpAndItsTangent(Lp,dLp_dMp,Mp,T,ph,me)
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3), intent(out) :: &
2021-01-26 13:09:17 +05:30
Lp
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3,3,3), intent(out) :: &
2021-01-26 13:09:17 +05:30
dLp_dMp
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3), intent(in) :: &
2021-01-26 13:09:17 +05:30
Mp
2021-01-26 05:41:32 +05:30
real(pReal), intent(in) :: &
T
integer, intent(in) :: &
ph, &
2021-01-26 13:09:17 +05:30
me
2021-01-26 12:03:04 +05:30
end subroutine dislotungsten_LpAndItsTangent
2021-01-26 05:41:32 +05:30
2021-01-26 12:03:04 +05:30
module subroutine nonlocal_LpAndItsTangent(Lp,dLp_dMp, &
2021-02-14 21:59:23 +05:30
Mp,Temperature,ph,me)
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3), intent(out) :: &
2021-01-26 13:09:17 +05:30
Lp
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3,3,3), intent(out) :: &
2021-01-26 13:09:17 +05:30
dLp_dMp
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3), intent(in) :: &
Mp !< Mandel stress
real(pReal), intent(in) :: &
Temperature
integer, intent(in) :: &
ph, &
2021-02-14 21:59:23 +05:30
me
2021-01-26 12:03:04 +05:30
end subroutine nonlocal_LpAndItsTangent
2021-01-26 05:41:32 +05:30
2021-01-26 16:15:39 +05:30
module subroutine isotropic_dotState(Mp,ph,me)
2021-01-26 16:15:39 +05:30
real(pReal), dimension(3,3), intent(in) :: &
Mp !< Mandel stress
integer, intent(in) :: &
ph, &
2021-01-26 16:15:39 +05:30
me
2021-01-26 16:47:00 +05:30
end subroutine isotropic_dotState
2021-01-26 16:15:39 +05:30
module subroutine phenopowerlaw_dotState(Mp,ph,me)
2021-01-26 16:15:39 +05:30
real(pReal), dimension(3,3), intent(in) :: &
Mp !< Mandel stress
integer, intent(in) :: &
ph, &
2021-01-26 16:15:39 +05:30
me
2021-01-26 16:47:00 +05:30
end subroutine phenopowerlaw_dotState
2021-01-26 16:15:39 +05:30
module subroutine plastic_kinehardening_dotState(Mp,ph,me)
2021-01-26 16:15:39 +05:30
real(pReal), dimension(3,3), intent(in) :: &
Mp !< Mandel stress
integer, intent(in) :: &
ph, &
2021-01-26 16:15:39 +05:30
me
end subroutine plastic_kinehardening_dotState
module subroutine dislotwin_dotState(Mp,T,ph,me)
2021-01-26 16:15:39 +05:30
real(pReal), dimension(3,3), intent(in) :: &
Mp !< Mandel stress
real(pReal), intent(in) :: &
T
integer, intent(in) :: &
ph, &
2021-01-26 16:15:39 +05:30
me
2021-01-26 16:47:00 +05:30
end subroutine dislotwin_dotState
2021-01-26 16:15:39 +05:30
module subroutine dislotungsten_dotState(Mp,T,ph,me)
2021-01-26 16:15:39 +05:30
real(pReal), dimension(3,3), intent(in) :: &
Mp !< Mandel stress
real(pReal), intent(in) :: &
T
integer, intent(in) :: &
ph, &
2021-01-26 16:15:39 +05:30
me
2021-01-26 16:47:00 +05:30
end subroutine dislotungsten_dotState
2021-01-26 16:15:39 +05:30
module subroutine nonlocal_dotState(Mp,Temperature,timestep,ph,me,ip,el)
2021-01-26 16:15:39 +05:30
real(pReal), dimension(3,3), intent(in) :: &
Mp !< MandelStress
real(pReal), intent(in) :: &
Temperature, & !< temperature
timestep !< substepped crystallite time increment
integer, intent(in) :: &
ph, &
2021-01-26 16:15:39 +05:30
me, &
ip, & !< current integration point
el !< current element number
2021-01-26 16:47:00 +05:30
end subroutine nonlocal_dotState
2021-01-26 16:15:39 +05:30
module subroutine dislotwin_dependentState(T,ph,me)
2021-01-26 16:15:39 +05:30
integer, intent(in) :: &
ph, &
2021-01-26 16:15:39 +05:30
me
real(pReal), intent(in) :: &
T
2021-01-26 16:47:00 +05:30
end subroutine dislotwin_dependentState
2021-01-26 16:15:39 +05:30
module subroutine dislotungsten_dependentState(ph,me)
2021-01-26 16:15:39 +05:30
integer, intent(in) :: &
ph, &
2021-01-26 16:15:39 +05:30
me
2021-01-26 16:47:00 +05:30
end subroutine dislotungsten_dependentState
2021-01-26 16:15:39 +05:30
module subroutine nonlocal_dependentState(ph, me, ip, el)
2021-01-26 16:15:39 +05:30
integer, intent(in) :: &
ph, &
2021-01-26 16:15:39 +05:30
me, &
ip, & !< current integration point
el !< current element number
2021-01-26 16:47:00 +05:30
end subroutine nonlocal_dependentState
2021-01-26 16:15:39 +05:30
2021-02-14 05:20:42 +05:30
module subroutine plastic_kinehardening_deltaState(Mp,ph,me)
2021-01-26 16:15:39 +05:30
real(pReal), dimension(3,3), intent(in) :: &
Mp !< Mandel stress
integer, intent(in) :: &
2021-02-14 05:20:42 +05:30
ph, &
2021-01-26 16:15:39 +05:30
me
end subroutine plastic_kinehardening_deltaState
2021-02-14 21:59:23 +05:30
module subroutine plastic_nonlocal_deltaState(Mp,ph,me)
2021-01-26 16:15:39 +05:30
real(pReal), dimension(3,3), intent(in) :: &
Mp
integer, intent(in) :: &
ph, &
2021-02-14 21:59:23 +05:30
me
2021-01-26 16:15:39 +05:30
end subroutine plastic_nonlocal_deltaState
2021-01-26 05:41:32 +05:30
end interface
2021-01-26 13:09:17 +05:30
2021-01-26 05:41:32 +05:30
contains
2021-01-27 05:02:44 +05:30
module subroutine plastic_init
2021-01-27 15:14:03 +05:30
2021-02-13 23:27:41 +05:30
print'(/,a)', ' <<<+- phase:mechanical:plastic init -+>>>'
2021-01-27 15:14:03 +05:30
2021-01-27 05:02:44 +05:30
where(plastic_none_init()) phase_plasticity = PLASTICITY_NONE_ID
where(plastic_isotropic_init()) phase_plasticity = PLASTICITY_ISOTROPIC_ID
where(plastic_phenopowerlaw_init()) phase_plasticity = PLASTICITY_PHENOPOWERLAW_ID
where(plastic_kinehardening_init()) phase_plasticity = PLASTICITY_KINEHARDENING_ID
where(plastic_dislotwin_init()) phase_plasticity = PLASTICITY_DISLOTWIN_ID
where(plastic_dislotungsten_init()) phase_plasticity = PLASTICITY_DISLOTUNGSTEN_ID
where(plastic_nonlocal_init()) phase_plasticity = PLASTICITY_NONLOCAL_ID
end subroutine plastic_init
2021-01-26 05:41:32 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief contains the constitutive equation for calculating the velocity gradient
! ToDo: Discuss whether it makes sense if crystallite handles the configuration conversion, i.e.
! Mp in, dLp_dMp out
!--------------------------------------------------------------------------------------------------
2021-01-26 16:11:19 +05:30
module subroutine plastic_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, &
2021-04-13 00:51:15 +05:30
S, Fi, ph,en)
2021-01-26 05:41:32 +05:30
integer, intent(in) :: &
2021-04-13 00:51:15 +05:30
ph,en
2021-01-26 05:41:32 +05:30
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, &
2021-04-13 00:51:15 +05:30
dLp_dFi !< derivative en Lp with respect to Fi
2021-01-26 05:41:32 +05:30
real(pReal), dimension(3,3,3,3) :: &
dLp_dMp !< derivative of Lp with respect to Mandel stress
real(pReal), dimension(3,3) :: &
Mp !< Mandel stress work conjugate with Lp
integer :: &
2021-02-14 21:59:23 +05:30
i, j
2021-01-26 05:41:32 +05:30
Mp = matmul(matmul(transpose(Fi),Fi),S)
2021-02-14 21:59:23 +05:30
plasticType: select case (phase_plasticity(ph))
2021-01-26 05:41:32 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_NONE_ID) plasticType
2021-01-26 05:41:32 +05:30
Lp = 0.0_pReal
dLp_dMp = 0.0_pReal
2021-02-09 03:51:53 +05:30
case (PLASTICITY_ISOTROPIC_ID) plasticType
2021-04-13 00:51:15 +05:30
call isotropic_LpAndItsTangent(Lp,dLp_dMp,Mp,ph,en)
2021-01-26 05:41:32 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_PHENOPOWERLAW_ID) plasticType
2021-04-13 00:51:15 +05:30
call phenopowerlaw_LpAndItsTangent(Lp,dLp_dMp,Mp,ph,en)
2021-01-26 05:41:32 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_KINEHARDENING_ID) plasticType
2021-04-13 00:51:15 +05:30
call kinehardening_LpAndItsTangent(Lp,dLp_dMp,Mp,ph,en)
2021-01-26 05:41:32 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_NONLOCAL_ID) plasticType
2021-04-13 00:51:15 +05:30
call nonlocal_LpAndItsTangent(Lp,dLp_dMp,Mp, thermal_T(ph,en),ph,en)
2021-01-26 05:41:32 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_DISLOTWIN_ID) plasticType
2021-04-13 00:51:15 +05:30
call dislotwin_LpAndItsTangent(Lp,dLp_dMp,Mp, thermal_T(ph,en),ph,en)
2021-01-26 05:41:32 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_DISLOTUNGSTEN_ID) plasticType
2021-04-13 00:51:15 +05:30
call dislotungsten_LpAndItsTangent(Lp,dLp_dMp,Mp, thermal_T(ph,en),ph,en)
2021-01-26 05:41:32 +05:30
2021-02-09 03:51:53 +05:30
end select plasticType
2021-01-26 05:41:32 +05:30
do i=1,3; do j=1,3
dLp_dFi(i,j,1:3,1:3) = matmul(matmul(Fi,S),transpose(dLp_dMp(i,j,1:3,1:3))) + &
matmul(matmul(Fi,dLp_dMp(i,j,1:3,1:3)),S)
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
2021-01-26 16:11:19 +05:30
end subroutine plastic_LpAndItsTangents
2021-01-26 13:09:17 +05:30
2021-01-26 16:15:39 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief contains the constitutive equation for calculating the rate of change of microstructure
!--------------------------------------------------------------------------------------------------
2021-04-13 00:51:15 +05:30
module function plastic_dotState(subdt,co,ip,el,ph,en) result(broken)
2021-01-26 16:15:39 +05:30
integer, intent(in) :: &
co, & !< component-ID of integration point
ip, & !< integration point
el, & !< element
ph, &
2021-04-13 00:51:15 +05:30
en
2021-01-26 16:15:39 +05:30
real(pReal), intent(in) :: &
subdt !< timestep
real(pReal), dimension(3,3) :: &
Mp
logical :: broken
2021-04-13 00:51:15 +05:30
Mp = matmul(matmul(transpose(phase_mechanical_Fi(ph)%data(1:3,1:3,en)),&
phase_mechanical_Fi(ph)%data(1:3,1:3,en)),phase_mechanical_S(ph)%data(1:3,1:3,en))
2021-01-26 16:15:39 +05:30
2021-02-09 03:51:53 +05:30
plasticType: select case (phase_plasticity(ph))
2021-01-26 16:15:39 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_ISOTROPIC_ID) plasticType
2021-04-13 00:51:15 +05:30
call isotropic_dotState(Mp,ph,en)
2021-01-26 16:15:39 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_PHENOPOWERLAW_ID) plasticType
2021-04-13 00:51:15 +05:30
call phenopowerlaw_dotState(Mp,ph,en)
2021-01-26 16:15:39 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_KINEHARDENING_ID) plasticType
2021-04-13 00:51:15 +05:30
call plastic_kinehardening_dotState(Mp,ph,en)
2021-01-26 16:15:39 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_DISLOTWIN_ID) plasticType
2021-04-13 00:51:15 +05:30
call dislotwin_dotState(Mp,thermal_T(ph,en),ph,en)
2021-01-26 16:15:39 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_DISLOTUNGSTEN_ID) plasticType
2021-04-13 00:51:15 +05:30
call dislotungsten_dotState(Mp,thermal_T(ph,en),ph,en)
2021-01-26 16:15:39 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_NONLOCAL_ID) plasticType
2021-04-13 00:51:15 +05:30
call nonlocal_dotState(Mp,thermal_T(ph,en),subdt,ph,en,ip,el)
2021-02-09 03:51:53 +05:30
end select plasticType
2021-04-13 00:51:15 +05:30
broken = any(IEEE_is_NaN(plasticState(ph)%dotState(:,en)))
2021-01-26 16:15:39 +05:30
2021-01-26 16:47:00 +05:30
end function plastic_dotState
2021-01-26 16:15:39 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief calls microstructure function of the different plasticity constitutive models
!--------------------------------------------------------------------------------------------------
2021-01-26 16:47:00 +05:30
module subroutine plastic_dependentState(co, ip, el)
2021-01-26 16:15:39 +05:30
integer, intent(in) :: &
co, & !< component-ID of integration point
ip, & !< integration point
el !< element
integer :: &
ph, &
me
2021-01-26 16:15:39 +05:30
ph = material_phaseAt(co,el)
me = material_phasememberAt(co,ip,el)
2021-02-09 03:51:53 +05:30
plasticType: select case (phase_plasticity(material_phaseAt(co,el)))
2021-01-26 16:15:39 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_DISLOTWIN_ID) plasticType
call dislotwin_dependentState(thermal_T(ph,me),ph,me)
2021-01-26 16:15:39 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_DISLOTUNGSTEN_ID) plasticType
call dislotungsten_dependentState(ph,me)
2021-01-26 16:15:39 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_NONLOCAL_ID) plasticType
call nonlocal_dependentState(ph,me,ip,el)
2021-01-26 16:15:39 +05:30
2021-02-09 03:51:53 +05:30
end select plasticType
2021-01-26 16:15:39 +05:30
2021-01-26 16:47:00 +05:30
end subroutine plastic_dependentState
2021-01-26 16:15:39 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief for constitutive models having an instantaneous change of state
!> will return false if delta state is not needed/supported by the constitutive model
!--------------------------------------------------------------------------------------------------
2021-04-13 00:51:15 +05:30
module function plastic_deltaState(ph, en) result(broken)
2021-01-26 16:15:39 +05:30
integer, intent(in) :: &
ph, &
2021-04-13 00:51:15 +05:30
en
2021-01-26 16:15:39 +05:30
logical :: &
broken
real(pReal), dimension(3,3) :: &
Mp
integer :: &
myOffset, &
mySize
2021-04-13 00:51:15 +05:30
Mp = matmul(matmul(transpose(phase_mechanical_Fi(ph)%data(1:3,1:3,en)),&
phase_mechanical_Fi(ph)%data(1:3,1:3,en)),phase_mechanical_S(ph)%data(1:3,1:3,en))
2021-01-26 16:15:39 +05:30
2021-02-09 03:51:53 +05:30
plasticType: select case (phase_plasticity(ph))
2021-01-26 16:15:39 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_KINEHARDENING_ID) plasticType
2021-04-13 00:51:15 +05:30
call plastic_kinehardening_deltaState(Mp,ph,en)
broken = any(IEEE_is_NaN(plasticState(ph)%deltaState(:,en)))
2021-01-26 16:15:39 +05:30
2021-02-09 03:51:53 +05:30
case (PLASTICITY_NONLOCAL_ID) plasticType
2021-04-13 00:51:15 +05:30
call plastic_nonlocal_deltaState(Mp,ph,en)
broken = any(IEEE_is_NaN(plasticState(ph)%deltaState(:,en)))
2021-01-26 16:15:39 +05:30
case default
broken = .false.
2021-02-09 03:51:53 +05:30
end select plasticType
2021-01-26 16:15:39 +05:30
if(.not. broken) then
select case(phase_plasticity(ph))
case (PLASTICITY_NONLOCAL_ID,PLASTICITY_KINEHARDENING_ID)
myOffset = plasticState(ph)%offsetDeltaState
mySize = plasticState(ph)%sizeDeltaState
2021-04-13 00:51:15 +05:30
plasticState(ph)%state(myOffset + 1:myOffset + mySize,en) = &
plasticState(ph)%state(myOffset + 1:myOffset + mySize,en) + plasticState(ph)%deltaState(1:mySize,en)
2021-01-26 16:15:39 +05:30
end select
endif
2021-01-26 16:47:00 +05:30
end function plastic_deltaState
2021-01-26 16:15:39 +05:30
2021-01-27 11:40:53 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief checks if a plastic module is active or not
!--------------------------------------------------------------------------------------------------
function plastic_active(plastic_label) result(active_plastic)
character(len=*), intent(in) :: plastic_label !< type of plasticity model
logical, dimension(:), allocatable :: active_plastic
class(tNode), pointer :: &
phases, &
phase, &
mech, &
pl
integer :: ph
phases => config_material%get('phase')
allocate(active_plastic(phases%length), source = .false. )
do ph = 1, phases%length
phase => phases%get(ph)
2021-03-25 23:52:59 +05:30
mech => phase%get('mechanical')
2021-03-27 01:46:11 +05:30
pl => mech%get('plastic',defaultVal = emptyDict)
if(pl%get_asString('type',defaultVal='none') == plastic_label) active_plastic(ph) = .true.
2021-01-27 11:40:53 +05:30
enddo
end function plastic_active
2021-01-26 05:41:32 +05:30
end submodule plastic