|
DAMASK with grid solvers
Revision: v2.0.3-2204-gdb1f2151
The Düsseldorf Advanced Material Simulation Kit with Grid Solvers
|
|
Go to the documentation of this file. 1 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/thermal_conduction.f90"
4 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/thermal_conduction.f90"
23 character(len=pStringLen),
allocatable,
dimension(:) :: &
48 integer :: ninstance,nofmyhomog,h
53 allocate(
param(ninstance))
84 integer,
intent(in) :: &
85 ip, & !< integration point number
87 real(preal),
intent(in) :: &
89 real(preal),
intent(out) :: &
102 homog = material_homogenizationat(el)
103 offset = material_homogenizationmemberat(ip,el)
104 instance = thermal_typeinstance(homog)
108 do grain = 1, homogenization_ngrains(homog)
109 phase = material_phaseat(grain,el)
110 constituent = material_phasememberat(grain,ip,el)
111 do source = 1, phase_nsources(phase)
112 select case(phase_source(source,phase))
113 case (source_thermal_dissipation_id)
114 call source_thermal_dissipation_getrateanditstangent(my_tdot, my_dtdot_dt, &
115 crystallite_s(1:3,1:3,grain,ip,el), &
116 crystallite_lp(1:3,1:3,grain,ip,el), &
119 case (source_thermal_externalheat_id)
120 call source_thermal_externalheat_getrateanditstangent(my_tdot, my_dtdot_dt, &
124 my_dtdot_dt = 0.0_preal
127 tdot = tdot + my_tdot
128 dtdot_dt = dtdot_dt + my_dtdot_dt
132 tdot = tdot/real(homogenization_ngrains(homog),preal)
133 dtdot_dt = dtdot_dt/real(homogenization_ngrains(homog),preal)
143 integer,
intent(in) :: &
144 ip, & !< integration point number
146 real(preal),
dimension(3,3) :: &
153 do grain = 1, homogenization_ngrains(material_homogenizationat(el))
155 crystallite_push33toref(grain,ip,el,lattice_thermalconductivity(:,:,material_phaseat(grain,el)))
159 / real(homogenization_ngrains(material_homogenizationat(el)),preal)
169 integer,
intent(in) :: &
170 ip, & !< integration point number
179 do grain = 1, homogenization_ngrains(material_homogenizationat(el))
181 + lattice_specificheat(material_phaseat(grain,el))
185 / real(homogenization_ngrains(material_homogenizationat(el)),preal)
195 integer,
intent(in) :: &
196 ip, & !< integration point number
206 do grain = 1, homogenization_ngrains(material_homogenizationat(el))
208 + lattice_massdensity(material_phaseat(grain,el))
212 / real(homogenization_ngrains(material_homogenizationat(el)),preal)
222 integer,
intent(in) :: &
223 ip, & !< integration point number
225 real(preal),
intent(in) :: &
232 homog = material_homogenizationat(el)
233 offset = thermalmapping(homog)%p(ip,el)
234 temperature(homog)%p(offset) = t
235 temperaturerate(homog)%p(offset) = tdot
245 integer,
intent(in) :: homog
246 character(len=*),
intent(in) :: group
250 associate(prm =>
param(damage_typeinstance(homog)))
251 outputsloop:
do o = 1,
size(prm%output)
252 select case(trim(prm%output(o)))
254 call results_writedataset(group,temperature(homog)%p,
'T',&
type(thomogmapping), dimension(:), allocatable, public thermalmapping
mapping for thermal state/fields
material subroutine for thermal source due to plastic dissipation
character(len=pstringlen), dimension(0), parameter emptystringarray
type(group_float), dimension(:), allocatable, public temperature
temperature field
real(preal) function, public thermal_conduction_getmassdensity(ip, el)
returns homogenized mass density
Parses material config file, either solverJobName.materialConfig or material.config.
subroutine, public thermal_conduction_results(homog, group)
writes results to HDF5 output file
Reads in the material configuration from file.
type(tparameters), dimension(:), allocatable param
containers of constitutive parameters (len Ninstance)
real(preal), dimension(:), allocatable, public, protected thermal_initialt
initial temperature per each homogenization
crystallite state integration functions and reporting of results
character(len= *), parameter, public thermal_conduction_label
integer(kind(thermal_isothermal_id)), dimension(:), allocatable, public, protected thermal_type
thermal transport model
setting precision for real and int type
subroutine, public thermal_conduction_getsourceanditstangent(Tdot, dTdot_dT, T, ip, el)
returns heat generation rate
subroutine, public thermal_conduction_puttemperatureanditsrate(T, Tdot, ip, el)
updates thermal state with solution from heat conduction PDE
type(tstate), dimension(:), allocatable, public thermalstate
real(preal) function, public thermal_conduction_getspecificheat(ip, el)
returns homogenized specific heat capacity
material subroutine for temperature evolution from heat conduction
type(tparameters), dimension(:), allocatable param
contains lattice structure definitions including Schmid matrices for slip, twin, trans,
integer, dimension(:), allocatable, public, protected thermal_typeinstance
instance of particular type of each thermal transport
integer, dimension(:), allocatable, public, protected material_homogenizationat
homogenization ID of each element (copy of discretization_homogenizationAt)
material subroutine for variable heat source
real(preal) function, dimension(3, 3), public thermal_conduction_getconductivity(ip, el)
returns homogenized thermal conductivity in reference configuration
integer, dimension(:,:), allocatable, target, public material_homogenizationmemberat
position of the element within its homogenization instance
subroutine, public thermal_conduction_init
module initialization
type(group_float), dimension(:), allocatable, public temperaturerate
temperature change rate field
type(tpartitionedstringlist), dimension(:), allocatable, public, protected config_homogenization
@, public thermal_conduction_id