2012-03-09 01:55:28 +05:30
!--------------------------------------------------------------------------------------------------
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
2013-06-11 22:05:04 +05:30
!> @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
2013-01-18 17:00:52 +05:30
!> @brief Parses material config file, either solverJobName.materialConfig or material.config
!> @details reads the material configuration file, where solverJobName.materialConfig takes
!! precedence over material.config and parses the sections 'homogenization', 'crystallite',
!! 'phase', 'texture', and 'microstucture'
2012-03-09 01:55:28 +05:30
!--------------------------------------------------------------------------------------------------
module material
2019-06-05 13:32:55 +05:30
use prec
use math
use config
use results
use IO
use debug
use mesh
use numerics
2019-06-07 09:48:42 +05:30
use discretization
2012-03-09 01:55:28 +05:30
implicit none
private
2019-06-05 13:32:55 +05:30
2013-12-16 16:26:56 +05:30
character ( len = * ) , parameter , public :: &
2015-05-28 22:32:23 +05:30
ELASTICITY_hooke_label = 'hooke' , &
PLASTICITY_none_label = 'none' , &
2016-01-09 01:15:20 +05:30
PLASTICITY_isotropic_label = 'isotropic' , &
2015-05-28 22:32:23 +05:30
PLASTICITY_phenopowerlaw_label = 'phenopowerlaw' , &
2017-09-30 04:06:28 +05:30
PLASTICITY_kinehardening_label = 'kinehardening' , &
2015-05-29 16:33:25 +05:30
PLASTICITY_dislotwin_label = 'dislotwin' , &
2015-05-28 22:32:23 +05:30
PLASTICITY_disloucla_label = 'disloucla' , &
PLASTICITY_nonlocal_label = 'nonlocal' , &
SOURCE_thermal_dissipation_label = 'thermal_dissipation' , &
2015-07-27 16:39:37 +05:30
SOURCE_thermal_externalheat_label = 'thermal_externalheat' , &
2015-05-28 22:32:23 +05:30
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' , &
2015-10-14 00:22:01 +05:30
HOMOGENIZATION_rgc_label = 'rgc'
2013-11-27 13:35:23 +05:30
2015-10-14 00:22:01 +05:30
enum , bind ( c )
2013-12-12 22:39:59 +05:30
enumerator :: ELASTICITY_undefined_ID , &
2019-05-01 02:36:16 +05:30
ELASTICITY_hooke_ID , &
PLASTICITY_undefined_ID , &
2013-12-12 22:39:59 +05:30
PLASTICITY_none_ID , &
2016-01-09 01:15:20 +05:30
PLASTICITY_isotropic_ID , &
2013-11-27 13:35:23 +05:30
PLASTICITY_phenopowerlaw_ID , &
2017-09-30 04:06:28 +05:30
PLASTICITY_kinehardening_ID , &
2013-11-27 13:35:23 +05:30
PLASTICITY_dislotwin_ID , &
2015-01-15 16:26:15 +05:30
PLASTICITY_disloucla_ID , &
2019-05-01 02:36:16 +05:30
PLASTICITY_nonlocal_ID , &
SOURCE_undefined_ID , &
2015-05-28 22:32:23 +05:30
SOURCE_thermal_dissipation_ID , &
2015-07-27 16:39:37 +05:30
SOURCE_thermal_externalheat_ID , &
2015-05-28 22:32:23 +05:30
SOURCE_damage_isoBrittle_ID , &
SOURCE_damage_isoDuctile_ID , &
SOURCE_damage_anisoBrittle_ID , &
2019-05-01 02:36:16 +05:30
SOURCE_damage_anisoDuctile_ID , &
KINEMATICS_undefined_ID , &
2015-05-28 22:32:23 +05:30
KINEMATICS_cleavage_opening_ID , &
KINEMATICS_slipplane_opening_ID , &
2019-05-01 02:36:16 +05:30
KINEMATICS_thermal_expansion_ID , &
STIFFNESS_DEGRADATION_undefined_ID , &
STIFFNESS_DEGRADATION_damage_ID , &
THERMAL_isothermal_ID , &
2015-05-28 22:32:23 +05:30
THERMAL_adiabatic_ID , &
2019-05-01 02:36:16 +05:30
THERMAL_conduction_ID , &
DAMAGE_none_ID , &
2015-05-28 22:32:23 +05:30
DAMAGE_local_ID , &
2019-05-01 02:36:16 +05:30
DAMAGE_nonlocal_ID , &
HOMOGENIZATION_undefined_ID , &
2014-03-14 04:50:50 +05:30
HOMOGENIZATION_none_ID , &
2013-12-12 22:39:59 +05:30
HOMOGENIZATION_isostrain_ID , &
2014-10-09 19:38:32 +05:30
HOMOGENIZATION_rgc_ID
2013-11-27 13:35:23 +05:30
end enum
2014-10-11 02:25:09 +05:30
integer ( kind ( ELASTICITY_undefined_ID ) ) , dimension ( : ) , allocatable , public , protected :: &
2015-10-14 00:22:01 +05:30
phase_elasticity !< elasticity of each phase
2014-10-11 02:25:09 +05:30
integer ( kind ( PLASTICITY_undefined_ID ) ) , dimension ( : ) , allocatable , public , protected :: &
2015-10-14 00:22:01 +05:30
phase_plasticity !< plasticity of each phase
2015-05-28 22:32:23 +05:30
integer ( kind ( THERMAL_isothermal_ID ) ) , dimension ( : ) , allocatable , public , protected :: &
2015-10-14 00:22:01 +05:30
thermal_type !< thermal transport model
2015-05-28 22:32:23 +05:30
integer ( kind ( DAMAGE_none_ID ) ) , dimension ( : ) , allocatable , public , protected :: &
2015-10-14 00:22:01 +05:30
damage_type !< nonlocal damage model
2015-05-28 22:32:23 +05:30
integer ( kind ( SOURCE_undefined_ID ) ) , dimension ( : , : ) , allocatable , public , protected :: &
phase_source , & !< active sources mechanisms of each phase
2015-10-14 00:22:01 +05:30
phase_kinematics , & !< active kinematic mechanisms of each phase
phase_stiffnessDegradation !< active stiffness degradation mechanisms of each phase
2014-07-02 17:57:39 +05:30
2013-12-13 19:44:17 +05:30
integer ( kind ( HOMOGENIZATION_undefined_ID ) ) , dimension ( : ) , allocatable , public , protected :: &
2013-11-27 13:35:23 +05:30
homogenization_type !< type of each homogenization
2019-05-15 02:14:38 +05:30
integer , public , protected :: &
2018-06-10 21:31:52 +05:30
homogenization_maxNgrains !< max number of grains in any USED homogenization
2015-10-14 00:22:01 +05:30
2019-05-15 02:14:38 +05:30
integer , dimension ( : ) , allocatable , public , protected :: &
2015-05-28 22:32:23 +05:30
phase_Nsources , & !< number of source mechanisms active in each phase
phase_Nkinematics , & !< number of kinematic mechanisms active in each phase
2015-07-24 20:23:50 +05:30
phase_NstiffnessDegradations , & !< number of stiffness degradation mechanisms active in each phase
phase_Noutput , & !< number of '(output)' items per phase
phase_elasticityInstance , & !< instance of particular elasticity of each phase
2018-10-14 15:57:42 +05:30
phase_plasticityInstance , & !< instance of particular plasticity of each phase
crystallite_Noutput , & !< number of '(output)' items per crystallite setting
2013-02-20 03:42:05 +05:30
homogenization_Ngrains , & !< number of grains in each homogenization
homogenization_Noutput , & !< number of '(output)' items per homogenization
homogenization_typeInstance , & !< instance of particular type of each homogenization
2015-05-28 22:32:23 +05:30
thermal_typeInstance , & !< instance of particular type of each thermal transport
damage_typeInstance , & !< instance of particular type of each nonlocal damage
2018-10-14 15:57:42 +05:30
microstructure_crystallite !< crystallite setting ID of each microstructure ! DEPRECATED !!!!
2012-03-09 01:55:28 +05:30
2015-07-24 20:23:50 +05:30
real ( pReal ) , dimension ( : ) , allocatable , public , protected :: &
2015-10-14 00:22:01 +05:30
thermal_initialT , & !< initial temperature per each homogenization
2018-12-30 15:11:11 +05:30
damage_initialPhi !< initial damage per each homogenization
2015-07-24 20:23:50 +05:30
2018-10-14 15:57:42 +05:30
! NEW MAPPINGS
2019-04-04 16:55:29 +05:30
integer , dimension ( : ) , allocatable , public , protected :: & ! (elem)
2019-06-07 11:48:37 +05:30
material_homogenizationAt !< homogenization ID of each element (copy of discretization_homogenizationAt)
2019-04-04 16:55:29 +05:30
integer , dimension ( : , : ) , allocatable , public , protected :: & ! (ip,elem)
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,ip,elem)
material_phaseMemberAt !< position of the element within its phase instance
2018-10-14 15:57:42 +05:30
! END NEW MAPPINGS
! DEPRECATED: use material_phaseAt
2019-05-15 02:14:38 +05:30
integer , dimension ( : , : , : ) , allocatable , public :: &
2014-05-08 20:25:19 +05:30
material_phase !< phase (index) of each grain,IP,element
2018-10-14 15:57:42 +05:30
2014-12-19 19:31:03 +05:30
type ( tPlasticState ) , allocatable , dimension ( : ) , public :: &
plasticState
2015-05-28 22:32:23 +05:30
type ( tSourceState ) , allocatable , dimension ( : ) , public :: &
sourceState
type ( tState ) , allocatable , dimension ( : ) , public :: &
homogState , &
thermalState , &
2018-12-30 15:11:11 +05:30
damageState
2014-05-08 20:25:19 +05:30
2019-05-15 02:14:38 +05:30
integer , dimension ( : , : , : ) , allocatable , public , protected :: &
2019-06-07 17:09:01 +05:30
material_texture !< texture (index) of each grain,IP,element. Used only by plastic_nonlocal
2015-10-14 00:22:01 +05:30
2013-12-16 16:26:56 +05:30
real ( pReal ) , dimension ( : , : , : , : ) , allocatable , public , protected :: &
2013-02-20 03:42:05 +05:30
material_EulerAngles !< initial orientation of each grain,IP,element
2015-10-14 00:22:01 +05:30
2013-12-16 16:26:56 +05:30
logical , dimension ( : ) , allocatable , public , protected :: &
2015-10-14 00:22:01 +05:30
microstructure_active , &
2013-02-20 03:42:05 +05:30
phase_localPlasticity !< flags phases with local constitutive law
2012-03-09 01:55:28 +05:30
2019-05-15 02:14:38 +05:30
integer , private :: &
2019-06-07 17:09:01 +05:30
microstructure_maxNconstituents !< max number of constituents in any phase
2012-03-09 01:55:28 +05:30
2019-05-15 02:14:38 +05:30
integer , dimension ( : ) , allocatable , private :: &
2019-06-07 17:09:01 +05:30
microstructure_Nconstituents !< number of constituents in each microstructure
2015-10-14 00:22:01 +05:30
2019-05-15 02:14:38 +05:30
integer , dimension ( : , : ) , allocatable , private :: &
2013-02-20 03:42:05 +05:30
microstructure_phase , & !< phase IDs of each microstructure
microstructure_texture !< texture IDs of each microstructure
2015-10-14 00:22:01 +05:30
2013-12-16 16:26:56 +05:30
real ( pReal ) , dimension ( : , : ) , allocatable , private :: &
2019-06-07 17:17:38 +05:30
texture_Gauss , & !< data of each Gauss component
2013-02-20 03:42:05 +05:30
microstructure_fraction !< vol fraction of each constituent in microstructure
2015-10-14 00:22:01 +05:30
2013-12-16 16:26:56 +05:30
real ( pReal ) , dimension ( : , : , : ) , allocatable , private :: &
2013-07-24 16:39:39 +05:30
texture_transformation !< transformation for each texture
2015-10-14 00:22:01 +05:30
2013-12-16 16:26:56 +05:30
logical , dimension ( : ) , allocatable , private :: &
2012-03-09 01:55:28 +05:30
homogenization_active
2015-10-14 00:22:01 +05:30
2018-10-14 15:57:42 +05:30
! BEGIN DEPRECATED
2019-05-15 02:14:38 +05:30
integer , dimension ( : , : , : ) , allocatable , public :: phaseAt !< phase ID of every material point (ipc,ip,el)
integer , dimension ( : , : , : ) , allocatable , public :: phasememberAt !< memberID of given phase at every material point (ipc,ip,el)
2018-10-14 15:57:42 +05:30
2019-05-15 02:14:38 +05:30
integer , dimension ( : , : , : ) , allocatable , public , target :: mappingHomogenization !< mapping from material points to offset in heterogenous state/field
integer , dimension ( : , : ) , allocatable , private , target :: mappingHomogenizationConst !< mapping from material points to offset in constant state/field
2018-10-14 15:57:42 +05:30
! END DEPRECATED
2015-10-14 00:22:01 +05:30
2015-05-28 22:32:23 +05:30
type ( tHomogMapping ) , allocatable , dimension ( : ) , public :: &
thermalMapping , & !< mapping for thermal state/fields
2018-12-30 15:11:11 +05:30
damageMapping !< mapping for damage state/fields
2015-10-14 00:22:01 +05:30
2018-08-20 19:39:40 +05:30
type ( group_float ) , allocatable , dimension ( : ) , public :: &
2015-05-28 22:32:23 +05:30
temperature , & !< temperature field
damage , & !< damage field
2018-12-22 13:30:57 +05:30
temperatureRate !< temperature change rate field
2014-09-18 20:57:52 +05:30
2013-10-16 18:34:59 +05:30
public :: &
2013-11-27 13:35:23 +05:30
material_init , &
2018-10-16 02:08:34 +05:30
material_allocatePlasticState , &
2019-02-13 11:52:37 +05:30
material_allocateSourceState , &
2013-12-16 16:26:56 +05:30
ELASTICITY_hooke_ID , &
2013-11-27 13:35:23 +05:30
PLASTICITY_none_ID , &
2016-01-09 01:15:20 +05:30
PLASTICITY_isotropic_ID , &
2013-11-27 13:35:23 +05:30
PLASTICITY_phenopowerlaw_ID , &
2017-09-30 04:06:28 +05:30
PLASTICITY_kinehardening_ID , &
2013-11-27 13:35:23 +05:30
PLASTICITY_dislotwin_ID , &
2015-01-15 16:26:15 +05:30
PLASTICITY_disloucla_ID , &
2013-11-27 13:35:23 +05:30
PLASTICITY_nonlocal_ID , &
2015-05-28 22:32:23 +05:30
SOURCE_thermal_dissipation_ID , &
2015-07-27 16:39:37 +05:30
SOURCE_thermal_externalheat_ID , &
2015-05-28 22:32:23 +05:30
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 , &
2014-03-14 04:50:50 +05:30
HOMOGENIZATION_none_ID , &
2013-11-27 13:35:23 +05:30
HOMOGENIZATION_isostrain_ID , &
HOMOGENIZATION_RGC_ID
2013-10-16 18:34:59 +05:30
private :: &
material_parseHomogenization , &
material_parseMicrostructure , &
material_parseCrystallite , &
material_parsePhase , &
material_parseTexture , &
material_populateGrains
2012-03-09 01:55:28 +05:30
contains
2009-03-04 17:18:54 +05:30
2013-01-18 17:00:52 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief parses material configuration file
2015-10-14 00:22:01 +05:30
!> @details figures out if solverJobName.materialConfig is present, if not looks for
2013-01-18 17:00:52 +05:30
!> material.config
!--------------------------------------------------------------------------------------------------
2019-04-04 16:55:29 +05:30
subroutine material_init
2015-10-14 00:22:01 +05:30
2019-05-15 02:14:38 +05:30
integer , parameter :: FILEUNIT = 210
integer :: m , c , h , myDebug , myPhase , myHomog
integer :: &
2014-06-23 00:28:29 +05:30
g , & !< grain number
i , & !< integration point number
2018-10-14 15:57:42 +05:30
e !< element number
2019-05-15 02:14:38 +05:30
integer , dimension ( : ) , allocatable :: &
2018-11-24 14:23:18 +05:30
CounterPhase , &
CounterHomogenization
2014-09-23 02:06:55 +05:30
2012-07-05 15:24:50 +05:30
myDebug = debug_level ( debug_material )
2015-10-14 00:22:01 +05:30
2018-06-02 13:09:05 +05:30
write ( 6 , '(/,a)' ) ' <<<+- material init -+>>>'
2013-01-18 17:00:52 +05:30
2018-06-11 03:46:48 +05:30
call material_parsePhase ( )
2019-05-15 02:14:38 +05:30
if ( iand ( myDebug , debug_levelBasic ) / = 0 ) write ( 6 , '(a)' ) ' Phase parsed' ; flush ( 6 )
2018-06-11 03:46:48 +05:30
call material_parseMicrostructure ( )
2019-05-15 02:14:38 +05:30
if ( iand ( myDebug , debug_levelBasic ) / = 0 ) write ( 6 , '(a)' ) ' Microstructure parsed' ; flush ( 6 )
2018-06-11 03:46:48 +05:30
call material_parseCrystallite ( )
2019-05-15 02:14:38 +05:30
if ( iand ( myDebug , debug_levelBasic ) / = 0 ) write ( 6 , '(a)' ) ' Crystallite parsed' ; flush ( 6 )
2018-06-11 03:46:48 +05:30
call material_parseHomogenization ( )
2019-05-15 02:14:38 +05:30
if ( iand ( myDebug , debug_levelBasic ) / = 0 ) write ( 6 , '(a)' ) ' Homogenization parsed' ; flush ( 6 )
2018-06-11 03:46:48 +05:30
call material_parseTexture ( )
2019-05-15 02:14:38 +05:30
if ( iand ( myDebug , debug_levelBasic ) / = 0 ) write ( 6 , '(a)' ) ' Texture parsed' ; flush ( 6 )
2018-06-02 22:57:03 +05:30
2018-06-27 00:24:54 +05:30
allocate ( plasticState ( size ( config_phase ) ) )
allocate ( sourceState ( size ( config_phase ) ) )
do myPhase = 1 , size ( config_phase )
2015-05-28 22:32:23 +05:30
allocate ( sourceState ( myPhase ) % p ( phase_Nsources ( myPhase ) ) )
2015-10-14 00:22:01 +05:30
enddo
2018-06-27 00:24:54 +05:30
allocate ( homogState ( size ( config_homogenization ) ) )
allocate ( thermalState ( size ( config_homogenization ) ) )
allocate ( damageState ( size ( config_homogenization ) ) )
allocate ( thermalMapping ( size ( config_homogenization ) ) )
allocate ( damageMapping ( size ( config_homogenization ) ) )
allocate ( temperature ( size ( config_homogenization ) ) )
allocate ( damage ( size ( config_homogenization ) ) )
allocate ( temperatureRate ( size ( config_homogenization ) ) )
2019-05-15 02:14:38 +05:30
do m = 1 , size ( config_microstructure )
if ( microstructure_crystallite ( m ) < 1 . or . &
2018-06-27 00:24:54 +05:30
microstructure_crystallite ( m ) > size ( config_crystallite ) ) &
2019-05-15 02:14:38 +05:30
call IO_error ( 150 , m , ext_msg = 'crystallite' )
if ( minval ( microstructure_phase ( 1 : microstructure_Nconstituents ( m ) , m ) ) < 1 . or . &
2018-06-27 00:24:54 +05:30
maxval ( microstructure_phase ( 1 : microstructure_Nconstituents ( m ) , m ) ) > size ( config_phase ) ) &
2019-05-15 02:14:38 +05:30
call IO_error ( 150 , m , ext_msg = 'phase' )
if ( minval ( microstructure_texture ( 1 : microstructure_Nconstituents ( m ) , m ) ) < 1 . or . &
2018-06-27 00:24:54 +05:30
maxval ( microstructure_texture ( 1 : microstructure_Nconstituents ( m ) , m ) ) > size ( config_texture ) ) &
2019-05-15 02:14:38 +05:30
call IO_error ( 150 , m , ext_msg = 'texture' )
if ( microstructure_Nconstituents ( m ) < 1 ) &
call IO_error ( 151 , m )
2009-03-04 17:18:54 +05:30
enddo
2015-10-14 00:22:01 +05:30
2019-05-15 02:14:38 +05:30
debugOut : if ( iand ( myDebug , debug_levelExtensive ) / = 0 ) then
2013-01-18 17:00:52 +05:30
write ( 6 , '(/,a,/)' ) ' MATERIAL configuration'
write ( 6 , '(a32,1x,a16,1x,a6)' ) 'homogenization ' , 'type ' , 'grains'
2019-05-15 02:14:38 +05:30
do h = 1 , size ( config_homogenization )
2013-05-29 22:53:49 +05:30
write ( 6 , '(1x,a32,1x,a16,1x,i6)' ) homogenization_name ( h ) , homogenization_type ( h ) , homogenization_Ngrains ( h )
2013-01-18 17:00:52 +05:30
enddo
2019-06-05 00:46:18 +05:30
write ( 6 , '(/,a14,18x,1x,a11,1x,a12,1x,a13)' ) 'microstructure' , 'crystallite' , 'constituents'
2019-05-15 02:14:38 +05:30
do m = 1 , size ( config_microstructure )
2019-06-05 00:46:18 +05:30
write ( 6 , '(1x,a32,1x,i11,1x,i12)' ) microstructure_name ( m ) , &
microstructure_crystallite ( m ) , &
microstructure_Nconstituents ( m )
2019-05-15 02:14:38 +05:30
if ( microstructure_Nconstituents ( m ) > 0 ) then
do c = 1 , microstructure_Nconstituents ( m )
2013-03-28 19:20:20 +05:30
write ( 6 , '(a1,1x,a32,1x,a32,1x,f7.4)' ) '>' , phase_name ( microstructure_phase ( c , m ) ) , &
texture_name ( microstructure_texture ( c , m ) ) , &
microstructure_fraction ( c , m )
2013-01-18 17:00:52 +05:30
enddo
write ( 6 , * )
endif
enddo
2013-03-28 19:20:20 +05:30
endif debugOut
2015-10-14 00:22:01 +05:30
2012-03-09 01:55:28 +05:30
call material_populateGrains
2019-04-04 16:55:29 +05:30
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! new mappings
2019-06-07 11:19:45 +05:30
allocate ( material_homogenizationAt , source = discretization_homogenizationAt )
2019-06-07 09:48:42 +05:30
allocate ( material_homogenizationMemberAt ( discretization_nIP , discretization_nElem ) , source = 0 )
2019-04-04 16:55:29 +05:30
allocate ( CounterHomogenization ( size ( config_homogenization ) ) , source = 0 )
2019-06-07 09:48:42 +05:30
do e = 1 , discretization_nElem
do i = 1 , discretization_nIP
2019-04-04 16:55:29 +05:30
CounterHomogenization ( material_homogenizationAt ( e ) ) = &
CounterHomogenization ( material_homogenizationAt ( e ) ) + 1
material_homogenizationMemberAt ( i , e ) = CounterHomogenization ( material_homogenizationAt ( e ) )
enddo
enddo
2009-03-04 17:18:54 +05:30
2019-04-04 16:55:29 +05:30
2019-06-07 09:48:42 +05:30
allocate ( material_phaseAt ( homogenization_maxNgrains , discretization_nElem ) , source = material_phase ( : , 1 , : ) )
allocate ( material_phaseMemberAt ( homogenization_maxNgrains , discretization_nIP , discretization_nElem ) , source = 0 )
2019-04-04 16:55:29 +05:30
allocate ( CounterPhase ( size ( config_phase ) ) , source = 0 )
2019-06-07 09:48:42 +05:30
do e = 1 , discretization_nElem
do i = 1 , discretization_nIP
2019-04-04 16:55:29 +05:30
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
2019-04-04 19:52:33 +05:30
2019-04-05 20:23:41 +05:30
#if defined(PETSc) || defined(DAMASK_HDF5)
2019-04-04 19:52:33 +05:30
call results_openJobFile
2019-04-05 17:32:24 +05:30
call results_mapping_constituent ( material_phaseAt , material_phaseMemberAt , phase_name )
2019-04-05 20:23:41 +05:30
call results_mapping_materialpoint ( material_homogenizationAt , material_homogenizationMemberAt , homogenization_name )
2019-04-04 19:52:33 +05:30
call results_closeJobFile
2019-04-05 17:32:24 +05:30
#endif
2019-04-04 16:55:29 +05:30
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2018-10-14 15:57:42 +05:30
! BEGIN DEPRECATED
2019-06-07 09:48:42 +05:30
allocate ( phaseAt ( homogenization_maxNgrains , discretization_nIP , discretization_nElem ) , source = 0 )
allocate ( phasememberAt ( homogenization_maxNgrains , discretization_nIP , discretization_nElem ) , source = 0 )
allocate ( mappingHomogenization ( 2 , discretization_nIP , discretization_nElem ) , source = 0 )
allocate ( mappingHomogenizationConst ( discretization_nIP , discretization_nElem ) , source = 1 )
2019-03-10 15:53:39 +05:30
2019-04-04 16:55:29 +05:30
CounterHomogenization = 0
CounterPhase = 0
2014-09-18 20:57:52 +05:30
2019-06-07 09:48:42 +05:30
do e = 1 , discretization_nElem
2019-06-07 11:19:45 +05:30
myHomog = discretization_homogenizationAt ( e )
2019-06-07 09:48:42 +05:30
do i = 1 , discretization_nIP
2019-05-15 02:14:38 +05:30
CounterHomogenization ( myHomog ) = CounterHomogenization ( myHomog ) + 1
2019-03-10 15:53:39 +05:30
mappingHomogenization ( 1 : 2 , i , e ) = [ CounterHomogenization ( myHomog ) , huge ( 1 ) ]
2019-05-15 02:14:38 +05:30
do g = 1 , homogenization_Ngrains ( myHomog )
2018-10-14 15:57:42 +05:30
myPhase = material_phase ( g , i , e )
2019-05-15 02:14:38 +05:30
CounterPhase ( myPhase ) = CounterPhase ( myPhase ) + 1 ! not distinguishing between instances of same phase
2018-10-14 15:57:42 +05:30
phaseAt ( g , i , e ) = myPhase
2018-11-24 14:23:18 +05:30
phasememberAt ( g , i , e ) = CounterPhase ( myPhase )
2018-10-14 15:57:42 +05:30
enddo
enddo
enddo
! END DEPRECATED
2014-06-24 19:21:17 +05:30
2018-10-14 15:57:42 +05:30
! REMOVE !!!!!
2015-05-28 22:32:23 +05:30
! hack needed to initialize field values used during constitutive and crystallite initializations
2018-06-27 00:24:54 +05:30
do myHomog = 1 , size ( config_homogenization )
2015-05-28 22:32:23 +05:30
thermalMapping ( myHomog ) % p = > mappingHomogenizationConst
damageMapping ( myHomog ) % p = > mappingHomogenizationConst
2015-07-24 20:23:50 +05:30
allocate ( temperature ( myHomog ) % p ( 1 ) , source = thermal_initialT ( myHomog ) )
allocate ( damage ( myHomog ) % p ( 1 ) , source = damage_initialPhi ( myHomog ) )
2015-05-28 22:32:23 +05:30
allocate ( temperatureRate ( myHomog ) % p ( 1 ) , source = 0.0_pReal )
2014-09-23 02:06:55 +05:30
enddo
2018-10-14 15:57:42 +05:30
2012-03-09 01:55:28 +05:30
end subroutine material_init
2009-03-04 17:18:54 +05:30
2013-01-18 17:00:52 +05:30
!--------------------------------------------------------------------------------------------------
2018-06-11 03:46:48 +05:30
!> @brief parses the homogenization part from the material configuration
2013-01-18 17:00:52 +05:30
!--------------------------------------------------------------------------------------------------
2018-06-10 21:31:52 +05:30
subroutine material_parseHomogenization
2015-10-14 00:22:01 +05:30
2019-05-15 02:14:38 +05:30
integer :: h
2018-06-10 22:08:31 +05:30
character ( len = 65536 ) :: tag
2018-06-02 22:57:03 +05:30
2018-06-27 00:24:54 +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 )
2019-05-15 02:14:38 +05:30
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_Noutput ( size ( config_homogenization ) ) , source = 0 )
2018-06-27 00:24:54 +05:30
allocate ( homogenization_active ( size ( config_homogenization ) ) , source = . false . ) !!!!!!!!!!!!!!!
allocate ( thermal_initialT ( size ( config_homogenization ) ) , source = 30 0.0_pReal )
allocate ( damage_initialPhi ( size ( config_homogenization ) ) , source = 1.0_pReal )
2019-05-15 02:14:38 +05:30
forall ( h = 1 : size ( config_homogenization ) ) &
2019-06-07 11:19:45 +05:30
homogenization_active ( h ) = any ( discretization_homogenizationAt == h )
2018-06-27 00:24:54 +05:30
2019-05-15 02:14:38 +05:30
do h = 1 , size ( config_homogenization )
2018-06-27 00:24:54 +05:30
homogenization_Noutput ( h ) = config_homogenization ( h ) % countKeys ( '(output)' )
tag = config_homogenization ( h ) % getString ( 'mech' )
2018-06-11 03:46:48 +05:30
select case ( trim ( tag ) )
case ( HOMOGENIZATION_NONE_label )
homogenization_type ( h ) = HOMOGENIZATION_NONE_ID
2019-05-15 02:14:38 +05:30
homogenization_Ngrains ( h ) = 1
2018-06-11 03:46:48 +05:30
case ( HOMOGENIZATION_ISOSTRAIN_label )
homogenization_type ( h ) = HOMOGENIZATION_ISOSTRAIN_ID
2018-06-27 00:24:54 +05:30
homogenization_Ngrains ( h ) = config_homogenization ( h ) % getInt ( 'nconstituents' )
2018-06-11 03:46:48 +05:30
case ( HOMOGENIZATION_RGC_label )
homogenization_type ( h ) = HOMOGENIZATION_RGC_ID
2018-06-27 00:24:54 +05:30
homogenization_Ngrains ( h ) = config_homogenization ( h ) % getInt ( 'nconstituents' )
2018-06-11 03:46:48 +05:30
case default
2019-05-15 02:14:38 +05:30
call IO_error ( 500 , ext_msg = trim ( tag ) )
2018-06-11 03:46:48 +05:30
end select
homogenization_typeInstance ( h ) = count ( homogenization_type == homogenization_type ( h ) )
2018-06-02 22:57:03 +05:30
2018-06-27 00:24:54 +05:30
if ( config_homogenization ( h ) % keyExists ( 'thermal' ) ) then
thermal_initialT ( h ) = config_homogenization ( h ) % getFloat ( 't0' , defaultVal = 30 0.0_pReal )
2018-06-11 03:46:48 +05:30
2018-06-27 00:24:54 +05:30
tag = config_homogenization ( h ) % getString ( 'thermal' )
2018-06-11 03:46:48 +05:30
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
2019-05-15 02:14:38 +05:30
call IO_error ( 500 , ext_msg = trim ( tag ) )
2018-06-11 03:46:48 +05:30
end select
endif
2015-05-28 22:32:23 +05:30
2018-06-27 00:24:54 +05:30
if ( config_homogenization ( h ) % keyExists ( 'damage' ) ) then
damage_initialPhi ( h ) = config_homogenization ( h ) % getFloat ( 'initialdamage' , defaultVal = 1.0_pReal )
2018-06-11 03:46:48 +05:30
2018-06-27 00:24:54 +05:30
tag = config_homogenization ( h ) % getString ( 'damage' )
2018-06-11 03:46:48 +05:30
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
2019-05-15 02:14:38 +05:30
call IO_error ( 500 , ext_msg = trim ( tag ) )
2018-06-11 03:46:48 +05:30
end select
endif
2009-03-04 17:18:54 +05:30
enddo
2019-05-15 02:14:38 +05:30
do h = 1 , size ( config_homogenization )
2018-06-02 22:57: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 ) )
2015-05-28 22:32:23 +05:30
enddo
2013-06-27 00:49:00 +05:30
homogenization_maxNgrains = maxval ( homogenization_Ngrains , homogenization_active )
2009-03-04 17:18:54 +05:30
2018-06-10 21:31:52 +05:30
end subroutine material_parseHomogenization
2009-03-04 17:18:54 +05:30
2013-01-18 17:00:52 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief parses the microstructure part in the material configuration file
!--------------------------------------------------------------------------------------------------
2018-06-10 21:31:52 +05:30
subroutine material_parseMicrostructure
2015-10-14 00:22:01 +05:30
2018-06-11 03:46:48 +05:30
character ( len = 65536 ) , dimension ( : ) , allocatable :: &
2018-07-04 02:28:49 +05:30
strings
2019-05-15 02:14:38 +05:30
integer , allocatable , dimension ( : ) :: chunkPos
integer :: e , m , c , i
2013-12-12 22:39:59 +05:30
character ( len = 65536 ) :: &
2018-06-11 03:46:48 +05:30
tag
2010-02-25 23:09:11 +05:30
2019-05-15 02:14:38 +05:30
allocate ( microstructure_crystallite ( size ( config_microstructure ) ) , source = 0 )
allocate ( microstructure_Nconstituents ( size ( config_microstructure ) ) , source = 0 )
2018-06-27 00:24:54 +05:30
allocate ( microstructure_active ( size ( config_microstructure ) ) , source = . false . )
2009-07-22 21:37:19 +05:30
2019-06-07 11:19:45 +05:30
if ( any ( discretization_microstructureAt > size ( config_microstructure ) ) ) &
2019-05-15 02:14:38 +05:30
call IO_error ( 155 , ext_msg = 'More microstructures in geometry than sections in material.config' )
2014-05-15 15:10:43 +05:30
2019-06-07 09:48:42 +05:30
forall ( e = 1 : discretization_nElem ) &
2019-06-07 11:19:45 +05:30
microstructure_active ( discretization_microstructureAt ( e ) ) = . true . ! current microstructure used in model? Elementwise view, maximum N operations for N elements
2015-10-14 00:22:01 +05:30
2019-05-15 02:14:38 +05:30
do m = 1 , size ( config_microstructure )
2018-06-27 00:24:54 +05:30
microstructure_Nconstituents ( m ) = config_microstructure ( m ) % countKeys ( '(constituent)' )
microstructure_crystallite ( m ) = config_microstructure ( m ) % getInt ( 'crystallite' )
2018-06-02 16:53:42 +05:30
enddo
2015-10-14 00:22:01 +05:30
2018-06-02 16:53:42 +05:30
microstructure_maxNconstituents = maxval ( microstructure_Nconstituents )
2019-05-15 02:14:38 +05:30
allocate ( microstructure_phase ( microstructure_maxNconstituents , size ( config_microstructure ) ) , source = 0 )
allocate ( microstructure_texture ( microstructure_maxNconstituents , size ( config_microstructure ) ) , source = 0 )
2018-06-27 00:24:54 +05:30
allocate ( microstructure_fraction ( microstructure_maxNconstituents , size ( config_microstructure ) ) , source = 0.0_pReal )
2015-10-14 00:22:01 +05:30
2018-07-04 02:28:49 +05:30
allocate ( strings ( 1 ) ) ! Intel 16.0 Bug
2019-05-15 02:14:38 +05:30
do m = 1 , size ( config_microstructure )
2018-07-04 02:28:49 +05:30
strings = config_microstructure ( m ) % getStrings ( '(constituent)' , raw = . true . )
2019-05-15 02:14:38 +05:30
do c = 1 , size ( strings )
2018-07-04 02:28:49 +05:30
chunkPos = IO_stringPos ( strings ( c ) )
2018-06-19 22:08:32 +05:30
2019-05-15 02:14:38 +05:30
do i = 1 , 5 , 2
2018-07-04 02:28:49 +05:30
tag = IO_stringValue ( strings ( c ) , chunkPos , i )
2018-06-11 03:46:48 +05:30
select case ( tag )
case ( 'phase' )
2019-05-15 02:14:38 +05:30
microstructure_phase ( c , m ) = IO_intValue ( strings ( c ) , chunkPos , i + 1 )
2018-06-11 03:46:48 +05:30
case ( 'texture' )
2019-05-15 02:14:38 +05:30
microstructure_texture ( c , m ) = IO_intValue ( strings ( c ) , chunkPos , i + 1 )
2018-06-11 03:46:48 +05:30
case ( 'fraction' )
2019-05-15 02:14:38 +05:30
microstructure_fraction ( c , m ) = IO_floatValue ( strings ( c ) , chunkPos , i + 1 )
2018-06-11 03:46:48 +05:30
end select
enddo
enddo
enddo
2009-03-04 17:18:54 +05:30
2019-05-15 02:14:38 +05:30
do m = 1 , size ( config_microstructure )
2018-06-02 16:53:42 +05:30
if ( dNeq ( sum ( microstructure_fraction ( : , m ) ) , 1.0_pReal ) ) &
2019-05-15 02:14:38 +05:30
call IO_error ( 153 , ext_msg = microstructure_name ( m ) )
2018-06-02 16:53:42 +05:30
enddo
2018-06-27 00:03:02 +05:30
2018-06-10 21:31:52 +05:30
end subroutine material_parseMicrostructure
2009-03-04 17:18:54 +05:30
2013-01-18 17:00:52 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief parses the crystallite part in the material configuration file
!--------------------------------------------------------------------------------------------------
2018-06-10 21:31:52 +05:30
subroutine material_parseCrystallite
2010-02-25 23:09:11 +05:30
2019-05-15 02:14:38 +05:30
integer :: c
2012-06-26 15:54:54 +05:30
2019-05-15 02:14:38 +05:30
allocate ( crystallite_Noutput ( size ( config_crystallite ) ) , source = 0 )
do c = 1 , size ( config_crystallite )
2018-06-27 00:24:54 +05:30
crystallite_Noutput ( c ) = config_crystallite ( c ) % countKeys ( '(output)' )
2018-06-02 16:53:42 +05:30
enddo
2018-06-10 21:31:52 +05:30
end subroutine material_parseCrystallite
2010-02-25 23:09:11 +05:30
2013-01-18 17:00:52 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief parses the phase part in the material configuration file
!--------------------------------------------------------------------------------------------------
2018-06-10 21:31:52 +05:30
subroutine material_parsePhase
2013-03-28 19:20:20 +05:30
2019-05-15 02:14:38 +05:30
integer :: sourceCtr , kinematicsCtr , stiffDegradationCtr , p
2018-06-22 02:09:18 +05:30
character ( len = 65536 ) , dimension ( : ) , allocatable :: str
2012-06-26 15:54:54 +05:30
2015-10-14 00:22:01 +05:30
2018-06-27 00:24:54 +05:30
allocate ( phase_elasticity ( size ( config_phase ) ) , source = ELASTICITY_undefined_ID )
allocate ( phase_plasticity ( size ( config_phase ) ) , source = PLASTICITY_undefined_ID )
2019-05-15 02:14:38 +05:30
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_Noutput ( size ( config_phase ) ) , source = 0 )
2018-06-27 00:24:54 +05:30
allocate ( phase_localPlasticity ( size ( config_phase ) ) , source = . false . )
2018-06-02 16:53:42 +05:30
2019-05-15 02:14:38 +05:30
do p = 1 , size ( config_phase )
2018-06-27 00:24:54 +05:30
phase_Noutput ( p ) = config_phase ( p ) % countKeys ( '(output)' )
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/' )
2018-06-02 13:09:05 +05:30
2018-06-27 00:24:54 +05:30
select case ( config_phase ( p ) % getString ( 'elasticity' ) )
2018-06-02 13:09:05 +05:30
case ( ELASTICITY_HOOKE_label )
phase_elasticity ( p ) = ELASTICITY_HOOKE_ID
case default
2019-05-15 02:14:38 +05:30
call IO_error ( 200 , ext_msg = trim ( config_phase ( p ) % getString ( 'elasticity' ) ) )
2018-06-02 13:09:05 +05:30
end select
2018-06-27 00:24:54 +05:30
select case ( config_phase ( p ) % getString ( 'plasticity' ) )
2018-06-02 13:09:05 +05:30
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
2019-05-15 02:14:38 +05:30
call IO_error ( 201 , ext_msg = trim ( config_phase ( p ) % getString ( 'plasticity' ) ) )
2018-06-02 13:09:05 +05:30
end select
enddo
2018-06-27 00:24:54 +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 ) ) , &
2018-06-02 13:09:05 +05:30
source = STIFFNESS_DEGRADATION_undefined_ID )
2019-05-15 02:14:38 +05:30
do p = 1 , size ( config_phase )
2019-03-10 13:43:25 +05:30
#if defined(__GFORTRAN__) || defined(__PGI)
2018-06-22 11:33:22 +05:30
str = [ 'GfortranBug86277' ]
2018-06-27 00:24:54 +05:30
str = config_phase ( p ) % getStrings ( '(source)' , defaultVal = str )
2018-06-22 11:33:22 +05:30
if ( str ( 1 ) == 'GfortranBug86277' ) str = [ character ( len = 65536 ) :: ]
#else
2018-06-27 00:24:54 +05:30
str = config_phase ( p ) % getStrings ( '(source)' , defaultVal = [ character ( len = 65536 ) :: ] )
2018-06-22 11:33:22 +05:30
#endif
2019-05-15 02:14:38 +05:30
do sourceCtr = 1 , size ( str )
2018-06-22 03:19:07 +05:30
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
2019-03-10 13:43:25 +05:30
#if defined(__GFORTRAN__) || defined(__PGI)
2018-06-22 11:33:22 +05:30
str = [ 'GfortranBug86277' ]
2018-06-27 00:24:54 +05:30
str = config_phase ( p ) % getStrings ( '(kinematics)' , defaultVal = str )
2018-06-22 11:33:22 +05:30
if ( str ( 1 ) == 'GfortranBug86277' ) str = [ character ( len = 65536 ) :: ]
#else
2018-06-27 00:24:54 +05:30
str = config_phase ( p ) % getStrings ( '(kinematics)' , defaultVal = [ character ( len = 65536 ) :: ] )
2018-06-22 11:33:22 +05:30
#endif
2019-05-15 02:14:38 +05:30
do kinematicsCtr = 1 , size ( str )
2018-06-22 03:19:07 +05:30
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
2019-03-10 13:43:25 +05:30
#if defined(__GFORTRAN__) || defined(__PGI)
2018-06-22 11:33:22 +05:30
str = [ 'GfortranBug86277' ]
2018-06-27 00:24:54 +05:30
str = config_phase ( p ) % getStrings ( '(stiffness_degradation)' , defaultVal = str )
2018-06-22 11:33:22 +05:30
if ( str ( 1 ) == 'GfortranBug86277' ) str = [ character ( len = 65536 ) :: ]
#else
2018-06-27 00:24:54 +05:30
str = config_phase ( p ) % getStrings ( '(stiffness_degradation)' , defaultVal = [ character ( len = 65536 ) :: ] )
2018-06-22 11:33:22 +05:30
#endif
2019-05-15 02:14:38 +05:30
do stiffDegradationCtr = 1 , size ( str )
2018-06-22 03:19:07 +05:30
select case ( trim ( str ( stiffDegradationCtr ) ) )
case ( STIFFNESS_DEGRADATION_damage_label )
phase_stiffnessDegradation ( stiffDegradationCtr , p ) = STIFFNESS_DEGRADATION_damage_ID
end select
enddo
2009-03-04 17:18:54 +05:30
enddo
2019-05-15 02:14:38 +05:30
allocate ( phase_plasticityInstance ( size ( config_phase ) ) , source = 0 )
allocate ( phase_elasticityInstance ( size ( config_phase ) ) , source = 0 )
2018-06-02 13:09:05 +05:30
2019-05-15 02:14:38 +05:30
do p = 1 , size ( config_phase )
2015-05-28 22:32:23 +05:30
phase_elasticityInstance ( p ) = count ( phase_elasticity ( 1 : p ) == phase_elasticity ( p ) )
phase_plasticityInstance ( p ) = count ( phase_plasticity ( 1 : p ) == phase_plasticity ( p ) )
2014-10-15 17:52:09 +05:30
enddo
2009-03-04 17:18:54 +05:30
2018-06-10 21:31:52 +05:30
end subroutine material_parsePhase
2014-10-15 17:52:09 +05:30
2013-01-18 17:00:52 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief parses the texture part in the material configuration file
!--------------------------------------------------------------------------------------------------
2018-06-10 21:31:52 +05:30
subroutine material_parseTexture
2015-10-14 00:22:01 +05:30
2019-06-07 17:17:38 +05:30
integer :: section , j , t , i
character ( len = 65536 ) , dimension ( : ) , allocatable :: strings ! Values for given key in material config
integer , dimension ( : ) , allocatable :: chunkPos
2009-03-04 17:18:54 +05:30
2015-10-14 00:22:01 +05:30
2019-06-07 17:17:38 +05:30
do t = 1 , size ( config_texture )
if ( config_texture ( t ) % countKeys ( '(gauss)' ) / = 1 ) call IO_error ( 147 , ext_msg = 'count((gauss)) !=1' )
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
2018-06-19 22:46:03 +05:30
2019-06-07 17:17:38 +05:30
allocate ( texture_Gauss ( 5 , size ( config_texture ) ) , source = 0.0_pReal )
allocate ( texture_transformation ( 3 , 3 , size ( config_texture ) ) , source = 0.0_pReal )
texture_transformation = spread ( math_I3 , 3 , size ( config_texture ) )
do t = 1 , size ( config_texture )
section = t
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' )
texture_transformation ( j , 1 : 3 , t ) = [ 1.0_pReal , 0.0_pReal , 0.0_pReal ] ! original axis is now +x-axis
case ( '-x' )
texture_transformation ( j , 1 : 3 , t ) = [ - 1.0_pReal , 0.0_pReal , 0.0_pReal ] ! original axis is now -x-axis
case ( 'y' , '+y' )
texture_transformation ( j , 1 : 3 , t ) = [ 0.0_pReal , 1.0_pReal , 0.0_pReal ] ! original axis is now +y-axis
case ( '-y' )
texture_transformation ( j , 1 : 3 , t ) = [ 0.0_pReal , - 1.0_pReal , 0.0_pReal ] ! original axis is now -y-axis
case ( 'z' , '+z' )
texture_transformation ( j , 1 : 3 , t ) = [ 0.0_pReal , 0.0_pReal , 1.0_pReal ] ! original axis is now +z-axis
case ( '-z' )
texture_transformation ( j , 1 : 3 , t ) = [ 0.0_pReal , 0.0_pReal , - 1.0_pReal ] ! original axis is now -z-axis
case default
call IO_error ( 157 , t )
end select
2018-06-25 18:58:15 +05:30
enddo
2019-06-07 17:17:38 +05:30
if ( dNeq ( math_det33 ( texture_transformation ( 1 : 3 , 1 : 3 , t ) ) , 1.0_pReal ) ) call IO_error ( 157 , t )
endif
strings = config_texture ( t ) % getStrings ( '(gauss)' , raw = . true . )
do i = 1 , size ( strings )
chunkPos = IO_stringPos ( strings ( i ) )
do j = 1 , 9 , 2
select case ( IO_stringValue ( strings ( i ) , chunkPos , j ) )
case ( 'phi1' )
texture_Gauss ( 1 , t ) = IO_floatValue ( strings ( i ) , chunkPos , j + 1 ) * inRad
case ( 'phi' )
texture_Gauss ( 2 , t ) = IO_floatValue ( strings ( i ) , chunkPos , j + 1 ) * inRad
case ( 'phi2' )
texture_Gauss ( 3 , t ) = IO_floatValue ( strings ( i ) , chunkPos , j + 1 ) * inRad
end select
enddo
enddo
enddo
call config_deallocate ( 'material.config/texture' )
2009-03-04 17:18:54 +05:30
2018-06-10 21:31:52 +05:30
end subroutine material_parseTexture
2009-03-04 17:18:54 +05:30
2018-10-14 23:46:30 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief allocates the plastic state of a phase
!--------------------------------------------------------------------------------------------------
2019-01-25 05:15:25 +05:30
subroutine material_allocatePlasticState ( phase , NofMyPhase , &
sizeState , sizeDotState , sizeDeltaState , &
2018-10-14 23:46:30 +05:30
Nslip , Ntwin , Ntrans )
2019-05-15 02:14:38 +05:30
integer , intent ( in ) :: &
2018-10-14 23:46:30 +05:30
phase , &
NofMyPhase , &
sizeState , &
sizeDotState , &
sizeDeltaState , &
Nslip , &
Ntwin , &
Ntrans
2019-01-25 05:15:25 +05:30
plasticState ( phase ) % sizeState = sizeState
plasticState ( phase ) % sizeDotState = sizeDotState
plasticState ( phase ) % sizeDeltaState = sizeDeltaState
plasticState ( phase ) % offsetDeltaState = sizeState - sizeDeltaState ! deltaState occupies latter part of state by definition
2018-10-14 23:46:30 +05:30
plasticState ( phase ) % Nslip = Nslip
plasticState ( phase ) % Ntwin = Ntwin
plasticState ( phase ) % Ntrans = Ntrans
allocate ( plasticState ( phase ) % aTolState ( sizeState ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % state0 ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % partionedState0 ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % subState0 ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % state ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % dotState ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
2019-05-15 02:14:38 +05:30
if ( numerics_integrator == 1 ) then
2018-10-14 23:46:30 +05:30
allocate ( plasticState ( phase ) % previousDotState ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % previousDotState2 ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
endif
2019-05-15 02:14:38 +05:30
if ( numerics_integrator == 4 ) &
2018-10-14 23:46:30 +05:30
allocate ( plasticState ( phase ) % RK4dotState ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
2019-05-15 02:14:38 +05:30
if ( numerics_integrator == 5 ) &
2018-10-14 23:46:30 +05:30
allocate ( plasticState ( phase ) % RKCK45dotState ( 6 , sizeDotState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % deltaState ( sizeDeltaState , NofMyPhase ) , source = 0.0_pReal )
end subroutine material_allocatePlasticState
2019-02-13 11:52:37 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief allocates the source state of a phase
!--------------------------------------------------------------------------------------------------
2019-02-13 14:41:25 +05:30
subroutine material_allocateSourceState ( phase , of , NofMyPhase , &
sizeState , sizeDotState , sizeDeltaState )
2019-02-13 11:52:37 +05:30
2019-05-15 02:14:38 +05:30
integer , intent ( in ) :: &
2019-02-13 11:52:37 +05:30
phase , &
of , &
NofMyPhase , &
2019-02-13 14:41:25 +05:30
sizeState , sizeDotState , sizeDeltaState
2019-02-13 11:52:37 +05:30
sourceState ( phase ) % p ( of ) % sizeState = sizeState
2019-02-13 14:41:25 +05:30
sourceState ( phase ) % p ( of ) % sizeDotState = sizeDotState
sourceState ( phase ) % p ( of ) % sizeDeltaState = sizeDeltaState
2019-02-27 11:51:40 +05:30
sourceState ( phase ) % p ( of ) % offsetDeltaState = sizeState - sizeDeltaState ! deltaState occupies latter part of state by definition
2019-02-13 11:52:37 +05:30
allocate ( sourceState ( phase ) % p ( of ) % aTolState ( sizeState ) , source = 0.0_pReal )
allocate ( sourceState ( phase ) % p ( of ) % state0 ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( sourceState ( phase ) % p ( of ) % partionedState0 ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( sourceState ( phase ) % p ( of ) % subState0 ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( sourceState ( phase ) % p ( of ) % state ( sizeState , NofMyPhase ) , source = 0.0_pReal )
2019-02-13 14:41:25 +05:30
allocate ( sourceState ( phase ) % p ( of ) % dotState ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
2019-05-15 02:14:38 +05:30
if ( numerics_integrator == 1 ) then
2019-02-13 14:41:25 +05:30
allocate ( sourceState ( phase ) % p ( of ) % previousDotState ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
allocate ( sourceState ( phase ) % p ( of ) % previousDotState2 ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
2019-02-13 11:52:37 +05:30
endif
2019-05-15 02:14:38 +05:30
if ( numerics_integrator == 4 ) &
2019-02-13 14:41:25 +05:30
allocate ( sourceState ( phase ) % p ( of ) % RK4dotState ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
2019-05-15 02:14:38 +05:30
if ( numerics_integrator == 5 ) &
2019-02-13 14:41:25 +05:30
allocate ( sourceState ( phase ) % p ( of ) % RKCK45dotState ( 6 , sizeDotState , NofMyPhase ) , source = 0.0_pReal )
2019-02-13 11:52:37 +05:30
2019-02-23 01:36:37 +05:30
allocate ( sourceState ( phase ) % p ( of ) % deltaState ( sizeDeltaState , NofMyPhase ) , source = 0.0_pReal )
2019-02-13 11:52:37 +05:30
end subroutine material_allocateSourceState
2013-01-18 17:00:52 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief populates the grains
!> @details populates the grains by identifying active microstructure/homogenization pairs,
2018-10-14 13:41:26 +05:30
!! calculates the volume of the grains and deals with texture components
2013-01-18 17:00:52 +05:30
!--------------------------------------------------------------------------------------------------
2012-03-09 01:55:28 +05:30
subroutine material_populateGrains
2009-03-04 17:18:54 +05:30
2019-05-15 02:14:38 +05:30
integer :: e , i , c , homog , micro
2015-10-14 00:22:01 +05:30
2019-06-07 09:48:42 +05:30
allocate ( material_phase ( homogenization_maxNgrains , discretization_nIP , discretization_nElem ) , source = 0 )
allocate ( material_texture ( homogenization_maxNgrains , discretization_nIP , discretization_nElem ) , source = 0 )
allocate ( material_EulerAngles ( 3 , homogenization_maxNgrains , discretization_nIP , discretization_nElem ) , source = 0.0_pReal )
2015-10-14 00:22:01 +05:30
2019-06-07 09:48:42 +05:30
do e = 1 , discretization_nElem
do i = 1 , discretization_nIP
2019-06-07 11:19:45 +05:30
homog = discretization_homogenizationAt ( e )
micro = discretization_microstructureAt ( e )
2019-05-05 01:37:10 +05:30
do c = 1 , homogenization_Ngrains ( homog )
material_phase ( c , i , e ) = microstructure_phase ( c , micro )
material_texture ( c , i , e ) = microstructure_texture ( c , micro )
2019-06-07 17:17:38 +05:30
material_EulerAngles ( 1 : 3 , c , i , e ) = texture_Gauss ( 1 : 3 , material_texture ( c , i , e ) )
2019-05-05 01:37:10 +05:30
material_EulerAngles ( 1 : 3 , c , i , e ) = math_RtoEuler ( & ! translate back to Euler angles
2019-05-09 02:11:09 +05:30
matmul ( & ! pre-multiply
2019-05-05 01:37:10 +05:30
math_EulertoR ( material_EulerAngles ( 1 : 3 , c , i , e ) ) , & ! face-value orientation
texture_transformation ( 1 : 3 , 1 : 3 , material_texture ( c , i , e ) ) & ! and transformation matrix
) &
)
enddo
enddo
enddo
2016-11-10 11:23:47 +05:30
deallocate ( texture_transformation )
2019-06-07 17:09:01 +05:30
deallocate ( microstructure_phase )
deallocate ( microstructure_texture )
2019-05-04 17:49:27 +05:30
2018-08-22 18:00:51 +05:30
call config_deallocate ( 'material.config/microstructure' )
2009-03-04 17:18:54 +05:30
2012-03-09 01:55:28 +05:30
end subroutine material_populateGrains
2009-03-04 17:18:54 +05:30
2013-02-20 03:42:05 +05:30
end module material