DAMASK_EICMD/src/material.f90

737 lines
35 KiB
Fortran
Raw Normal View History

!--------------------------------------------------------------------------------------------------
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
2018-06-26 22:39:46 +05:30
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @brief Parses material config file, either solverJobName.materialConfig or material.config
!--------------------------------------------------------------------------------------------------
module material
2019-06-05 13:32:55 +05:30
use prec
use math
use config
use results
use IO
use debug
2019-06-07 18:01:42 +05:30
use rotations
2019-06-07 09:48:42 +05:30
use discretization
2019-09-20 00:10:59 +05:30
implicit none
private
2020-03-16 22:59:15 +05:30
character(len=*), parameter, public :: &
2019-09-20 00:10:59 +05:30
ELASTICITY_hooke_label = 'hooke', &
PLASTICITY_none_label = 'none', &
PLASTICITY_isotropic_label = 'isotropic', &
PLASTICITY_phenopowerlaw_label = 'phenopowerlaw', &
PLASTICITY_kinehardening_label = 'kinehardening', &
PLASTICITY_dislotwin_label = 'dislotwin', &
PLASTICITY_disloucla_label = 'disloucla', &
PLASTICITY_nonlocal_label = 'nonlocal', &
SOURCE_thermal_dissipation_label = 'thermal_dissipation', &
SOURCE_thermal_externalheat_label = 'thermal_externalheat', &
SOURCE_damage_isoBrittle_label = 'damage_isobrittle', &
SOURCE_damage_isoDuctile_label = 'damage_isoductile', &
SOURCE_damage_anisoBrittle_label = 'damage_anisobrittle', &
SOURCE_damage_anisoDuctile_label = 'damage_anisoductile', &
KINEMATICS_thermal_expansion_label = 'thermal_expansion', &
KINEMATICS_cleavage_opening_label = 'cleavage_opening', &
KINEMATICS_slipplane_opening_label = 'slipplane_opening', &
STIFFNESS_DEGRADATION_damage_label = 'damage', &
THERMAL_isothermal_label = 'isothermal', &
THERMAL_adiabatic_label = 'adiabatic', &
THERMAL_conduction_label = 'conduction', &
DAMAGE_none_label = 'none', &
DAMAGE_local_label = 'local', &
DAMAGE_nonlocal_label = 'nonlocal', &
HOMOGENIZATION_none_label = 'none', &
HOMOGENIZATION_isostrain_label = 'isostrain', &
HOMOGENIZATION_rgc_label = 'rgc'
2020-03-16 22:59:15 +05:30
2020-03-17 12:47:14 +05:30
enum, bind(c); enumerator :: &
ELASTICITY_UNDEFINED_ID ,&
ELASTICITY_HOOKE_ID ,&
PLASTICITY_UNDEFINED_ID ,&
PLASTICITY_NONE_ID, &
PLASTICITY_ISOTROPIC_ID, &
PLASTICITY_PHENOPOWERLAW_ID, &
PLASTICITY_KINEHARDENING_ID, &
PLASTICITY_DISLOTWIN_ID, &
PLASTICITY_DISLOUCLA_ID, &
PLASTICITY_NONLOCAL_ID, &
SOURCE_UNDEFINED_ID ,&
SOURCE_THERMAL_DISSIPATION_ID, &
SOURCE_THERMAL_EXTERNALHEAT_ID, &
SOURCE_DAMAGE_ISOBRITTLE_ID, &
SOURCE_DAMAGE_ISODUCTILE_ID, &
SOURCE_DAMAGE_ANISOBRITTLE_ID, &
SOURCE_DAMAGE_ANISODUCTILE_ID, &
KINEMATICS_UNDEFINED_ID ,&
KINEMATICS_CLEAVAGE_OPENING_ID, &
KINEMATICS_SLIPPLANE_OPENING_ID, &
KINEMATICS_THERMAL_EXPANSION_ID, &
STIFFNESS_DEGRADATION_UNDEFINED_ID, &
STIFFNESS_DEGRADATION_DAMAGE_ID, &
THERMAL_ISOTHERMAL_ID, &
THERMAL_ADIABATIC_ID, &
THERMAL_CONDUCTION_ID, &
DAMAGE_NONE_ID, &
DAMAGE_LOCAL_ID, &
DAMAGE_NONLOCAL_ID, &
HOMOGENIZATION_UNDEFINED_ID, &
HOMOGENIZATION_NONE_ID, &
HOMOGENIZATION_ISOSTRAIN_ID, &
HOMOGENIZATION_RGC_ID
2019-09-20 00:10:59 +05:30
end enum
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
integer(kind(ELASTICITY_undefined_ID)), dimension(:), allocatable, public, protected :: &
phase_elasticity !< elasticity of each phase
integer(kind(PLASTICITY_undefined_ID)), dimension(:), allocatable, public, protected :: &
phase_plasticity !< plasticity of each phase
integer(kind(THERMAL_isothermal_ID)), dimension(:), allocatable, public, protected :: &
thermal_type !< thermal transport model
integer(kind(DAMAGE_none_ID)), dimension(:), allocatable, public, protected :: &
damage_type !< nonlocal damage model
integer(kind(HOMOGENIZATION_undefined_ID)), dimension(:), allocatable, public, protected :: &
homogenization_type !< type of each homogenization
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
integer, public, protected :: &
material_Nphase, & !< number of phases
material_Nhomogenization !< number of homogenizations
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
integer(kind(SOURCE_undefined_ID)), dimension(:,:), allocatable, public, protected :: &
phase_source, & !< active sources mechanisms of each phase
phase_kinematics, & !< active kinematic mechanisms of each phase
phase_stiffnessDegradation !< active stiffness degradation mechanisms of each phase
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
integer, public, protected :: &
homogenization_maxNgrains !< max number of grains in any USED homogenization
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
integer, dimension(:), allocatable, public, protected :: &
phase_Nsources, & !< number of source mechanisms active in each phase
phase_Nkinematics, & !< number of kinematic mechanisms active in each phase
phase_NstiffnessDegradations, & !< number of stiffness degradation mechanisms active in each phase
phase_elasticityInstance, & !< instance of particular elasticity of each phase
phase_plasticityInstance, & !< instance of particular plasticity of each phase
homogenization_Ngrains, & !< number of grains in each homogenization
homogenization_typeInstance, & !< instance of particular type of each homogenization
thermal_typeInstance, & !< instance of particular type of each thermal transport
2019-11-25 13:14:44 +05:30
damage_typeInstance !< instance of particular type of each nonlocal damage
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
real(pReal), dimension(:), allocatable, public, protected :: &
thermal_initialT, & !< initial temperature per each homogenization
damage_initialPhi !< initial damage per each homogenization
2019-09-20 00:10:59 +05:30
integer, dimension(:), allocatable, public, protected :: & ! (elem)
material_homogenizationAt !< homogenization ID of each element (copy of discretization_homogenizationAt)
integer, dimension(:,:), allocatable, public, target :: & ! (ip,elem) ToDo: ugly target for mapping hack
2019-09-20 00:10:59 +05:30
material_homogenizationMemberAt !< position of the element within its homogenization instance
integer, dimension(:,:), allocatable, public, protected :: & ! (constituent,elem)
material_phaseAt !< phase ID of each element
integer, dimension(:,:,:), allocatable, public, protected :: & ! (constituent,elem)
2019-09-20 00:10:59 +05:30
material_phaseMemberAt !< position of the element within its phase instance
2019-09-20 00:10:59 +05:30
type(tPlasticState), allocatable, dimension(:), public :: &
plasticState
type(tSourceState), allocatable, dimension(:), public :: &
sourceState
type(tState), allocatable, dimension(:), public :: &
homogState, &
thermalState, &
damageState
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
integer, dimension(:,:,:), allocatable, public, protected :: &
material_texture !< texture (index) of each grain,IP,element. Only used by plastic_nonlocal
2020-03-16 22:59:15 +05:30
type(Rotation), dimension(:,:,:), allocatable, public, protected :: &
material_orientation0 !< initial orientation of each grain,IP,element
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
logical, dimension(:), allocatable, public, protected :: &
phase_localPlasticity !< flags phases with local constitutive law
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
integer, dimension(:), allocatable, private :: &
microstructure_Nconstituents !< number of constituents in each microstructure
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
integer, dimension(:,:), allocatable, private :: &
microstructure_phase, & !< phase IDs of each microstructure
microstructure_texture !< texture IDs of each microstructure
2020-03-16 22:59:15 +05:30
2019-09-20 07:44:37 +05:30
type(Rotation), dimension(:), allocatable, private :: &
2019-09-22 19:52:24 +05:30
texture_orientation !< Euler angles in material.config (possibly rotated for alignment)
2020-03-16 22:59:15 +05:30
2015-10-14 00:22:01 +05:30
! BEGIN DEPRECATED
2019-09-20 00:10:59 +05:30
integer, dimension(:,:), allocatable, private, target :: mappingHomogenizationConst !< mapping from material points to offset in constant state/field
! END DEPRECATED
2015-10-14 00:22:01 +05:30
2019-09-20 00:10:59 +05:30
type(tHomogMapping), allocatable, dimension(:), public :: &
thermalMapping, & !< mapping for thermal state/fields
damageMapping !< mapping for damage state/fields
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
type(group_float), allocatable, dimension(:), public :: &
temperature, & !< temperature field
damage, & !< damage field
temperatureRate !< temperature change rate field
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
public :: &
material_init, &
2020-04-01 13:26:59 +05:30
material_allocateState, &
2020-03-17 12:47:14 +05:30
ELASTICITY_HOOKE_ID ,&
PLASTICITY_NONE_ID, &
PLASTICITY_ISOTROPIC_ID, &
PLASTICITY_PHENOPOWERLAW_ID, &
PLASTICITY_KINEHARDENING_ID, &
PLASTICITY_DISLOTWIN_ID, &
PLASTICITY_DISLOUCLA_ID, &
PLASTICITY_NONLOCAL_ID, &
SOURCE_THERMAL_DISSIPATION_ID, &
SOURCE_THERMAL_EXTERNALHEAT_ID, &
SOURCE_DAMAGE_ISOBRITTLE_ID, &
SOURCE_DAMAGE_ISODUCTILE_ID, &
SOURCE_DAMAGE_ANISOBRITTLE_ID, &
SOURCE_DAMAGE_ANISODUCTILE_ID, &
KINEMATICS_CLEAVAGE_OPENING_ID, &
KINEMATICS_SLIPPLANE_OPENING_ID, &
KINEMATICS_THERMAL_EXPANSION_ID, &
STIFFNESS_DEGRADATION_DAMAGE_ID, &
THERMAL_ISOTHERMAL_ID, &
THERMAL_ADIABATIC_ID, &
THERMAL_CONDUCTION_ID, &
DAMAGE_NONE_ID, &
DAMAGE_LOCAL_ID, &
DAMAGE_NONLOCAL_ID, &
HOMOGENIZATION_NONE_ID, &
HOMOGENIZATION_ISOSTRAIN_ID, &
2019-09-20 00:10:59 +05:30
HOMOGENIZATION_RGC_ID
contains
!--------------------------------------------------------------------------------------------------
!> @brief parses material configuration file
!--------------------------------------------------------------------------------------------------
subroutine material_init(restart)
logical, intent(in) :: restart
2015-10-14 00:22:01 +05:30
2019-09-20 00:10:59 +05:30
integer :: i,e,m,c,h, myDebug, myPhase, myHomog, myMicro
integer, dimension(:), allocatable :: &
CounterPhase, &
CounterHomogenization
class(tNode), pointer :: &
2020-06-26 23:42:05 +05:30
debug_material ! pointer to material debug options
2020-03-16 22:59:15 +05:30
write(6,'(/,a)') ' <<<+- material init -+>>>'; flush(6)
2020-03-16 22:59:15 +05:30
debug_material => debug_root%get('material',defaultVal=emptyList)
2019-09-20 00:10:59 +05:30
call material_parsePhase()
if (debug_material%contains('basic')) write(6,'(a)') ' Phase parsed'; flush(6)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
call material_parseMicrostructure()
if (debug_material%contains('basic')) write(6,'(a)') ' Microstructure parsed'; flush(6)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
call material_parseHomogenization()
if (debug_material%contains('basic')) write(6,'(a)') ' Homogenization parsed'; flush(6)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
call material_parseTexture()
if (debug_material%contains('basic')) write(6,'(a)') ' Texture parsed'; flush(6)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
material_Nphase = size(config_phase)
material_Nhomogenization = size(config_homogenization)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
allocate(plasticState(material_Nphase))
allocate(sourceState (material_Nphase))
do myPhase = 1,material_Nphase
allocate(sourceState(myPhase)%p(phase_Nsources(myPhase)))
enddo
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
allocate(homogState (material_Nhomogenization))
allocate(thermalState (material_Nhomogenization))
allocate(damageState (material_Nhomogenization))
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
allocate(thermalMapping (material_Nhomogenization))
allocate(damageMapping (material_Nhomogenization))
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
allocate(temperature (material_Nhomogenization))
allocate(damage (material_Nhomogenization))
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
allocate(temperatureRate (material_Nhomogenization))
2019-09-20 00:10:59 +05:30
do m = 1,size(config_microstructure)
if(minval(microstructure_phase(1:microstructure_Nconstituents(m),m)) < 1 .or. &
maxval(microstructure_phase(1:microstructure_Nconstituents(m),m)) > size(config_phase)) &
call IO_error(150,m,ext_msg='phase')
if(minval(microstructure_texture(1:microstructure_Nconstituents(m),m)) < 1 .or. &
maxval(microstructure_texture(1:microstructure_Nconstituents(m),m)) > size(config_texture)) &
call IO_error(150,m,ext_msg='texture')
if(microstructure_Nconstituents(m) < 1) &
call IO_error(151,m)
enddo
if(homogenization_maxNgrains > size(microstructure_phase,1)) call IO_error(148)
2020-03-16 22:59:15 +05:30
debugOut: if (debug_material%contains('extensive')) then
2019-09-20 00:10:59 +05:30
write(6,'(/,a,/)') ' MATERIAL configuration'
write(6,'(a32,1x,a16,1x,a6)') 'homogenization ','type ','grains'
do h = 1,size(config_homogenization)
write(6,'(1x,a32,1x,a16,1x,i6)') config_name_homogenization(h),homogenization_type(h),homogenization_Ngrains(h)
enddo
2020-02-03 01:07:05 +05:30
write(6,'(/,a14,18x,1x,a11,1x,a12,1x,a13)') 'microstructure','constituents'
2019-09-20 00:10:59 +05:30
do m = 1,size(config_microstructure)
2020-02-03 01:07:05 +05:30
write(6,'(1x,a32,1x,i12)') config_name_microstructure(m), microstructure_Nconstituents(m)
2019-09-20 00:10:59 +05:30
if (microstructure_Nconstituents(m) > 0) then
do c = 1,microstructure_Nconstituents(m)
2020-01-23 18:30:56 +05:30
write(6,'(a1,1x,a32,1x,a32)') '>',config_name_phase(microstructure_phase(c,m)),&
config_name_texture(microstructure_texture(c,m))
2019-09-20 00:10:59 +05:30
enddo
write(6,*)
endif
enddo
endif debugOut
2015-10-14 00:22:01 +05:30
allocate(material_phaseAt(homogenization_maxNgrains,discretization_nElem), source=0)
allocate(material_texture(homogenization_maxNgrains,discretization_nIP,discretization_nElem),source=0) !this is only needed by plasticity nonlocal
allocate(material_orientation0(homogenization_maxNgrains,discretization_nIP,discretization_nElem))
2019-09-22 19:52:24 +05:30
2019-09-20 00:10:59 +05:30
do e = 1, discretization_nElem
do i = 1, discretization_nIP
myMicro = discretization_microstructureAt(e)
do c = 1, homogenization_Ngrains(discretization_homogenizationAt(e))
if(microstructure_phase(c,myMicro) > 0) then
material_phaseAt(c,e) = microstructure_phase(c,myMicro)
else
call IO_error(150,ext_msg='phase')
endif
if(microstructure_texture(c,myMicro) > 0) then
material_texture(c,i,e) = microstructure_texture(c,myMicro)
material_orientation0(c,i,e) = texture_orientation(material_texture(c,i,e))
else
call IO_error(150,ext_msg='texture')
endif
2019-09-20 00:10:59 +05:30
enddo
2019-04-04 16:55:29 +05:30
enddo
enddo
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
deallocate(microstructure_phase)
deallocate(microstructure_texture)
2020-02-22 16:12:06 +05:30
deallocate(texture_orientation)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
allocate(material_homogenizationAt,source=discretization_homogenizationAt)
allocate(material_homogenizationMemberAt(discretization_nIP,discretization_nElem),source=0)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
allocate(CounterHomogenization(size(config_homogenization)),source=0)
do e = 1, discretization_nElem
do i = 1, discretization_nIP
CounterHomogenization(material_homogenizationAt(e)) = &
CounterHomogenization(material_homogenizationAt(e)) + 1
material_homogenizationMemberAt(i,e) = CounterHomogenization(material_homogenizationAt(e))
enddo
enddo
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
allocate(material_phaseMemberAt(homogenization_maxNgrains,discretization_nIP,discretization_nElem),source=0)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
allocate(CounterPhase(size(config_phase)),source=0)
do e = 1, discretization_nElem
do i = 1, discretization_nIP
do c = 1, homogenization_maxNgrains
CounterPhase(material_phaseAt(c,e)) = &
CounterPhase(material_phaseAt(c,e)) + 1
material_phaseMemberAt(c,i,e) = CounterPhase(material_phaseAt(c,e))
enddo
enddo
enddo
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
call config_deallocate('material.config/microstructure')
call config_deallocate('material.config/texture')
2019-06-13 03:01:46 +05:30
if (.not. restart) then
call results_openJobFile
call results_mapping_constituent(material_phaseAt,material_phaseMemberAt,config_name_phase)
call results_mapping_materialpoint(material_homogenizationAt,material_homogenizationMemberAt,config_name_homogenization)
call results_closeJobFile
endif
2019-04-04 16:55:29 +05:30
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! BEGIN DEPRECATED
2019-09-20 00:10:59 +05:30
allocate(mappingHomogenizationConst( discretization_nIP,discretization_nElem),source=1)
2020-02-03 01:07:05 +05:30
! hack needed to initialize field values used during constitutive initialization
2019-09-20 00:10:59 +05:30
do myHomog = 1,size(config_homogenization)
thermalMapping (myHomog)%p => mappingHomogenizationConst
damageMapping (myHomog)%p => mappingHomogenizationConst
allocate(temperature (myHomog)%p(1), source=thermal_initialT(myHomog))
allocate(damage (myHomog)%p(1), source=damage_initialPhi(myHomog))
allocate(temperatureRate (myHomog)%p(1), source=0.0_pReal)
enddo
! END DEPRECATED
end subroutine material_init
!--------------------------------------------------------------------------------------------------
2018-06-11 03:46:48 +05:30
!> @brief parses the homogenization part from the material configuration
!--------------------------------------------------------------------------------------------------
subroutine material_parseHomogenization
2015-10-14 00:22:01 +05:30
2019-12-21 16:16:12 +05:30
integer :: h
character(len=pStringLen) :: tag
2020-01-23 18:30:56 +05:30
logical, dimension(:), allocatable :: homogenization_active
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
allocate(homogenization_type(size(config_homogenization)), source=HOMOGENIZATION_undefined_ID)
allocate(thermal_type(size(config_homogenization)), source=THERMAL_isothermal_ID)
allocate(damage_type (size(config_homogenization)), source=DAMAGE_none_ID)
allocate(homogenization_typeInstance(size(config_homogenization)), source=0)
allocate(thermal_typeInstance(size(config_homogenization)), source=0)
allocate(damage_typeInstance(size(config_homogenization)), source=0)
allocate(homogenization_Ngrains(size(config_homogenization)), source=0)
allocate(homogenization_active(size(config_homogenization)), source=.false.) !!!!!!!!!!!!!!!
allocate(thermal_initialT(size(config_homogenization)), source=300.0_pReal)
allocate(damage_initialPhi(size(config_homogenization)), source=1.0_pReal)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
forall (h = 1:size(config_homogenization)) &
homogenization_active(h) = any(discretization_homogenizationAt == h)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
do h=1, size(config_homogenization)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
tag = config_homogenization(h)%getString('mech')
select case (trim(tag))
case(HOMOGENIZATION_NONE_label)
homogenization_type(h) = HOMOGENIZATION_NONE_ID
homogenization_Ngrains(h) = 1
case(HOMOGENIZATION_ISOSTRAIN_label)
homogenization_type(h) = HOMOGENIZATION_ISOSTRAIN_ID
homogenization_Ngrains(h) = config_homogenization(h)%getInt('nconstituents')
case(HOMOGENIZATION_RGC_label)
homogenization_type(h) = HOMOGENIZATION_RGC_ID
homogenization_Ngrains(h) = config_homogenization(h)%getInt('nconstituents')
case default
call IO_error(500,ext_msg=trim(tag))
end select
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
homogenization_typeInstance(h) = count(homogenization_type==homogenization_type(h))
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
if (config_homogenization(h)%keyExists('thermal')) then
thermal_initialT(h) = config_homogenization(h)%getFloat('t0',defaultVal=300.0_pReal)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
tag = config_homogenization(h)%getString('thermal')
select case (trim(tag))
case(THERMAL_isothermal_label)
thermal_type(h) = THERMAL_isothermal_ID
case(THERMAL_adiabatic_label)
thermal_type(h) = THERMAL_adiabatic_ID
case(THERMAL_conduction_label)
thermal_type(h) = THERMAL_conduction_ID
case default
call IO_error(500,ext_msg=trim(tag))
end select
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
endif
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
if (config_homogenization(h)%keyExists('damage')) then
damage_initialPhi(h) = config_homogenization(h)%getFloat('initialdamage',defaultVal=1.0_pReal)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
tag = config_homogenization(h)%getString('damage')
select case (trim(tag))
case(DAMAGE_NONE_label)
damage_type(h) = DAMAGE_none_ID
case(DAMAGE_LOCAL_label)
damage_type(h) = DAMAGE_local_ID
case(DAMAGE_NONLOCAL_label)
damage_type(h) = DAMAGE_nonlocal_ID
case default
call IO_error(500,ext_msg=trim(tag))
end select
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
endif
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
enddo
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
do h=1, size(config_homogenization)
2019-09-20 02:10:03 +05:30
homogenization_typeInstance(h) = count(homogenization_type(1:h) == homogenization_type(h))
thermal_typeInstance(h) = count(thermal_type (1:h) == thermal_type (h))
damage_typeInstance(h) = count(damage_type (1:h) == damage_type (h))
2019-09-20 00:10:59 +05:30
enddo
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
homogenization_maxNgrains = maxval(homogenization_Ngrains,homogenization_active)
end subroutine material_parseHomogenization
!--------------------------------------------------------------------------------------------------
!> @brief parses the microstructure part in the material configuration file
!--------------------------------------------------------------------------------------------------
subroutine material_parseMicrostructure
2015-10-14 00:22:01 +05:30
2019-12-21 16:16:12 +05:30
character(len=pStringLen), dimension(:), allocatable :: &
2019-09-20 00:10:59 +05:30
strings
integer, allocatable, dimension(:) :: chunkPos
2020-01-26 23:01:56 +05:30
integer :: m, c, i
2019-12-21 16:16:12 +05:30
character(len=pStringLen) :: &
2019-09-20 00:10:59 +05:30
tag
2020-01-23 18:30:56 +05:30
real(pReal), dimension(:,:), allocatable :: &
microstructure_fraction !< vol fraction of each constituent in microstructure
integer :: &
maxNconstituents !< max number of constituents in any phase
2020-03-16 22:59:15 +05:30
2019-09-20 02:10:03 +05:30
allocate(microstructure_Nconstituents(size(config_microstructure)), source=0)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
if(any(discretization_microstructureAt > size(config_microstructure))) &
call IO_error(155,ext_msg='More microstructures in geometry than sections in material.config')
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
do m=1, size(config_microstructure)
microstructure_Nconstituents(m) = config_microstructure(m)%countKeys('(constituent)')
enddo
2020-03-16 22:59:15 +05:30
maxNconstituents = maxval(microstructure_Nconstituents)
allocate(microstructure_phase (maxNconstituents,size(config_microstructure)),source=0)
allocate(microstructure_texture (maxNconstituents,size(config_microstructure)),source=0)
allocate(microstructure_fraction(maxNconstituents,size(config_microstructure)),source=0.0_pReal)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
allocate(strings(1)) ! Intel 16.0 Bug
do m=1, size(config_microstructure)
strings = config_microstructure(m)%getStrings('(constituent)',raw=.true.)
do c = 1, size(strings)
chunkPos = IO_stringPos(strings(c))
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
do i = 1,5,2
tag = IO_stringValue(strings(c),chunkPos,i)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
select case (tag)
case('phase')
microstructure_phase(c,m) = IO_intValue(strings(c),chunkPos,i+1)
case('texture')
microstructure_texture(c,m) = IO_intValue(strings(c),chunkPos,i+1)
case('fraction')
2019-09-20 02:10:03 +05:30
microstructure_fraction(c,m) = IO_floatValue(strings(c),chunkPos,i+1)
2019-09-20 00:10:59 +05:30
end select
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
enddo
enddo
if (dNeq(sum(microstructure_fraction(:,m)),1.0_pReal)) call IO_error(153,ext_msg=config_name_microstructure(m))
enddo
2020-03-16 22:59:15 +05:30
end subroutine material_parseMicrostructure
!--------------------------------------------------------------------------------------------------
!> @brief parses the phase part in the material configuration file
!--------------------------------------------------------------------------------------------------
subroutine material_parsePhase
2013-03-28 19:20:20 +05:30
2019-09-20 00:10:59 +05:30
integer :: sourceCtr, kinematicsCtr, stiffDegradationCtr, p
2020-03-16 22:59:15 +05:30
character(len=pStringLen), dimension(:), allocatable :: str
2019-09-20 00:10:59 +05:30
allocate(phase_elasticity(size(config_phase)),source=ELASTICITY_undefined_ID)
allocate(phase_plasticity(size(config_phase)),source=PLASTICITY_undefined_ID)
allocate(phase_Nsources(size(config_phase)), source=0)
allocate(phase_Nkinematics(size(config_phase)), source=0)
allocate(phase_NstiffnessDegradations(size(config_phase)),source=0)
allocate(phase_localPlasticity(size(config_phase)), source=.false.)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
do p=1, size(config_phase)
phase_Nsources(p) = config_phase(p)%countKeys('(source)')
phase_Nkinematics(p) = config_phase(p)%countKeys('(kinematics)')
phase_NstiffnessDegradations(p) = config_phase(p)%countKeys('(stiffness_degradation)')
phase_localPlasticity(p) = .not. config_phase(p)%KeyExists('/nonlocal/')
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
select case (config_phase(p)%getString('elasticity'))
case (ELASTICITY_HOOKE_label)
phase_elasticity(p) = ELASTICITY_HOOKE_ID
case default
call IO_error(200,ext_msg=trim(config_phase(p)%getString('elasticity')))
end select
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
select case (config_phase(p)%getString('plasticity'))
case (PLASTICITY_NONE_label)
phase_plasticity(p) = PLASTICITY_NONE_ID
case (PLASTICITY_ISOTROPIC_label)
phase_plasticity(p) = PLASTICITY_ISOTROPIC_ID
case (PLASTICITY_PHENOPOWERLAW_label)
phase_plasticity(p) = PLASTICITY_PHENOPOWERLAW_ID
case (PLASTICITY_KINEHARDENING_label)
phase_plasticity(p) = PLASTICITY_KINEHARDENING_ID
case (PLASTICITY_DISLOTWIN_label)
phase_plasticity(p) = PLASTICITY_DISLOTWIN_ID
case (PLASTICITY_DISLOUCLA_label)
phase_plasticity(p) = PLASTICITY_DISLOUCLA_ID
case (PLASTICITY_NONLOCAL_label)
phase_plasticity(p) = PLASTICITY_NONLOCAL_ID
case default
call IO_error(201,ext_msg=trim(config_phase(p)%getString('plasticity')))
end select
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
enddo
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
allocate(phase_source(maxval(phase_Nsources),size(config_phase)), source=SOURCE_undefined_ID)
allocate(phase_kinematics(maxval(phase_Nkinematics),size(config_phase)), source=KINEMATICS_undefined_ID)
allocate(phase_stiffnessDegradation(maxval(phase_NstiffnessDegradations),size(config_phase)), &
source=STIFFNESS_DEGRADATION_undefined_ID)
do p=1, size(config_phase)
#if defined(__GFORTRAN__) || defined(__PGI)
2019-09-20 00:10:59 +05:30
str = ['GfortranBug86277']
str = config_phase(p)%getStrings('(source)',defaultVal=str)
2019-12-21 16:16:12 +05:30
if (str(1) == 'GfortranBug86277') str = [character(len=pStringLen)::]
#else
2019-12-21 16:16:12 +05:30
str = config_phase(p)%getStrings('(source)',defaultVal=[character(len=pStringLen)::])
#endif
2019-09-20 00:10:59 +05:30
do sourceCtr = 1, size(str)
select case (trim(str(sourceCtr)))
case (SOURCE_thermal_dissipation_label)
phase_source(sourceCtr,p) = SOURCE_thermal_dissipation_ID
case (SOURCE_thermal_externalheat_label)
phase_source(sourceCtr,p) = SOURCE_thermal_externalheat_ID
case (SOURCE_damage_isoBrittle_label)
phase_source(sourceCtr,p) = SOURCE_damage_isoBrittle_ID
case (SOURCE_damage_isoDuctile_label)
phase_source(sourceCtr,p) = SOURCE_damage_isoDuctile_ID
case (SOURCE_damage_anisoBrittle_label)
phase_source(sourceCtr,p) = SOURCE_damage_anisoBrittle_ID
case (SOURCE_damage_anisoDuctile_label)
phase_source(sourceCtr,p) = SOURCE_damage_anisoDuctile_ID
end select
enddo
#if defined(__GFORTRAN__) || defined(__PGI)
2019-09-20 00:10:59 +05:30
str = ['GfortranBug86277']
str = config_phase(p)%getStrings('(kinematics)',defaultVal=str)
2019-12-21 16:16:12 +05:30
if (str(1) == 'GfortranBug86277') str = [character(len=pStringLen)::]
#else
2019-12-21 16:16:12 +05:30
str = config_phase(p)%getStrings('(kinematics)',defaultVal=[character(len=pStringLen)::])
#endif
2019-09-20 00:10:59 +05:30
do kinematicsCtr = 1, size(str)
select case (trim(str(kinematicsCtr)))
case (KINEMATICS_cleavage_opening_label)
phase_kinematics(kinematicsCtr,p) = KINEMATICS_cleavage_opening_ID
case (KINEMATICS_slipplane_opening_label)
phase_kinematics(kinematicsCtr,p) = KINEMATICS_slipplane_opening_ID
case (KINEMATICS_thermal_expansion_label)
phase_kinematics(kinematicsCtr,p) = KINEMATICS_thermal_expansion_ID
end select
enddo
#if defined(__GFORTRAN__) || defined(__PGI)
2019-09-20 00:10:59 +05:30
str = ['GfortranBug86277']
str = config_phase(p)%getStrings('(stiffness_degradation)',defaultVal=str)
2019-12-21 16:16:12 +05:30
if (str(1) == 'GfortranBug86277') str = [character(len=pStringLen)::]
#else
2019-12-21 16:16:12 +05:30
str = config_phase(p)%getStrings('(stiffness_degradation)',defaultVal=[character(len=pStringLen)::])
#endif
2019-09-20 00:10:59 +05:30
do stiffDegradationCtr = 1, size(str)
select case (trim(str(stiffDegradationCtr)))
case (STIFFNESS_DEGRADATION_damage_label)
phase_stiffnessDegradation(stiffDegradationCtr,p) = STIFFNESS_DEGRADATION_damage_ID
end select
enddo
enddo
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
allocate(phase_plasticityInstance(size(config_phase)),source=0)
allocate(phase_elasticityInstance(size(config_phase)),source=0)
2020-03-16 22:59:15 +05:30
2019-09-20 00:10:59 +05:30
do p=1, size(config_phase)
phase_elasticityInstance(p) = count(phase_elasticity(1:p) == phase_elasticity(p))
phase_plasticityInstance(p) = count(phase_plasticity(1:p) == phase_plasticity(p))
enddo
end subroutine material_parsePhase
2019-06-13 03:01:46 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief parses the texture part in the material configuration file
!--------------------------------------------------------------------------------------------------
subroutine material_parseTexture
2015-10-14 00:22:01 +05:30
2019-12-21 16:16:12 +05:30
integer :: j,t
2020-03-16 22:59:15 +05:30
character(len=pStringLen), dimension(:), allocatable :: strings ! Values for given key in material config
2019-06-07 17:17:38 +05:30
integer, dimension(:), allocatable :: chunkPos
2019-09-22 19:52:24 +05:30
real(pReal), dimension(3,3) :: transformation ! maps texture to microstructure coordinate system
2019-09-20 07:44:37 +05:30
real(pReal), dimension(3) :: Eulers ! Euler angles in degrees from file
2019-09-22 19:52:24 +05:30
type(rotation) :: transformation_
2019-06-07 17:17:38 +05:30
do t=1, size(config_texture)
2019-06-07 18:01:42 +05:30
if (config_texture(t)%countKeys('(gauss)') /= 1) call IO_error(147,ext_msg='count((gauss)) != 1')
2019-06-07 17:17:38 +05:30
if (config_texture(t)%keyExists('symmetry')) call IO_error(147,ext_msg='symmetry')
if (config_texture(t)%keyExists('(random)')) call IO_error(147,ext_msg='(random)')
if (config_texture(t)%keyExists('(fiber)')) call IO_error(147,ext_msg='(fiber)')
enddo
2019-09-22 19:52:24 +05:30
allocate(texture_orientation(size(config_texture)))
2019-06-07 17:17:38 +05:30
do t=1, size(config_texture)
2020-03-16 22:59:15 +05:30
2019-06-07 18:01:42 +05:30
strings = config_texture(t)%getStrings('(gauss)',raw= .true.)
2019-09-20 07:44:37 +05:30
chunkPos = IO_stringPos(strings(1))
2020-01-26 23:01:56 +05:30
do j = 1,5,2
2019-09-20 07:44:37 +05:30
select case (IO_stringValue(strings(1),chunkPos,j))
case('phi1')
Eulers(1) = IO_floatValue(strings(1),chunkPos,j+1)
case('phi')
Eulers(2) = IO_floatValue(strings(1),chunkPos,j+1)
case('phi2')
Eulers(3) = IO_floatValue(strings(1),chunkPos,j+1)
end select
2019-06-07 18:01:42 +05:30
enddo
2019-09-22 19:52:24 +05:30
call texture_orientation(t)%fromEulers(Eulers,degrees=.true.)
2019-06-07 18:01:42 +05:30
2019-06-07 17:17:38 +05:30
if (config_texture(t)%keyExists('axes')) then
strings = config_texture(t)%getStrings('axes')
do j = 1, 3 ! look for "x", "y", and "z" entries
select case (strings(j))
case('x', '+x')
2019-12-21 16:16:12 +05:30
transformation(j,1:3) = [ 1.0_pReal, 0.0_pReal, 0.0_pReal] ! original axis is now +x-axis
2019-06-07 17:17:38 +05:30
case('-x')
2019-12-21 16:16:12 +05:30
transformation(j,1:3) = [-1.0_pReal, 0.0_pReal, 0.0_pReal] ! original axis is now -x-axis
2019-06-07 17:17:38 +05:30
case('y', '+y')
2019-12-21 16:16:12 +05:30
transformation(j,1:3) = [ 0.0_pReal, 1.0_pReal, 0.0_pReal] ! original axis is now +y-axis
2019-06-07 17:17:38 +05:30
case('-y')
2019-12-21 16:16:12 +05:30
transformation(j,1:3) = [ 0.0_pReal,-1.0_pReal, 0.0_pReal] ! original axis is now -y-axis
2019-06-07 17:17:38 +05:30
case('z', '+z')
2019-12-21 16:16:12 +05:30
transformation(j,1:3) = [ 0.0_pReal, 0.0_pReal, 1.0_pReal] ! original axis is now +z-axis
2019-06-07 17:17:38 +05:30
case('-z')
2019-12-21 16:16:12 +05:30
transformation(j,1:3) = [ 0.0_pReal, 0.0_pReal,-1.0_pReal] ! original axis is now -z-axis
2019-06-07 17:17:38 +05:30
case default
call IO_error(157,t)
end select
enddo
2019-09-22 19:52:24 +05:30
call transformation_%fromMatrix(transformation)
texture_orientation(t) = texture_orientation(t) * transformation_
2019-06-07 17:17:38 +05:30
endif
2020-03-16 22:59:15 +05:30
enddo
end subroutine material_parseTexture
2018-10-14 23:46:30 +05:30
!--------------------------------------------------------------------------------------------------
2020-04-01 13:26:59 +05:30
!> @brief Allocate the components of the state structure for a given phase
2018-10-14 23:46:30 +05:30
!--------------------------------------------------------------------------------------------------
2020-04-01 13:26:59 +05:30
subroutine material_allocateState(state, &
NipcMyPhase,sizeState,sizeDotState,sizeDeltaState)
2018-10-14 23:46:30 +05:30
2020-04-01 13:26:59 +05:30
class(tState), intent(out) :: &
state
2019-06-16 00:02:53 +05:30
integer, intent(in) :: &
2020-03-16 22:59:15 +05:30
NipcMyPhase, &
2019-06-16 00:02:53 +05:30
sizeState, &
sizeDotState, &
sizeDeltaState
2019-06-16 00:02:53 +05:30
2020-04-01 13:26:59 +05:30
state%sizeState = sizeState
state%sizeDotState = sizeDotState
state%sizeDeltaState = sizeDeltaState
state%offsetDeltaState = sizeState-sizeDeltaState ! deltaState occupies latter part of state by definition
2019-06-16 00:02:53 +05:30
2020-04-01 13:26:59 +05:30
allocate(state%atol (sizeState), source=0.0_pReal)
allocate(state%state0 (sizeState,NipcMyPhase), source=0.0_pReal)
allocate(state%partionedState0(sizeState,NipcMyPhase), source=0.0_pReal)
allocate(state%subState0 (sizeState,NipcMyPhase), source=0.0_pReal)
allocate(state%state (sizeState,NipcMyPhase), source=0.0_pReal)
2019-06-16 00:02:53 +05:30
2020-04-01 13:26:59 +05:30
allocate(state%dotState (sizeDotState,NipcMyPhase), source=0.0_pReal)
2019-06-16 00:02:53 +05:30
2020-04-01 13:26:59 +05:30
allocate(state%deltaState(sizeDeltaState,NipcMyPhase), source=0.0_pReal)
2018-10-14 23:46:30 +05:30
2020-04-01 13:26:59 +05:30
end subroutine material_allocateState
2018-10-14 23:46:30 +05:30
end module material