unified style

This commit is contained in:
Martin Diehl 2018-12-30 18:11:03 +01:00
parent 53d2d4e23d
commit c5dd8d1265
2 changed files with 103 additions and 106 deletions

View File

@ -1,6 +1,7 @@
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH !> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH !> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @brief material subroutine for isotropic plasticity !> @brief material subroutine for isotropic plasticity
!> @details Isotropic Plasticity which resembles the phenopowerlaw plasticity without !> @details Isotropic Plasticity which resembles the phenopowerlaw plasticity without
!! resolving the stress on the slip systems. Will give the response of phenopowerlaw for an !! resolving the stress on the slip systems. Will give the response of phenopowerlaw for an
@ -81,6 +82,8 @@ subroutine plastic_isotropic_init()
compiler_version, & compiler_version, &
compiler_options compiler_options
#endif #endif
use prec, only: &
pStringLen
use debug, only: & use debug, only: &
#ifdef DEBUG #ifdef DEBUG
debug_e, & debug_e, &
@ -91,9 +94,6 @@ subroutine plastic_isotropic_init()
debug_level, & debug_level, &
debug_constitutive,& debug_constitutive,&
debug_levelBasic debug_levelBasic
use math, only: &
math_Mandel3333to66, &
math_Voigt66to3333
use IO, only: & use IO, only: &
IO_error, & IO_error, &
IO_timeStamp IO_timeStamp
@ -115,42 +115,46 @@ subroutine plastic_isotropic_init()
use lattice use lattice
implicit none implicit none
integer(pInt) :: & integer(pInt) :: &
p, & Ninstance, &
instance, & p, i, &
maxNinstance, & NipcMyPhase, &
sizeDotState, & sizeState, sizeDotState
sizeState
character(len=65536) :: & character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
extmsg = ''
integer(pInt) :: NipcMyPhase,i
integer(kind(undefined_ID)) :: & integer(kind(undefined_ID)) :: &
outputID !< ID of each post result output outputID
character(len=65536), dimension(:), allocatable :: outputs character(len=pStringLen) :: &
extmsg = ''
character(len=65536), dimension(:), allocatable :: &
outputs
write(6,'(/,a)') ' <<<+- constitutive_'//PLASTICITY_ISOTROPIC_label//' init -+>>>' write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_ISOTROPIC_label//' init -+>>>'
write(6,'(/,a)') ' Maiti and Eisenlohr, Scripta Materialia, 145:37-40, 2018'
write(6,'(/,a)') ' https://doi.org/10.1016/j.scriptamat.2017.09.047'
write(6,'(a15,a)') ' Current time: ',IO_timeStamp() write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
#include "compilation_info.f90" #include "compilation_info.f90"
maxNinstance = int(count(phase_plasticity == PLASTICITY_ISOTROPIC_ID),pInt) Ninstance = int(count(phase_plasticity == PLASTICITY_ISOTROPIC_ID),pInt)
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) & if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
allocate(plastic_isotropic_sizePostResult(maxval(phase_Noutput), Ninstance),source=0_pInt)
allocate(plastic_isotropic_sizePostResult(maxval(phase_Noutput), maxNinstance),source=0_pInt) allocate(plastic_isotropic_output(maxval(phase_Noutput), Ninstance))
allocate(plastic_isotropic_output(maxval(phase_Noutput), maxNinstance))
plastic_isotropic_output = '' plastic_isotropic_output = ''
allocate(param(maxNinstance)) ! one container of parameters per instance allocate(param(Ninstance))
allocate(state(maxNinstance)) ! internal state aliases allocate(state(Ninstance))
allocate(dotState(maxNinstance)) allocate(dotState(Ninstance))
do p = 1_pInt, size(phase_plasticityInstance) do p = 1_pInt, size(phase_plasticityInstance)
if (phase_plasticity(p) /= PLASTICITY_ISOTROPIC_ID) cycle if (phase_plasticity(p) /= PLASTICITY_ISOTROPIC_ID) cycle
instance = phase_plasticityInstance(p) associate(prm => param(phase_plasticityInstance(p)), &
associate(prm => param(instance)) dot => dotState(phase_plasticityInstance(p)), &
stt => state(phase_plasticityInstance(p)), &
config => config_phase(p))
#ifdef DEBUG #ifdef DEBUG
if (p==material_phase(debug_g,debug_i,debug_e)) then if (p==material_phase(debug_g,debug_i,debug_e)) then
@ -158,30 +162,44 @@ subroutine plastic_isotropic_init()
endif endif
#endif #endif
prm%tau0 = config_phase(p)%getFloat('tau0') prm%tau0 = config%getFloat('tau0')
prm%tausat = config_phase(p)%getFloat('tausat') prm%tausat = config%getFloat('tausat')
prm%gdot0 = config_phase(p)%getFloat('gdot0') prm%gdot0 = config%getFloat('gdot0')
prm%n = config_phase(p)%getFloat('n') prm%n = config%getFloat('n')
prm%h0 = config_phase(p)%getFloat('h0') prm%h0 = config%getFloat('h0')
prm%fTaylor = config_phase(p)%getFloat('m') prm%fTaylor = config%getFloat('m')
prm%h0_slopeLnRate = config_phase(p)%getFloat('h0_slopelnrate', defaultVal=0.0_pReal) prm%h0_slopeLnRate = config%getFloat('h0_slopelnrate', defaultVal=0.0_pReal)
prm%tausat_SinhFitA = config_phase(p)%getFloat('tausat_sinhfita',defaultVal=0.0_pReal) prm%tausat_SinhFitA = config%getFloat('tausat_sinhfita',defaultVal=0.0_pReal)
prm%tausat_SinhFitB = config_phase(p)%getFloat('tausat_sinhfitb',defaultVal=0.0_pReal) prm%tausat_SinhFitB = config%getFloat('tausat_sinhfitb',defaultVal=0.0_pReal)
prm%tausat_SinhFitC = config_phase(p)%getFloat('tausat_sinhfitc',defaultVal=0.0_pReal) prm%tausat_SinhFitC = config%getFloat('tausat_sinhfitc',defaultVal=0.0_pReal)
prm%tausat_SinhFitD = config_phase(p)%getFloat('tausat_sinhfitd',defaultVal=0.0_pReal) prm%tausat_SinhFitD = config%getFloat('tausat_sinhfitd',defaultVal=0.0_pReal)
prm%a = config_phase(p)%getFloat('a') prm%a = config%getFloat('a')
prm%aTolFlowStress = config_phase(p)%getFloat('atol_flowstress',defaultVal=1.0_pReal) prm%aTolFlowStress = config%getFloat('atol_flowstress',defaultVal=1.0_pReal)
prm%aTolShear = config_phase(p)%getFloat('atol_shear',defaultVal=1.0e-6_pReal) prm%aTolShear = config%getFloat('atol_shear', defaultVal=1.0e-6_pReal)
prm%dilatation = config_phase(p)%keyExists('/dilatation/') prm%dilatation = config%keyExists('/dilatation/')
#if defined(__GFORTRAN__) !--------------------------------------------------------------------------------------------------
outputs = ['GfortranBug86277'] ! sanity checks
outputs = config_phase(p)%getStrings('(output)',defaultVal=outputs) extmsg = ''
if (outputs(1) == 'GfortranBug86277') outputs = [character(len=65536)::] if (prm%aTolShear <= 0.0_pReal) extmsg = trim(extmsg)//'aTolShear '
#else if (prm%tau0 < 0.0_pReal) extmsg = trim(extmsg)//'tau0 '
outputs = config_phase(p)%getStrings('(output)',defaultVal=[character(len=65536)::]) if (prm%gdot0 <= 0.0_pReal) extmsg = trim(extmsg)//'gdot0 '
#endif if (prm%n <= 0.0_pReal) extmsg = trim(extmsg)//'n '
if (prm%tausat <= prm%tau0) extmsg = trim(extmsg)//'tausat '
if (prm%a <= 0.0_pReal) extmsg = trim(extmsg)//'a '
if (prm%fTaylor <= 0.0_pReal) extmsg = trim(extmsg)//'m '
if (prm%aTolFlowstress <= 0.0_pReal) extmsg = trim(extmsg)//'atol_flowstress '
if (prm%aTolShear <= 0.0_pReal) extmsg = trim(extmsg)//'atol_shear '
!--------------------------------------------------------------------------------------------------
! exit if any parameter is out of range
if (extmsg /= '') &
call IO_error(211_pInt,ext_msg=trim(extmsg)//'('//PLASTICITY_ISOTROPIC_label//')')
!--------------------------------------------------------------------------------------------------
! output pararameters
outputs = config%getStrings('(output)',defaultVal=emptyStringArray)
allocate(prm%outputID(0)) allocate(prm%outputID(0))
do i=1_pInt, size(outputs) do i=1_pInt, size(outputs)
outputID = undefined_ID outputID = undefined_ID
@ -198,48 +216,34 @@ subroutine plastic_isotropic_init()
prm%outputID = [prm%outputID , outputID] prm%outputID = [prm%outputID , outputID]
endif endif
enddo end do
!--------------------------------------------------------------------------------------------------
! sanity checks
extmsg = ''
if (prm%aTolShear <= 0.0_pReal) extmsg = trim(extmsg)//"'aTolShear' "
if (prm%tau0 < 0.0_pReal) extmsg = trim(extmsg)//"'tau0' "
if (prm%gdot0 <= 0.0_pReal) extmsg = trim(extmsg)//"'gdot0' "
if (prm%n <= 0.0_pReal) extmsg = trim(extmsg)//"'n' "
if (prm%tausat <= prm%tau0) extmsg = trim(extmsg)//"'tausat' "
if (prm%a <= 0.0_pReal) extmsg = trim(extmsg)//"'a' "
if (prm%fTaylor <= 0.0_pReal) extmsg = trim(extmsg)//"'m' "
if (prm%aTolFlowstress <= 0.0_pReal) extmsg = trim(extmsg)//"'atol_flowstress' "
if (extmsg /= '') call IO_error(211_pInt,ip=instance,&
ext_msg=trim(extmsg)//'('//PLASTICITY_ISOTROPIC_label//')')
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! allocate state arrays ! allocate state arrays
NipcMyPhase = count(material_phase == p) ! number of own material points (including point components ipc) NipcMyPhase = count(material_phase == p)
sizeState = size(["flowstress ","accumulated_shear"])
sizeDotState = sizeState
sizeDotState = size(["flowstress ","accumulated_shear"])
sizeState = sizeDotState
call material_allocatePlasticState(p,NipcMyPhase,sizeState,sizeDotState,0_pInt, & call material_allocatePlasticState(p,NipcMyPhase,sizeState,sizeDotState,0_pInt, &
1_pInt,0_pInt,0_pInt) 1_pInt,0_pInt,0_pInt)
plasticState(p)%sizePostResults = sum(plastic_isotropic_sizePostResult(:,phase_plasticityInstance(p))) plasticState(p)%sizePostResults = sum(plastic_isotropic_sizePostResult(:,phase_plasticityInstance(p)))
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! locally defined state aliases and initialization of state0 and aTolState ! locally defined state aliases and initialization of state0 and aTolState
stt%flowstress => plasticState(p)%state (1,1:NipcMyPhase)
state(instance)%flowstress => plasticState(p)%state (1,1:NipcMyPhase) stt%flowstress = prm%tau0
dotState(instance)%flowstress => plasticState(p)%dotState (1,1:NipcMyPhase) dot%flowstress => plasticState(p)%dotState (1,1:NipcMyPhase)
plasticState(p)%state0(1,1:NipcMyPhase) = prm%tau0
plasticState(p)%aTolState(1) = prm%aTolFlowstress plasticState(p)%aTolState(1) = prm%aTolFlowstress
state(instance)%accumulatedShear => plasticState(p)%state (2,1:NipcMyPhase) stt%accumulatedShear => plasticState(p)%state (2,1:NipcMyPhase)
dotState(instance)%accumulatedShear => plasticState(p)%dotState (2,1:NipcMyPhase) dot%accumulatedShear => plasticState(p)%dotState (2,1:NipcMyPhase)
plasticState(p)%state0 (2,1:NipcMyPhase) = 0.0_pReal
plasticState(p)%aTolState(2) = prm%aTolShear plasticState(p)%aTolState(2) = prm%aTolShear
! global alias ! global alias
plasticState(p)%slipRate => plasticState(p)%dotState(2:2,1:NipcMyPhase) plasticState(p)%slipRate => plasticState(p)%dotState(2:2,1:NipcMyPhase)
plasticState(p)%accumulatedSlip => plasticState(p)%state (2:2,1:NipcMyPhase) plasticState(p)%accumulatedSlip => plasticState(p)%state (2:2,1:NipcMyPhase)
plasticState(p)%state0 = plasticState(p)%state ! ToDo: this could be done centrally
end associate end associate
enddo enddo
@ -290,9 +294,7 @@ subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of)
norm_Mp_dev = sqrt(squarenorm_Mp_dev) norm_Mp_dev = sqrt(squarenorm_Mp_dev)
if (norm_Mp_dev > 0.0_pReal) then if (norm_Mp_dev > 0.0_pReal) then
gamma_dot = prm%gdot0 & gamma_dot = prm%gdot0 * (sqrt(1.5_pReal) * norm_Mp_dev/(prm%fTaylor*stt%flowstress(of))) **prm%n
* ( sqrt(1.5_pReal) * norm_Mp_dev / prm%fTaylor / stt%flowstress(of) ) &
**prm%n
Lp = Mp_dev/norm_Mp_dev * gamma_dot/prm%fTaylor Lp = Mp_dev/norm_Mp_dev * gamma_dot/prm%fTaylor
#ifdef DEBUG #ifdef DEBUG
@ -323,7 +325,7 @@ end subroutine plastic_isotropic_LpAndItsTangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates plastic velocity gradient and its tangent !> @brief calculates plastic velocity gradient and its tangent
! ToDo: Rename to Tstar to Mi? ! ToDo: Rename Tstar to Mi?
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dTstar,Tstar,instance,of) subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dTstar,Tstar,instance,of)
use math, only: & use math, only: &
@ -459,8 +461,6 @@ function plastic_isotropic_postResults(Mp,instance,of) result(postResults)
associate(prm => param(instance), stt => state(instance)) associate(prm => param(instance), stt => state(instance))
!--------------------------------------------------------------------------------------------------
! norm of (deviatoric) Mandel stress
if (prm%dilatation) then if (prm%dilatation) then
norm_Mp = sqrt(math_mul33xx33(Mp,Mp)) norm_Mp = sqrt(math_mul33xx33(Mp,Mp))
else else

View File

@ -82,8 +82,7 @@ module plastic_phenopowerlaw
xi_slip, & xi_slip, &
xi_twin, & xi_twin, &
gamma_slip, & gamma_slip, &
gamma_twin, & gamma_twin
whole
end type end type
type(tPhenopowerlawState), allocatable, dimension(:), private :: & type(tPhenopowerlawState), allocatable, dimension(:), private :: &
@ -95,6 +94,9 @@ module plastic_phenopowerlaw
plastic_phenopowerlaw_LpAndItsTangent, & plastic_phenopowerlaw_LpAndItsTangent, &
plastic_phenopowerlaw_dotState, & plastic_phenopowerlaw_dotState, &
plastic_phenopowerlaw_postResults plastic_phenopowerlaw_postResults
private :: &
kinetics_slip, &
kinetics_twin
contains contains
@ -110,8 +112,7 @@ subroutine plastic_phenopowerlaw_init
compiler_options compiler_options
#endif #endif
use prec, only: & use prec, only: &
pStringLen, & pStringLen
dEq0
use debug, only: & use debug, only: &
debug_level, & debug_level, &
debug_constitutive,& debug_constitutive,&
@ -119,7 +120,6 @@ subroutine plastic_phenopowerlaw_init
use math, only: & use math, only: &
math_expand math_expand
use IO, only: & use IO, only: &
IO_warning, &
IO_error, & IO_error, &
IO_timeStamp IO_timeStamp
use material, only: & use material, only: &
@ -149,7 +149,7 @@ subroutine plastic_phenopowerlaw_init
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::] character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
integer(kind(undefined_ID)) :: & integer(kind(undefined_ID)) :: &
outputID !< ID of each post result output outputID
character(len=pStringLen) :: & character(len=pStringLen) :: &
structure = '',& structure = '',&
@ -157,7 +157,7 @@ subroutine plastic_phenopowerlaw_init
character(len=65536), dimension(:), allocatable :: & character(len=65536), dimension(:), allocatable :: &
outputs outputs
write(6,'(/,a)') ' <<<+- constitutive_'//PLASTICITY_PHENOPOWERLAW_label//' init -+>>>' write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_PHENOPOWERLAW_label//' init -+>>>'
write(6,'(a15,a)') ' Current time: ',IO_timeStamp() write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
#include "compilation_info.f90" #include "compilation_info.f90"
@ -235,8 +235,8 @@ subroutine plastic_phenopowerlaw_init
! sanity checks ! sanity checks
if (prm%gdot0_slip <= 0.0_pReal) extmsg = trim(extmsg)//'gdot0_slip ' if (prm%gdot0_slip <= 0.0_pReal) extmsg = trim(extmsg)//'gdot0_slip '
if (dEq0(prm%a_slip)) extmsg = trim(extmsg)//'a_slip ' ! ToDo: negative values ok? if (prm%a_slip <= 0.0_pReal) extmsg = trim(extmsg)//'a_slip '
if (dEq0(prm%n_slip)) extmsg = trim(extmsg)//'n_slip ' ! ToDo: negative values ok? if (prm%n_slip <= 0.0_pReal) extmsg = trim(extmsg)//'n_slip '
if (any(prm%xi_slip_0 <= 0.0_pReal)) extmsg = trim(extmsg)//'xi_slip_0 ' if (any(prm%xi_slip_0 <= 0.0_pReal)) extmsg = trim(extmsg)//'xi_slip_0 '
if (any(prm%xi_slip_sat < prm%xi_slip_0)) extmsg = trim(extmsg)//'xi_slip_sat ' if (any(prm%xi_slip_sat < prm%xi_slip_0)) extmsg = trim(extmsg)//'xi_slip_sat '
else slipActive else slipActive
@ -269,7 +269,7 @@ subroutine plastic_phenopowerlaw_init
! sanity checks ! sanity checks
if (prm%gdot0_twin <= 0.0_pReal) extmsg = trim(extmsg)//'gdot0_twin ' if (prm%gdot0_twin <= 0.0_pReal) extmsg = trim(extmsg)//'gdot0_twin '
if (dEq0(prm%n_twin)) extmsg = trim(extmsg)//'n_twin ' ! ToDo: negative values ok? if (prm%n_twin <= 0.0_pReal) extmsg = trim(extmsg)//'n_twin '
else twinActive else twinActive
allocate(prm%interaction_TwinTwin(0,0)) allocate(prm%interaction_TwinTwin(0,0))
allocate(prm%xi_twin_0(0)) allocate(prm%xi_twin_0(0))
@ -341,7 +341,7 @@ subroutine plastic_phenopowerlaw_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! allocate state arrays ! allocate state arrays
NipcMyPhase = count(material_phase == p) ! number of IPCs containing my phase NipcMyPhase = count(material_phase == p)
sizeState = size(['tau_slip ','gamma_slip']) * prm%TotalNslip & sizeState = size(['tau_slip ','gamma_slip']) * prm%TotalNslip &
+ size(['tau_twin ','gamma_twin']) * prm%TotalNtwin + size(['tau_twin ','gamma_twin']) * prm%TotalNtwin
sizeDotState = sizeState sizeDotState = sizeState
@ -350,7 +350,6 @@ subroutine plastic_phenopowerlaw_init
prm%totalNslip,prm%totalNtwin,0_pInt) prm%totalNslip,prm%totalNtwin,0_pInt)
plasticState(p)%sizePostResults = sum(plastic_phenopowerlaw_sizePostResult(:,phase_plasticityInstance(p))) plasticState(p)%sizePostResults = sum(plastic_phenopowerlaw_sizePostResult(:,phase_plasticityInstance(p)))
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! locally defined state aliases and initialization of state0 and aTolState ! locally defined state aliases and initialization of state0 and aTolState
startIndex = 1_pInt startIndex = 1_pInt
@ -383,7 +382,6 @@ subroutine plastic_phenopowerlaw_init
plasticState(p)%aTolState(startIndex:endIndex) = prm%aTolShear plasticState(p)%aTolState(startIndex:endIndex) = prm%aTolShear
plasticState(p)%state0 = plasticState(p)%state ! ToDo: this could be done centrally plasticState(p)%state0 = plasticState(p)%state ! ToDo: this could be done centrally
dot%whole => plasticState(p)%dotState
end associate end associate
enddo enddo
@ -469,7 +467,6 @@ subroutine plastic_phenopowerlaw_dotState(Mp,instance,of)
associate(prm => param(instance), stt => state(instance), dot => dotState(instance)) associate(prm => param(instance), stt => state(instance), dot => dotState(instance))
dot%whole(:,of) = 0.0_pReal
sumGamma = sum(stt%gamma_slip(:,of)) sumGamma = sum(stt%gamma_slip(:,of))
sumF = sum(stt%gamma_twin(:,of)/prm%gamma_twin_char) sumF = sum(stt%gamma_twin(:,of)/prm%gamma_twin_char)