leaner APIs

This commit is contained in:
Martin Diehl 2018-12-13 09:34:40 +01:00
parent 98cc79d629
commit 416d3411c1
2 changed files with 69 additions and 118 deletions

View File

@ -516,7 +516,9 @@ subroutine constitutive_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, S6, Fi, ipc, ip, e
call plastic_phenopowerlaw_LpAndItsTangent (Lp,dLp_dMp, Mp,instance,of) call plastic_phenopowerlaw_LpAndItsTangent (Lp,dLp_dMp, Mp,instance,of)
case (PLASTICITY_KINEHARDENING_ID) plasticityType case (PLASTICITY_KINEHARDENING_ID) plasticityType
call plastic_kinehardening_LpAndItsTangent (Lp,dLp_dMp, Mp,ipc,ip,el) of = phasememberAt(ipc,ip,el)
instance = phase_plasticityInstance(material_phase(ipc,ip,el))
call plastic_kinehardening_LpAndItsTangent (Lp,dLp_dMp, Mp,instance,of)
case (PLASTICITY_NONLOCAL_ID) plasticityType case (PLASTICITY_NONLOCAL_ID) plasticityType
call plastic_nonlocal_LpAndItsTangent (Lp,dLp_dMp99, math_Mandel33to6(Mp), & call plastic_nonlocal_LpAndItsTangent (Lp,dLp_dMp99, math_Mandel33to6(Mp), &
@ -918,7 +920,9 @@ subroutine constitutive_collectDotState(S6, FeArray, Fi, FpArray, subdt, subfrac
call plastic_phenopowerlaw_dotState(Mp,instance,of) call plastic_phenopowerlaw_dotState(Mp,instance,of)
case (PLASTICITY_KINEHARDENING_ID) plasticityType case (PLASTICITY_KINEHARDENING_ID) plasticityType
call plastic_kinehardening_dotState(Mp,ipc,ip,el) of = phasememberAt(ipc,ip,el)
instance = phase_plasticityInstance(material_phase(ipc,ip,el))
call plastic_kinehardening_dotState(Mp,instance,of)
case (PLASTICITY_DISLOTWIN_ID) plasticityType case (PLASTICITY_DISLOTWIN_ID) plasticityType
call plastic_dislotwin_dotState (math_Mandel33to6(Mp),temperature(ho)%p(tme), & call plastic_dislotwin_dotState (math_Mandel33to6(Mp),temperature(ho)%p(tme), &
@ -972,6 +976,8 @@ subroutine constitutive_collectDeltaState(S6, Fe, Fi, ipc, ip, el)
math_Mandel33to6, & math_Mandel33to6, &
math_mul33x33 math_mul33x33
use material, only: & use material, only: &
phasememberAt, &
phase_plasticityInstance, &
phase_plasticity, & phase_plasticity, &
phase_source, & phase_source, &
phase_Nsources, & phase_Nsources, &
@ -1003,19 +1009,22 @@ subroutine constitutive_collectDeltaState(S6, Fe, Fi, ipc, ip, el)
Fe, & !< elastic deformation gradient Fe, & !< elastic deformation gradient
Fi !< intermediate deformation gradient Fi !< intermediate deformation gradient
real(pReal), dimension(3,3) :: & real(pReal), dimension(3,3) :: &
Mstar Mp
integer(pInt) :: & integer(pInt) :: &
s !< counter in source loop s, & !< counter in source loop
instance, of
Mstar = math_mul33x33(math_mul33x33(transpose(Fi),Fi),math_Mandel6to33(S6)) Mp = math_mul33x33(math_mul33x33(transpose(Fi),Fi),math_Mandel6to33(S6))
plasticityType: select case (phase_plasticity(material_phase(ipc,ip,el))) plasticityType: select case (phase_plasticity(material_phase(ipc,ip,el)))
case (PLASTICITY_KINEHARDENING_ID) plasticityType case (PLASTICITY_KINEHARDENING_ID) plasticityType
call plastic_kinehardening_deltaState(Mstar,ipc,ip,el) of = phasememberAt(ipc,ip,el)
instance = phase_plasticityInstance(material_phase(ipc,ip,el))
call plastic_kinehardening_deltaState(Mp,instance,of)
case (PLASTICITY_NONLOCAL_ID) plasticityType case (PLASTICITY_NONLOCAL_ID) plasticityType
call plastic_nonlocal_deltaState(math_Mandel33to6(Mstar),ip,el) call plastic_nonlocal_deltaState(math_Mandel33to6(Mp),ip,el)
end select plasticityType end select plasticityType
@ -1140,8 +1149,10 @@ function constitutive_postResults(S6, Fi, FeArray, ipc, ip, el)
constitutive_postResults(startPos:endPos) = & constitutive_postResults(startPos:endPos) = &
plastic_phenopowerlaw_postResults(Mp,instance,of) plastic_phenopowerlaw_postResults(Mp,instance,of)
case (PLASTICITY_KINEHARDENING_ID) plasticityType case (PLASTICITY_KINEHARDENING_ID) plasticityType
of = phasememberAt(ipc,ip,el)
instance = phase_plasticityInstance(material_phase(ipc,ip,el))
constitutive_postResults(startPos:endPos) = & constitutive_postResults(startPos:endPos) = &
plastic_kinehardening_postResults(Mp,ipc,ip,el) plastic_kinehardening_postResults(Mp,instance,of)
case (PLASTICITY_DISLOTWIN_ID) plasticityType case (PLASTICITY_DISLOTWIN_ID) plasticityType
constitutive_postResults(startPos:endPos) = & constitutive_postResults(startPos:endPos) = &
plastic_dislotwin_postResults(S6,temperature(ho)%p(tme),ipc,ip,el) plastic_dislotwin_postResults(S6,temperature(ho)%p(tme),ipc,ip,el)

View File

@ -520,11 +520,6 @@ subroutine plastic_kinehardening_shearRates(gdot_pos,gdot_neg,tau_pos,tau_neg, &
Mp,instance,of) Mp,instance,of)
use math use math
use lattice, only: &
lattice_NslipSystem, &
lattice_Sslip, &
lattice_maxNslipFamily, &
lattice_NnonSchmid
implicit none implicit none
real(pReal), dimension(3,3), intent(in) :: & real(pReal), dimension(3,3), intent(in) :: &
@ -532,7 +527,7 @@ subroutine plastic_kinehardening_shearRates(gdot_pos,gdot_neg,tau_pos,tau_neg, &
integer(pInt), intent(in) :: & integer(pInt), intent(in) :: &
instance, & !< instance of that phase instance, & !< instance of that phase
of !< index of phaseMember of !< index of phaseMember
real(pReal), dimension(plastic_kinehardening_totalNslip(instance)), intent(out) :: & real(pReal), dimension(paramNew(instance)%totalNslip), intent(out) :: &
gdot_pos, & !< shear rates from positive line segments gdot_pos, & !< shear rates from positive line segments
gdot_neg, & !< shear rates from negative line segments gdot_neg, & !< shear rates from negative line segments
tau_pos, & !< shear stress on positive line segments tau_pos, & !< shear stress on positive line segments
@ -563,13 +558,9 @@ end subroutine plastic_kinehardening_shearRates
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates plastic velocity gradient and its tangent !> @brief calculates plastic velocity gradient and its tangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine plastic_kinehardening_LpAndItsTangent(Lp,dLp_dMp, & subroutine plastic_kinehardening_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of)
Mp,ipc,ip,el)
use prec, only: & use prec, only: &
dNeq0 dNeq0
use material, only: &
phaseAt, phasememberAt, &
phase_plasticityInstance
implicit none implicit none
real(pReal), dimension(3,3), intent(out) :: & real(pReal), dimension(3,3), intent(out) :: &
@ -577,29 +568,22 @@ subroutine plastic_kinehardening_LpAndItsTangent(Lp,dLp_dMp, &
real(pReal), dimension(3,3,3,3), intent(out) :: & real(pReal), dimension(3,3,3,3), intent(out) :: &
dLp_dMp !< derivative of Lp with respect to the Mandel stress dLp_dMp !< derivative of Lp with respect to the Mandel stress
integer(pInt), intent(in) :: &
ipc, & !< component-ID of integration point
ip, & !< integration point
el !< element
real(pReal), dimension(3,3), intent(in) :: & real(pReal), dimension(3,3), intent(in) :: &
Mp Mp !< Mandel stress
integer(pInt), intent(in) :: &
instance, &
of
integer(pInt) :: & integer(pInt) :: &
instance, & f,i,j,k,l,m,n
f,i,j,k,l,m,n, &
of, &
ph
real(pReal), dimension(plastic_kinehardening_totalNslip(phase_plasticityInstance(phaseAt(ipc,ip,el)))) :: &
real(pReal), dimension(paramNew(instance)%totalNslip) :: &
gdot_pos,gdot_neg, & gdot_pos,gdot_neg, &
tau_pos,tau_neg tau_pos,tau_neg
real(pReal) :: & real(pReal) :: &
dgdot_dtau_pos,dgdot_dtau_neg dgdot_dtau_pos,dgdot_dtau_neg
ph = phaseAt(ipc,ip,el) !< figures phase for each material point
of = phasememberAt(ipc,ip,el) !< index of the positions of each constituent of material point, phasememberAt is a function in material that helps figure them out
instance = phase_plasticityInstance(ph)
associate(prm => paramNew(instance), stt => state(instance)) associate(prm => paramNew(instance), stt => state(instance))
Lp = 0.0_pReal Lp = 0.0_pReal
dLp_dMp = 0.0_pReal dLp_dMp = 0.0_pReal
@ -636,35 +620,22 @@ end subroutine plastic_kinehardening_LpAndItsTangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates (instantaneous) incremental change of microstructure !> @brief calculates (instantaneous) incremental change of microstructure
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine plastic_kinehardening_deltaState(Mp,ipc,ip,el) subroutine plastic_kinehardening_deltaState(Mp,instance,of)
use prec, only: & use prec, only: &
dNeq, & dNeq, &
dEq0 dEq0
use material, only: &
phaseAt, &
phasememberAt, &
phase_plasticityInstance
implicit none implicit none
real(pReal), dimension(3,3), intent(in) :: & real(pReal), dimension(3,3), intent(in) :: &
Mp Mp !< Mandel stress
integer(pInt), intent(in) :: & integer(pInt), intent(in) :: &
ipc, & !< component-ID of integration point instance, &
ip, & !< integration point of
el !< element
real(pReal), dimension(plastic_kinehardening_totalNslip(phase_plasticityInstance(phaseAt(ipc,ip,el)))) :: & real(pReal), dimension(paramNew(instance)%totalNslip) :: &
gdot_pos,gdot_neg, & gdot_pos,gdot_neg, &
tau_pos,tau_neg, & tau_pos,tau_neg, &
sense sense
integer(pInt) :: &
ph, &
instance, & !< instance of my instance (unique number of my constitutive model)
of, &
j !< shortcut notation for offset position in state array
ph = phaseAt(ipc,ip,el)
of = phasememberAt(ipc,ip,el) ! phasememberAt should be tackled by material and be renamed to material_phasemember
instance = phase_plasticityInstance(ph)
call plastic_kinehardening_shearRates(gdot_pos,gdot_neg,tau_pos,tau_neg, & call plastic_kinehardening_shearRates(gdot_pos,gdot_neg,tau_pos,tau_neg, &
Mp,instance,of) Mp,instance,of)
@ -707,38 +678,24 @@ end subroutine plastic_kinehardening_deltaState
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates the rate of change of microstructure !> @brief calculates the rate of change of microstructure
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine plastic_kinehardening_dotState(Mp,ipc,ip,el) subroutine plastic_kinehardening_dotState(Mp,instance,of)
use lattice, only: &
lattice_maxNslipFamily
use material, only: &
material_phase, &
phaseAt, phasememberAt, &
phase_plasticityInstance
implicit none implicit none
real(pReal), dimension(3,3), intent(in) :: & real(pReal), dimension(3,3), intent(in) :: &
Mp Mp !< Mandel stress
integer(pInt), intent(in) :: & integer(pInt), intent(in) :: &
ipc, & !< component-ID of integration point instance, &
ip, & !< integration point of !< element !< microstructure state
el !< element !< microstructure state
integer(pInt) :: & integer(pInt) :: &
instance,ph, & f,i,j
f,i,j, &
nSlip, &
of
real(pReal), dimension(plastic_kinehardening_totalNslip(phase_plasticityInstance(material_phase(ipc,ip,el)))) :: & real(pReal), dimension(paramNew(instance)%totalNslip) :: &
gdot_pos,gdot_neg, & gdot_pos,gdot_neg, &
tau_pos,tau_neg tau_pos,tau_neg
real(pReal) :: & real(pReal) :: &
sumGamma sumGamma
of = phasememberAt(ipc,ip,el)
ph = phaseAt(ipc,ip,el)
instance = phase_plasticityInstance(ph)
nSlip = plastic_kinehardening_totalNslip(instance)
associate( prm => paramNew(instance), stt => state(instance), dot => dotState(instance)) associate( prm => paramNew(instance), stt => state(instance), dot => dotState(instance))
@ -775,43 +732,26 @@ end subroutine plastic_kinehardening_dotState
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief return array of constitutive results !> @brief return array of constitutive results
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function plastic_kinehardening_postResults(Mp,ipc,ip,el) result(postResults) function plastic_kinehardening_postResults(Mp,instance,of) result(postResults)
use math use math, only: &
use material, only: & math_mul33xx33
material_phase, &
phaseAt, phasememberAt, &
phase_plasticityInstance
use lattice, only: &
lattice_Sslip, &
lattice_maxNslipFamily, &
lattice_NslipSystem
implicit none implicit none
real(pReal), dimension(3,3), intent(in) :: & real(pReal), dimension(3,3), intent(in) :: &
Mp Mp !< Mandel stress
integer(pInt), intent(in) :: & integer(pInt), intent(in) :: &
ipc, & !< component-ID of integration point instance, &
ip, & !< integration point of
el !< element !< microstructure state
real(pReal), dimension(sum(plastic_kinehardening_sizePostResult(:,phase_plasticityInstance(material_phase(ipc,ip,el))))) :: & real(pReal), dimension(sum(plastic_kinehardening_sizePostResult(:,instance))) :: &
postResults postResults
integer(pInt) :: & integer(pInt) :: &
instance,ph, of, & o,c,f,j
nSlip,&
o,f,i,c,j,&
index_myFamily
real(pReal), dimension(plastic_kinehardening_totalNslip(phase_plasticityInstance(material_phase(ipc,ip,el)))) :: & real(pReal), dimension(paramNew(instance)%totalNslip) :: &
gdot_pos,gdot_neg, & gdot_pos,gdot_neg, &
tau_pos,tau_neg tau_pos,tau_neg
of = phasememberAt(ipc,ip,el)
ph = phaseAt(ipc,ip,el)
instance = phase_plasticityInstance(ph)
nSlip = plastic_kinehardening_totalNslip(instance)
postResults = 0.0_pReal postResults = 0.0_pReal
c = 0_pInt c = 0_pInt
@ -821,38 +761,38 @@ function plastic_kinehardening_postResults(Mp,ipc,ip,el) result(postResults)
outputsLoop: do o = 1_pInt,plastic_kinehardening_Noutput(instance) outputsLoop: do o = 1_pInt,plastic_kinehardening_Noutput(instance)
select case(prm%outputID(o)) select case(prm%outputID(o))
case (crss_ID) case (crss_ID)
postResults(c+1_pInt:c+nSlip) = stt%crss(:,of) postResults(c+1_pInt:c+prm%totalNslip) = stt%crss(:,of)
c = c + nSlip c = c + prm%totalNslip
case(crss_back_ID) case(crss_back_ID)
postResults(c+1_pInt:c+nSlip) = stt%crss_back(:,of) postResults(c+1_pInt:c+prm%totalNslip) = stt%crss_back(:,of)
c = c + nSlip c = c + prm%totalNslip
case (sense_ID) case (sense_ID)
postResults(c+1_pInt:c+nSlip) = stt%sense(:,of) postResults(c+1_pInt:c+prm%totalNslip) = stt%sense(:,of)
c = c + nSlip c = c + prm%totalNslip
case (chi0_ID) case (chi0_ID)
postResults(c+1_pInt:c+nSlip) = stt%chi0(:,of) postResults(c+1_pInt:c+prm%totalNslip) = stt%chi0(:,of)
c = c + nSlip c = c + prm%totalNslip
case (gamma0_ID) case (gamma0_ID)
postResults(c+1_pInt:c+nSlip) = stt%gamma0(:,of) postResults(c+1_pInt:c+prm%totalNslip) = stt%gamma0(:,of)
c = c + nSlip c = c + prm%totalNslip
case (accshear_ID) case (accshear_ID)
postResults(c+1_pInt:c+nSlip) = stt%accshear(:,of) postResults(c+1_pInt:c+prm%totalNslip) = stt%accshear(:,of)
c = c + nSlip c = c + prm%totalNslip
case (shearrate_ID) case (shearrate_ID)
postResults(c+1_pInt:c+nSlip) = gdot_pos+gdot_neg postResults(c+1_pInt:c+prm%totalNslip) = gdot_pos+gdot_neg
c = c + nSlip c = c + prm%totalNslip
case (resolvedstress_ID) case (resolvedstress_ID)
do j = 1_pInt, prm%totalNslip do j = 1_pInt, prm%totalNslip
postResults(c+j) = math_mul33xx33(Mp,prm%Schmid_slip(1:3,1:3,j)) postResults(c+j) = math_mul33xx33(Mp,prm%Schmid_slip(1:3,1:3,j))
enddo enddo
c = c + nSlip c = c + prm%totalNslip
end select end select
enddo outputsLoop enddo outputsLoop