DAMASK with grid solvers  Revision: v2.0.3-2204-gdb1f2151
The Düsseldorf Advanced Material Simulation Kit with Grid Solvers
kinematics_thermal_expansion.f90
Go to the documentation of this file.
1 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/kinematics_thermal_expansion.f90"
2 # 1 "<built-in>"
3 # 1 "<command-line>"
4 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/kinematics_thermal_expansion.f90"
5 !--------------------------------------------------------------------------------------------------
9 !--------------------------------------------------------------------------------------------------
11  use prec
12  use io
13  use config
14  use debug
15  use math
16  use lattice
17  use material
18 
19  implicit none
20  private
21 
22  integer, dimension(:), allocatable :: kinematics_thermal_expansion_instance
23 
24  type :: tparameters
25  real(preal) :: &
26  t_ref
27  real(preal), dimension(3,3,3) :: &
28  expansion = 0.0_preal
29  end type tparameters
30 
31  type(tparameters), dimension(:), allocatable :: param
32 
33  public :: &
37 
38 contains
39 
40 
41 !--------------------------------------------------------------------------------------------------
44 !--------------------------------------------------------------------------------------------------
46 
47  integer :: ninstance,p,i
48  real(preal), dimension(:), allocatable :: temp
49 
50  write(6,'(/,a)') ' <<<+- kinematics_'//kinematics_thermal_expansion_label//' init -+>>>'; flush(6)
51 
54  write(6,'(a16,1x,i5,/)') '# instances:',ninstance
55 
56  allocate(kinematics_thermal_expansion_instance(size(config_phase)), source=0)
57  allocate(param(ninstance))
58 
59  do p = 1, size(config_phase)
62 
63  associate(prm => param(kinematics_thermal_expansion_instance(p)), &
64  config => config_phase(p))
65 
66  prm%T_ref = config%getFloat('reference_temperature', defaultval=0.0_preal)
67 
68  ! read up to three parameters (constant, linear, quadratic with T)
69  temp = config%getFloats('thermal_expansion11')
70  prm%expansion(1,1,1:size(temp)) = temp
71  temp = config%getFloats('thermal_expansion22',defaultval=[(0.0_preal, i=1,size(temp))],requiredsize=size(temp))
72  prm%expansion(2,2,1:size(temp)) = temp
73  temp = config%getFloats('thermal_expansion33',defaultval=[(0.0_preal, i=1,size(temp))],requiredsize=size(temp))
74  prm%expansion(3,3,1:size(temp)) = temp
75  do i=1, size(prm%expansion,3)
76  prm%expansion(1:3,1:3,i) = lattice_applylatticesymmetry33(prm%expansion(1:3,1:3,i),config%getString('lattice_structure'))
77  enddo
78 
79  end associate
80  enddo
81 
83 
84 
85 !--------------------------------------------------------------------------------------------------
87 !--------------------------------------------------------------------------------------------------
88 pure function kinematics_thermal_expansion_initialstrain(homog,phase,offset)
89 
90  integer, intent(in) :: &
91  phase, &
92  homog, &
93  offset
94 
95  real(preal), dimension(3,3) :: &
97 
98  associate(prm => param(kinematics_thermal_expansion_instance(phase)))
100  (temperature(homog)%p(offset) - prm%T_ref)**1 / 1. * prm%expansion(1:3,1:3,1) + & ! constant coefficient
101  (temperature(homog)%p(offset) - prm%T_ref)**2 / 2. * prm%expansion(1:3,1:3,2) + & ! linear coefficient
102  (temperature(homog)%p(offset) - prm%T_ref)**3 / 3. * prm%expansion(1:3,1:3,3) ! quadratic coefficient
103  end associate
104 
106 
107 
108 !--------------------------------------------------------------------------------------------------
110 !--------------------------------------------------------------------------------------------------
111 subroutine kinematics_thermal_expansion_lianditstangent(Li, dLi_dTstar, ipc, ip, el)
112 
113  integer, intent(in) :: &
114  ipc, & !< grain number
115  ip, & !< integration point number
116  el
117  real(preal), intent(out), dimension(3,3) :: &
118  li
119  real(preal), intent(out), dimension(3,3,3,3) :: &
120  dli_dtstar
121 
122  integer :: &
123  phase, &
124  homog
125  real(preal) :: &
126  t, tdot
127 
128  phase = material_phaseat(ipc,el)
129  homog = material_homogenizationat(el)
130  t = temperature(homog)%p(thermalmapping(homog)%p(ip,el))
131  tdot = temperaturerate(homog)%p(thermalmapping(homog)%p(ip,el))
132 
133  associate(prm => param(kinematics_thermal_expansion_instance(phase)))
134  li = tdot * ( &
135  prm%expansion(1:3,1:3,1)*(t - prm%T_ref)**0 & ! constant coefficient
136  + prm%expansion(1:3,1:3,2)*(t - prm%T_ref)**1 & ! linear coefficient
137  + prm%expansion(1:3,1:3,3)*(t - prm%T_ref)**2 & ! quadratic coefficient
138  ) / &
139  (1.0_preal &
140  + prm%expansion(1:3,1:3,1)*(t - prm%T_ref)**1 / 1. &
141  + prm%expansion(1:3,1:3,2)*(t - prm%T_ref)**2 / 2. &
142  + prm%expansion(1:3,1:3,3)*(t - prm%T_ref)**3 / 3. &
143  )
144  end associate
145  dli_dtstar = 0.0_preal
146 
148 
kinematics_thermal_expansion::kinematics_thermal_expansion_lianditstangent
subroutine, public kinematics_thermal_expansion_lianditstangent(Li, dLi_dTstar, ipc, ip, el)
contains the constitutive equation for calculating the velocity gradient
Definition: kinematics_thermal_expansion.f90:112
kinematics_thermal_expansion::kinematics_thermal_expansion_initialstrain
pure real(preal) function, dimension(3, 3), public kinematics_thermal_expansion_initialstrain(homog, phase, offset)
report initial thermal strain based on current temperature deviation from reference
Definition: kinematics_thermal_expansion.f90:89
config::config_phase
type(tpartitionedstringlist), dimension(:), allocatable, public, protected config_phase
Definition: config.f90:23
material::kinematics_thermal_expansion_id
@, public kinematics_thermal_expansion_id
Definition: material.f90:87
debug::debug_level
integer, dimension(debug_maxntype+2), public, protected debug_level
Definition: debug.f90:48
kinematics_thermal_expansion::kinematics_thermal_expansion_init
subroutine, public kinematics_thermal_expansion_init
module initialization
Definition: kinematics_thermal_expansion.f90:46
material
Parses material config file, either solverJobName.materialConfig or material.config.
Definition: material.f90:11
config
Reads in the material configuration from file.
Definition: config.f90:13
lattice::lattice_applylatticesymmetry33
real(preal) function, dimension(3, 3), public lattice_applylatticesymmetry33(T, structure)
Return 3x3 tensor with symmetry according to given crystal structure.
Definition: lattice.f90:1692
kinematics_thermal_expansion
material subroutine incorporating kinematics resulting from thermal expansion
Definition: kinematics_thermal_expansion.f90:10
prec
setting precision for real and int type
Definition: prec.f90:13
io
input/output functions, partly depending on chosen solver
Definition: IO.f90:12
debug::debug_levelbasic
integer, parameter, public debug_levelbasic
Definition: debug.f90:19
prec::preal
integer, parameter preal
number with 15 significant digits, up to 1e+-307 (typically 64 bit)
Definition: prec.f90:20
debug
Reading in and interpretating the debugging settings for the various modules.
Definition: debug.f90:12
material::phase_kinematics
integer(kind(source_undefined_id)), dimension(:,:), allocatable, public, protected phase_kinematics
active kinematic mechanisms of each phase
Definition: material.f90:105
lattice
contains lattice structure definitions including Schmid matrices for slip, twin, trans,
Definition: lattice.f90:13
kinematics_thermal_expansion::tparameters
Definition: kinematics_thermal_expansion.f90:24
math
Mathematical library, including random number generation and tensor representations.
Definition: math.f90:12
debug::debug_constitutive
integer, parameter, public debug_constitutive
stores debug level for constitutive part of DAMASK bitwise coded
Definition: debug.f90:32
material::kinematics_thermal_expansion_label
character(len= *), parameter, public kinematics_thermal_expansion_label
Definition: material.f90:25
kinematics_thermal_expansion::kinematics_thermal_expansion_instance
integer, dimension(:), allocatable kinematics_thermal_expansion_instance
Definition: kinematics_thermal_expansion.f90:22
kinematics_thermal_expansion::param
type(tparameters), dimension(:), allocatable param
Definition: kinematics_thermal_expansion.f90:31