parent
7311d50df7
commit
420d9bd036
|
@ -170,7 +170,7 @@ module subroutine plastic_nonlocal_init
|
|||
integer :: &
|
||||
sizeState, sizeDotState,sizeDependentState, sizeDeltaState, &
|
||||
maxNinstances, &
|
||||
p, i, &
|
||||
p, &
|
||||
l, &
|
||||
s1, s2, &
|
||||
s, &
|
||||
|
|
|
@ -16,14 +16,9 @@ module thermal_adiabatic
|
|||
implicit none
|
||||
private
|
||||
|
||||
enum, bind(c)
|
||||
enumerator :: undefined_ID, &
|
||||
temperature_ID
|
||||
end enum
|
||||
|
||||
type :: tParameters
|
||||
integer(kind(undefined_ID)), dimension(:), allocatable :: &
|
||||
outputID
|
||||
character(len=pStringLen), allocatable, dimension(:) :: &
|
||||
output
|
||||
end type tParameters
|
||||
|
||||
type(tparameters), dimension(:), allocatable :: &
|
||||
|
@ -47,9 +42,8 @@ contains
|
|||
subroutine thermal_adiabatic_init
|
||||
|
||||
integer :: maxNinstance,o,h,NofMyHomog
|
||||
character(len=pStringLen), dimension(:), allocatable :: outputs
|
||||
|
||||
write(6,'(/,a)') ' <<<+- thermal_'//THERMAL_ADIABATIC_label//' init -+>>>'; flush(6)
|
||||
write(6,'(/,a)') ' <<<+- thermal_'//THERMAL_ADIABATIC_label//' init -+>>>'; flush(6)
|
||||
|
||||
maxNinstance = count(thermal_type == THERMAL_adiabatic_ID)
|
||||
if (maxNinstance == 0) return
|
||||
|
@ -60,15 +54,7 @@ subroutine thermal_adiabatic_init
|
|||
if (thermal_type(h) /= THERMAL_adiabatic_ID) cycle
|
||||
associate(prm => param(thermal_typeInstance(h)),config => config_homogenization(h))
|
||||
|
||||
outputs = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||
allocate(prm%outputID(0))
|
||||
|
||||
do o=1, size(outputs)
|
||||
select case(outputs(o))
|
||||
case('temperature')
|
||||
prm%outputID = [prm%outputID, temperature_ID]
|
||||
end select
|
||||
enddo
|
||||
prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||
|
||||
NofMyHomog=count(material_homogenizationAt==h)
|
||||
thermalState(h)%sizeState = 1
|
||||
|
@ -76,7 +62,6 @@ subroutine thermal_adiabatic_init
|
|||
allocate(thermalState(h)%subState0(1,NofMyHomog), source=thermal_initialT(h))
|
||||
allocate(thermalState(h)%state (1,NofMyHomog), source=thermal_initialT(h))
|
||||
|
||||
nullify(thermalMapping(h)%p)
|
||||
thermalMapping(h)%p => material_homogenizationMemberAt
|
||||
deallocate(temperature(h)%p)
|
||||
temperature(h)%p => thermalState(h)%state(1,:)
|
||||
|
@ -246,14 +231,13 @@ subroutine thermal_adiabatic_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%outputID)
|
||||
select case(prm%outputID(o))
|
||||
|
||||
case (temperature_ID)
|
||||
outputsLoop: do o = 1,size(prm%output)
|
||||
select case(trim(prm%output(o)))
|
||||
case('temperature') ! ToDo: should be 'T'
|
||||
call results_writeDataset(group,temperature(homog)%p,'T',&
|
||||
'temperature','K')
|
||||
end select
|
||||
|
|
|
@ -15,15 +15,9 @@ module thermal_conduction
|
|||
implicit none
|
||||
private
|
||||
|
||||
enum, bind(c)
|
||||
enumerator :: &
|
||||
undefined_ID, &
|
||||
temperature_ID
|
||||
end enum
|
||||
|
||||
type :: tParameters
|
||||
integer(kind(undefined_ID)), dimension(:), allocatable :: &
|
||||
outputID
|
||||
character(len=pStringLen), allocatable, dimension(:) :: &
|
||||
output
|
||||
end type tParameters
|
||||
|
||||
type(tparameters), dimension(:), allocatable :: &
|
||||
|
@ -49,9 +43,8 @@ subroutine thermal_conduction_init
|
|||
|
||||
|
||||
integer :: maxNinstance,o,NofMyHomog,h
|
||||
character(len=pStringLen), dimension(:), allocatable :: outputs
|
||||
|
||||
write(6,'(/,a)') ' <<<+- thermal_'//THERMAL_CONDUCTION_label//' init -+>>>'; flush(6)
|
||||
write(6,'(/,a)') ' <<<+- thermal_'//THERMAL_CONDUCTION_label//' init -+>>>'; flush(6)
|
||||
|
||||
maxNinstance = count(thermal_type == THERMAL_conduction_ID)
|
||||
if (maxNinstance == 0) return
|
||||
|
@ -62,15 +55,7 @@ subroutine thermal_conduction_init
|
|||
if (thermal_type(h) /= THERMAL_conduction_ID) cycle
|
||||
associate(prm => param(thermal_typeInstance(h)),config => config_homogenization(h))
|
||||
|
||||
outputs = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||
allocate(prm%outputID(0))
|
||||
|
||||
do o=1, size(outputs)
|
||||
select case(outputs(o))
|
||||
case('temperature')
|
||||
prm%outputID = [prm%outputID, temperature_ID]
|
||||
end select
|
||||
enddo
|
||||
prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||
|
||||
NofMyHomog=count(material_homogenizationAt==h)
|
||||
thermalState(h)%sizeState = 0
|
||||
|
@ -78,7 +63,6 @@ subroutine thermal_conduction_init
|
|||
allocate(thermalState(h)%subState0(0,NofMyHomog))
|
||||
allocate(thermalState(h)%state (0,NofMyHomog))
|
||||
|
||||
nullify(thermalMapping(h)%p)
|
||||
thermalMapping(h)%p => material_homogenizationMemberAt
|
||||
deallocate(temperature (h)%p)
|
||||
allocate (temperature (h)%p(NofMyHomog), source=thermal_initialT(h))
|
||||
|
@ -259,14 +243,13 @@ 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%outputID)
|
||||
select case(prm%outputID(o))
|
||||
|
||||
case (temperature_ID)
|
||||
outputsLoop: do o = 1,size(prm%output)
|
||||
select case(trim(prm%output(o)))
|
||||
case('temperature') ! ToDo: should be 'T'
|
||||
call results_writeDataset(group,temperature(homog)%p,'T',&
|
||||
'temperature','K')
|
||||
end select
|
||||
|
|
Loading…
Reference in New Issue