systematic names
This commit is contained in:
parent
0fc7f66ef8
commit
d59051f576
|
@ -258,7 +258,6 @@ subroutine formResidual(in,x_scal,f_scal,dummy,ierr)
|
|||
PetscObject :: dummy
|
||||
PetscErrorCode :: ierr
|
||||
integer :: i, j, k, ce
|
||||
real(pReal) :: Tdot
|
||||
|
||||
T_current = x_scal
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
@ -271,7 +270,7 @@ subroutine formResidual(in,x_scal,f_scal,dummy,ierr)
|
|||
ce = 0
|
||||
do k = 1, grid3; do j = 1, grid(2); do i = 1,grid(1)
|
||||
ce = ce + 1
|
||||
vectorField_real(1:3,i,j,k) = matmul(thermal_conduction_getConductivity(ce) - K_ref, &
|
||||
vectorField_real(1:3,i,j,k) = matmul(homogenization_K(ce) - K_ref, &
|
||||
vectorField_real(1:3,i,j,k))
|
||||
enddo; enddo; enddo
|
||||
call utilities_FFTvectorForward
|
||||
|
@ -280,8 +279,7 @@ subroutine formResidual(in,x_scal,f_scal,dummy,ierr)
|
|||
ce = 0
|
||||
do k = 1, grid3; do j = 1, grid(2); do i = 1,grid(1)
|
||||
ce = ce + 1
|
||||
call thermal_conduction_getSource(Tdot,1,ce)
|
||||
scalarField_real(i,j,k) = params%timeinc*(scalarField_real(i,j,k) + Tdot) &
|
||||
scalarField_real(i,j,k) = params%timeinc*(scalarField_real(i,j,k) + homogenization_f_T(ce)) &
|
||||
+ homogenization_thermal_mu_T(ce) * (T_lastInc(i,j,k) - T_current(i,j,k)) &
|
||||
+ mu_ref*T_current(i,j,k)
|
||||
enddo; enddo; enddo
|
||||
|
@ -311,7 +309,7 @@ subroutine updateReference
|
|||
mu_ref = 0.0_pReal
|
||||
do k = 1, grid3; do j = 1, grid(2); do i = 1,grid(1)
|
||||
ce = ce + 1
|
||||
K_ref = K_ref + thermal_conduction_getConductivity(ce)
|
||||
K_ref = K_ref + homogenization_K(ce)
|
||||
mu_ref = mu_ref + homogenization_thermal_mu_T(ce)
|
||||
enddo; enddo; enddo
|
||||
K_ref = K_ref*wgt
|
||||
|
|
|
@ -136,10 +136,10 @@ module homogenization
|
|||
end function mechanical_updateState
|
||||
|
||||
|
||||
module function thermal_conduction_getConductivity(ce) result(K)
|
||||
module function homogenization_K(ce) result(K)
|
||||
integer, intent(in) :: ce
|
||||
real(pReal), dimension(3,3) :: K
|
||||
end function thermal_conduction_getConductivity
|
||||
end function homogenization_K
|
||||
|
||||
module function homogenization_thermal_mu_T(ce) result(mu_T)
|
||||
integer, intent(in) :: ce
|
||||
|
@ -151,17 +151,15 @@ module homogenization
|
|||
real(pReal), intent(in) :: T, dot_T
|
||||
end subroutine homogenization_thermal_setField
|
||||
|
||||
module function homogenization_thermal_T(ce) result(T)
|
||||
module function homogenization_T(ce) result(T)
|
||||
integer, intent(in) :: ce
|
||||
real(pReal) :: T
|
||||
end function homogenization_thermal_T
|
||||
end function homogenization_T
|
||||
|
||||
module subroutine thermal_conduction_getSource(Tdot, ip, el)
|
||||
integer, intent(in) :: &
|
||||
ip, &
|
||||
el
|
||||
real(pReal), intent(out) :: Tdot
|
||||
end subroutine thermal_conduction_getSource
|
||||
module function homogenization_f_T(ce) result(f_T)
|
||||
integer, intent(in) :: ce
|
||||
real(pReal) :: f_T
|
||||
end function homogenization_f_T
|
||||
|
||||
module function damage_nonlocal_getMobility(ce) result(M)
|
||||
integer, intent(in) :: ce
|
||||
|
@ -188,13 +186,13 @@ module homogenization
|
|||
homogenization_init, &
|
||||
materialpoint_stressAndItsTangent, &
|
||||
homogenization_thermal_mu_T, &
|
||||
thermal_conduction_getConductivity, &
|
||||
thermal_conduction_getSource, &
|
||||
homogenization_K, &
|
||||
homogenization_f_T, &
|
||||
damage_nonlocal_getMobility, &
|
||||
damage_nonlocal_getSourceAndItsTangent, &
|
||||
homogenization_set_phi, &
|
||||
homogenization_thermal_setfield, &
|
||||
homogenization_thermal_T, &
|
||||
homogenization_T, &
|
||||
homogenization_forward, &
|
||||
homogenization_results, &
|
||||
homogenization_restartRead, &
|
||||
|
|
|
@ -109,7 +109,7 @@ end subroutine thermal_homogenize
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief return homogenized thermal conductivity in reference configuration
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module function thermal_conduction_getConductivity(ce) result(K)
|
||||
module function homogenization_K(ce) result(K)
|
||||
|
||||
integer, intent(in) :: ce
|
||||
real(pReal), dimension(3,3) :: K
|
||||
|
@ -125,7 +125,7 @@ module function thermal_conduction_getConductivity(ce) result(K)
|
|||
|
||||
K = K / real(homogenization_Nconstituents(material_homogenizationID(ce)),pReal)
|
||||
|
||||
end function thermal_conduction_getConductivity
|
||||
end function homogenization_K
|
||||
|
||||
|
||||
module function homogenization_thermal_mu_T(ce) result(mu_T)
|
||||
|
@ -220,43 +220,35 @@ module subroutine thermal_results(ho,group)
|
|||
end subroutine thermal_results
|
||||
|
||||
|
||||
module function homogenization_thermal_T(ce) result(T)
|
||||
module function homogenization_T(ce) result(T)
|
||||
|
||||
integer, intent(in) :: ce
|
||||
real(pReal) :: T
|
||||
|
||||
T = current(material_homogenizationID(ce))%T(material_homogenizationEntry(ce))
|
||||
|
||||
end function homogenization_thermal_T
|
||||
end function homogenization_T
|
||||
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief return heat generation rate
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module subroutine thermal_conduction_getSource(Tdot, ip, el)
|
||||
module function homogenization_f_T(ce) result(f_T)
|
||||
|
||||
integer, intent(in) :: &
|
||||
ip, &
|
||||
el
|
||||
real(pReal), intent(out) :: &
|
||||
Tdot
|
||||
integer, intent(in) :: ce
|
||||
real(pReal) :: f_T
|
||||
|
||||
integer :: co, ho,ph,me
|
||||
real(pReal) :: dot_T_temp
|
||||
integer :: co
|
||||
|
||||
ho = material_homogenizationAt(el)
|
||||
Tdot = 0.0_pReal
|
||||
do co = 1, homogenization_Nconstituents(ho)
|
||||
ph = material_phaseAt(co,el)
|
||||
me = material_phasememberAt(co,ip,el)
|
||||
call phase_thermal_getRate(dot_T_temp, ph,me)
|
||||
Tdot = Tdot + dot_T_temp
|
||||
f_T = phase_f_T(material_phaseID(1,ce),material_phaseEntry(1,ce))
|
||||
do co = 2, homogenization_Nconstituents(material_homogenizationID(ce))
|
||||
f_T = f_T + phase_f_T(material_phaseID(co,ce),material_phaseEntry(co,ce))
|
||||
enddo
|
||||
|
||||
Tdot = Tdot/real(homogenization_Nconstituents(ho),pReal)
|
||||
f_T = f_T/real(homogenization_Nconstituents(material_homogenizationID(ce)),pReal)
|
||||
|
||||
end subroutine thermal_conduction_getSource
|
||||
end function homogenization_f_T
|
||||
|
||||
|
||||
end submodule thermal
|
||||
|
|
|
@ -235,11 +235,10 @@ module phase
|
|||
phi_dot
|
||||
end function phase_damage_phi_dot
|
||||
|
||||
module subroutine phase_thermal_getRate(TDot, ph,me)
|
||||
module function phase_f_T(ph,me) result(f_T)
|
||||
integer, intent(in) :: ph, me
|
||||
real(pReal), intent(out) :: &
|
||||
TDot
|
||||
end subroutine phase_thermal_getRate
|
||||
real(pReal) :: f_T
|
||||
end function phase_f_T
|
||||
|
||||
module subroutine plastic_nonlocal_updateCompatibility(orientation,ph,i,e)
|
||||
integer, intent(in) :: &
|
||||
|
@ -301,7 +300,7 @@ module phase
|
|||
phase_init, &
|
||||
phase_homogenizedC, &
|
||||
phase_damage_phi_dot, &
|
||||
phase_thermal_getRate, &
|
||||
phase_f_T, &
|
||||
phase_results, &
|
||||
phase_allocateState, &
|
||||
phase_forward, &
|
||||
|
|
|
@ -21,7 +21,7 @@ submodule(phase) thermal
|
|||
integer(kind(THERMAL_UNDEFINED_ID)), dimension(:,:), allocatable :: &
|
||||
thermal_source
|
||||
|
||||
type(tDataContainer), dimension(:), allocatable :: current ! ?? not very telling name. Better: "field" ??
|
||||
type(tDataContainer), dimension(:), allocatable :: current ! ?? not very telling name. Better: "field" ?? MD: current(ho)%T(me) reads quite good
|
||||
|
||||
integer :: thermal_source_maxSizeDotState
|
||||
|
||||
|
@ -45,21 +45,19 @@ submodule(phase) thermal
|
|||
me
|
||||
end subroutine externalheat_dotState
|
||||
|
||||
module subroutine dissipation_getRate(TDot, ph,me)
|
||||
module function dissipation_f_T(ph,me) result(f_T)
|
||||
integer, intent(in) :: &
|
||||
ph, &
|
||||
me
|
||||
real(pReal), intent(out) :: &
|
||||
TDot
|
||||
end subroutine dissipation_getRate
|
||||
real(pReal) :: f_T
|
||||
end function dissipation_f_T
|
||||
|
||||
module subroutine externalheat_getRate(TDot, ph,me)
|
||||
module function externalheat_f_T(ph,me) result(f_T)
|
||||
integer, intent(in) :: &
|
||||
ph, &
|
||||
me
|
||||
real(pReal), intent(out) :: &
|
||||
TDot
|
||||
end subroutine externalheat_getRate
|
||||
real(pReal) :: f_T
|
||||
end function externalheat_f_T
|
||||
|
||||
end interface
|
||||
|
||||
|
@ -123,35 +121,31 @@ end subroutine thermal_init
|
|||
!----------------------------------------------------------------------------------------------
|
||||
!< @brief calculates thermal dissipation rate
|
||||
!----------------------------------------------------------------------------------------------
|
||||
module subroutine phase_thermal_getRate(TDot, ph,me)
|
||||
module function phase_f_T(ph,me) result(f_T)
|
||||
|
||||
integer, intent(in) :: ph, me
|
||||
real(pReal), intent(out) :: &
|
||||
TDot
|
||||
|
||||
real(pReal) :: &
|
||||
my_Tdot
|
||||
integer :: &
|
||||
so
|
||||
real(pReal) :: f_T
|
||||
|
||||
|
||||
TDot = 0.0_pReal
|
||||
integer :: so
|
||||
|
||||
|
||||
f_T = 0.0_pReal
|
||||
|
||||
do so = 1, thermal_Nsources(ph)
|
||||
select case(thermal_source(so,ph))
|
||||
|
||||
case (THERMAL_DISSIPATION_ID)
|
||||
call dissipation_getRate(my_Tdot, ph,me)
|
||||
f_T = f_T + dissipation_f_T(ph,me)
|
||||
|
||||
case (THERMAL_EXTERNALHEAT_ID)
|
||||
call externalheat_getRate(my_Tdot, ph,me)
|
||||
f_T = f_T + externalheat_f_T(ph,me)
|
||||
|
||||
case default
|
||||
my_Tdot = 0.0_pReal
|
||||
end select
|
||||
Tdot = Tdot + my_Tdot
|
||||
|
||||
enddo
|
||||
|
||||
end subroutine phase_thermal_getRate
|
||||
end function phase_f_T
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
|
|
@ -69,17 +69,17 @@ end function dissipation_init
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief Ninstancess dissipation rate
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module subroutine dissipation_getRate(TDot, ph,me)
|
||||
module function dissipation_f_T(ph,me) result(f_T)
|
||||
|
||||
integer, intent(in) :: ph, me
|
||||
real(pReal), intent(out) :: &
|
||||
TDot
|
||||
real(pReal) :: &
|
||||
f_T
|
||||
|
||||
|
||||
associate(prm => param(ph))
|
||||
TDot = prm%kappa*sum(abs(mechanical_S(ph,me)*mechanical_L_p(ph,me)))
|
||||
f_T = prm%kappa*sum(abs(mechanical_S(ph,me)*mechanical_L_p(ph,me)))
|
||||
end associate
|
||||
|
||||
end subroutine dissipation_getRate
|
||||
end function dissipation_f_T
|
||||
|
||||
end submodule dissipation
|
||||
|
|
|
@ -100,13 +100,13 @@ end subroutine externalheat_dotState
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns local heat generation rate
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module subroutine externalheat_getRate(TDot, ph, me)
|
||||
module function externalheat_f_T(ph,me) result(f_T)
|
||||
|
||||
integer, intent(in) :: &
|
||||
ph, &
|
||||
me
|
||||
real(pReal), intent(out) :: &
|
||||
TDot
|
||||
real(pReal) :: &
|
||||
f_T
|
||||
|
||||
integer :: &
|
||||
so, interval
|
||||
|
@ -122,12 +122,12 @@ module subroutine externalheat_getRate(TDot, ph, me)
|
|||
if ( (frac_time < 0.0_pReal .and. interval == 1) &
|
||||
.or. (frac_time >= 1.0_pReal .and. interval == prm%nIntervals) &
|
||||
.or. (frac_time >= 0.0_pReal .and. frac_time < 1.0_pReal) ) &
|
||||
TDot = prm%f_T(interval ) * (1.0_pReal - frac_time) + &
|
||||
f_T = prm%f_T(interval ) * (1.0_pReal - frac_time) + &
|
||||
prm%f_T(interval+1) * frac_time ! interpolate heat rate between segment boundaries...
|
||||
! ...or extrapolate if outside me bounds
|
||||
enddo
|
||||
end associate
|
||||
|
||||
end subroutine externalheat_getRate
|
||||
end function externalheat_f_T
|
||||
|
||||
end submodule externalheat
|
||||
|
|
Loading…
Reference in New Issue