not needed anymore
This commit is contained in:
parent
599dc2a2c6
commit
26c7969837
|
@ -180,10 +180,10 @@ subroutine CPFEM_general(mode, ffn, ffn1, temperature_inp, dt, elFE, ip, cauchyS
|
||||||
if (iand(mode, CPFEM_AGERESULTS) /= 0_pInt) call CPFEM_forward
|
if (iand(mode, CPFEM_AGERESULTS) /= 0_pInt) call CPFEM_forward
|
||||||
|
|
||||||
chosenThermal1: select case (thermal_type(material_homogenizationAt(elCP)))
|
chosenThermal1: select case (thermal_type(material_homogenizationAt(elCP)))
|
||||||
case (THERMAL_conduction_ID) chosenThermal1
|
!case (THERMAL_conduction_ID) chosenThermal1
|
||||||
temperature(material_homogenizationAt(elCP))%p(material_homogenizationMemberAt(ip,elCP)) = &
|
! temperature(material_homogenizationAt(elCP))%p(material_homogenizationMemberAt(ip,elCP)) = &
|
||||||
temperature_inp
|
! temperature_inp
|
||||||
end select chosenThermal1
|
end select chosenThermal1
|
||||||
homogenization_F0(1:3,1:3,ma) = ffn
|
homogenization_F0(1:3,1:3,ma) = ffn
|
||||||
homogenization_F(1:3,1:3,ma) = ffn1
|
homogenization_F(1:3,1:3,ma) = ffn1
|
||||||
|
|
||||||
|
|
|
@ -351,7 +351,7 @@ end subroutine hypela2
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine flux(f,ts,n,time)
|
subroutine flux(f,ts,n,time)
|
||||||
use prec
|
use prec
|
||||||
use thermal_conduction
|
use homogenization
|
||||||
use discretization_marc
|
use discretization_marc
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
|
|
|
@ -42,8 +42,6 @@
|
||||||
#include "source_damage_anisoDuctile.f90"
|
#include "source_damage_anisoDuctile.f90"
|
||||||
#include "kinematics_cleavage_opening.f90"
|
#include "kinematics_cleavage_opening.f90"
|
||||||
#include "kinematics_slipplane_opening.f90"
|
#include "kinematics_slipplane_opening.f90"
|
||||||
#include "thermal_isothermal.f90"
|
|
||||||
#include "thermal_conduction.f90"
|
|
||||||
#include "damage_none.f90"
|
#include "damage_none.f90"
|
||||||
#include "damage_nonlocal.f90"
|
#include "damage_nonlocal.f90"
|
||||||
#include "homogenization.f90"
|
#include "homogenization.f90"
|
||||||
|
|
|
@ -15,7 +15,6 @@ module grid_thermal_spectral
|
||||||
use IO
|
use IO
|
||||||
use spectral_utilities
|
use spectral_utilities
|
||||||
use discretization_grid
|
use discretization_grid
|
||||||
use thermal_conduction
|
|
||||||
use homogenization
|
use homogenization
|
||||||
use YAML_types
|
use YAML_types
|
||||||
use config
|
use config
|
||||||
|
@ -188,9 +187,6 @@ function grid_thermal_spectral_solution(timeinc) result(solution)
|
||||||
ce = 0
|
ce = 0
|
||||||
do k = 1, grid3; do j = 1, grid(2); do i = 1,grid(1)
|
do k = 1, grid3; do j = 1, grid(2); do i = 1,grid(1)
|
||||||
ce = ce + 1
|
ce = ce + 1
|
||||||
call thermal_conduction_putTemperatureAndItsRate(T_current(i,j,k), &
|
|
||||||
(T_current(i,j,k)-T_lastInc(i,j,k))/params%timeinc, &
|
|
||||||
1,ce)
|
|
||||||
call homogenization_thermal_setField(T_current(i,j,k), &
|
call homogenization_thermal_setField(T_current(i,j,k), &
|
||||||
(T_current(i,j,k)-T_lastInc(i,j,k))/params%timeinc, &
|
(T_current(i,j,k)-T_lastInc(i,j,k))/params%timeinc, &
|
||||||
ce)
|
ce)
|
||||||
|
@ -231,10 +227,6 @@ subroutine grid_thermal_spectral_forward(cutBack)
|
||||||
call DMDAVecRestoreArrayF90(dm_local,solution_vec,x_scal,ierr); CHKERRQ(ierr)
|
call DMDAVecRestoreArrayF90(dm_local,solution_vec,x_scal,ierr); CHKERRQ(ierr)
|
||||||
do k = 1, grid3; do j = 1, grid(2); do i = 1,grid(1)
|
do k = 1, grid3; do j = 1, grid(2); do i = 1,grid(1)
|
||||||
ce = ce + 1
|
ce = ce + 1
|
||||||
call thermal_conduction_putTemperatureAndItsRate(T_current(i,j,k), &
|
|
||||||
(T_current(i,j,k) - &
|
|
||||||
T_lastInc(i,j,k))/params%timeinc, &
|
|
||||||
1,ce)
|
|
||||||
call homogenization_thermal_setField(T_current(i,j,k), &
|
call homogenization_thermal_setField(T_current(i,j,k), &
|
||||||
(T_current(i,j,k)-T_lastInc(i,j,k))/params%timeinc, &
|
(T_current(i,j,k)-T_lastInc(i,j,k))/params%timeinc, &
|
||||||
ce)
|
ce)
|
||||||
|
|
|
@ -12,8 +12,6 @@ module homogenization
|
||||||
use material
|
use material
|
||||||
use constitutive
|
use constitutive
|
||||||
use discretization
|
use discretization
|
||||||
use thermal_isothermal
|
|
||||||
use thermal_conduction
|
|
||||||
use damage_none
|
use damage_none
|
||||||
use damage_nonlocal
|
use damage_nonlocal
|
||||||
use HDF5_utilities
|
use HDF5_utilities
|
||||||
|
@ -144,6 +142,13 @@ module homogenization
|
||||||
real(pReal) :: T
|
real(pReal) :: T
|
||||||
end function homogenization_thermal_T
|
end function homogenization_thermal_T
|
||||||
|
|
||||||
|
module subroutine thermal_conduction_getSource(Tdot, ip,el)
|
||||||
|
integer, intent(in) :: &
|
||||||
|
ip, & !< integration point number
|
||||||
|
el !< element number
|
||||||
|
real(pReal), intent(out) :: Tdot
|
||||||
|
end subroutine thermal_conduction_getSource
|
||||||
|
|
||||||
end interface
|
end interface
|
||||||
|
|
||||||
public :: &
|
public :: &
|
||||||
|
@ -152,6 +157,7 @@ module homogenization
|
||||||
thermal_conduction_getSpecificHeat, &
|
thermal_conduction_getSpecificHeat, &
|
||||||
thermal_conduction_getConductivity, &
|
thermal_conduction_getConductivity, &
|
||||||
thermal_conduction_getMassDensity, &
|
thermal_conduction_getMassDensity, &
|
||||||
|
thermal_conduction_getSource, &
|
||||||
homogenization_thermal_setfield, &
|
homogenization_thermal_setfield, &
|
||||||
homogenization_thermal_T, &
|
homogenization_thermal_T, &
|
||||||
homogenization_forward, &
|
homogenization_forward, &
|
||||||
|
@ -191,9 +197,6 @@ subroutine homogenization_init()
|
||||||
call thermal_init()
|
call thermal_init()
|
||||||
call damage_init()
|
call damage_init()
|
||||||
|
|
||||||
if (any(thermal_type == THERMAL_isothermal_ID)) call thermal_isothermal_init()
|
|
||||||
if (any(thermal_type == THERMAL_conduction_ID)) call thermal_conduction_init()
|
|
||||||
|
|
||||||
if (any(damage_type == DAMAGE_none_ID)) call damage_none_init
|
if (any(damage_type == DAMAGE_none_ID)) call damage_none_init
|
||||||
if (any(damage_type == DAMAGE_nonlocal_ID)) call damage_nonlocal_init
|
if (any(damage_type == DAMAGE_nonlocal_ID)) call damage_nonlocal_init
|
||||||
|
|
||||||
|
|
|
@ -213,4 +213,27 @@ module function homogenization_thermal_T(ce) result(T)
|
||||||
end function homogenization_thermal_T
|
end function homogenization_thermal_T
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief return heat generation rate
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
module subroutine thermal_conduction_getSource(Tdot, ip,el)
|
||||||
|
|
||||||
|
integer, intent(in) :: &
|
||||||
|
ip, & !< integration point number
|
||||||
|
el !< element number
|
||||||
|
real(pReal), intent(out) :: &
|
||||||
|
Tdot
|
||||||
|
|
||||||
|
integer :: &
|
||||||
|
homog
|
||||||
|
|
||||||
|
homog = material_homogenizationAt(el)
|
||||||
|
call constitutive_thermal_getRate(TDot, ip,el)
|
||||||
|
|
||||||
|
Tdot = Tdot/real(homogenization_Nconstituents(homog),pReal)
|
||||||
|
|
||||||
|
end subroutine thermal_conduction_getSource
|
||||||
|
|
||||||
|
|
||||||
end submodule homogenization_thermal
|
end submodule homogenization_thermal
|
||||||
|
|
|
@ -71,9 +71,7 @@ module material
|
||||||
material_orientation0 !< initial orientation of each grain,IP,element
|
material_orientation0 !< initial orientation of each grain,IP,element
|
||||||
|
|
||||||
type(group_float), allocatable, dimension(:), public :: &
|
type(group_float), allocatable, dimension(:), public :: &
|
||||||
temperature, & !< temperature field
|
damage !< damage field
|
||||||
damage, & !< damage field
|
|
||||||
temperatureRate !< temperature change rate field
|
|
||||||
|
|
||||||
public :: &
|
public :: &
|
||||||
material_init, &
|
material_init, &
|
||||||
|
@ -107,9 +105,7 @@ subroutine material_init(restart)
|
||||||
allocate(homogState (size(material_name_homogenization)))
|
allocate(homogState (size(material_name_homogenization)))
|
||||||
allocate(damageState_h (size(material_name_homogenization)))
|
allocate(damageState_h (size(material_name_homogenization)))
|
||||||
|
|
||||||
allocate(temperature (size(material_name_homogenization)))
|
|
||||||
allocate(damage (size(material_name_homogenization)))
|
allocate(damage (size(material_name_homogenization)))
|
||||||
allocate(temperatureRate (size(material_name_homogenization)))
|
|
||||||
|
|
||||||
|
|
||||||
if (.not. restart) then
|
if (.not. restart) then
|
||||||
|
|
|
@ -1,98 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine for temperature evolution from heat conduction
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module thermal_conduction
|
|
||||||
use prec
|
|
||||||
use material
|
|
||||||
use config
|
|
||||||
use lattice
|
|
||||||
use results
|
|
||||||
use constitutive
|
|
||||||
use YAML_types
|
|
||||||
use discretization
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
thermal_conduction_init, &
|
|
||||||
thermal_conduction_getSource, &
|
|
||||||
thermal_conduction_putTemperatureAndItsRate
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief module initialization
|
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine thermal_conduction_init()
|
|
||||||
|
|
||||||
integer :: Nmaterialpoints,ho
|
|
||||||
class(tNode), pointer :: &
|
|
||||||
material_homogenization
|
|
||||||
|
|
||||||
|
|
||||||
print'(/,a)', ' <<<+- thermal_conduction init -+>>>'; flush(6)
|
|
||||||
|
|
||||||
material_homogenization => config_material%get('homogenization')
|
|
||||||
do ho = 1, size(material_name_homogenization)
|
|
||||||
if (thermal_type(ho) /= THERMAL_conduction_ID) cycle
|
|
||||||
|
|
||||||
Nmaterialpoints=count(material_homogenizationAt==ho)
|
|
||||||
|
|
||||||
allocate (temperature (ho)%p(Nmaterialpoints), source=thermal_initialT(ho))
|
|
||||||
allocate (temperatureRate(ho)%p(Nmaterialpoints), source=0.0_pReal)
|
|
||||||
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end subroutine thermal_conduction_init
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief return heat generation rate
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine thermal_conduction_getSource(Tdot, ip,el)
|
|
||||||
|
|
||||||
integer, intent(in) :: &
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
real(pReal), intent(out) :: &
|
|
||||||
Tdot
|
|
||||||
|
|
||||||
integer :: &
|
|
||||||
homog
|
|
||||||
|
|
||||||
homog = material_homogenizationAt(el)
|
|
||||||
call constitutive_thermal_getRate(TDot, ip,el)
|
|
||||||
|
|
||||||
Tdot = Tdot/real(homogenization_Nconstituents(homog),pReal)
|
|
||||||
|
|
||||||
end subroutine thermal_conduction_getSource
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief updates thermal state with solution from heat conduction PDE
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine thermal_conduction_putTemperatureAndItsRate(T,Tdot,ip,el)
|
|
||||||
|
|
||||||
integer, intent(in) :: &
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
T, &
|
|
||||||
Tdot
|
|
||||||
integer :: &
|
|
||||||
homog, &
|
|
||||||
offset
|
|
||||||
|
|
||||||
homog = material_homogenizationAt(el)
|
|
||||||
offset = material_homogenizationMemberAt(ip,el)
|
|
||||||
temperature (homog)%p(offset) = T
|
|
||||||
temperatureRate(homog)%p(offset) = Tdot
|
|
||||||
|
|
||||||
end subroutine thermal_conduction_putTemperatureAndItsRate
|
|
||||||
|
|
||||||
|
|
||||||
end module thermal_conduction
|
|
|
@ -1,37 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine for isothermal temperature field
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module thermal_isothermal
|
|
||||||
use prec
|
|
||||||
use config
|
|
||||||
use material
|
|
||||||
use discretization
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
public
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief allocates fields, reads information from material configuration file
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine thermal_isothermal_init()
|
|
||||||
|
|
||||||
integer :: Ninstances,Nmaterialpoints,ho,ip,el,ce
|
|
||||||
|
|
||||||
print'(/,a)', ' <<<+- thermal_isothermal init -+>>>'; flush(6)
|
|
||||||
|
|
||||||
do ho = 1, size(thermal_type)
|
|
||||||
if (thermal_type(ho) /= THERMAL_isothermal_ID) cycle
|
|
||||||
|
|
||||||
Nmaterialpoints = count(material_homogenizationAt == ho)
|
|
||||||
|
|
||||||
allocate(temperature (ho)%p(Nmaterialpoints),source=thermal_initialT(ho))
|
|
||||||
allocate(temperatureRate(ho)%p(Nmaterialpoints),source = 0.0_pReal)
|
|
||||||
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end subroutine thermal_isothermal_init
|
|
||||||
|
|
||||||
end module thermal_isothermal
|
|
Loading…
Reference in New Issue