private functions at the end

This commit is contained in:
Martin Diehl 2018-12-21 22:41:39 +01:00
parent 2476dd4d8b
commit 9094bb9a64
1 changed files with 63 additions and 60 deletions

View File

@ -21,8 +21,6 @@ module plastic_kinehardening
integer(pInt), dimension(:), allocatable, target, public :: &
plastic_kinehardening_Noutput !< number of outputs per instance
integer(pInt), dimension(:), allocatable, public, protected :: &
plastic_kinehardening_totalNslip !< no. of slip system used in simulation
integer(pInt), dimension(:,:), allocatable, private :: &
@ -193,13 +191,14 @@ subroutine plastic_kinehardening_init
plastic_kinehardening_output = ''
allocate(plastic_kinehardening_Noutput(maxNinstance), source=0_pInt)
allocate(plastic_kinehardening_Nslip(lattice_maxNslipFamily,maxNinstance), source=0_pInt)
allocate(plastic_kinehardening_totalNslip(maxNinstance), source=0_pInt)
allocate(param(maxNinstance)) ! one container of parameters per instance
allocate(paramNew(maxNinstance))
allocate(state(maxNinstance))
allocate(state0(maxNinstance))
allocate(dotState(maxNinstance))
allocate(deltaState(maxNinstance))
do p = 1_pInt, size(phase_plasticityInstance)
if (phase_plasticity(p) /= PLASTICITY_KINEHARDENING_ID) cycle
instance = phase_plasticityInstance(p) ! which instance of my phase
@ -421,63 +420,6 @@ param(instance)%outputID = prm%outputID
end subroutine plastic_kinehardening_init
!--------------------------------------------------------------------------------------------------
!> @brief calculation of shear rates (\dot \gamma)
!--------------------------------------------------------------------------------------------------
subroutine plastic_kinehardening_shearRates(gdot_pos,gdot_neg,tau_pos,tau_neg, &
Mp,instance,of, dgdot_dtau_pos, &
dgdot_dtau_neg)
use prec
use math
implicit none
real(pReal), dimension(3,3), intent(in) :: &
Mp
integer(pInt), intent(in) :: &
instance, & !< instance of that phase
of !< index of phaseMember
real(pReal), dimension(paramNew(instance)%totalNslip), intent(out) :: &
gdot_pos, & !< shear rates from positive line segments
gdot_neg, & !< shear rates from negative line segments
tau_pos, & !< shear stress on positive line segments
tau_neg !< shear stress on negative line segments
real(pReal), dimension(paramNew(instance)%totalNslip), intent(out),optional :: &
dgdot_dtau_pos, &
dgdot_dtau_neg
integer(pInt) :: &
i
associate(prm => paramNew(instance), stt => state(instance))
do i = 1_pInt, prm%totalNslip
tau_pos(i) = math_mul33xx33(Mp,prm%nonSchmid_pos(1:3,1:3,i))
tau_neg(i) = math_mul33xx33(Mp,prm%nonSchmid_neg(1:3,1:3,i))
enddo
tau_pos = tau_pos - stt%crss_back(:,of)
tau_neg = tau_neg - stt%crss_back(:,of)
gdot_pos = sign(0.5_pReal * prm%gdot0 *(abs(tau_pos)/ state(instance)%crss(:,of))**prm%n_slip,tau_pos)
gdot_neg = sign(0.5_pReal * prm%gdot0 *(abs(tau_neg)/ state(instance)%crss(:,of))**prm%n_slip,tau_neg)
if (present(dgdot_dtau_pos)) then
where(dNeq0(gdot_pos))
dgdot_dtau_pos = gdot_pos*prm%n_slip/tau_pos
else where
dgdot_dtau_pos = 0.0_pReal
end where
endif
if (present(dgdot_dtau_neg)) then
where(dNeq0(gdot_neg))
dgdot_dtau_neg = gdot_neg*prm%n_slip/tau_neg
else where
dgdot_dtau_neg = 0.0_pReal
end where
endif
end associate
end subroutine plastic_kinehardening_shearRates
!--------------------------------------------------------------------------------------------------
!> @brief calculates plastic velocity gradient and its tangent
@ -525,6 +467,7 @@ end associate
end subroutine plastic_kinehardening_LpAndItsTangent
!--------------------------------------------------------------------------------------------------
!> @brief calculates (instantaneous) incremental change of microstructure
!--------------------------------------------------------------------------------------------------
@ -635,6 +578,7 @@ subroutine plastic_kinehardening_dotState(Mp,instance,of)
end subroutine plastic_kinehardening_dotState
!--------------------------------------------------------------------------------------------------
!> @brief return array of constitutive results
!--------------------------------------------------------------------------------------------------
@ -782,4 +726,63 @@ pure subroutine kinetics(prm,stt,of,Mp,gdot_pos,gdot_neg,dgdot_dtau_pos,dgdot_dt
end subroutine kinetics
!--------------------------------------------------------------------------------------------------
!> @brief calculation of shear rates (\dot \gamma)
!--------------------------------------------------------------------------------------------------
subroutine plastic_kinehardening_shearRates(gdot_pos,gdot_neg,tau_pos,tau_neg, &
Mp,instance,of, dgdot_dtau_pos, &
dgdot_dtau_neg)
use prec
use math
implicit none
real(pReal), dimension(3,3), intent(in) :: &
Mp
integer(pInt), intent(in) :: &
instance, & !< instance of that phase
of !< index of phaseMember
real(pReal), dimension(paramNew(instance)%totalNslip), intent(out) :: &
gdot_pos, & !< shear rates from positive line segments
gdot_neg, & !< shear rates from negative line segments
tau_pos, & !< shear stress on positive line segments
tau_neg !< shear stress on negative line segments
real(pReal), dimension(paramNew(instance)%totalNslip), intent(out),optional :: &
dgdot_dtau_pos, &
dgdot_dtau_neg
integer(pInt) :: &
i
associate(prm => paramNew(instance), stt => state(instance))
do i = 1_pInt, prm%totalNslip
tau_pos(i) = math_mul33xx33(Mp,prm%nonSchmid_pos(1:3,1:3,i))
tau_neg(i) = math_mul33xx33(Mp,prm%nonSchmid_neg(1:3,1:3,i))
enddo
tau_pos = tau_pos - stt%crss_back(:,of)
tau_neg = tau_neg - stt%crss_back(:,of)
gdot_pos = sign(0.5_pReal * prm%gdot0 *(abs(tau_pos)/ state(instance)%crss(:,of))**prm%n_slip,tau_pos)
gdot_neg = sign(0.5_pReal * prm%gdot0 *(abs(tau_neg)/ state(instance)%crss(:,of))**prm%n_slip,tau_neg)
if (present(dgdot_dtau_pos)) then
where(dNeq0(gdot_pos))
dgdot_dtau_pos = gdot_pos*prm%n_slip/tau_pos
else where
dgdot_dtau_pos = 0.0_pReal
end where
endif
if (present(dgdot_dtau_neg)) then
where(dNeq0(gdot_neg))
dgdot_dtau_neg = gdot_neg*prm%n_slip/tau_neg
else where
dgdot_dtau_neg = 0.0_pReal
end where
endif
end associate
end subroutine plastic_kinehardening_shearRates
end module plastic_kinehardening