no need for outputID

just adds overhead, one string comparison per output and increment is
computationally not an issue

also unified to PEP recommendation of function description
This commit is contained in:
Martin Diehl 2020-02-14 07:17:30 +01:00
parent 6adb116712
commit 486385978c
3 changed files with 264 additions and 393 deletions

View File

@ -9,13 +9,6 @@
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
submodule(constitutive) plastic_isotropic submodule(constitutive) plastic_isotropic
enum, bind(c)
enumerator :: &
undefined_ID, &
xi_ID, &
dot_gamma_ID
end enum
type :: tParameters type :: tParameters
real(pReal) :: & real(pReal) :: &
M, & !< Taylor factor M, & !< Taylor factor
@ -34,10 +27,10 @@ submodule(constitutive) plastic_isotropic
aTol_gamma aTol_gamma
integer :: & integer :: &
of_debug = 0 of_debug = 0
integer(kind(undefined_ID)), allocatable, dimension(:) :: &
outputID
logical :: & logical :: &
dilatation dilatation
character(len=pStringLen), allocatable, dimension(:) :: &
output
end type tParameters end type tParameters
type :: tIsotropicState type :: tIsotropicState
@ -56,26 +49,21 @@ submodule(constitutive) plastic_isotropic
contains contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief module initialization !> @brief Perform module initialization.
!> @details reads in material parameters, allocates arrays, and does sanity checks !> @details reads in material parameters, allocates arrays, and does sanity checks
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine plastic_isotropic_init module subroutine plastic_isotropic_init
integer :: & integer :: &
Ninstance, & Ninstance, &
p, i, & p, &
NipcMyPhase, & NipcMyPhase, &
sizeState, sizeDotState sizeState, sizeDotState
integer(kind(undefined_ID)) :: &
outputID
character(len=pStringLen) :: & character(len=pStringLen) :: &
extmsg = '' extmsg = ''
character(len=pStringLen), dimension(:), allocatable :: &
outputs
write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_ISOTROPIC_label//' init -+>>>' write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_ISOTROPIC_label//' init -+>>>'; flush(6)
write(6,'(/,a)') ' Maiti and Eisenlohr, Scripta Materialia 145:3740, 2018' write(6,'(/,a)') ' Maiti and Eisenlohr, Scripta Materialia 145:3740, 2018'
write(6,'(a)') ' https://doi.org/10.1016/j.scriptamat.2017.09.047' write(6,'(a)') ' https://doi.org/10.1016/j.scriptamat.2017.09.047'
@ -136,24 +124,7 @@ module subroutine plastic_isotropic_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! output pararameters ! output pararameters
outputs = config%getStrings('(output)',defaultVal=emptyStringArray) prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
allocate(prm%outputID(0))
do i=1, size(outputs)
outputID = undefined_ID
select case(outputs(i))
case ('flowstress')
outputID = xi_ID
case ('strainrate')
outputID = dot_gamma_ID
end select
if (outputID /= undefined_ID) then
prm%outputID = [prm%outputID, outputID]
endif
enddo
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! allocate state arrays ! allocate state arrays
@ -186,7 +157,7 @@ end subroutine plastic_isotropic_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates plastic velocity gradient and its tangent !> @brief Calculate plastic velocity gradient and its tangent.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of) module subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of)
@ -247,7 +218,7 @@ end subroutine plastic_isotropic_LpAndItsTangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates plastic velocity gradient and its tangent !> @brief Calculate inelastic velocity gradient and its tangent.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dMi,Mi,instance,of) module subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dMi,Mi,instance,of)
@ -299,7 +270,7 @@ module subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dMi,Mi,instance,of)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates the rate of change of microstructure !> @brief Calculate the rate of change of microstructure.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine plastic_isotropic_dotState(Mp,instance,of) module subroutine plastic_isotropic_dotState(Mp,instance,of)
@ -348,7 +319,7 @@ end subroutine plastic_isotropic_dotState
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief writes results to HDF5 output file !> @brief Write results to HDF5 output file.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine plastic_isotropic_results(instance,group) module subroutine plastic_isotropic_results(instance,group)
@ -358,9 +329,9 @@ module subroutine plastic_isotropic_results(instance,group)
integer :: o integer :: o
associate(prm => param(instance), stt => state(instance)) associate(prm => param(instance), stt => state(instance))
outputsLoop: do o = 1,size(prm%outputID) outputsLoop: do o = 1,size(prm%output)
select case(prm%outputID(o)) select case(trim(prm%output(o)))
case (xi_ID) case ('flowstress') ! ToDo: should be 'xi'
call results_writeDataset(group,stt%xi,'xi','resistance against plastic flow','Pa') call results_writeDataset(group,stt%xi,'xi','resistance against plastic flow','Pa')
end select end select
enddo outputsLoop enddo outputsLoop

View File

@ -7,19 +7,6 @@
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
submodule(constitutive) plastic_kinehardening submodule(constitutive) plastic_kinehardening
enum, bind(c)
enumerator :: &
undefined_ID, &
crss_ID, & !< critical resolved stress
crss_back_ID, & !< critical resolved back stress
sense_ID, & !< sense of acting shear stress (-1 or +1)
chi0_ID, & !< backstress at last switch of stress sense (positive?)
gamma0_ID, & !< accumulated shear at last switch of stress sense (at current switch?)
accshear_ID, &
shearrate_ID, &
resolvedstress_ID
end enum
type :: tParameters type :: tParameters
real(pReal) :: & real(pReal) :: &
gdot0, & !< reference shear strain rate for slip gdot0, & !< reference shear strain rate for slip
@ -46,8 +33,8 @@ submodule(constitutive) plastic_kinehardening
of_debug = 0 of_debug = 0
integer, allocatable, dimension(:) :: & integer, allocatable, dimension(:) :: &
Nslip !< number of active slip systems for each family Nslip !< number of active slip systems for each family
integer(kind(undefined_ID)), allocatable, dimension(:) :: & character(len=pStringLen), allocatable, dimension(:) :: &
outputID !< ID of each post result output output
end type tParameters end type tParameters
type :: tKinehardeningState type :: tKinehardeningState
@ -72,27 +59,22 @@ contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief module initialization !> @brief Perform module initialization.
!> @details reads in material parameters, allocates arrays, and does sanity checks !> @details reads in material parameters, allocates arrays, and does sanity checks
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine plastic_kinehardening_init module subroutine plastic_kinehardening_init
integer :: & integer :: &
Ninstance, & Ninstance, &
p, i, o, & p, o, &
NipcMyPhase, & NipcMyPhase, &
sizeState, sizeDeltaState, sizeDotState, & sizeState, sizeDeltaState, sizeDotState, &
startIndex, endIndex startIndex, endIndex
integer(kind(undefined_ID)) :: &
outputID
character(len=pStringLen) :: & character(len=pStringLen) :: &
extmsg = '' extmsg = ''
character(len=pStringLen), dimension(:), allocatable :: &
outputs
write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_KINEHARDENING_label//' init -+>>>' write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_KINEHARDENING_label//' init -+>>>'; flush(6)
Ninstance = count(phase_plasticity == PLASTICITY_KINEHARDENING_ID) Ninstance = count(phase_plasticity == PLASTICITY_KINEHARDENING_ID)
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) & if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
@ -188,36 +170,7 @@ module subroutine plastic_kinehardening_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! output pararameters ! output pararameters
outputs = config%getStrings('(output)',defaultVal=emptyStringArray) prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
allocate(prm%outputID(0))
do i=1, size(outputs)
outputID = undefined_ID
select case(outputs(i))
case ('resistance')
outputID = merge(crss_ID,undefined_ID,prm%totalNslip>0)
case ('accumulatedshear')
outputID = merge(accshear_ID,undefined_ID,prm%totalNslip>0)
case ('shearrate')
outputID = merge(shearrate_ID,undefined_ID,prm%totalNslip>0)
case ('resolvedstress')
outputID = merge(resolvedstress_ID,undefined_ID,prm%totalNslip>0)
case ('backstress')
outputID = merge(crss_back_ID,undefined_ID,prm%totalNslip>0)
case ('sense')
outputID = merge(sense_ID,undefined_ID,prm%totalNslip>0)
case ('chi0')
outputID = merge(chi0_ID,undefined_ID,prm%totalNslip>0)
case ('gamma0')
outputID = merge(gamma0_ID,undefined_ID,prm%totalNslip>0)
end select
if (outputID /= undefined_ID) then
prm%outputID = [prm%outputID , outputID]
endif
enddo
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! allocate state arrays ! allocate state arrays
@ -277,7 +230,7 @@ end subroutine plastic_kinehardening_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates plastic velocity gradient and its tangent !> @brief Calculate plastic velocity gradient and its tangent.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
pure module subroutine plastic_kinehardening_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of) pure module subroutine plastic_kinehardening_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of)
@ -319,7 +272,7 @@ end subroutine plastic_kinehardening_LpAndItsTangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates the rate of change of microstructure !> @brief Calculate the rate of change of microstructure.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine plastic_kinehardening_dotState(Mp,instance,of) module subroutine plastic_kinehardening_dotState(Mp,instance,of)
@ -361,7 +314,7 @@ end subroutine plastic_kinehardening_dotState
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates (instantaneous) incremental change of microstructure !> @brief Calculate (instantaneous) incremental change of microstructure.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine plastic_kinehardening_deltaState(Mp,instance,of) module subroutine plastic_kinehardening_deltaState(Mp,instance,of)
@ -409,36 +362,37 @@ end subroutine plastic_kinehardening_deltaState
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief writes results to HDF5 output file !> @brief Write results to HDF5 output file.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine plastic_kinehardening_results(instance,group) module subroutine plastic_kinehardening_results(instance,group)
integer, intent(in) :: instance integer, intent(in) :: instance
character(len=*), intent(in) :: group character(len=*), intent(in) :: group
integer :: o integer :: o
associate(prm => param(instance), stt => state(instance)) associate(prm => param(instance), stt => state(instance))
outputsLoop: do o = 1,size(prm%outputID) outputsLoop: do o = 1,size(prm%output)
select case(prm%outputID(o)) select case(trim(prm%output(o)))
case (crss_ID) case('resistance')
call results_writeDataset(group,stt%crss,'xi_sl', & if(prm%totalNslip>0) call results_writeDataset(group,stt%crss,'xi_sl', &
'resistance against plastic slip','Pa') 'resistance against plastic slip','Pa')
case(crss_back_ID) case('backstress') ! ToDo: should be 'tau_back'
call results_writeDataset(group,stt%crss_back,'tau_back', & if(prm%totalNslip>0) call results_writeDataset(group,stt%crss_back,'tau_back', &
'back stress against plastic slip','Pa') 'back stress against plastic slip','Pa')
case (sense_ID) case ('sense')
call results_writeDataset(group,stt%sense,'sense_of_shear','tbd','1') if(prm%totalNslip>0) call results_writeDataset(group,stt%sense,'sense_of_shear','tbd','1')
case (chi0_ID) case ('chi0')
call results_writeDataset(group,stt%chi0,'chi0','tbd','Pa') if(prm%totalNslip>0) call results_writeDataset(group,stt%chi0,'chi0','tbd','Pa')
case (gamma0_ID) case ('gamma0')
call results_writeDataset(group,stt%gamma0,'gamma0','tbd','1') if(prm%totalNslip>0) call results_writeDataset(group,stt%gamma0,'gamma0','tbd','1')
case (accshear_ID) case ('accumulatedshear')
call results_writeDataset(group,stt%accshear,'gamma_sl', & if(prm%totalNslip>0) call results_writeDataset(group,stt%accshear,'gamma_sl', &
'plastic shear','1') 'plastic shear','1')
end select end select
@ -449,10 +403,11 @@ end subroutine plastic_kinehardening_results
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates shear rates on slip systems and derivatives with respect to resolved stress !> @brief Calculate shear rates on slip systems and their derivatives with respect to resolved
!> @details: Shear rates are calculated only optionally. ! stress.
!> @details: Derivatives are calculated only optionally.
! NOTE: Against the common convention, the result (i.e. intent(out)) variables are the last to ! NOTE: Against the common convention, the result (i.e. intent(out)) variables are the last to
! have the optional arguments at the end ! have the optional arguments at the end.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
pure subroutine kinetics(Mp,instance,of, & pure subroutine kinetics(Mp,instance,of, &
gdot_pos,gdot_neg,dgdot_dtau_pos,dgdot_dtau_neg) gdot_pos,gdot_neg,dgdot_dtau_pos,dgdot_dtau_neg)

View File

@ -6,19 +6,6 @@
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
submodule(constitutive) plastic_phenopowerlaw submodule(constitutive) plastic_phenopowerlaw
enum, bind(c)
enumerator :: &
undefined_ID, &
resistance_slip_ID, &
accumulatedshear_slip_ID, &
shearrate_slip_ID, &
resolvedstress_slip_ID, &
resistance_twin_ID, &
accumulatedshear_twin_ID, &
shearrate_twin_ID, &
resolvedstress_twin_ID
end enum
type :: tParameters type :: tParameters
real(pReal) :: & real(pReal) :: &
gdot0_slip, & !< reference shear strain rate for slip gdot0_slip, & !< reference shear strain rate for slip
@ -60,8 +47,8 @@ submodule(constitutive) plastic_phenopowerlaw
integer, allocatable, dimension(:) :: & integer, allocatable, dimension(:) :: &
Nslip, & !< number of active slip systems for each family Nslip, & !< number of active slip systems for each family
Ntwin !< number of active twin systems for each family Ntwin !< number of active twin systems for each family
integer(kind(undefined_ID)), allocatable, dimension(:) :: & character(len=pStringLen), allocatable, dimension(:) :: &
outputID !< ID of each post result output output
end type tParameters end type tParameters
type :: tPhenopowerlawState type :: tPhenopowerlawState
@ -83,7 +70,7 @@ contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief module initialization !> @brief Perform module initialization.
!> @details reads in material parameters, allocates arrays, and does sanity checks !> @details reads in material parameters, allocates arrays, and does sanity checks
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine plastic_phenopowerlaw_init module subroutine plastic_phenopowerlaw_init
@ -91,19 +78,14 @@ module subroutine plastic_phenopowerlaw_init
integer :: & integer :: &
Ninstance, & Ninstance, &
p, i, & p, i, &
NipcMyPhase, outputSize, & NipcMyPhase, &
sizeState, sizeDotState, & sizeState, sizeDotState, &
startIndex, endIndex startIndex, endIndex
integer(kind(undefined_ID)) :: &
outputID
character(len=pStringLen) :: & character(len=pStringLen) :: &
extmsg = '' extmsg = ''
character(len=pStringLen), dimension(:), allocatable :: &
outputs
write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_PHENOPOWERLAW_label//' init -+>>>' write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_PHENOPOWERLAW_label//' init -+>>>'; flush(6)
Ninstance = count(phase_plasticity == PLASTICITY_PHENOPOWERLAW_ID) Ninstance = count(phase_plasticity == PLASTICITY_PHENOPOWERLAW_ID)
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) & if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
@ -239,45 +221,7 @@ module subroutine plastic_phenopowerlaw_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! output pararameters ! output pararameters
outputs = config%getStrings('(output)',defaultVal=emptyStringArray) prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
allocate(prm%outputID(0))
do i=1, size(outputs)
outputID = undefined_ID
select case(outputs(i))
case ('resistance_slip')
outputID = merge(resistance_slip_ID,undefined_ID,prm%totalNslip>0)
outputSize = prm%totalNslip
case ('accumulatedshear_slip')
outputID = merge(accumulatedshear_slip_ID,undefined_ID,prm%totalNslip>0)
outputSize = prm%totalNslip
case ('shearrate_slip')
outputID = merge(shearrate_slip_ID,undefined_ID,prm%totalNslip>0)
outputSize = prm%totalNslip
case ('resolvedstress_slip')
outputID = merge(resolvedstress_slip_ID,undefined_ID,prm%totalNslip>0)
outputSize = prm%totalNslip
case ('resistance_twin')
outputID = merge(resistance_twin_ID,undefined_ID,prm%totalNtwin>0)
outputSize = prm%totalNtwin
case ('accumulatedshear_twin')
outputID = merge(accumulatedshear_twin_ID,undefined_ID,prm%totalNtwin>0)
outputSize = prm%totalNtwin
case ('shearrate_twin')
outputID = merge(shearrate_twin_ID,undefined_ID,prm%totalNtwin>0)
outputSize = prm%totalNtwin
case ('resolvedstress_twin')
outputID = merge(resolvedstress_twin_ID,undefined_ID,prm%totalNtwin>0)
outputSize = prm%totalNtwin
end select
if (outputID /= undefined_ID) then
prm%outputID = [prm%outputID, outputID]
endif
enddo
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! allocate state arrays ! allocate state arrays
@ -328,7 +272,7 @@ end subroutine plastic_phenopowerlaw_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates plastic velocity gradient and its tangent !> @brief Calculate plastic velocity gradient and its tangent.
!> @details asummes that deformation by dislocation glide affects twinned and untwinned volume !> @details asummes that deformation by dislocation glide affects twinned and untwinned volume
! equally (Taylor assumption). Twinning happens only in untwinned volume ! equally (Taylor assumption). Twinning happens only in untwinned volume
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
@ -381,7 +325,7 @@ end subroutine plastic_phenopowerlaw_LpAndItsTangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates the rate of change of microstructure !> @brief Calculate the rate of change of microstructure.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine plastic_phenopowerlaw_dotState(Mp,instance,of) module subroutine plastic_phenopowerlaw_dotState(Mp,instance,of)
@ -437,7 +381,7 @@ end subroutine plastic_phenopowerlaw_dotState
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief writes results to HDF5 output file !> @brief Write results to HDF5 output file.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine plastic_phenopowerlaw_results(instance,group) module subroutine plastic_phenopowerlaw_results(instance,group)
@ -447,21 +391,21 @@ module subroutine plastic_phenopowerlaw_results(instance,group)
integer :: o integer :: o
associate(prm => param(instance), stt => state(instance)) associate(prm => param(instance), stt => state(instance))
outputsLoop: do o = 1,size(prm%outputID) outputsLoop: do o = 1,size(prm%output)
select case(prm%outputID(o)) select case(trim(prm%output(o)))
case (resistance_slip_ID) case('resistance_slip')
call results_writeDataset(group,stt%xi_slip, 'xi_sl', & if(prm%totalNslip>0) call results_writeDataset(group,stt%xi_slip, 'xi_sl', &
'resistance against plastic slip','Pa') 'resistance against plastic slip','Pa')
case (accumulatedshear_slip_ID) case('accumulatedshear_slip')
call results_writeDataset(group,stt%gamma_slip,'gamma_sl', & if(prm%totalNslip>0) call results_writeDataset(group,stt%gamma_slip,'gamma_sl', &
'plastic shear','1') 'plastic shear','1')
case (resistance_twin_ID) case('resistance_twin')
call results_writeDataset(group,stt%xi_twin, 'xi_tw', & if(prm%totalNtwin>0) call results_writeDataset(group,stt%xi_twin, 'xi_tw', &
'resistance against twinning','Pa') 'resistance against twinning','Pa')
case (accumulatedshear_twin_ID) case('accumulatedshear_twin')
call results_writeDataset(group,stt%gamma_twin,'gamma_tw', & if(prm%totalNtwin>0) call results_writeDataset(group,stt%gamma_twin,'gamma_tw', &
'twinning shear','1') 'twinning shear','1')
end select end select
@ -472,10 +416,11 @@ end subroutine plastic_phenopowerlaw_results
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief Shear rates on slip systems and their derivatives with respect to resolved stress !> @brief Calculate shear rates on slip systems and their derivatives with respect to resolved.
! stress.
!> @details Derivatives are calculated only optionally. !> @details Derivatives are calculated only optionally.
! NOTE: Against the common convention, the result (i.e. intent(out)) variables are the last to ! NOTE: Against the common convention, the result (i.e. intent(out)) variables are the last to
! have the optional arguments at the end ! have the optional arguments at the end.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
pure subroutine kinetics_slip(Mp,instance,of, & pure subroutine kinetics_slip(Mp,instance,of, &
gdot_slip_pos,gdot_slip_neg,dgdot_dtau_slip_pos,dgdot_dtau_slip_neg) gdot_slip_pos,gdot_slip_neg,dgdot_dtau_slip_pos,dgdot_dtau_slip_neg)
@ -543,9 +488,9 @@ end subroutine kinetics_slip
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief Shear rates on twin systems and their derivatives with respect to resolved stress. !> @brief Calculate shear rates on twin systems and their derivatives with respect to resolved
! twinning is assumed to take place only in untwinned volume. ! stress. Twinning is assumed to take place only in untwinned volume.
!> @details Derivates are calculated only optionally. !> @details Derivatives are calculated only optionally.
! NOTE: Against the common convention, the result (i.e. intent(out)) variables are the last to ! NOTE: Against the common convention, the result (i.e. intent(out)) variables are the last to
! have the optional arguments at the end. ! have the optional arguments at the end.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------