use new structure
This commit is contained in:
parent
e22d76be9e
commit
c2ae2c919b
|
@ -132,7 +132,7 @@ subroutine grid_thermal_spectral_init
|
||||||
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
|
||||||
T_current(i,j,k) = temperature(material_homogenizationAt(ce))%p(material_homogenizationMemberAt(1,ce))
|
T_current(i,j,k) = homogenization_thermal_T(ce)
|
||||||
T_lastInc(i,j,k) = T_current(i,j,k)
|
T_lastInc(i,j,k) = T_current(i,j,k)
|
||||||
T_stagInc(i,j,k) = T_current(i,j,k)
|
T_stagInc(i,j,k) = T_current(i,j,k)
|
||||||
enddo; enddo; enddo
|
enddo; enddo; enddo
|
||||||
|
@ -194,7 +194,6 @@ function grid_thermal_spectral_solution(timeinc) result(solution)
|
||||||
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)
|
||||||
homogenization_T(ce) = T_current(i,j,k)
|
|
||||||
enddo; enddo; enddo
|
enddo; enddo; enddo
|
||||||
|
|
||||||
call VecMin(solution_vec,devNull,T_min,ierr); CHKERRQ(ierr)
|
call VecMin(solution_vec,devNull,T_min,ierr); CHKERRQ(ierr)
|
||||||
|
@ -239,7 +238,6 @@ subroutine grid_thermal_spectral_forward(cutBack)
|
||||||
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)
|
||||||
homogenization_T(ce) = T_current(i,j,k)
|
|
||||||
enddo; enddo; enddo
|
enddo; enddo; enddo
|
||||||
else
|
else
|
||||||
T_lastInc = T_current
|
T_lastInc = T_current
|
||||||
|
|
|
@ -28,8 +28,6 @@ module homogenization
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! General variables for the homogenization at a material point
|
! General variables for the homogenization at a material point
|
||||||
real(pReal), dimension(:), allocatable, public :: &
|
real(pReal), dimension(:), allocatable, public :: &
|
||||||
homogenization_T, &
|
|
||||||
homogenization_dot_T, &
|
|
||||||
homogenization_phi, &
|
homogenization_phi, &
|
||||||
homogenization_dot_phi
|
homogenization_dot_phi
|
||||||
real(pReal), dimension(:,:,:), allocatable, public :: &
|
real(pReal), dimension(:,:,:), allocatable, public :: &
|
||||||
|
@ -136,6 +134,12 @@ module homogenization
|
||||||
real(pReal), intent(in) :: T, dot_T
|
real(pReal), intent(in) :: T, dot_T
|
||||||
end subroutine homogenization_thermal_setField
|
end subroutine homogenization_thermal_setField
|
||||||
|
|
||||||
|
|
||||||
|
module function homogenization_thermal_T(ce) result(T)
|
||||||
|
integer, intent(in) :: ce
|
||||||
|
real(pReal) :: T
|
||||||
|
end function homogenization_thermal_T
|
||||||
|
|
||||||
end interface
|
end interface
|
||||||
|
|
||||||
public :: &
|
public :: &
|
||||||
|
@ -145,6 +149,7 @@ module homogenization
|
||||||
thermal_conduction_getConductivity, &
|
thermal_conduction_getConductivity, &
|
||||||
thermal_conduction_getMassDensity, &
|
thermal_conduction_getMassDensity, &
|
||||||
homogenization_thermal_setfield, &
|
homogenization_thermal_setfield, &
|
||||||
|
homogenization_thermal_T, &
|
||||||
homogenization_forward, &
|
homogenization_forward, &
|
||||||
homogenization_results, &
|
homogenization_results, &
|
||||||
homogenization_restartRead, &
|
homogenization_restartRead, &
|
||||||
|
@ -182,8 +187,8 @@ 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(homogenization_T)
|
if (any(thermal_type == THERMAL_isothermal_ID)) call thermal_isothermal_init()
|
||||||
if (any(thermal_type == THERMAL_conduction_ID)) call thermal_conduction_init(homogenization_T)
|
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
|
||||||
|
|
|
@ -37,9 +37,6 @@ module subroutine thermal_init()
|
||||||
print'(/,a)', ' <<<+- homogenization_thermal init -+>>>'
|
print'(/,a)', ' <<<+- homogenization_thermal init -+>>>'
|
||||||
|
|
||||||
|
|
||||||
allocate(homogenization_T(discretization_nIPs*discretization_Nelems))
|
|
||||||
allocate(homogenization_dot_T(discretization_nIPs*discretization_Nelems))
|
|
||||||
|
|
||||||
configHomogenizations => config_material%get('homogenization')
|
configHomogenizations => config_material%get('homogenization')
|
||||||
allocate(param(configHomogenizations%length))
|
allocate(param(configHomogenizations%length))
|
||||||
allocate(current(configHomogenizations%length))
|
allocate(current(configHomogenizations%length))
|
||||||
|
@ -92,7 +89,7 @@ module subroutine thermal_homogenize(ip,el)
|
||||||
|
|
||||||
integer, intent(in) :: ip,el
|
integer, intent(in) :: ip,el
|
||||||
|
|
||||||
call constitutive_thermal_getRate(homogenization_dot_T((el-1)*discretization_nIPs+ip), ip,el)
|
!call constitutive_thermal_getRate(homogenization_dot_T((el-1)*discretization_nIPs+ip), ip,el)
|
||||||
|
|
||||||
end subroutine thermal_homogenize
|
end subroutine thermal_homogenize
|
||||||
|
|
||||||
|
@ -182,4 +179,15 @@ module subroutine homogenization_thermal_setField(T,dot_T, ce)
|
||||||
|
|
||||||
end subroutine homogenization_thermal_setField
|
end subroutine homogenization_thermal_setField
|
||||||
|
|
||||||
|
|
||||||
|
module function homogenization_thermal_T(ce) result(T)
|
||||||
|
|
||||||
|
integer, intent(in) :: ce
|
||||||
|
real(pReal) :: T
|
||||||
|
|
||||||
|
T = current(material_homogenizationAt2(ce))%T(material_homogenizationMemberAt2(ce))
|
||||||
|
|
||||||
|
end function homogenization_thermal_T
|
||||||
|
|
||||||
|
|
||||||
end submodule homogenization_thermal
|
end submodule homogenization_thermal
|
||||||
|
|
|
@ -36,9 +36,7 @@ contains
|
||||||
!> @brief module initialization
|
!> @brief module initialization
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine thermal_conduction_init(T)
|
subroutine thermal_conduction_init()
|
||||||
|
|
||||||
real(pReal), dimension(:), intent(inout) :: T
|
|
||||||
|
|
||||||
integer :: Ninstances,Nmaterialpoints,ho,ip,el,ce
|
integer :: Ninstances,Nmaterialpoints,ho,ip,el,ce
|
||||||
class(tNode), pointer :: &
|
class(tNode), pointer :: &
|
||||||
|
@ -73,15 +71,6 @@ subroutine thermal_conduction_init(T)
|
||||||
end associate
|
end associate
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
ce = 0
|
|
||||||
do el = 1, discretization_Nelems
|
|
||||||
do ip = 1, discretization_nIPs
|
|
||||||
ce = ce + 1
|
|
||||||
ho = material_homogenizationAt(el)
|
|
||||||
if (thermal_type(ho) == THERMAL_conduction_ID) T(ce) = thermal_initialT(ho)
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end subroutine thermal_conduction_init
|
end subroutine thermal_conduction_init
|
||||||
|
|
||||||
|
|
||||||
|
|
|
@ -16,9 +16,7 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief allocates fields, reads information from material configuration file
|
!> @brief allocates fields, reads information from material configuration file
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine thermal_isothermal_init(T)
|
subroutine thermal_isothermal_init()
|
||||||
|
|
||||||
real(pReal), dimension(:), intent(inout) :: T
|
|
||||||
|
|
||||||
integer :: Ninstances,Nmaterialpoints,ho,ip,el,ce
|
integer :: Ninstances,Nmaterialpoints,ho,ip,el,ce
|
||||||
|
|
||||||
|
@ -34,15 +32,6 @@ subroutine thermal_isothermal_init(T)
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
ce = 0
|
|
||||||
do el = 1, discretization_Nelems
|
|
||||||
do ip = 1, discretization_nIPs
|
|
||||||
ce = ce + 1
|
|
||||||
ho = material_homogenizationAt(el)
|
|
||||||
if (thermal_type(ho) == THERMAL_isothermal_ID) T(ce) = thermal_initialT(ho)
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end subroutine thermal_isothermal_init
|
end subroutine thermal_isothermal_init
|
||||||
|
|
||||||
end module thermal_isothermal
|
end module thermal_isothermal
|
||||||
|
|
Loading…
Reference in New Issue