plastic isotropic parses material.config from main memory, not from file

This commit is contained in:
Martin Diehl 2018-06-01 10:24:42 +02:00
parent 052a0af2ac
commit 5de4b47438
2 changed files with 69 additions and 153 deletions

View File

@ -157,7 +157,7 @@ subroutine constitutive_init()
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! parse plasticities from config file ! parse plasticities from config file
if (any(phase_plasticity == PLASTICITY_NONE_ID)) call plastic_none_init if (any(phase_plasticity == PLASTICITY_NONE_ID)) call plastic_none_init
if (any(phase_plasticity == PLASTICITY_ISOTROPIC_ID)) call plastic_isotropic_init(FILEUNIT) if (any(phase_plasticity == PLASTICITY_ISOTROPIC_ID)) call plastic_isotropic_init
if (any(phase_plasticity == PLASTICITY_PHENOPOWERLAW_ID)) call plastic_phenopowerlaw_init(FILEUNIT) if (any(phase_plasticity == PLASTICITY_PHENOPOWERLAW_ID)) call plastic_phenopowerlaw_init(FILEUNIT)
if (any(phase_plasticity == PLASTICITY_KINEHARDENING_ID)) call plastic_kinehardening_init(FILEUNIT) if (any(phase_plasticity == PLASTICITY_KINEHARDENING_ID)) call plastic_kinehardening_init(FILEUNIT)
if (any(phase_plasticity == PLASTICITY_DISLOTWIN_ID)) call plastic_dislotwin_init(FILEUNIT) if (any(phase_plasticity == PLASTICITY_DISLOTWIN_ID)) call plastic_dislotwin_init(FILEUNIT)

View File

@ -40,17 +40,17 @@ module plastic_isotropic
gdot0, & gdot0, &
n, & n, &
h0, & h0, &
h0_slopeLnRate = 0.0_pReal, & h0_slopeLnRate, &
tausat, & tausat, &
a, & a, &
aTolFlowstress = 1.0_pReal, & aTolFlowstress, &
aTolShear = 1.0e-6_pReal, & aTolShear, &
tausat_SinhFitA= 0.0_pReal, & tausat_SinhFitA, &
tausat_SinhFitB= 0.0_pReal, & tausat_SinhFitB, &
tausat_SinhFitC= 0.0_pReal, & tausat_SinhFitC, &
tausat_SinhFitD= 0.0_pReal tausat_SinhFitD
logical :: & logical :: &
dilatation = .false. dilatation
end type end type
type(tParameters), dimension(:), allocatable, target, private :: param !< containers of constitutive parameters (len Ninstance) type(tParameters), dimension(:), allocatable, target, private :: param !< containers of constitutive parameters (len Ninstance)
@ -79,12 +79,13 @@ contains
!> @brief module initialization !> @brief module initialization
!> @details reads in material parameters, allocates arrays, and does sanity checks !> @details reads in material parameters, allocates arrays, and does sanity checks
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine plastic_isotropic_init(fileUnit) subroutine plastic_isotropic_init()
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800 #if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
use, intrinsic :: iso_fortran_env, only: & use, intrinsic :: iso_fortran_env, only: &
compiler_version, & compiler_version, &
compiler_options compiler_options
#endif #endif
use IO
use debug, only: & use debug, only: &
debug_level, & debug_level, &
debug_constitutive, & debug_constitutive, &
@ -94,17 +95,6 @@ subroutine plastic_isotropic_init(fileUnit)
use math, only: & use math, only: &
math_Mandel3333to66, & math_Mandel3333to66, &
math_Voigt66to3333 math_Voigt66to3333
use IO, only: &
IO_read, &
IO_lc, &
IO_getTag, &
IO_isBlank, &
IO_stringPos, &
IO_stringValue, &
IO_floatValue, &
IO_error, &
IO_timeStamp, &
IO_EOF
use material, only: & use material, only: &
phase_plasticity, & phase_plasticity, &
phase_plasticityInstance, & phase_plasticityInstance, &
@ -113,16 +103,15 @@ subroutine plastic_isotropic_init(fileUnit)
PLASTICITY_ISOTROPIC_ID, & PLASTICITY_ISOTROPIC_ID, &
material_phase, & material_phase, &
plasticState, & plasticState, &
MATERIAL_partPhase MATERIAL_partPhase, &
phaseConfig
use lattice use lattice
implicit none implicit none
integer(pInt), intent(in) :: fileUnit
type(tParameters), pointer :: p type(tParameters), pointer :: p
integer(pInt), allocatable, dimension(:) :: chunkPos
integer(pInt) :: & integer(pInt) :: &
o, & o, &
phase, & phase, &
@ -133,160 +122,90 @@ subroutine plastic_isotropic_init(fileUnit)
sizeState, & sizeState, &
sizeDeltaState sizeDeltaState
character(len=65536) :: & character(len=65536) :: &
tag = '', &
line = '', &
extmsg = '' extmsg = ''
character(len=64) :: & integer(pInt) :: NipcMyPhase,i
outputtag = '' character(len=64), dimension(:), allocatable :: outputs
integer(pInt) :: NipcMyPhase
write(6,'(/,a)') ' <<<+- constitutive_'//PLASTICITY_ISOTROPIC_label//' init -+>>>' write(6,'(/,a)') ' <<<+- constitutive_'//PLASTICITY_ISOTROPIC_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"
maxNinstance = int(count(phase_plasticity == PLASTICITY_ISOTROPIC_ID),pInt) maxNinstance = int(count(phase_plasticity == PLASTICITY_ISOTROPIC_ID),pInt)
if (maxNinstance == 0_pInt) return
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:',maxNinstance
! public variables
allocate(plastic_isotropic_sizePostResults(maxNinstance), source=0_pInt) allocate(plastic_isotropic_sizePostResults(maxNinstance), source=0_pInt)
allocate(plastic_isotropic_sizePostResult(maxval(phase_Noutput), maxNinstance),source=0_pInt) allocate(plastic_isotropic_sizePostResult(maxval(phase_Noutput), maxNinstance),source=0_pInt)
allocate(plastic_isotropic_output(maxval(phase_Noutput), maxNinstance)) allocate(plastic_isotropic_output(maxval(phase_Noutput), maxNinstance))
plastic_isotropic_output = '' plastic_isotropic_output = ''
allocate(plastic_isotropic_Noutput(maxNinstance), source=0_pInt) allocate(plastic_isotropic_Noutput(maxNinstance), source=0_pInt)
! inernal variable
allocate(param(maxNinstance)) ! one container of parameters per instance allocate(param(maxNinstance)) ! one container of parameters per instance
rewind(fileUnit)
phase = 0_pInt
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= material_partPhase) ! wind forward to <phase>
line = IO_read(fileUnit)
enddo
parsingFile: do while (trim(line) /= IO_EOF) ! read through sections of phase part
line = IO_read(fileUnit)
if (IO_isBlank(line)) cycle ! skip empty lines
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
line = IO_read(fileUnit, .true.) ! reset IO_read
exit
endif
if (IO_getTag(line,'[',']') /= '') then ! next section
phase = phase + 1_pInt ! advance section counter
cycle ! skip to next line
endif
if (phase > 0_pInt) then; if (phase_plasticity(phase) == PLASTICITY_ISOTROPIC_ID) then ! one of my phases. Do not short-circuit here (.and. between if-statements), it's not safe in Fortran
instance = phase_plasticityInstance(phase) ! which instance of my plasticity is present phase
p => param(instance) ! shorthand pointer to parameter object of my constitutive law
chunkPos = IO_stringPos(line)
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
select case(tag)
case ('(output)')
outputtag = IO_lc(IO_stringValue(line,chunkPos,2_pInt))
select case(outputtag)
case ('flowstress')
plastic_isotropic_Noutput(instance) = plastic_isotropic_Noutput(instance) + 1_pInt
plastic_isotropic_output(plastic_isotropic_Noutput(instance),instance) = outputtag
p%outputID = [p%outputID,flowstress_ID]
case ('strainrate')
plastic_isotropic_Noutput(instance) = plastic_isotropic_Noutput(instance) + 1_pInt
plastic_isotropic_output(plastic_isotropic_Noutput(instance),instance) = outputtag
p%outputID = [p%outputID,strainrate_ID]
end select
case ('/dilatation/')
p%dilatation = .true.
case ('tau0')
p%tau0 = IO_floatValue(line,chunkPos,2_pInt)
case ('gdot0')
p%gdot0 = IO_floatValue(line,chunkPos,2_pInt)
case ('n')
p%n = IO_floatValue(line,chunkPos,2_pInt)
case ('h0')
p%h0 = IO_floatValue(line,chunkPos,2_pInt)
case ('h0_slope','slopelnrate')
p%h0_slopeLnRate = IO_floatValue(line,chunkPos,2_pInt)
case ('tausat')
p%tausat = IO_floatValue(line,chunkPos,2_pInt)
case ('tausat_sinhfita')
p%tausat_SinhFitA = IO_floatValue(line,chunkPos,2_pInt)
case ('tausat_sinhfitb')
p%tausat_SinhFitB = IO_floatValue(line,chunkPos,2_pInt)
case ('tausat_sinhfitc')
p%tausat_SinhFitC = IO_floatValue(line,chunkPos,2_pInt)
case ('tausat_sinhfitd')
p%tausat_SinhFitD = IO_floatValue(line,chunkPos,2_pInt)
case ('a', 'w0')
p%a = IO_floatValue(line,chunkPos,2_pInt)
case ('taylorfactor')
p%fTaylor = IO_floatValue(line,chunkPos,2_pInt)
case ('atol_flowstress')
p%aTolFlowstress = IO_floatValue(line,chunkPos,2_pInt)
case ('atol_shear')
p%aTolShear = IO_floatValue(line,chunkPos,2_pInt)
case default
end select
endif; endif
enddo parsingFile
allocate(state(maxNinstance)) ! internal state aliases allocate(state(maxNinstance)) ! internal state aliases
allocate(dotState(maxNinstance)) allocate(dotState(maxNinstance))
initializeInstances: do phase = 1_pInt, size(phase_plasticity) ! loop over every plasticity do phase = 1_pInt, size(phase_plasticityInstance)
myPhase: if (phase_plasticity(phase) == PLASTICITY_isotropic_ID) then ! isolate instances of own constitutive description if (phase_plasticity(phase) == PLASTICITY_ISOTROPIC_ID) then
NipcMyPhase = count(material_phase == phase) ! number of own material points (including point components ipc)
instance = phase_plasticityInstance(phase) instance = phase_plasticityInstance(phase)
p => param(instance) p => param(instance) ! shorthand pointer to parameter object of my constitutive law
p%tau0 = phaseConfig(phase)%getFloat('tau0')
p%tausat = phaseConfig(phase)%getFloat('tausat')
p%gdot0 = phaseConfig(phase)%getFloat('gdot0')
p%n = phaseConfig(phase)%getFloat('n')
p%h0 = phaseConfig(phase)%getFloat('h0')
p%fTaylor = phaseConfig(phase)%getFloat('taylorfactor')
p%h0_slopeLnRate = phaseConfig(phase)%getFloat('h0_slopelnrate', default=0.0_pReal) ! ToDo: alias allowed?
p%tausat_SinhFitA = phaseConfig(phase)%getFloat('tausat_sinhfita',default=0.0_pReal)
p%tausat_SinhFitB = phaseConfig(phase)%getFloat('tausat_sinhfitb',default=0.0_pReal)
p%tausat_SinhFitC = phaseConfig(phase)%getFloat('tausat_sinhfitc',default=0.0_pReal)
p%tausat_SinhFitD = phaseConfig(phase)%getFloat('tausat_sinhfitd',default=0.0_pReal)
p%a = phaseConfig(phase)%getFloat('a') ! ToDo: alias
p%aTolFlowStress = phaseConfig(phase)%getFloat('atol_flowstress',default=1.0_pReal)
p%aTolShear = phaseConfig(phase)%getFloat('atol_shear',default=1.0e-6_pReal)
p%dilatation = phaseConfig(phase)%keyExists('/dilatation/')
outputs = phaseConfig(phase)%getStrings('(output)')
allocate(p%outputID(0))
do i=1_pInt, size(outputs)
select case(outputs(i))
case ('flowstress')
plastic_isotropic_Noutput(instance) = plastic_isotropic_Noutput(instance) + 1_pInt
plastic_isotropic_output(plastic_isotropic_Noutput(instance),instance) = outputs(i)
plastic_isotropic_sizePostResults(instance) = &
plastic_isotropic_sizePostResults(instance) + 1_pInt
plastic_isotropic_sizePostResult(i,instance) = 1_pInt
p%outputID = [p%outputID,flowstress_ID]
case ('strainrate')
plastic_isotropic_Noutput(instance) = plastic_isotropic_Noutput(instance) + 1_pInt
plastic_isotropic_output(plastic_isotropic_Noutput(instance),instance) = outputs(i)
plastic_isotropic_sizePostResults(instance) = &
plastic_isotropic_sizePostResults(instance) + 1_pInt
plastic_isotropic_sizePostResult(i,instance) = 1_pInt
p%outputID = [p%outputID,strainrate_ID]
end select
enddo
extmsg = '' extmsg = ''
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! sanity checks ! sanity checks
if (p%aTolShear <= 0.0_pReal) p%aTolShear = 1.0e-6_pReal ! default absolute tolerance 1e-6 if (p%aTolShear <= 0.0_pReal) extmsg = trim(extmsg)//"'aTolShear' "
if (p%tau0 < 0.0_pReal) extmsg = trim(extmsg)//' tau0' if (p%tau0 < 0.0_pReal) extmsg = trim(extmsg)//"'tau0' "
if (p%gdot0 <= 0.0_pReal) extmsg = trim(extmsg)//' gdot0' if (p%gdot0 <= 0.0_pReal) extmsg = trim(extmsg)//"'gdot0' "
if (p%n <= 0.0_pReal) extmsg = trim(extmsg)//' n' if (p%n <= 0.0_pReal) extmsg = trim(extmsg)//"'n' "
if (p%tausat <= 0.0_pReal) extmsg = trim(extmsg)//' tausat' if (p%tausat <= 0.0_pReal) extmsg = trim(extmsg)//"'tausat' "
if (p%a <= 0.0_pReal) extmsg = trim(extmsg)//' a' if (p%a <= 0.0_pReal) extmsg = trim(extmsg)//"'a' "
if (p%fTaylor <= 0.0_pReal) extmsg = trim(extmsg)//' taylorfactor' if (p%fTaylor <= 0.0_pReal) extmsg = trim(extmsg)//"'taylorfactor' "
if (p%aTolFlowstress <= 0.0_pReal) extmsg = trim(extmsg)//' atol_flowstress' if (p%aTolFlowstress <= 0.0_pReal) extmsg = trim(extmsg)//"'atol_flowstress' "
if (extmsg /= '') then if (extmsg /= '') then
extmsg = trim(extmsg)//' ('//PLASTICITY_ISOTROPIC_label//')' ! prepare error message identifier extmsg = trim(extmsg)//' ('//PLASTICITY_ISOTROPIC_label//')' ! prepare error message identifier
call IO_error(211_pInt,ip=instance,ext_msg=extmsg) call IO_error(211_pInt,ip=instance,ext_msg=extmsg)
endif endif
!--------------------------------------------------------------------------------------------------
! Determine size of postResults array
outputsLoop: do o = 1_pInt,plastic_isotropic_Noutput(instance)
select case(p%outputID(o))
case(flowstress_ID,strainrate_ID)
mySize = 1_pInt
case default
end select
outputFound: if (mySize > 0_pInt) then
plastic_isotropic_sizePostResult(o,instance) = mySize
plastic_isotropic_sizePostResults(instance) = &
plastic_isotropic_sizePostResults(instance) + mySize
endif outputFound
enddo outputsLoop
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! allocate state arrays ! allocate state arrays
NipcMyPhase = count(material_phase == phase) ! number of own material points (including point components ipc)
sizeDotState = size(["flowstress ","accumulated_shear"]) sizeDotState = size(["flowstress ","accumulated_shear"])
sizeDeltaState = 0_pInt ! no sudden jumps in state sizeDeltaState = 0_pInt ! no sudden jumps in state
sizeState = sizeDotState + sizeDeltaState sizeState = sizeDotState + sizeDeltaState
@ -295,12 +214,8 @@ subroutine plastic_isotropic_init(fileUnit)
plasticState(phase)%sizeDeltaState = sizeDeltaState plasticState(phase)%sizeDeltaState = sizeDeltaState
plasticState(phase)%sizePostResults = plastic_isotropic_sizePostResults(instance) plasticState(phase)%sizePostResults = plastic_isotropic_sizePostResults(instance)
plasticState(phase)%nSlip = 1 plasticState(phase)%nSlip = 1
plasticState(phase)%nTwin = 0
plasticState(phase)%nTrans= 0
allocate(plasticState(phase)%aTolState ( sizeState)) allocate(plasticState(phase)%aTolState ( sizeState))
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)
allocate(plasticState(phase)%subState0 ( sizeState,NipcMyPhase),source=0.0_pReal) allocate(plasticState(phase)%subState0 ( sizeState,NipcMyPhase),source=0.0_pReal)
allocate(plasticState(phase)%state ( sizeState,NipcMyPhase),source=0.0_pReal) allocate(plasticState(phase)%state ( sizeState,NipcMyPhase),source=0.0_pReal)
@ -331,11 +246,12 @@ subroutine plastic_isotropic_init(fileUnit)
plasticState(phase)%slipRate => plasticState(phase)%dotState(2:2,1:NipcMyPhase) plasticState(phase)%slipRate => plasticState(phase)%dotState(2:2,1:NipcMyPhase)
plasticState(phase)%accumulatedSlip => plasticState(phase)%state (2:2,1:NipcMyPhase) plasticState(phase)%accumulatedSlip => plasticState(phase)%state (2:2,1:NipcMyPhase)
endif myPhase endif
enddo initializeInstances enddo
end subroutine plastic_isotropic_init end subroutine plastic_isotropic_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates plastic velocity gradient and its tangent !> @brief calculates plastic velocity gradient and its tangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------