DAMASK with grid solvers  Revision: v2.0.3-2204-gdb1f2151
The Düsseldorf Advanced Material Simulation Kit with Grid Solvers
source_thermal_externalheat.f90
Go to the documentation of this file.
1 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/source_thermal_externalheat.f90"
2 # 1 "<built-in>"
3 # 1 "<command-line>"
4 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/source_thermal_externalheat.f90"
5 !--------------------------------------------------------------------------------------------------
10 !--------------------------------------------------------------------------------------------------
12  use prec
13  use debug
14  use discretization
15  use material
16  use config
17 
18  implicit none
19  private
20 
21  integer, dimension(:), allocatable :: &
22  source_thermal_externalheat_offset, & !< which source is my current thermal dissipation mechanism?
24 
25  type :: tparameters
26  real(preal), dimension(:), allocatable :: &
27  time, &
28  heat_rate
29  integer :: &
30  nintervals
31  end type tparameters
32 
33  type(tparameters), dimension(:), allocatable :: param
34 
35 
36  public :: &
40 
41 contains
42 
43 
44 !--------------------------------------------------------------------------------------------------
47 !--------------------------------------------------------------------------------------------------
49 
50  integer :: ninstance,sourceoffset,nipcmyphase,p
51 
52  write(6,'(/,a)') ' <<<+- source_'//source_thermal_externalheat_label//' init -+>>>'; flush(6)
53 
54  ninstance = count(phase_source == source_thermal_externalheat_id)
56  write(6,'(a16,1x,i5,/)') '# instances:',ninstance
57 
58  allocate(source_thermal_externalheat_offset(size(config_phase)), source=0)
59  allocate(source_thermal_externalheat_instance(size(config_phase)), source=0)
60  allocate(param(ninstance))
61 
62  do p = 1, size(config_phase)
64  do sourceoffset = 1, phase_nsources(p)
65  if (phase_source(sourceoffset,p) == source_thermal_externalheat_id) then
66  source_thermal_externalheat_offset(p) = sourceoffset
67  exit
68  endif
69  enddo
70 
71  if (all(phase_source(:,p) /= source_thermal_externalheat_id)) cycle
72  associate(prm => param(source_thermal_externalheat_instance(p)), &
73  config => config_phase(p))
74 
75  prm%time = config%getFloats('externalheat_time')
76  prm%nIntervals = size(prm%time) - 1
77 
78  prm%heat_rate = config%getFloats('externalheat_rate',requiredsize = size(prm%time))
79 
80  nipcmyphase = count(material_phaseat==p) * discretization_nip
81  call material_allocatesourcestate(p,sourceoffset,nipcmyphase,1,1,0)
82 
83  end associate
84  enddo
85 
87 
88 
89 !--------------------------------------------------------------------------------------------------
92 !--------------------------------------------------------------------------------------------------
93 subroutine source_thermal_externalheat_dotstate(phase, of)
94 
95  integer, intent(in) :: &
96  phase, &
97  of
98 
99  integer :: &
100  sourceoffset
101 
102  sourceoffset = source_thermal_externalheat_offset(phase)
103 
104  sourcestate(phase)%p(sourceoffset)%dotState(1,of) = 1.0_preal ! state is current time
105 
107 
108 
109 !--------------------------------------------------------------------------------------------------
111 !--------------------------------------------------------------------------------------------------
112 subroutine source_thermal_externalheat_getrateanditstangent(TDot, dTDot_dT, phase, of)
113 
114  integer, intent(in) :: &
115  phase, &
116  of
117  real(preal), intent(out) :: &
118  tdot, &
119  dtdot_dt
120 
121  integer :: &
122  sourceoffset, interval
123  real(preal) :: &
124  frac_time
125 
126  sourceoffset = source_thermal_externalheat_offset(phase)
127 
128  associate(prm => param(source_thermal_externalheat_instance(phase)))
129  do interval = 1, prm%nIntervals ! scan through all rate segments
130  frac_time = (sourcestate(phase)%p(sourceoffset)%state(1,of) - prm%time(interval)) &
131  / (prm%time(interval+1) - prm%time(interval)) ! fractional time within segment
132  if ( (frac_time < 0.0_preal .and. interval == 1) &
133  .or. (frac_time >= 1.0_preal .and. interval == prm%nIntervals) &
134  .or. (frac_time >= 0.0_preal .and. frac_time < 1.0_preal) ) &
135  tdot = prm%heat_rate(interval ) * (1.0_preal - frac_time) + &
136  prm%heat_rate(interval+1) * frac_time ! interpolate heat rate between segment boundaries...
137  ! ...or extrapolate if outside of bounds
138  enddo
139  dtdot_dt = 0.0
140  end associate
141 
143 
material::material_phaseat
integer, dimension(:,:), allocatable, public, protected material_phaseat
phase ID of each element
Definition: material.f90:132
source_thermal_externalheat::source_thermal_externalheat_dotstate
subroutine, public source_thermal_externalheat_dotstate(phase, of)
rate of change of state
Definition: source_thermal_externalheat.f90:94
config::config_phase
type(tpartitionedstringlist), dimension(:), allocatable, public, protected config_phase
Definition: config.f90:23
debug::debug_level
integer, dimension(debug_maxntype+2), public, protected debug_level
Definition: debug.f90:48
material::source_thermal_externalheat_label
character(len= *), parameter, public source_thermal_externalheat_label
Definition: material.f90:25
material
Parses material config file, either solverJobName.materialConfig or material.config.
Definition: material.f90:11
source_thermal_externalheat::source_thermal_externalheat_getrateanditstangent
subroutine, public source_thermal_externalheat_getrateanditstangent(TDot, dTDot_dT, phase, of)
returns local heat generation rate
Definition: source_thermal_externalheat.f90:113
config
Reads in the material configuration from file.
Definition: config.f90:13
source_thermal_externalheat::source_thermal_externalheat_instance
integer, dimension(:), allocatable source_thermal_externalheat_instance
instance of thermal dissipation source mechanism
Definition: source_thermal_externalheat.f90:21
source_thermal_externalheat::tparameters
container type for internal constitutive parameters
Definition: source_thermal_externalheat.f90:25
prec
setting precision for real and int type
Definition: prec.f90:13
discretization
spatial discretization
Definition: discretization.f90:9
discretization::discretization_nip
integer, public, protected discretization_nip
Definition: discretization.f90:17
material::source_thermal_externalheat_id
@, public source_thermal_externalheat_id
Definition: material.f90:87
source_thermal_externalheat::source_thermal_externalheat_offset
integer, dimension(:), allocatable source_thermal_externalheat_offset
which source is my current thermal dissipation mechanism?
Definition: source_thermal_externalheat.f90:21
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::material_allocatesourcestate
subroutine, public material_allocatesourcestate(phase, of, NipcMyPhase, sizeState, sizeDotState, sizeDeltaState)
allocates the source state of a phase
Definition: material.f90:750
source_thermal_externalheat
material subroutine for variable heat source
Definition: source_thermal_externalheat.f90:11
debug::debug_constitutive
integer, parameter, public debug_constitutive
stores debug level for constitutive part of DAMASK bitwise coded
Definition: debug.f90:32
material::phase_source
integer(kind(source_undefined_id)), dimension(:,:), allocatable, public, protected phase_source
active sources mechanisms of each phase
Definition: material.f90:105
material::phase_nsources
integer, dimension(:), allocatable, public, protected phase_nsources
number of source mechanisms active in each phase
Definition: material.f90:113
source_thermal_externalheat::source_thermal_externalheat_init
subroutine, public source_thermal_externalheat_init
module initialization
Definition: source_thermal_externalheat.f90:49
source_thermal_externalheat::param
type(tparameters), dimension(:), allocatable param
containers of constitutive parameters (len Ninstance)
Definition: source_thermal_externalheat.f90:33