DAMASK_EICMD/src/phase_thermal_dissipation.f90

86 lines
2.9 KiB
Fortran
Raw Normal View History

!--------------------------------------------------------------------------------------------------
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
!> @brief material subroutine for thermal source due to plastic dissipation
!> @details to be done
!--------------------------------------------------------------------------------------------------
submodule(phase:thermal) dissipation
type :: tParameters !< container type for internal constitutive parameters
real(pReal) :: &
2020-08-15 19:32:10 +05:30
kappa !< TAYLOR-QUINNEY factor
end type tParameters
2020-02-26 23:07:17 +05:30
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstances)
2020-02-26 23:07:17 +05:30
contains
!--------------------------------------------------------------------------------------------------
!> @brief module initialization
!> @details reads in material parameters, allocates arrays, and does sanity checks
!--------------------------------------------------------------------------------------------------
2021-01-26 12:25:06 +05:30
module function dissipation_init(source_length) result(mySources)
2020-02-26 23:07:17 +05:30
2021-01-08 12:07:51 +05:30
integer, intent(in) :: source_length
2020-08-15 19:32:10 +05:30
logical, dimension(:,:), allocatable :: mySources
class(tNode), pointer :: &
phases, &
phase, &
2021-01-08 12:07:51 +05:30
sources, thermal, &
src
2021-03-05 01:46:36 +05:30
integer :: so,Nmembers,ph
2020-02-26 23:07:17 +05:30
2021-01-08 12:07:51 +05:30
mySources = thermal_active('dissipation',source_length)
2021-02-13 23:11:30 +05:30
if(count(mySources) == 0) return
print'(/,1x,a)', '<<<+- phase:thermal:dissipation init -+>>>'
print'(/,a,i2)', ' # phases: ',count(mySources); flush(IO_STDOUT)
2020-02-26 23:07:17 +05:30
phases => config_material%get('phase')
2021-01-27 04:14:11 +05:30
allocate(param(phases%length))
do ph = 1, phases%length
phase => phases%get(ph)
if (count(mySources(:,ph)) == 0) cycle !ToDo: error if > 1
2021-01-08 12:07:51 +05:30
thermal => phase%get('thermal')
sources => thermal%get('source')
2021-01-27 04:14:11 +05:30
do so = 1, sources%length
if (mySources(so,ph)) then
2021-01-27 04:14:11 +05:30
associate(prm => param(ph))
src => sources%get(so)
2020-02-29 12:28:33 +05:30
2021-01-27 04:14:11 +05:30
prm%kappa = src%get_asFloat('kappa')
2021-04-06 15:08:44 +05:30
Nmembers = count(material_phaseID == ph)
2021-03-05 01:46:36 +05:30
call phase_allocateState(thermalState(ph)%p(so),Nmembers,0,0,0)
2020-02-26 23:07:17 +05:30
2020-08-15 19:32:10 +05:30
end associate
end if
end do
end do
2020-02-26 23:07:17 +05:30
2020-08-15 19:32:10 +05:30
2021-01-26 12:25:06 +05:30
end function dissipation_init
!--------------------------------------------------------------------------------------------------
!> @brief Ninstancess dissipation rate
!--------------------------------------------------------------------------------------------------
2021-04-25 11:36:52 +05:30
module function dissipation_f_T(ph,en) result(f_T)
2020-02-29 19:04:19 +05:30
2021-04-25 11:36:52 +05:30
integer, intent(in) :: ph, en
2021-04-08 02:11:49 +05:30
real(pReal) :: &
f_T
2020-02-26 23:07:17 +05:30
2021-01-27 04:14:11 +05:30
associate(prm => param(ph))
2021-04-25 11:36:52 +05:30
f_T = prm%kappa*sum(abs(mechanical_S(ph,en)*mechanical_L_p(ph,en)))
2020-02-29 12:28:33 +05:30
end associate
2020-02-26 23:07:17 +05:30
2021-04-08 02:11:49 +05:30
end function dissipation_f_T
2020-02-26 23:07:17 +05:30
2021-01-26 05:50:45 +05:30
end submodule dissipation