check N_constituents only if active
This commit is contained in:
parent
bc2a9de095
commit
2bdf0d11cb
|
@ -21,13 +21,13 @@ module homogenization
|
|||
implicit none
|
||||
private
|
||||
|
||||
|
||||
enum, bind(c); enumerator :: &
|
||||
HOMOGENIZATION_UNDEFINED_ID, &
|
||||
HOMOGENIZATION_NONE_ID, &
|
||||
HOMOGENIZATION_ISOSTRAIN_ID, &
|
||||
HOMOGENIZATION_RGC_ID
|
||||
THERMAL_UNDEFINED_ID, &
|
||||
THERMAL_PASS_ID, &
|
||||
THERMAL_ISOTEMPERATURE_ID
|
||||
end enum
|
||||
integer(kind(THERMAL_UNDEFINED_ID)), dimension(:), allocatable :: &
|
||||
thermal_type !< type of each homogenization
|
||||
|
||||
type(tState), allocatable, dimension(:), public :: &
|
||||
homogState, &
|
||||
|
@ -448,6 +448,7 @@ subroutine parseHomogenization
|
|||
|
||||
material_homogenization => config_material%get('homogenization')
|
||||
|
||||
allocate(thermal_type(size(material_name_homogenization)),source=THERMAL_UNDEFINED_ID)
|
||||
allocate(thermal_active(size(material_name_homogenization)),source=.false.)
|
||||
allocate(damage_active(size(material_name_homogenization)),source=.false.)
|
||||
|
||||
|
@ -457,7 +458,11 @@ subroutine parseHomogenization
|
|||
if (homog%contains('thermal')) then
|
||||
homogThermal => homog%get('thermal')
|
||||
select case (homogThermal%get_asString('type'))
|
||||
case('pass','isotemperature')
|
||||
case('pass')
|
||||
thermal_type(h) = THERMAL_PASS_ID
|
||||
thermal_active(h) = .true.
|
||||
case('isotemperature')
|
||||
thermal_type(h) = THERMAL_ISOTEMPERATURE_ID
|
||||
thermal_active(h) = .true.
|
||||
case default
|
||||
call IO_error(500,ext_msg=homogThermal%get_asString('type'))
|
||||
|
|
|
@ -8,10 +8,18 @@ contains
|
|||
|
||||
module subroutine pass_init()
|
||||
|
||||
integer :: &
|
||||
ho
|
||||
|
||||
print'(/,1x,a)', '<<<+- homogenization:damage:pass init -+>>>'
|
||||
|
||||
do ho = 1, size(damage_active)
|
||||
|
||||
if (.not. damage_active(ho)) cycle
|
||||
|
||||
if (homogenization_Nconstituents(1) /= 1) & !ToDo: needs extension to multiple homogenizations
|
||||
call IO_error(211,ext_msg='(pass) with N_constituents !=1')
|
||||
end do
|
||||
|
||||
end subroutine pass_init
|
||||
|
||||
|
|
|
@ -56,8 +56,14 @@ submodule(homogenization) mechanical
|
|||
end type tOutput
|
||||
type(tOutput), allocatable, dimension(:) :: output_mechanical
|
||||
|
||||
integer(kind(HOMOGENIZATION_undefined_ID)), dimension(:), allocatable :: &
|
||||
homogenization_type !< type of each homogenization
|
||||
enum, bind(c); enumerator :: &
|
||||
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
|
||||
|
||||
|
@ -75,9 +81,9 @@ module subroutine mechanical_init()
|
|||
homogenization_F = homogenization_F0
|
||||
allocate(homogenization_P(3,3,discretization_Ncells),source=0.0_pReal)
|
||||
|
||||
if (any(homogenization_type == HOMOGENIZATION_NONE_ID)) call pass_init()
|
||||
if (any(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)) call isostrain_init()
|
||||
if (any(homogenization_type == HOMOGENIZATION_RGC_ID)) call RGC_init()
|
||||
if (any(mechanical_type == MECHANICAL_PASS_ID)) call pass_init()
|
||||
if (any(mechanical_type == MECHANICAL_ISOSTRAIN_ID)) call isostrain_init()
|
||||
if (any(mechanical_type == MECHANICAL_RGC_ID)) call RGC_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
|
||||
|
||||
|
||||
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
|
||||
|
||||
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
|
||||
case (MECHANICAL_ISOSTRAIN_ID) chosenHomogenization
|
||||
call isostrain_partitionDeformation(Fs,subF)
|
||||
|
||||
case (HOMOGENIZATION_RGC_ID) chosenHomogenization
|
||||
case (MECHANICAL_RGC_ID) chosenHomogenization
|
||||
call RGC_partitionDeformation(Fs,subF,ce)
|
||||
|
||||
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)))
|
||||
|
||||
|
||||
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))
|
||||
dPdFs(:,:,:,:,co) = phase_mechanical_dPdF(subdt,co,ce)
|
||||
Fs(:,:,co) = phase_F(co,ce)
|
||||
|
@ -189,9 +195,9 @@ module subroutine mechanical_results(group_base,ho)
|
|||
group = trim(group_base)//'/mechanical'
|
||||
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)
|
||||
|
||||
end select
|
||||
|
@ -226,7 +232,7 @@ subroutine parseMechanical()
|
|||
|
||||
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)))
|
||||
|
||||
do ho=1, size(material_name_homogenization)
|
||||
|
@ -239,11 +245,11 @@ subroutine parseMechanical()
|
|||
#endif
|
||||
select case (mechanical%get_asString('type'))
|
||||
case('pass')
|
||||
homogenization_type(ho) = HOMOGENIZATION_NONE_ID
|
||||
mechanical_type(ho) = MECHANICAL_PASS_ID
|
||||
case('isostrain')
|
||||
homogenization_type(ho) = HOMOGENIZATION_ISOSTRAIN_ID
|
||||
mechanical_type(ho) = MECHANICAL_ISOSTRAIN_ID
|
||||
case('RGC')
|
||||
homogenization_type(ho) = HOMOGENIZATION_RGC_ID
|
||||
mechanical_type(ho) = MECHANICAL_RGC_ID
|
||||
case default
|
||||
call IO_error(500,ext_msg=mechanical%get_asString('type'))
|
||||
end select
|
||||
|
|
|
@ -88,7 +88,7 @@ module subroutine 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)
|
||||
|
||||
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')
|
||||
|
||||
|
||||
do ho = 1, size(homogenization_type)
|
||||
if (homogenization_type(ho) /= HOMOGENIZATION_RGC_ID) cycle
|
||||
do ho = 1, size(mechanical_type)
|
||||
if (mechanical_type(ho) /= MECHANICAL_RGC_ID) cycle
|
||||
homog => material_homogenization%get(ho)
|
||||
homogMech => homog%get('mechanical')
|
||||
associate(prm => param(ho), &
|
||||
|
|
|
@ -19,11 +19,11 @@ module subroutine 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)
|
||||
|
||||
do ho = 1, size(homogenization_type)
|
||||
if (homogenization_type(ho) /= HOMOGENIZATION_ISOSTRAIN_ID) cycle
|
||||
do ho = 1, size(mechanical_type)
|
||||
if (mechanical_type(ho) /= MECHANICAL_ISOSTRAIN_ID) cycle
|
||||
|
||||
Nmembers = count(material_homogenizationID == ho)
|
||||
homogState(ho)%sizeState = 0
|
||||
|
|
|
@ -19,11 +19,11 @@ module subroutine 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)
|
||||
|
||||
do ho = 1, size(homogenization_type)
|
||||
if (homogenization_type(ho) /= HOMOGENIZATION_NONE_ID) cycle
|
||||
do ho = 1, size(mechanical_type)
|
||||
if (mechanical_type(ho) /= MECHANICAL_PASS_ID) cycle
|
||||
|
||||
if (homogenization_Nconstituents(ho) /= 1) &
|
||||
call IO_error(211,ext_msg='(pass) with N_constituents !=1')
|
||||
|
|
|
@ -8,10 +8,19 @@ contains
|
|||
|
||||
module subroutine pass_init()
|
||||
|
||||
integer :: &
|
||||
ho
|
||||
|
||||
print'(/,1x,a)', '<<<+- homogenization:thermal:pass init -+>>>'
|
||||
|
||||
if (homogenization_Nconstituents(1) /= 1) & !ToDo: needs extension to multiple homogenizations
|
||||
call IO_error(211,ext_msg='(pass) with N_constituents !=1')
|
||||
do ho = 1, size(thermal_type)
|
||||
|
||||
if (thermal_type(ho) /= THERMAL_PASS_ID) cycle
|
||||
|
||||
if (homogenization_Nconstituents(1) /= 1) & !ToDo: needs extension to multiple homogenizations
|
||||
call IO_error(211,ext_msg='(pass) with N_constituents !=1')
|
||||
|
||||
end do
|
||||
|
||||
end subroutine pass_init
|
||||
|
||||
|
|
Loading…
Reference in New Issue