DAMASK with grid solvers  Revision: v2.0.3-2204-gdb1f2151
The Düsseldorf Advanced Material Simulation Kit with Grid Solvers
source_thermal_dissipation.f90
Go to the documentation of this file.
1 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/source_thermal_dissipation.f90"
2 # 1 "<built-in>"
3 # 1 "<command-line>"
4 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/source_thermal_dissipation.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_dissipation_offset, & !< which source is my current thermal dissipation mechanism?
24 
25  type :: tparameters
26  real(preal) :: &
27  kappa
28  end type tparameters
29 
30  type(tparameters), dimension(:), allocatable :: param
31 
32 
33  public :: &
36 
37 contains
38 
39 
40 !--------------------------------------------------------------------------------------------------
43 !--------------------------------------------------------------------------------------------------
45 
46  integer :: ninstance,sourceoffset,nipcmyphase,p
47 
48  write(6,'(/,a)') ' <<<+- source_'//source_thermal_dissipation_label//' init -+>>>'; flush(6)
49 
50  ninstance = count(phase_source == source_thermal_dissipation_id)
52  write(6,'(a16,1x,i5,/)') '# instances:',ninstance
53 
54  allocate(source_thermal_dissipation_offset(size(config_phase)), source=0)
55  allocate(source_thermal_dissipation_instance(size(config_phase)), source=0)
56  allocate(param(ninstance))
57 
58  do p = 1, size(config_phase)
60  do sourceoffset = 1, phase_nsources(p)
61  if (phase_source(sourceoffset,p) == source_thermal_dissipation_id) then
62  source_thermal_dissipation_offset(p) = sourceoffset
63  exit
64  endif
65  enddo
66 
67  if (all(phase_source(:,p) /= source_thermal_dissipation_id)) cycle
68  associate(prm => param(source_thermal_dissipation_instance(p)), &
69  config => config_phase(p))
70 
71  prm%kappa = config%getFloat('dissipation_coldworkcoeff')
72 
73  nipcmyphase = count(material_phaseat==p) * discretization_nip
74  call material_allocatesourcestate(p,sourceoffset,nipcmyphase,0,0,0)
75 
76  end associate
77  enddo
78 
80 
81 
82 !--------------------------------------------------------------------------------------------------
84 !--------------------------------------------------------------------------------------------------
85 subroutine source_thermal_dissipation_getrateanditstangent(TDot, dTDot_dT, Tstar, Lp, phase)
86 
87  integer, intent(in) :: &
88  phase
89  real(preal), intent(in), dimension(3,3) :: &
90  tstar
91  real(preal), intent(in), dimension(3,3) :: &
92  lp
93 
94  real(preal), intent(out) :: &
95  tdot, &
96  dtdot_dt
97 
98  associate(prm => param(source_thermal_dissipation_instance(phase)))
99  tdot = prm%kappa*sum(abs(tstar*lp))
100  dtdot_dt = 0.0_preal
101  end associate
102 
104 
material::material_phaseat
integer, dimension(:,:), allocatable, public, protected material_phaseat
phase ID of each element
Definition: material.f90:132
source_thermal_dissipation::source_thermal_dissipation_instance
integer, dimension(:), allocatable source_thermal_dissipation_instance
instance of thermal dissipation source mechanism
Definition: source_thermal_dissipation.f90:21
config::config_phase
type(tpartitionedstringlist), dimension(:), allocatable, public, protected config_phase
Definition: config.f90:23
material::source_thermal_dissipation_id
@, public source_thermal_dissipation_id
Definition: material.f90:87
debug::debug_level
integer, dimension(debug_maxntype+2), public, protected debug_level
Definition: debug.f90:48
source_thermal_dissipation
material subroutine for thermal source due to plastic dissipation
Definition: source_thermal_dissipation.f90:11
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
source_thermal_dissipation::param
type(tparameters), dimension(:), allocatable param
containers of constitutive parameters (len Ninstance)
Definition: source_thermal_dissipation.f90:30
source_thermal_dissipation::source_thermal_dissipation_getrateanditstangent
subroutine, public source_thermal_dissipation_getrateanditstangent(TDot, dTDot_dT, Tstar, Lp, phase)
Ninstances dissipation rate.
Definition: source_thermal_dissipation.f90:86
source_thermal_dissipation::tparameters
container type for internal constitutive parameters
Definition: source_thermal_dissipation.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
source_thermal_dissipation::source_thermal_dissipation_offset
integer, dimension(:), allocatable source_thermal_dissipation_offset
which source is my current thermal dissipation mechanism?
Definition: source_thermal_dissipation.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
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_dissipation::source_thermal_dissipation_init
subroutine, public source_thermal_dissipation_init
module initialization
Definition: source_thermal_dissipation.f90:45
material::source_thermal_dissipation_label
character(len= *), parameter, public source_thermal_dissipation_label
Definition: material.f90:25