Merge branch 'thermal-partioning' into development
This commit is contained in:
commit
c4fdbf88c8
2
PRIVATE
2
PRIVATE
|
@ -1 +1 @@
|
||||||
Subproject commit 4c8116ba3b9e9fbb325a580705028e8310139117
|
Subproject commit 02f5ad78ed8af3a34314d8d7a1c0bc0bc44ebe2e
|
|
@ -302,21 +302,21 @@ program DAMASK_grid
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! doing initialization depending on active solvers
|
! doing initialization depending on active solvers
|
||||||
call spectral_Utilities_init
|
call spectral_Utilities_init
|
||||||
do field = 1, nActiveFields
|
do field = 2, nActiveFields
|
||||||
select case (ID(field))
|
select case (ID(field))
|
||||||
case(FIELD_MECH_ID)
|
|
||||||
call mechanical_init
|
|
||||||
|
|
||||||
case(FIELD_THERMAL_ID)
|
case (FIELD_THERMAL_ID)
|
||||||
initial_conditions => config_load%get('initial_conditions',defaultVal=emptyDict)
|
initial_conditions => config_load%get('initial_conditions',defaultVal=emptyDict)
|
||||||
thermal => initial_conditions%get('thermal',defaultVal=emptyDict)
|
thermal => initial_conditions%get('thermal',defaultVal=emptyDict)
|
||||||
call grid_thermal_spectral_init(thermal%get_asFloat('T'))
|
call grid_thermal_spectral_init(thermal%get_asFloat('T'))
|
||||||
|
|
||||||
case(FIELD_DAMAGE_ID)
|
case (FIELD_DAMAGE_ID)
|
||||||
call grid_damage_spectral_init
|
call grid_damage_spectral_init()
|
||||||
|
|
||||||
end select
|
end select
|
||||||
enddo
|
end do
|
||||||
|
|
||||||
|
call mechanical_init()
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! write header of output file
|
! write header of output file
|
||||||
|
|
|
@ -21,26 +21,21 @@ module homogenization
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
|
||||||
|
|
||||||
enum, bind(c); enumerator :: &
|
enum, bind(c); enumerator :: &
|
||||||
THERMAL_ISOTHERMAL_ID, &
|
THERMAL_UNDEFINED_ID, &
|
||||||
THERMAL_CONDUCTION_ID, &
|
THERMAL_PASS_ID, &
|
||||||
DAMAGE_NONE_ID, &
|
THERMAL_ISOTEMPERATURE_ID
|
||||||
DAMAGE_NONLOCAL_ID, &
|
|
||||||
HOMOGENIZATION_UNDEFINED_ID, &
|
|
||||||
HOMOGENIZATION_NONE_ID, &
|
|
||||||
HOMOGENIZATION_ISOSTRAIN_ID, &
|
|
||||||
HOMOGENIZATION_RGC_ID
|
|
||||||
end enum
|
end enum
|
||||||
|
integer(kind(THERMAL_UNDEFINED_ID)), dimension(:), allocatable :: &
|
||||||
|
thermal_type !< type of each homogenization
|
||||||
|
|
||||||
type(tState), allocatable, dimension(:), public :: &
|
type(tState), allocatable, dimension(:), public :: &
|
||||||
homogState, &
|
homogState, &
|
||||||
damageState_h
|
damageState_h
|
||||||
|
|
||||||
integer(kind(THERMAL_isothermal_ID)), dimension(:), allocatable :: &
|
logical, allocatable, dimension(:) :: &
|
||||||
thermal_type !< thermal transport model
|
thermal_active, &
|
||||||
integer(kind(DAMAGE_none_ID)), dimension(:), allocatable :: &
|
damage_active
|
||||||
damage_type !< nonlocal damage model
|
|
||||||
|
|
||||||
logical, public :: &
|
logical, public :: &
|
||||||
terminallyIll = .false. !< at least one material point is terminally ill
|
terminallyIll = .false. !< at least one material point is terminally ill
|
||||||
|
@ -182,9 +177,7 @@ module homogenization
|
||||||
homogenization_forward, &
|
homogenization_forward, &
|
||||||
homogenization_results, &
|
homogenization_results, &
|
||||||
homogenization_restartRead, &
|
homogenization_restartRead, &
|
||||||
homogenization_restartWrite, &
|
homogenization_restartWrite
|
||||||
THERMAL_CONDUCTION_ID, &
|
|
||||||
DAMAGE_NONLOCAL_ID
|
|
||||||
|
|
||||||
contains
|
contains
|
||||||
|
|
||||||
|
@ -292,7 +285,6 @@ subroutine homogenization_thermal_response(Delta_t,cell_start,cell_end)
|
||||||
do ce = cell_start, cell_end
|
do ce = cell_start, cell_end
|
||||||
if (terminallyIll) continue
|
if (terminallyIll) continue
|
||||||
ho = material_homogenizationID(ce)
|
ho = material_homogenizationID(ce)
|
||||||
call thermal_partition(ce)
|
|
||||||
do co = 1, homogenization_Nconstituents(ho)
|
do co = 1, homogenization_Nconstituents(ho)
|
||||||
if (.not. phase_thermal_constitutive(Delta_t,material_phaseID(co,ce),material_phaseEntry(co,ce))) then
|
if (.not. phase_thermal_constitutive(Delta_t,material_phaseID(co,ce),material_phaseEntry(co,ce))) then
|
||||||
if (.not. terminallyIll) print*, ' Cell ', ce, ' terminally ill'
|
if (.not. terminallyIll) print*, ' Cell ', ce, ' terminally ill'
|
||||||
|
@ -352,19 +344,17 @@ subroutine homogenization_results
|
||||||
|
|
||||||
call mechanical_results(group_base,ho)
|
call mechanical_results(group_base,ho)
|
||||||
|
|
||||||
select case(damage_type(ho))
|
if (damage_active(ho)) then
|
||||||
case(DAMAGE_NONLOCAL_ID)
|
group = trim(group_base)//'/damage'
|
||||||
group = trim(group_base)//'/damage'
|
call results_closeGroup(results_addGroup(group))
|
||||||
call results_closeGroup(results_addGroup(group))
|
call damage_results(ho,group)
|
||||||
call damage_results(ho,group)
|
end if
|
||||||
end select
|
|
||||||
|
|
||||||
select case(thermal_type(ho))
|
if (thermal_active(ho)) then
|
||||||
case(THERMAL_CONDUCTION_ID)
|
group = trim(group_base)//'/thermal'
|
||||||
group = trim(group_base)//'/thermal'
|
call results_closeGroup(results_addGroup(group))
|
||||||
call results_closeGroup(results_addGroup(group))
|
call thermal_results(ho,group)
|
||||||
call thermal_results(ho,group)
|
end if
|
||||||
end select
|
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
@ -458,8 +448,9 @@ subroutine parseHomogenization
|
||||||
|
|
||||||
material_homogenization => config_material%get('homogenization')
|
material_homogenization => config_material%get('homogenization')
|
||||||
|
|
||||||
allocate(thermal_type(size(material_name_homogenization)),source=THERMAL_isothermal_ID)
|
allocate(thermal_type(size(material_name_homogenization)),source=THERMAL_UNDEFINED_ID)
|
||||||
allocate(damage_type (size(material_name_homogenization)),source=DAMAGE_none_ID)
|
allocate(thermal_active(size(material_name_homogenization)),source=.false.)
|
||||||
|
allocate(damage_active(size(material_name_homogenization)),source=.false.)
|
||||||
|
|
||||||
do h=1, size(material_name_homogenization)
|
do h=1, size(material_name_homogenization)
|
||||||
homog => material_homogenization%get(h)
|
homog => material_homogenization%get(h)
|
||||||
|
@ -467,8 +458,12 @@ subroutine parseHomogenization
|
||||||
if (homog%contains('thermal')) then
|
if (homog%contains('thermal')) then
|
||||||
homogThermal => homog%get('thermal')
|
homogThermal => homog%get('thermal')
|
||||||
select case (homogThermal%get_asString('type'))
|
select case (homogThermal%get_asString('type'))
|
||||||
case('pass','isotemperature')
|
case('pass')
|
||||||
thermal_type(h) = THERMAL_conduction_ID
|
thermal_type(h) = THERMAL_PASS_ID
|
||||||
|
thermal_active(h) = .true.
|
||||||
|
case('isotemperature')
|
||||||
|
thermal_type(h) = THERMAL_ISOTEMPERATURE_ID
|
||||||
|
thermal_active(h) = .true.
|
||||||
case default
|
case default
|
||||||
call IO_error(500,ext_msg=homogThermal%get_asString('type'))
|
call IO_error(500,ext_msg=homogThermal%get_asString('type'))
|
||||||
end select
|
end select
|
||||||
|
@ -478,7 +473,7 @@ subroutine parseHomogenization
|
||||||
homogDamage => homog%get('damage')
|
homogDamage => homog%get('damage')
|
||||||
select case (homogDamage%get_asString('type'))
|
select case (homogDamage%get_asString('type'))
|
||||||
case('pass')
|
case('pass')
|
||||||
damage_type(h) = DAMAGE_nonlocal_ID
|
damage_active(h) = .true.
|
||||||
case default
|
case default
|
||||||
call IO_error(500,ext_msg=homogDamage%get_asString('type'))
|
call IO_error(500,ext_msg=homogDamage%get_asString('type'))
|
||||||
end select
|
end select
|
||||||
|
|
|
@ -7,9 +7,20 @@ submodule(homogenization:damage) damage_pass
|
||||||
contains
|
contains
|
||||||
|
|
||||||
module subroutine pass_init()
|
module subroutine pass_init()
|
||||||
|
|
||||||
|
integer :: &
|
||||||
|
ho
|
||||||
|
|
||||||
print'(/,1x,a)', '<<<+- homogenization:damage:pass init -+>>>'
|
print'(/,1x,a)', '<<<+- homogenization:damage:pass init -+>>>'
|
||||||
|
|
||||||
|
do ho = 1, size(damage_active)
|
||||||
|
|
||||||
|
if (.not. damage_active(ho)) cycle
|
||||||
|
|
||||||
|
if (homogenization_Nconstituents(ho) /= 1) &
|
||||||
|
call IO_error(211,ext_msg='(pass) with N_constituents !=1')
|
||||||
|
end do
|
||||||
|
|
||||||
end subroutine pass_init
|
end subroutine pass_init
|
||||||
|
|
||||||
end submodule damage_pass
|
end submodule damage_pass
|
||||||
|
|
|
@ -56,8 +56,14 @@ submodule(homogenization) mechanical
|
||||||
end type tOutput
|
end type tOutput
|
||||||
type(tOutput), allocatable, dimension(:) :: output_mechanical
|
type(tOutput), allocatable, dimension(:) :: output_mechanical
|
||||||
|
|
||||||
integer(kind(HOMOGENIZATION_undefined_ID)), dimension(:), allocatable :: &
|
enum, bind(c); enumerator :: &
|
||||||
homogenization_type !< type of each homogenization
|
MECHANICAL_UNDEFINED_ID, &
|
||||||
|
MECHANICAL_PASS_ID, &
|
||||||
|
MECHANICAL_ISOSTRAIN_ID, &
|
||||||
|
MECHANICAL_RGC_ID
|
||||||
|
end enum
|
||||||
|
integer(kind(MECHANICAL_UNDEFINED_ID)), dimension(:), allocatable :: &
|
||||||
|
mechanical_type !< type of each homogenization
|
||||||
|
|
||||||
contains
|
contains
|
||||||
|
|
||||||
|
@ -75,9 +81,9 @@ module subroutine mechanical_init()
|
||||||
homogenization_F = homogenization_F0
|
homogenization_F = homogenization_F0
|
||||||
allocate(homogenization_P(3,3,discretization_Ncells),source=0.0_pReal)
|
allocate(homogenization_P(3,3,discretization_Ncells),source=0.0_pReal)
|
||||||
|
|
||||||
if (any(homogenization_type == HOMOGENIZATION_NONE_ID)) call pass_init()
|
if (any(mechanical_type == MECHANICAL_PASS_ID)) call pass_init()
|
||||||
if (any(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)) call isostrain_init()
|
if (any(mechanical_type == MECHANICAL_ISOSTRAIN_ID)) call isostrain_init()
|
||||||
if (any(homogenization_type == HOMOGENIZATION_RGC_ID)) call RGC_init()
|
if (any(mechanical_type == MECHANICAL_RGC_ID)) call RGC_init()
|
||||||
|
|
||||||
end subroutine mechanical_init
|
end subroutine mechanical_init
|
||||||
|
|
||||||
|
@ -96,15 +102,15 @@ module subroutine mechanical_partition(subF,ce)
|
||||||
real(pReal), dimension (3,3,homogenization_Nconstituents(material_homogenizationID(ce))) :: Fs
|
real(pReal), dimension (3,3,homogenization_Nconstituents(material_homogenizationID(ce))) :: Fs
|
||||||
|
|
||||||
|
|
||||||
chosenHomogenization: select case(homogenization_type(material_homogenizationID(ce)))
|
chosenHomogenization: select case(mechanical_type(material_homogenizationID(ce)))
|
||||||
|
|
||||||
case (HOMOGENIZATION_NONE_ID) chosenHomogenization
|
case (MECHANICAL_PASS_ID) chosenHomogenization
|
||||||
Fs(1:3,1:3,1) = subF
|
Fs(1:3,1:3,1) = subF
|
||||||
|
|
||||||
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
|
case (MECHANICAL_ISOSTRAIN_ID) chosenHomogenization
|
||||||
call isostrain_partitionDeformation(Fs,subF)
|
call isostrain_partitionDeformation(Fs,subF)
|
||||||
|
|
||||||
case (HOMOGENIZATION_RGC_ID) chosenHomogenization
|
case (MECHANICAL_RGC_ID) chosenHomogenization
|
||||||
call RGC_partitionDeformation(Fs,subF,ce)
|
call RGC_partitionDeformation(Fs,subF,ce)
|
||||||
|
|
||||||
end select chosenHomogenization
|
end select chosenHomogenization
|
||||||
|
@ -160,7 +166,7 @@ module function mechanical_updateState(subdt,subF,ce) result(doneAndHappy)
|
||||||
real(pReal) :: Ps(3,3,homogenization_Nconstituents(material_homogenizationID(ce)))
|
real(pReal) :: Ps(3,3,homogenization_Nconstituents(material_homogenizationID(ce)))
|
||||||
|
|
||||||
|
|
||||||
if (homogenization_type(material_homogenizationID(ce)) == HOMOGENIZATION_RGC_ID) then
|
if (mechanical_type(material_homogenizationID(ce)) == MECHANICAL_RGC_ID) then
|
||||||
do co = 1, homogenization_Nconstituents(material_homogenizationID(ce))
|
do co = 1, homogenization_Nconstituents(material_homogenizationID(ce))
|
||||||
dPdFs(:,:,:,:,co) = phase_mechanical_dPdF(subdt,co,ce)
|
dPdFs(:,:,:,:,co) = phase_mechanical_dPdF(subdt,co,ce)
|
||||||
Fs(:,:,co) = phase_F(co,ce)
|
Fs(:,:,co) = phase_F(co,ce)
|
||||||
|
@ -189,9 +195,9 @@ module subroutine mechanical_results(group_base,ho)
|
||||||
group = trim(group_base)//'/mechanical'
|
group = trim(group_base)//'/mechanical'
|
||||||
call results_closeGroup(results_addGroup(group))
|
call results_closeGroup(results_addGroup(group))
|
||||||
|
|
||||||
select case(homogenization_type(ho))
|
select case(mechanical_type(ho))
|
||||||
|
|
||||||
case(HOMOGENIZATION_rgc_ID)
|
case(MECHANICAL_RGC_ID)
|
||||||
call RGC_results(ho,group)
|
call RGC_results(ho,group)
|
||||||
|
|
||||||
end select
|
end select
|
||||||
|
@ -204,7 +210,7 @@ module subroutine mechanical_results(group_base,ho)
|
||||||
'deformation gradient','1')
|
'deformation gradient','1')
|
||||||
case('P')
|
case('P')
|
||||||
call results_writeDataset(reshape(homogenization_P,[3,3,discretization_nCells]),group,'P', &
|
call results_writeDataset(reshape(homogenization_P,[3,3,discretization_nCells]),group,'P', &
|
||||||
'deformation gradient','1')
|
'first Piola-Kirchhoff stress','Pa')
|
||||||
end select
|
end select
|
||||||
end do
|
end do
|
||||||
|
|
||||||
|
@ -226,7 +232,7 @@ subroutine parseMechanical()
|
||||||
|
|
||||||
material_homogenization => config_material%get('homogenization')
|
material_homogenization => config_material%get('homogenization')
|
||||||
|
|
||||||
allocate(homogenization_type(size(material_name_homogenization)), source=HOMOGENIZATION_undefined_ID)
|
allocate(mechanical_type(size(material_name_homogenization)), source=MECHANICAL_UNDEFINED_ID)
|
||||||
allocate(output_mechanical(size(material_name_homogenization)))
|
allocate(output_mechanical(size(material_name_homogenization)))
|
||||||
|
|
||||||
do ho=1, size(material_name_homogenization)
|
do ho=1, size(material_name_homogenization)
|
||||||
|
@ -239,11 +245,11 @@ subroutine parseMechanical()
|
||||||
#endif
|
#endif
|
||||||
select case (mechanical%get_asString('type'))
|
select case (mechanical%get_asString('type'))
|
||||||
case('pass')
|
case('pass')
|
||||||
homogenization_type(ho) = HOMOGENIZATION_NONE_ID
|
mechanical_type(ho) = MECHANICAL_PASS_ID
|
||||||
case('isostrain')
|
case('isostrain')
|
||||||
homogenization_type(ho) = HOMOGENIZATION_ISOSTRAIN_ID
|
mechanical_type(ho) = MECHANICAL_ISOSTRAIN_ID
|
||||||
case('RGC')
|
case('RGC')
|
||||||
homogenization_type(ho) = HOMOGENIZATION_RGC_ID
|
mechanical_type(ho) = MECHANICAL_RGC_ID
|
||||||
case default
|
case default
|
||||||
call IO_error(500,ext_msg=mechanical%get_asString('type'))
|
call IO_error(500,ext_msg=mechanical%get_asString('type'))
|
||||||
end select
|
end select
|
||||||
|
|
|
@ -88,7 +88,7 @@ module subroutine RGC_init()
|
||||||
|
|
||||||
print'(/,1x,a)', '<<<+- homogenization:mechanical:RGC init -+>>>'
|
print'(/,1x,a)', '<<<+- homogenization:mechanical:RGC init -+>>>'
|
||||||
|
|
||||||
print'(/,a,i0)', ' # homogenizations: ',count(homogenization_type == HOMOGENIZATION_RGC_ID)
|
print'(/,a,i0)', ' # homogenizations: ',count(mechanical_type == MECHANICAL_RGC_ID)
|
||||||
flush(IO_STDOUT)
|
flush(IO_STDOUT)
|
||||||
|
|
||||||
print'(/,1x,a)', 'D.D. Tjahjanto et al., International Journal of Material Forming 2(1):939–942, 2009'
|
print'(/,1x,a)', 'D.D. Tjahjanto et al., International Journal of Material Forming 2(1):939–942, 2009'
|
||||||
|
@ -137,8 +137,8 @@ module subroutine RGC_init()
|
||||||
if (num%volDiscrPow <= 0.0_pReal) call IO_error(301,ext_msg='volDiscrPw_RGC')
|
if (num%volDiscrPow <= 0.0_pReal) call IO_error(301,ext_msg='volDiscrPw_RGC')
|
||||||
|
|
||||||
|
|
||||||
do ho = 1, size(homogenization_type)
|
do ho = 1, size(mechanical_type)
|
||||||
if (homogenization_type(ho) /= HOMOGENIZATION_RGC_ID) cycle
|
if (mechanical_type(ho) /= MECHANICAL_RGC_ID) cycle
|
||||||
homog => material_homogenization%get(ho)
|
homog => material_homogenization%get(ho)
|
||||||
homogMech => homog%get('mechanical')
|
homogMech => homog%get('mechanical')
|
||||||
associate(prm => param(ho), &
|
associate(prm => param(ho), &
|
||||||
|
|
|
@ -19,11 +19,11 @@ module subroutine isostrain_init
|
||||||
|
|
||||||
print'(/,1x,a)', '<<<+- homogenization:mechanical:isostrain init -+>>>'
|
print'(/,1x,a)', '<<<+- homogenization:mechanical:isostrain init -+>>>'
|
||||||
|
|
||||||
print'(/,a,i0)', ' # homogenizations: ',count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)
|
print'(/,a,i0)', ' # homogenizations: ',count(mechanical_type == MECHANICAL_ISOSTRAIN_ID)
|
||||||
flush(IO_STDOUT)
|
flush(IO_STDOUT)
|
||||||
|
|
||||||
do ho = 1, size(homogenization_type)
|
do ho = 1, size(mechanical_type)
|
||||||
if (homogenization_type(ho) /= HOMOGENIZATION_ISOSTRAIN_ID) cycle
|
if (mechanical_type(ho) /= MECHANICAL_ISOSTRAIN_ID) cycle
|
||||||
|
|
||||||
Nmembers = count(material_homogenizationID == ho)
|
Nmembers = count(material_homogenizationID == ho)
|
||||||
homogState(ho)%sizeState = 0
|
homogState(ho)%sizeState = 0
|
||||||
|
|
|
@ -11,7 +11,7 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief allocates all necessary fields, reads information from material configuration file
|
!> @brief allocates all necessary fields, reads information from material configuration file
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module subroutine pass_init
|
module subroutine pass_init()
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
ho, &
|
ho, &
|
||||||
|
@ -19,14 +19,14 @@ module subroutine pass_init
|
||||||
|
|
||||||
print'(/,1x,a)', '<<<+- homogenization:mechanical:pass init -+>>>'
|
print'(/,1x,a)', '<<<+- homogenization:mechanical:pass init -+>>>'
|
||||||
|
|
||||||
print'(/,a,i0)', ' # homogenizations: ',count(homogenization_type == HOMOGENIZATION_NONE_ID)
|
print'(/,a,i0)', ' # homogenizations: ',count(mechanical_type == MECHANICAL_PASS_ID)
|
||||||
flush(IO_STDOUT)
|
flush(IO_STDOUT)
|
||||||
|
|
||||||
do ho = 1, size(homogenization_type)
|
do ho = 1, size(mechanical_type)
|
||||||
if (homogenization_type(ho) /= HOMOGENIZATION_NONE_ID) cycle
|
if (mechanical_type(ho) /= MECHANICAL_PASS_ID) cycle
|
||||||
|
|
||||||
if (homogenization_Nconstituents(ho) /= 1) &
|
if (homogenization_Nconstituents(ho) /= 1) &
|
||||||
call IO_error(211,ext_msg='N_constituents (pass)')
|
call IO_error(211,ext_msg='(pass) with N_constituents !=1')
|
||||||
|
|
||||||
Nmembers = count(material_homogenizationID == ho)
|
Nmembers = count(material_homogenizationID == ho)
|
||||||
homogState(ho)%sizeState = 0
|
homogState(ho)%sizeState = 0
|
||||||
|
|
|
@ -69,7 +69,7 @@ module subroutine thermal_init()
|
||||||
case ('pass')
|
case ('pass')
|
||||||
call pass_init()
|
call pass_init()
|
||||||
|
|
||||||
case ('isothermal')
|
case ('isotemperature')
|
||||||
call isotemperature_init()
|
call isotemperature_init()
|
||||||
|
|
||||||
end select
|
end select
|
||||||
|
@ -172,7 +172,7 @@ module subroutine homogenization_thermal_setField(T,dot_T, ce)
|
||||||
|
|
||||||
current(material_homogenizationID(ce))%T(material_homogenizationEntry(ce)) = T
|
current(material_homogenizationID(ce))%T(material_homogenizationEntry(ce)) = T
|
||||||
current(material_homogenizationID(ce))%dot_T(material_homogenizationEntry(ce)) = dot_T
|
current(material_homogenizationID(ce))%dot_T(material_homogenizationEntry(ce)) = dot_T
|
||||||
|
call thermal_partition(ce)
|
||||||
|
|
||||||
end subroutine homogenization_thermal_setField
|
end subroutine homogenization_thermal_setField
|
||||||
|
|
||||||
|
|
|
@ -8,10 +8,19 @@ contains
|
||||||
|
|
||||||
module subroutine pass_init()
|
module subroutine pass_init()
|
||||||
|
|
||||||
|
integer :: &
|
||||||
|
ho
|
||||||
|
|
||||||
print'(/,1x,a)', '<<<+- homogenization:thermal:pass init -+>>>'
|
print'(/,1x,a)', '<<<+- homogenization:thermal:pass init -+>>>'
|
||||||
|
|
||||||
if (homogenization_Nconstituents(1) /= 1) &
|
do ho = 1, size(thermal_type)
|
||||||
call IO_error(211,ext_msg='N_constituents (pass)')
|
|
||||||
|
if (thermal_type(ho) /= THERMAL_PASS_ID) cycle
|
||||||
|
|
||||||
|
if (homogenization_Nconstituents(ho) /= 1) &
|
||||||
|
call IO_error(211,ext_msg='(pass) with N_constituents !=1')
|
||||||
|
|
||||||
|
end do
|
||||||
|
|
||||||
end subroutine pass_init
|
end subroutine pass_init
|
||||||
|
|
||||||
|
|
|
@ -388,7 +388,7 @@ end function thermal_active
|
||||||
|
|
||||||
|
|
||||||
!----------------------------------------------------------------------------------------------
|
!----------------------------------------------------------------------------------------------
|
||||||
!< @brief writes damage sources results to HDF5 output file
|
!< @brief writes thermal sources results to HDF5 output file
|
||||||
!----------------------------------------------------------------------------------------------
|
!----------------------------------------------------------------------------------------------
|
||||||
module subroutine thermal_results(group,ph)
|
module subroutine thermal_results(group,ph)
|
||||||
|
|
||||||
|
@ -398,18 +398,16 @@ module subroutine thermal_results(group,ph)
|
||||||
|
|
||||||
integer :: ou
|
integer :: ou
|
||||||
|
|
||||||
if (allocated(param(ph)%output)) then
|
if (.not. allocated(param(ph)%output)) return
|
||||||
call results_closeGroup(results_addGroup(group//'thermal'))
|
|
||||||
else
|
call results_closeGroup(results_addGroup(group//'thermal'))
|
||||||
return
|
|
||||||
endif
|
|
||||||
|
|
||||||
do ou = 1, size(param(ph)%output)
|
do ou = 1, size(param(ph)%output)
|
||||||
|
|
||||||
select case(trim(param(ph)%output(ou)))
|
select case(trim(param(ph)%output(ou)))
|
||||||
|
|
||||||
case ('T')
|
case ('T')
|
||||||
call results_writeDataset(current(ph)%T,group//'thermal','T', 'temperature','T')
|
call results_writeDataset(current(ph)%T,group//'thermal','T', 'temperature','K')
|
||||||
|
|
||||||
end select
|
end select
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue