base HDF5 output on new data
This commit is contained in:
parent
c2ae2c919b
commit
599dc2a2c6
|
@ -134,6 +134,10 @@ 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 subroutine thermal_conduction_results(ho,group)
|
||||||
|
integer, intent(in) :: ho
|
||||||
|
character(len=*), intent(in) :: group
|
||||||
|
end subroutine thermal_conduction_results
|
||||||
|
|
||||||
module function homogenization_thermal_T(ce) result(T)
|
module function homogenization_thermal_T(ce) result(T)
|
||||||
integer, intent(in) :: ce
|
integer, intent(in) :: ce
|
||||||
|
|
|
@ -180,6 +180,29 @@ module subroutine homogenization_thermal_setField(T,dot_T, ce)
|
||||||
end subroutine homogenization_thermal_setField
|
end subroutine homogenization_thermal_setField
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief writes results to HDF5 output file
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
module subroutine thermal_conduction_results(ho,group)
|
||||||
|
|
||||||
|
integer, intent(in) :: ho
|
||||||
|
character(len=*), intent(in) :: group
|
||||||
|
|
||||||
|
integer :: o
|
||||||
|
|
||||||
|
associate(prm => param(ho))
|
||||||
|
outputsLoop: do o = 1,size(prm%output)
|
||||||
|
select case(trim(prm%output(o)))
|
||||||
|
case('T')
|
||||||
|
call results_writeDataset(group,current(ho)%T,'T','temperature','K')
|
||||||
|
end select
|
||||||
|
enddo outputsLoop
|
||||||
|
end associate
|
||||||
|
|
||||||
|
end subroutine thermal_conduction_results
|
||||||
|
|
||||||
|
|
||||||
module function homogenization_thermal_T(ce) result(T)
|
module function homogenization_thermal_T(ce) result(T)
|
||||||
|
|
||||||
integer, intent(in) :: ce
|
integer, intent(in) :: ce
|
||||||
|
|
|
@ -15,19 +15,10 @@ module thermal_conduction
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
|
||||||
type :: tParameters
|
|
||||||
character(len=pStringLen), allocatable, dimension(:) :: &
|
|
||||||
output
|
|
||||||
end type tParameters
|
|
||||||
|
|
||||||
type(tparameters), dimension(:), allocatable :: &
|
|
||||||
param
|
|
||||||
|
|
||||||
public :: &
|
public :: &
|
||||||
thermal_conduction_init, &
|
thermal_conduction_init, &
|
||||||
thermal_conduction_getSource, &
|
thermal_conduction_getSource, &
|
||||||
thermal_conduction_putTemperatureAndItsRate, &
|
thermal_conduction_putTemperatureAndItsRate
|
||||||
thermal_conduction_results
|
|
||||||
|
|
||||||
contains
|
contains
|
||||||
|
|
||||||
|
@ -38,37 +29,22 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine thermal_conduction_init()
|
subroutine thermal_conduction_init()
|
||||||
|
|
||||||
integer :: Ninstances,Nmaterialpoints,ho,ip,el,ce
|
integer :: Nmaterialpoints,ho
|
||||||
class(tNode), pointer :: &
|
class(tNode), pointer :: &
|
||||||
material_homogenization, &
|
material_homogenization
|
||||||
homog, &
|
|
||||||
homogThermal
|
|
||||||
|
|
||||||
|
|
||||||
print'(/,a)', ' <<<+- thermal_conduction init -+>>>'; flush(6)
|
print'(/,a)', ' <<<+- thermal_conduction init -+>>>'; flush(6)
|
||||||
|
|
||||||
Ninstances = count(thermal_type == THERMAL_conduction_ID)
|
|
||||||
allocate(param(Ninstances))
|
|
||||||
|
|
||||||
material_homogenization => config_material%get('homogenization')
|
material_homogenization => config_material%get('homogenization')
|
||||||
do ho = 1, size(material_name_homogenization)
|
do ho = 1, size(material_name_homogenization)
|
||||||
if (thermal_type(ho) /= THERMAL_conduction_ID) cycle
|
if (thermal_type(ho) /= THERMAL_conduction_ID) cycle
|
||||||
homog => material_homogenization%get(ho)
|
|
||||||
homogThermal => homog%get('thermal')
|
|
||||||
associate(prm => param(thermal_typeInstance(ho)))
|
|
||||||
|
|
||||||
#if defined (__GFORTRAN__)
|
|
||||||
prm%output = output_asStrings(homogThermal)
|
|
||||||
#else
|
|
||||||
prm%output = homogThermal%get_asStrings('output',defaultVal=emptyStringArray)
|
|
||||||
#endif
|
|
||||||
|
|
||||||
Nmaterialpoints=count(material_homogenizationAt==ho)
|
Nmaterialpoints=count(material_homogenizationAt==ho)
|
||||||
|
|
||||||
allocate (temperature (ho)%p(Nmaterialpoints), source=thermal_initialT(ho))
|
allocate (temperature (ho)%p(Nmaterialpoints), source=thermal_initialT(ho))
|
||||||
allocate (temperatureRate(ho)%p(Nmaterialpoints), source=0.0_pReal)
|
allocate (temperatureRate(ho)%p(Nmaterialpoints), source=0.0_pReal)
|
||||||
|
|
||||||
end associate
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end subroutine thermal_conduction_init
|
end subroutine thermal_conduction_init
|
||||||
|
@ -119,26 +95,4 @@ subroutine thermal_conduction_putTemperatureAndItsRate(T,Tdot,ip,el)
|
||||||
end subroutine thermal_conduction_putTemperatureAndItsRate
|
end subroutine thermal_conduction_putTemperatureAndItsRate
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief writes results to HDF5 output file
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine thermal_conduction_results(homog,group)
|
|
||||||
|
|
||||||
integer, intent(in) :: homog
|
|
||||||
character(len=*), intent(in) :: group
|
|
||||||
|
|
||||||
integer :: o
|
|
||||||
|
|
||||||
associate(prm => param(damage_typeInstance(homog)))
|
|
||||||
outputsLoop: do o = 1,size(prm%output)
|
|
||||||
select case(trim(prm%output(o)))
|
|
||||||
case('T')
|
|
||||||
call results_writeDataset(group,temperature(homog)%p,'T',&
|
|
||||||
'temperature','K')
|
|
||||||
end select
|
|
||||||
enddo outputsLoop
|
|
||||||
end associate
|
|
||||||
|
|
||||||
end subroutine thermal_conduction_results
|
|
||||||
|
|
||||||
end module thermal_conduction
|
end module thermal_conduction
|
||||||
|
|
Loading…
Reference in New Issue