using config module
This commit is contained in:
parent
d7da70cefb
commit
13f280367e
|
@ -431,7 +431,7 @@ function getFloats(this,key,defaultVal)
|
||||||
real(pReal), dimension(:), allocatable :: getFloats
|
real(pReal), dimension(:), allocatable :: getFloats
|
||||||
class(tPartitionedStringList), intent(in) :: this
|
class(tPartitionedStringList), intent(in) :: this
|
||||||
character(len=*), intent(in) :: key
|
character(len=*), intent(in) :: key
|
||||||
integer(pInt), dimension(:), intent(in), optional :: defaultVal
|
real(pReal), dimension(:), intent(in), optional :: defaultVal
|
||||||
type(tPartitionedStringList), pointer :: item
|
type(tPartitionedStringList), pointer :: item
|
||||||
integer(pInt) :: i
|
integer(pInt) :: i
|
||||||
logical :: found, &
|
logical :: found, &
|
||||||
|
|
|
@ -130,7 +130,8 @@ subroutine plastic_phenopowerlaw_init
|
||||||
material_phase, &
|
material_phase, &
|
||||||
plasticState
|
plasticState
|
||||||
use config, only: &
|
use config, only: &
|
||||||
MATERIAL_partPhase
|
MATERIAL_partPhase, &
|
||||||
|
phaseConfig
|
||||||
use lattice
|
use lattice
|
||||||
use numerics,only: &
|
use numerics,only: &
|
||||||
numerics_integrator
|
numerics_integrator
|
||||||
|
@ -148,7 +149,7 @@ subroutine plastic_phenopowerlaw_init
|
||||||
integer(pInt), dimension(0), parameter :: emptyInt = [integer(pInt)::]
|
integer(pInt), dimension(0), parameter :: emptyInt = [integer(pInt)::]
|
||||||
real(pReal), dimension(0), parameter :: emptyReal = [real(pReal)::]
|
real(pReal), dimension(0), parameter :: emptyReal = [real(pReal)::]
|
||||||
|
|
||||||
type(tParameters), pointer :: p
|
type(tParameters), pointer :: prm
|
||||||
|
|
||||||
integer(kind(undefined_ID)) :: &
|
integer(kind(undefined_ID)) :: &
|
||||||
outputID !< ID of each post result output
|
outputID !< ID of each post result output
|
||||||
|
@ -176,86 +177,86 @@ subroutine plastic_phenopowerlaw_init
|
||||||
do phase = 1_pInt, size(phase_plasticityInstance)
|
do phase = 1_pInt, size(phase_plasticityInstance)
|
||||||
if (phase_plasticity(phase) == PLASTICITY_PHENOPOWERLAW_ID) then
|
if (phase_plasticity(phase) == PLASTICITY_PHENOPOWERLAW_ID) then
|
||||||
instance = phase_plasticityInstance(phase)
|
instance = phase_plasticityInstance(phase)
|
||||||
p => param(instance)
|
prm => param(instance)
|
||||||
|
|
||||||
p%Nslip = phaseConfig(phase)%getIntArray('nslip',defaultVal=emptyInt)
|
prm%Nslip = phaseConfig(phase)%getInts('nslip',defaultVal=emptyInt)
|
||||||
!if (size > Nchunks_SlipFamilies + 1_pInt) call IO_error(150_pInt,ext_msg=extmsg)
|
!if (size > Nchunks_SlipFamilies + 1_pInt) call IO_error(150_pInt,ext_msg=extmsg)
|
||||||
if (sum(p%Nslip) > 0_pInt) then
|
if (sum(prm%Nslip) > 0_pInt) then
|
||||||
p%tau0_slip = phaseConfig(phase)%getFloatArray('tau0_slip')
|
prm%tau0_slip = phaseConfig(phase)%getFloats('tau0_slip')
|
||||||
p%tausat_slip = phaseConfig(phase)%getFloatArray('tausat_slip')
|
prm%tausat_slip = phaseConfig(phase)%getFloats('tausat_slip')
|
||||||
p%interaction_SlipSlip = phaseConfig(phase)%getFloatArray('interaction_slipslip')
|
prm%interaction_SlipSlip = phaseConfig(phase)%getFloats('interaction_slipslip')
|
||||||
p%H_int = phaseConfig(phase)%getFloatArray('h_int',&
|
prm%H_int = phaseConfig(phase)%getFloats('h_int',&
|
||||||
defaultVal=[(0.0_pReal,i=1_pInt,size(p%Nslip))])
|
defaultVal=[(0.0_pReal,i=1_pInt,size(prm%Nslip))])
|
||||||
p%nonSchmidCoeff = phaseConfig(phase)%getFloatArray('nonschmid_coefficients',&
|
prm%nonSchmidCoeff = phaseConfig(phase)%getFloats('nonschmid_coefficients',&
|
||||||
defaultVal = [real(pReal)::1] )
|
defaultVal = [real(pReal)::1] )
|
||||||
|
|
||||||
p%gdot0_slip = phaseConfig(phase)%getFloat('gdot0_slip')
|
prm%gdot0_slip = phaseConfig(phase)%getFloat('gdot0_slip')
|
||||||
p%n_slip = phaseConfig(phase)%getFloat('n_slip')
|
prm%n_slip = phaseConfig(phase)%getFloat('n_slip')
|
||||||
p%a_slip = phaseConfig(phase)%getFloat('a_slip')
|
prm%a_slip = phaseConfig(phase)%getFloat('a_slip')
|
||||||
p%h0_SlipSlip = phaseConfig(phase)%getFloat('h0_slipslip')
|
prm%h0_SlipSlip = phaseConfig(phase)%getFloat('h0_slipslip')
|
||||||
endif
|
endif
|
||||||
|
|
||||||
p%Ntwin = phaseConfig(phase)%getIntArray('ntwin', defaultVal=emptyInt)
|
prm%Ntwin = phaseConfig(phase)%getInts('ntwin', defaultVal=emptyInt)
|
||||||
!if (size > Nchunks_SlipFamilies + 1_pInt) call IO_error(150_pInt,ext_msg=extmsg)
|
!if (size > Nchunks_SlipFamilies + 1_pInt) call IO_error(150_pInt,ext_msg=extmsg)
|
||||||
if (sum(p%Ntwin) > 0_pInt) then
|
if (sum(prm%Ntwin) > 0_pInt) then
|
||||||
p%tau0_twin = phaseConfig(phase)%getFloatArray('tau0_twin')
|
prm%tau0_twin = phaseConfig(phase)%getFloats('tau0_twin')
|
||||||
p%interaction_TwinTwin = phaseConfig(phase)%getFloatArray('interaction_twintwin')
|
prm%interaction_TwinTwin = phaseConfig(phase)%getFloats('interaction_twintwin')
|
||||||
|
|
||||||
p%gdot0_twin = phaseConfig(phase)%getFloat('gdot0_twin')
|
prm%gdot0_twin = phaseConfig(phase)%getFloat('gdot0_twin')
|
||||||
p%n_twin = phaseConfig(phase)%getFloat('n_twin')
|
prm%n_twin = phaseConfig(phase)%getFloat('n_twin')
|
||||||
p%spr = phaseConfig(phase)%getFloat('s_pr')
|
prm%spr = phaseConfig(phase)%getFloat('s_pr')
|
||||||
p%twinB = phaseConfig(phase)%getFloat('twin_b')
|
prm%twinB = phaseConfig(phase)%getFloat('twin_b')
|
||||||
p%twinC = phaseConfig(phase)%getFloat('twin_c')
|
prm%twinC = phaseConfig(phase)%getFloat('twin_c')
|
||||||
p%twinD = phaseConfig(phase)%getFloat('twin_d')
|
prm%twinD = phaseConfig(phase)%getFloat('twin_d')
|
||||||
p%twinE = phaseConfig(phase)%getFloat('twin_e')
|
prm%twinE = phaseConfig(phase)%getFloat('twin_e')
|
||||||
p%h0_TwinTwin = phaseConfig(phase)%getFloat('h0_twintwin')
|
prm%h0_TwinTwin = phaseConfig(phase)%getFloat('h0_twintwin')
|
||||||
endif
|
endif
|
||||||
|
|
||||||
if (sum(p%Nslip) > 0_pInt .and. sum(p%Ntwin) > 0_pInt) then
|
if (sum(prm%Nslip) > 0_pInt .and. sum(prm%Ntwin) > 0_pInt) then
|
||||||
p%interaction_SlipTwin = phaseConfig(phase)%getFloatArray('interaction_sliptwin')
|
prm%interaction_SlipTwin = phaseConfig(phase)%getFloats('interaction_sliptwin')
|
||||||
p%interaction_TwinSlip = phaseConfig(phase)%getFloatArray('interaction_twinslip')
|
prm%interaction_TwinSlip = phaseConfig(phase)%getFloats('interaction_twinslip')
|
||||||
p%h0_TwinSlip = phaseConfig(phase)%getFloat('h0_twinslip')
|
prm%h0_TwinSlip = phaseConfig(phase)%getFloat('h0_twinslip')
|
||||||
endif
|
endif
|
||||||
|
|
||||||
allocate(p%matrix_SlipSlip(sum(p%Nslip),sum(p%Nslip)),source =0.0_pReal)
|
allocate(prm%matrix_SlipSlip(sum(prm%Nslip),sum(prm%Nslip)),source =0.0_pReal)
|
||||||
allocate(p%matrix_SlipTwin(sum(p%Nslip),sum(p%Ntwin)),source =0.0_pReal)
|
allocate(prm%matrix_SlipTwin(sum(prm%Nslip),sum(prm%Ntwin)),source =0.0_pReal)
|
||||||
allocate(p%matrix_TwinSlip(sum(p%Ntwin),sum(p%Nslip)),source =0.0_pReal)
|
allocate(prm%matrix_TwinSlip(sum(prm%Ntwin),sum(prm%Nslip)),source =0.0_pReal)
|
||||||
allocate(p%matrix_TwinTwin(sum(p%Ntwin),sum(p%Ntwin)),source =0.0_pReal)
|
allocate(prm%matrix_TwinTwin(sum(prm%Ntwin),sum(prm%Ntwin)),source =0.0_pReal)
|
||||||
|
|
||||||
p%aTolResistance = phaseConfig(phase)%getFloat('atol_resistance',defaultVal=1.0_pReal)
|
prm%aTolResistance = phaseConfig(phase)%getFloat('atol_resistance',defaultVal=1.0_pReal)
|
||||||
p%aTolShear = phaseConfig(phase)%getFloat('atol_shear',defaultVal=1.0e-6_pReal)
|
prm%aTolShear = phaseConfig(phase)%getFloat('atol_shear',defaultVal=1.0e-6_pReal)
|
||||||
p%aTolTwinfrac = phaseConfig(phase)%getFloat('atol_twinfrac',defaultVal=1.0e-6_pReal)
|
prm%aTolTwinfrac = phaseConfig(phase)%getFloat('atol_twinfrac',defaultVal=1.0e-6_pReal)
|
||||||
|
|
||||||
outputs = phaseConfig(phase)%getStrings('(output)')
|
outputs = phaseConfig(phase)%getStrings('(output)')
|
||||||
allocate(p%outputID(0))
|
allocate(prm%outputID(0))
|
||||||
do i=1_pInt, size(outputs)
|
do i=1_pInt, size(outputs)
|
||||||
outputID = undefined_ID
|
outputID = undefined_ID
|
||||||
select case(outputs(i))
|
select case(outputs(i))
|
||||||
case ('resistance_slip')
|
case ('resistance_slip')
|
||||||
outputID = resistance_slip_ID
|
outputID = resistance_slip_ID
|
||||||
outputSize = sum(p%Nslip)
|
outputSize = sum(prm%Nslip)
|
||||||
case ('acumulatedshear_slip','accumulated_shear_slip')
|
case ('acumulatedshear_slip','accumulated_shear_slip')
|
||||||
outputID = accumulatedshear_slip_ID
|
outputID = accumulatedshear_slip_ID
|
||||||
outputSize = sum(p%Nslip)
|
outputSize = sum(prm%Nslip)
|
||||||
case ('shearrate_slip')
|
case ('shearrate_slip')
|
||||||
outputID = shearrate_slip_ID
|
outputID = shearrate_slip_ID
|
||||||
outputSize = sum(p%Nslip)
|
outputSize = sum(prm%Nslip)
|
||||||
case ('resolvedstress_slip')
|
case ('resolvedstress_slip')
|
||||||
outputID = resolvedstress_slip_ID
|
outputID = resolvedstress_slip_ID
|
||||||
outputSize = sum(p%Nslip)
|
outputSize = sum(prm%Nslip)
|
||||||
|
|
||||||
case ('resistance_twin')
|
case ('resistance_twin')
|
||||||
outputID = resistance_twin_ID
|
outputID = resistance_twin_ID
|
||||||
outputSize = sum(p%Ntwin)
|
outputSize = sum(prm%Ntwin)
|
||||||
case ('accumulatedshear_twin','accumulated_shear_twin')
|
case ('accumulatedshear_twin','accumulated_shear_twin')
|
||||||
outputID = accumulatedshear_twin_ID
|
outputID = accumulatedshear_twin_ID
|
||||||
outputSize = sum(p%Ntwin)
|
outputSize = sum(prm%Ntwin)
|
||||||
case ('shearrate_twin')
|
case ('shearrate_twin')
|
||||||
outputID = shearrate_twin_ID
|
outputID = shearrate_twin_ID
|
||||||
outputSize = sum(p%Ntwin)
|
outputSize = sum(prm%Ntwin)
|
||||||
case ('resolvedstress_twin')
|
case ('resolvedstress_twin')
|
||||||
outputID = resolvedstress_twin_ID
|
outputID = resolvedstress_twin_ID
|
||||||
outputSize = sum(p%Ntwin)
|
outputSize = sum(prm%Ntwin)
|
||||||
|
|
||||||
case ('totalvolfrac_twin')
|
case ('totalvolfrac_twin')
|
||||||
outputID = totalvolfrac_twin_ID
|
outputID = totalvolfrac_twin_ID
|
||||||
|
@ -268,40 +269,40 @@ subroutine plastic_phenopowerlaw_init
|
||||||
if (outputID /= undefined_ID) then
|
if (outputID /= undefined_ID) then
|
||||||
plastic_phenopowerlaw_output(i,instance) = outputs(i)
|
plastic_phenopowerlaw_output(i,instance) = outputs(i)
|
||||||
plastic_phenopowerlaw_sizePostResult(i,instance) = outputSize
|
plastic_phenopowerlaw_sizePostResult(i,instance) = outputSize
|
||||||
p%outputID = [p%outputID , outputID]
|
prm%outputID = [prm%outputID , outputID]
|
||||||
endif
|
endif
|
||||||
|
|
||||||
end do
|
end do
|
||||||
|
|
||||||
extmsg = ''
|
extmsg = ''
|
||||||
if (sum(p%Nslip) > 0_pInt) then
|
if (sum(prm%Nslip) > 0_pInt) then
|
||||||
if (size(p%tau0_slip) /= size(p%nslip)) extmsg = trim(extmsg)//" shape(tau0_slip) "
|
if (size(prm%tau0_slip) /= size(prm%nslip)) extmsg = trim(extmsg)//" shape(tau0_slip) "
|
||||||
if (size(p%tausat_slip) /= size(p%nslip)) extmsg = trim(extmsg)//" shape(tausat_slip) "
|
if (size(prm%tausat_slip) /= size(prm%nslip)) extmsg = trim(extmsg)//" shape(tausat_slip) "
|
||||||
if (size(p%H_int) /= size(p%nslip)) extmsg = trim(extmsg)//" shape(h_int) "
|
if (size(prm%H_int) /= size(prm%nslip)) extmsg = trim(extmsg)//" shape(h_int) "
|
||||||
|
|
||||||
if (any(p%tau0_slip < 0.0_pReal .and. p%Nslip > 0_pInt)) &
|
if (any(prm%tau0_slip < 0.0_pReal .and. prm%Nslip > 0_pInt)) &
|
||||||
extmsg = trim(extmsg)//" 'tau0_slip' "
|
extmsg = trim(extmsg)//" 'tau0_slip' "
|
||||||
if (any(p%tausat_slip < p%tau0_slip .and. p%Nslip > 0_pInt)) &
|
if (any(prm%tausat_slip < prm%tau0_slip .and. prm%Nslip > 0_pInt)) &
|
||||||
extmsg = trim(extmsg)//" 'tausat_slip' "
|
extmsg = trim(extmsg)//" 'tausat_slip' "
|
||||||
|
|
||||||
if (p%gdot0_slip <= 0.0_pReal) extmsg = trim(extmsg)//" 'gdot0_slip' "
|
if (prm%gdot0_slip <= 0.0_pReal) extmsg = trim(extmsg)//" 'gdot0_slip' "
|
||||||
if (dEq0(p%a_slip)) extmsg = trim(extmsg)//" a_slip " ! ToDo: negative values ok?
|
if (dEq0(prm%a_slip)) extmsg = trim(extmsg)//" a_slip " ! ToDo: negative values ok?
|
||||||
if (dEq0(p%n_slip)) extmsg = trim(extmsg)//" n_slip " ! ToDo: negative values ok?
|
if (dEq0(prm%n_slip)) extmsg = trim(extmsg)//" n_slip " ! ToDo: negative values ok?
|
||||||
endif
|
endif
|
||||||
|
|
||||||
if (sum(p%Ntwin) > 0_pInt) then
|
if (sum(prm%Ntwin) > 0_pInt) then
|
||||||
if (size(p%tau0_twin) /= size(p%ntwin)) extmsg = trim(extmsg)//" shape(tau0_twin) "
|
if (size(prm%tau0_twin) /= size(prm%ntwin)) extmsg = trim(extmsg)//" shape(tau0_twin) "
|
||||||
|
|
||||||
if (any(p%tau0_twin < 0.0_pReal .and. p%Ntwin > 0_pInt)) &
|
if (any(prm%tau0_twin < 0.0_pReal .and. prm%Ntwin > 0_pInt)) &
|
||||||
extmsg = trim(extmsg)//" 'tau0_twin' "
|
extmsg = trim(extmsg)//" 'tau0_twin' "
|
||||||
|
|
||||||
if (p%gdot0_twin <= 0.0_pReal) extmsg = trim(extmsg)//" 'gdot0_twin' "
|
if (prm%gdot0_twin <= 0.0_pReal) extmsg = trim(extmsg)//" 'gdot0_twin' "
|
||||||
if (dEq0(p%n_twin)) extmsg = trim(extmsg)//" n_twin " ! ToDo: negative values ok?
|
if (dEq0(prm%n_twin)) extmsg = trim(extmsg)//" n_twin " ! ToDo: negative values ok?
|
||||||
endif
|
endif
|
||||||
|
|
||||||
if (p%aTolResistance <= 0.0_pReal) extmsg = trim(extmsg)//" 'aTolresistance' "
|
if (prm%aTolResistance <= 0.0_pReal) extmsg = trim(extmsg)//" 'aTolresistance' "
|
||||||
if (p%aTolShear <= 0.0_pReal) extmsg = trim(extmsg)//" 'aTolShear' "
|
if (prm%aTolShear <= 0.0_pReal) extmsg = trim(extmsg)//" 'aTolShear' "
|
||||||
if (p%aTolTwinfrac <= 0.0_pReal) extmsg = trim(extmsg)//" 'atoltwinfrac' "
|
if (prm%aTolTwinfrac <= 0.0_pReal) extmsg = trim(extmsg)//" 'atoltwinfrac' "
|
||||||
|
|
||||||
if (extmsg /= '') call IO_error(211_pInt,ip=instance,&
|
if (extmsg /= '') call IO_error(211_pInt,ip=instance,&
|
||||||
ext_msg=trim(extmsg)//'('//PLASTICITY_PHENOPOWERLAW_label//')')
|
ext_msg=trim(extmsg)//'('//PLASTICITY_PHENOPOWERLAW_label//')')
|
||||||
|
@ -309,15 +310,15 @@ subroutine plastic_phenopowerlaw_init
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! allocate state arrays
|
! allocate state arrays
|
||||||
NipcMyPhase = count(material_phase == phase) ! number of IPCs containing my phase
|
NipcMyPhase = count(material_phase == phase) ! number of IPCs containing my phase
|
||||||
sizeState = size(['tau_slip ','accshear_slip']) * sum(p%nslip) &
|
sizeState = size(['tau_slip ','accshear_slip']) * sum(prm%nslip) &
|
||||||
+ size(['tau_twin ','accshear_twin']) * sum(p%ntwin) &
|
+ size(['tau_twin ','accshear_twin']) * sum(prm%ntwin) &
|
||||||
+ size(['sum(gamma)', 'sum(f) '])
|
+ size(['sum(gamma)', 'sum(f) '])
|
||||||
|
|
||||||
sizeDotState = sizeState
|
sizeDotState = sizeState
|
||||||
plasticState(phase)%sizeState = sizeState
|
plasticState(phase)%sizeState = sizeState
|
||||||
plasticState(phase)%sizeDotState = sizeDotState
|
plasticState(phase)%sizeDotState = sizeDotState
|
||||||
plasticState(phase)%nSlip = sum(p%Nslip)
|
plasticState(phase)%nSlip = sum(prm%Nslip)
|
||||||
plasticState(phase)%nTwin = sum(p%Ntwin)
|
plasticState(phase)%nTwin = sum(prm%Ntwin)
|
||||||
allocate(plasticState(phase)%aTolState ( sizeState), source=0.0_pReal)
|
allocate(plasticState(phase)%aTolState ( sizeState), source=0.0_pReal)
|
||||||
allocate(plasticState(phase)%state0 ( sizeState,NipcMyPhase), source=0.0_pReal)
|
allocate(plasticState(phase)%state0 ( sizeState,NipcMyPhase), source=0.0_pReal)
|
||||||
allocate(plasticState(phase)%partionedState0 ( sizeState,NipcMyPhase), source=0.0_pReal)
|
allocate(plasticState(phase)%partionedState0 ( sizeState,NipcMyPhase), source=0.0_pReal)
|
||||||
|
@ -337,25 +338,25 @@ subroutine plastic_phenopowerlaw_init
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! calculate hardening matrices
|
! calculate hardening matrices
|
||||||
mySlipFamilies: do f = 1_pInt,size(p%Nslip,1) ! >>> interaction slip -- X
|
mySlipFamilies: do f = 1_pInt,size(prm%Nslip,1) ! >>> interaction slip -- X
|
||||||
index_myFamily = sum(p%Nslip(1:f-1_pInt))
|
index_myFamily = sum(prm%Nslip(1:f-1_pInt))
|
||||||
|
|
||||||
mySlipSystems: do j = 1_pInt,p%Nslip(f)
|
mySlipSystems: do j = 1_pInt,prm%Nslip(f)
|
||||||
otherSlipFamilies: do o = 1_pInt,size(p%Nslip,1)
|
otherSlipFamilies: do o = 1_pInt,size(prm%Nslip,1)
|
||||||
index_otherFamily = sum(p%Nslip(1:o-1_pInt))
|
index_otherFamily = sum(prm%Nslip(1:o-1_pInt))
|
||||||
otherSlipSystems: do k = 1_pInt,p%Nslip(o)
|
otherSlipSystems: do k = 1_pInt,prm%Nslip(o)
|
||||||
p%matrix_SlipSlip(index_myFamily+j,index_otherFamily+k) = &
|
prm%matrix_SlipSlip(index_myFamily+j,index_otherFamily+k) = &
|
||||||
p%interaction_SlipSlip(lattice_interactionSlipSlip( &
|
prm%interaction_SlipSlip(lattice_interactionSlipSlip( &
|
||||||
sum(lattice_NslipSystem(1:f-1,phase))+j, &
|
sum(lattice_NslipSystem(1:f-1,phase))+j, &
|
||||||
sum(lattice_NslipSystem(1:o-1,phase))+k, &
|
sum(lattice_NslipSystem(1:o-1,phase))+k, &
|
||||||
phase))
|
phase))
|
||||||
enddo otherSlipSystems; enddo otherSlipFamilies
|
enddo otherSlipSystems; enddo otherSlipFamilies
|
||||||
|
|
||||||
twinFamilies: do o = 1_pInt,size(p%Ntwin,1)
|
twinFamilies: do o = 1_pInt,size(prm%Ntwin,1)
|
||||||
index_otherFamily = sum(p%Ntwin(1:o-1_pInt))
|
index_otherFamily = sum(prm%Ntwin(1:o-1_pInt))
|
||||||
twinSystems: do k = 1_pInt,p%Ntwin(o)
|
twinSystems: do k = 1_pInt,prm%Ntwin(o)
|
||||||
p%matrix_SlipTwin(index_myFamily+j,index_otherFamily+k) = &
|
prm%matrix_SlipTwin(index_myFamily+j,index_otherFamily+k) = &
|
||||||
p%interaction_SlipTwin(lattice_interactionSlipTwin( &
|
prm%interaction_SlipTwin(lattice_interactionSlipTwin( &
|
||||||
sum(lattice_NslipSystem(1:f-1_pInt,phase))+j, &
|
sum(lattice_NslipSystem(1:f-1_pInt,phase))+j, &
|
||||||
sum(lattice_NtwinSystem(1:o-1_pInt,phase))+k, &
|
sum(lattice_NtwinSystem(1:o-1_pInt,phase))+k, &
|
||||||
phase))
|
phase))
|
||||||
|
@ -363,24 +364,24 @@ subroutine plastic_phenopowerlaw_init
|
||||||
enddo mySlipSystems
|
enddo mySlipSystems
|
||||||
enddo mySlipFamilies
|
enddo mySlipFamilies
|
||||||
|
|
||||||
myTwinFamilies: do f = 1_pInt,size(p%Ntwin,1) ! >>> interaction twin -- X
|
myTwinFamilies: do f = 1_pInt,size(prm%Ntwin,1) ! >>> interaction twin -- X
|
||||||
index_myFamily = sum(p%Ntwin(1:f-1_pInt))
|
index_myFamily = sum(prm%Ntwin(1:f-1_pInt))
|
||||||
myTwinSystems: do j = 1_pInt,p%Ntwin(f)
|
myTwinSystems: do j = 1_pInt,prm%Ntwin(f)
|
||||||
slipFamilies: do o = 1_pInt,size(p%Nslip,1)
|
slipFamilies: do o = 1_pInt,size(prm%Nslip,1)
|
||||||
index_otherFamily = sum(p%Nslip(1:o-1_pInt))
|
index_otherFamily = sum(prm%Nslip(1:o-1_pInt))
|
||||||
slipSystems: do k = 1_pInt,p%Nslip(o)
|
slipSystems: do k = 1_pInt,prm%Nslip(o)
|
||||||
p%matrix_TwinSlip(index_myFamily+j,index_otherFamily+k) = &
|
prm%matrix_TwinSlip(index_myFamily+j,index_otherFamily+k) = &
|
||||||
p%interaction_TwinSlip(lattice_interactionTwinSlip( &
|
prm%interaction_TwinSlip(lattice_interactionTwinSlip( &
|
||||||
sum(lattice_NtwinSystem(1:f-1_pInt,phase))+j, &
|
sum(lattice_NtwinSystem(1:f-1_pInt,phase))+j, &
|
||||||
sum(lattice_NslipSystem(1:o-1_pInt,phase))+k, &
|
sum(lattice_NslipSystem(1:o-1_pInt,phase))+k, &
|
||||||
phase))
|
phase))
|
||||||
enddo slipSystems; enddo slipFamilies
|
enddo slipSystems; enddo slipFamilies
|
||||||
|
|
||||||
otherTwinFamilies: do o = 1_pInt,size(p%Ntwin,1)
|
otherTwinFamilies: do o = 1_pInt,size(prm%Ntwin,1)
|
||||||
index_otherFamily = sum(p%Ntwin(1:o-1_pInt))
|
index_otherFamily = sum(prm%Ntwin(1:o-1_pInt))
|
||||||
otherTwinSystems: do k = 1_pInt,p%Ntwin(o)
|
otherTwinSystems: do k = 1_pInt,prm%Ntwin(o)
|
||||||
p%matrix_TwinTwin(index_myFamily+j,index_otherFamily+k) = &
|
prm%matrix_TwinTwin(index_myFamily+j,index_otherFamily+k) = &
|
||||||
p%interaction_TwinTwin(lattice_interactionTwinTwin( &
|
prm%interaction_TwinTwin(lattice_interactionTwinTwin( &
|
||||||
sum(lattice_NtwinSystem(1:f-1_pInt,phase))+j, &
|
sum(lattice_NtwinSystem(1:f-1_pInt,phase))+j, &
|
||||||
sum(lattice_NtwinSystem(1:o-1_pInt,phase))+k, &
|
sum(lattice_NtwinSystem(1:o-1_pInt,phase))+k, &
|
||||||
phase))
|
phase))
|
||||||
|
@ -395,35 +396,35 @@ subroutine plastic_phenopowerlaw_init
|
||||||
state (instance)%s_slip=>plasticState(phase)%state (startIndex:endIndex,:)
|
state (instance)%s_slip=>plasticState(phase)%state (startIndex:endIndex,:)
|
||||||
dotState(instance)%s_slip=>plasticState(phase)%dotState(startIndex:endIndex,:)
|
dotState(instance)%s_slip=>plasticState(phase)%dotState(startIndex:endIndex,:)
|
||||||
plasticState(phase)%state0(startIndex:endIndex,:) = &
|
plasticState(phase)%state0(startIndex:endIndex,:) = &
|
||||||
spread(math_expand(p%tau0_slip, p%Nslip), 2, NipcMyPhase)
|
spread(math_expand(prm%tau0_slip, prm%Nslip), 2, NipcMyPhase)
|
||||||
|
|
||||||
plasticState(phase)%aTolState(startIndex:endIndex) = p%aTolResistance
|
plasticState(phase)%aTolState(startIndex:endIndex) = prm%aTolResistance
|
||||||
|
|
||||||
startIndex = endIndex + 1_pInt
|
startIndex = endIndex + 1_pInt
|
||||||
endIndex = endIndex + plasticState(phase)%nTwin
|
endIndex = endIndex + plasticState(phase)%nTwin
|
||||||
state (instance)%s_twin=>plasticState(phase)%state (startIndex:endIndex,:)
|
state (instance)%s_twin=>plasticState(phase)%state (startIndex:endIndex,:)
|
||||||
dotState(instance)%s_twin=>plasticState(phase)%dotState(startIndex:endIndex,:)
|
dotState(instance)%s_twin=>plasticState(phase)%dotState(startIndex:endIndex,:)
|
||||||
plasticState(phase)%state0(startIndex:endIndex,:) = &
|
plasticState(phase)%state0(startIndex:endIndex,:) = &
|
||||||
spread(math_expand(p%tau0_twin, p%Ntwin), 2, NipcMyPhase)
|
spread(math_expand(prm%tau0_twin, prm%Ntwin), 2, NipcMyPhase)
|
||||||
plasticState(phase)%aTolState(startIndex:endIndex) = p%aTolResistance
|
plasticState(phase)%aTolState(startIndex:endIndex) = prm%aTolResistance
|
||||||
|
|
||||||
startIndex = endIndex + 1_pInt
|
startIndex = endIndex + 1_pInt
|
||||||
endIndex = endIndex + 1_pInt
|
endIndex = endIndex + 1_pInt
|
||||||
state (instance)%sumGamma=>plasticState(phase)%state (startIndex,:)
|
state (instance)%sumGamma=>plasticState(phase)%state (startIndex,:)
|
||||||
dotState(instance)%sumGamma=>plasticState(phase)%dotState(startIndex,:)
|
dotState(instance)%sumGamma=>plasticState(phase)%dotState(startIndex,:)
|
||||||
plasticState(phase)%aTolState(startIndex:endIndex) = p%aTolShear
|
plasticState(phase)%aTolState(startIndex:endIndex) = prm%aTolShear
|
||||||
|
|
||||||
startIndex = endIndex + 1_pInt
|
startIndex = endIndex + 1_pInt
|
||||||
endIndex = endIndex + 1_pInt
|
endIndex = endIndex + 1_pInt
|
||||||
state (instance)%sumF=>plasticState(phase)%state (startIndex,:)
|
state (instance)%sumF=>plasticState(phase)%state (startIndex,:)
|
||||||
dotState(instance)%sumF=>plasticState(phase)%dotState(startIndex,:)
|
dotState(instance)%sumF=>plasticState(phase)%dotState(startIndex,:)
|
||||||
plasticState(phase)%aTolState(startIndex:endIndex) = p%aTolTwinFrac
|
plasticState(phase)%aTolState(startIndex:endIndex) = prm%aTolTwinFrac
|
||||||
|
|
||||||
startIndex = endIndex + 1_pInt
|
startIndex = endIndex + 1_pInt
|
||||||
endIndex = endIndex + plasticState(phase)%nSlip
|
endIndex = endIndex + plasticState(phase)%nSlip
|
||||||
state (instance)%accshear_slip=>plasticState(phase)%state (startIndex:endIndex,:)
|
state (instance)%accshear_slip=>plasticState(phase)%state (startIndex:endIndex,:)
|
||||||
dotState(instance)%accshear_slip=>plasticState(phase)%dotState(startIndex:endIndex,:)
|
dotState(instance)%accshear_slip=>plasticState(phase)%dotState(startIndex:endIndex,:)
|
||||||
plasticState(phase)%aTolState(startIndex:endIndex) = p%aTolShear
|
plasticState(phase)%aTolState(startIndex:endIndex) = prm%aTolShear
|
||||||
! global alias
|
! global alias
|
||||||
plasticState(phase)%slipRate =>plasticState(phase)%dotState(startIndex:endIndex,:)
|
plasticState(phase)%slipRate =>plasticState(phase)%dotState(startIndex:endIndex,:)
|
||||||
plasticState(phase)%accumulatedSlip =>plasticState(phase)%state(startIndex:endIndex,:)
|
plasticState(phase)%accumulatedSlip =>plasticState(phase)%state(startIndex:endIndex,:)
|
||||||
|
@ -432,7 +433,7 @@ subroutine plastic_phenopowerlaw_init
|
||||||
endIndex = endIndex + plasticState(phase)%nTwin
|
endIndex = endIndex + plasticState(phase)%nTwin
|
||||||
state (instance)%accshear_twin=>plasticState(phase)%state (startIndex:endIndex,:)
|
state (instance)%accshear_twin=>plasticState(phase)%state (startIndex:endIndex,:)
|
||||||
dotState(instance)%accshear_twin=>plasticState(phase)%dotState(startIndex:endIndex,:)
|
dotState(instance)%accshear_twin=>plasticState(phase)%dotState(startIndex:endIndex,:)
|
||||||
plasticState(phase)%aTolState(startIndex:endIndex) = p%aTolShear
|
plasticState(phase)%aTolState(startIndex:endIndex) = prm%aTolShear
|
||||||
|
|
||||||
offset_slip = plasticState(phase)%nSlip+plasticState(phase)%nTwin+2_pInt
|
offset_slip = plasticState(phase)%nSlip+plasticState(phase)%nTwin+2_pInt
|
||||||
plasticState(phase)%slipRate => &
|
plasticState(phase)%slipRate => &
|
||||||
|
|
Loading…
Reference in New Issue