simplifying
no extral handling for homogeneous temperature (the memory that was saved was consumed by the extra mapping)
This commit is contained in:
parent
d7f035235c
commit
f8756ad95a
|
@ -182,7 +182,7 @@ subroutine CPFEM_general(mode, ffn, ffn1, temperature_inp, dt, elFE, ip, cauchyS
|
||||||
|
|
||||||
chosenThermal1: select case (thermal_type(material_homogenizationAt(elCP)))
|
chosenThermal1: select case (thermal_type(material_homogenizationAt(elCP)))
|
||||||
case (THERMAL_conduction_ID) chosenThermal1
|
case (THERMAL_conduction_ID) chosenThermal1
|
||||||
temperature(material_homogenizationAt(elCP))%p(thermalMapping(material_homogenizationAt(elCP))%p(ip,elCP)) = &
|
temperature(material_homogenizationAt(elCP))%p(material_homogenizationMemberAt(ip,elCP)) = &
|
||||||
temperature_inp
|
temperature_inp
|
||||||
end select chosenThermal1
|
end select chosenThermal1
|
||||||
homogenization_F0(1:3,1:3,ip,elCP) = ffn
|
homogenization_F0(1:3,1:3,ip,elCP) = ffn
|
||||||
|
|
|
@ -19,25 +19,21 @@ module constitutive
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
|
||||||
integer(kind(ELASTICITY_undefined_ID)), dimension(:), allocatable :: & !ToDo: old intel compiler complains about protected
|
integer(kind(PLASTICITY_undefined_ID)), dimension(:), allocatable :: &
|
||||||
phase_elasticity !< elasticity of each phase
|
|
||||||
|
|
||||||
integer(kind(PLASTICITY_undefined_ID)), dimension(:), allocatable :: & !ToDo: old intel compiler complains about protected
|
|
||||||
phase_plasticity !< plasticity of each phase
|
phase_plasticity !< plasticity of each phase
|
||||||
|
|
||||||
integer(kind(SOURCE_undefined_ID)), dimension(:,:), allocatable :: & ! ToDo: old intel compiler complains about protected
|
integer(kind(SOURCE_undefined_ID)), dimension(:,:), allocatable :: &
|
||||||
phase_source, & !< active sources mechanisms of each phase
|
phase_source, & !< active sources mechanisms of each phase
|
||||||
phase_kinematics, & !< active kinematic mechanisms of each phase
|
phase_kinematics !< active kinematic mechanisms of each phase
|
||||||
phase_stiffnessDegradation !< active stiffness degradation mechanisms of each phase
|
|
||||||
|
|
||||||
integer, dimension(:), allocatable, public :: & ! ToDo: old intel compiler complains about protected
|
integer, dimension(:), allocatable, public :: & !< ToDo: should be protected (bug in Intel compiler)
|
||||||
phase_Nsources, & !< number of source mechanisms active in each phase
|
phase_Nsources, & !< number of source mechanisms active in each phase
|
||||||
phase_Nkinematics, & !< number of kinematic mechanisms active in each phase
|
phase_Nkinematics, & !< number of kinematic mechanisms active in each phase
|
||||||
phase_NstiffnessDegradations, & !< number of stiffness degradation mechanisms active in each phase
|
phase_NstiffnessDegradations, & !< number of stiffness degradation mechanisms active in each phase
|
||||||
phase_plasticityInstance, & !< instance of particular plasticity of each phase
|
phase_plasticityInstance, & !< instance of particular plasticity of each phase
|
||||||
phase_elasticityInstance !< instance of particular elasticity of each phase
|
phase_elasticityInstance !< instance of particular elasticity of each phase
|
||||||
|
|
||||||
logical, dimension(:), allocatable, public :: & ! ToDo: old intel compiler complains about protected
|
logical, dimension(:), allocatable, public :: & ! ToDo: should be protected (bug in Intel Compiler)
|
||||||
phase_localPlasticity !< flags phases with local constitutive law
|
phase_localPlasticity !< flags phases with local constitutive law
|
||||||
|
|
||||||
type(tPlasticState), allocatable, dimension(:), public :: &
|
type(tPlasticState), allocatable, dimension(:), public :: &
|
||||||
|
@ -634,10 +630,10 @@ pure function constitutive_initialFi(ipc, ip, el)
|
||||||
KinematicsLoop: do k = 1, phase_Nkinematics(phase) !< Warning: small initial strain assumption
|
KinematicsLoop: do k = 1, phase_Nkinematics(phase) !< Warning: small initial strain assumption
|
||||||
kinematicsType: select case (phase_kinematics(k,phase))
|
kinematicsType: select case (phase_kinematics(k,phase))
|
||||||
case (KINEMATICS_thermal_expansion_ID) kinematicsType
|
case (KINEMATICS_thermal_expansion_ID) kinematicsType
|
||||||
homog = material_homogenizationAt(el)
|
homog = material_homogenizationAt(el)
|
||||||
offset = thermalMapping(homog)%p(ip,el)
|
offset = material_homogenizationMemberAt(ip,el)
|
||||||
constitutive_initialFi = &
|
constitutive_initialFi = constitutive_initialFi &
|
||||||
constitutive_initialFi + kinematics_thermal_expansion_initialStrain(homog,phase,offset)
|
+ kinematics_thermal_expansion_initialStrain(homog,phase,offset)
|
||||||
end select kinematicsType
|
end select kinematicsType
|
||||||
enddo KinematicsLoop
|
enddo KinematicsLoop
|
||||||
|
|
||||||
|
@ -674,7 +670,7 @@ function constitutive_collectDotState(S, FArray, Fi, FpArray, subdt, ipc, ip, el
|
||||||
logical :: broken
|
logical :: broken
|
||||||
|
|
||||||
ho = material_homogenizationAt(el)
|
ho = material_homogenizationAt(el)
|
||||||
tme = thermalMapping(ho)%p(ip,el)
|
tme = material_homogenizationMemberAt(ip,el)
|
||||||
instance = phase_plasticityInstance(phase)
|
instance = phase_plasticityInstance(phase)
|
||||||
|
|
||||||
Mp = matmul(matmul(transpose(Fi),Fi),S)
|
Mp = matmul(matmul(transpose(Fi),Fi),S)
|
||||||
|
|
|
@ -3,6 +3,12 @@
|
||||||
!----------------------------------------------------------------------------------------------------
|
!----------------------------------------------------------------------------------------------------
|
||||||
submodule(constitutive) constitutive_mech
|
submodule(constitutive) constitutive_mech
|
||||||
|
|
||||||
|
integer(kind(ELASTICITY_undefined_ID)), dimension(:), allocatable :: &
|
||||||
|
phase_elasticity !< elasticity of each phase
|
||||||
|
integer(kind(SOURCE_undefined_ID)), dimension(:,:), allocatable :: &
|
||||||
|
phase_stiffnessDegradation !< active stiffness degradation mechanisms of each phase
|
||||||
|
|
||||||
|
|
||||||
interface
|
interface
|
||||||
|
|
||||||
module function plastic_none_init() result(myPlasticity)
|
module function plastic_none_init() result(myPlasticity)
|
||||||
|
@ -360,7 +366,7 @@ module subroutine constitutive_plastic_dependentState(F, Fp, ipc, ip, el)
|
||||||
instance, of
|
instance, of
|
||||||
|
|
||||||
ho = material_homogenizationAt(el)
|
ho = material_homogenizationAt(el)
|
||||||
tme = thermalMapping(ho)%p(ip,el)
|
tme = material_homogenizationMemberAt(ip,el)
|
||||||
of = material_phasememberAt(ipc,ip,el)
|
of = material_phasememberAt(ipc,ip,el)
|
||||||
instance = phase_plasticityInstance(material_phaseAt(ipc,el))
|
instance = phase_plasticityInstance(material_phaseAt(ipc,el))
|
||||||
|
|
||||||
|
@ -407,7 +413,7 @@ module subroutine constitutive_plastic_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, &
|
||||||
i, j, instance, of
|
i, j, instance, of
|
||||||
|
|
||||||
ho = material_homogenizationAt(el)
|
ho = material_homogenizationAt(el)
|
||||||
tme = thermalMapping(ho)%p(ip,el)
|
tme = material_homogenizationMemberAt(ip,el)
|
||||||
|
|
||||||
Mp = matmul(matmul(transpose(Fi),Fi),S)
|
Mp = matmul(matmul(transpose(Fi),Fi),S)
|
||||||
of = material_phasememberAt(ipc,ip,el)
|
of = material_phasememberAt(ipc,ip,el)
|
||||||
|
|
|
@ -75,13 +75,11 @@ subroutine damage_local_init
|
||||||
|
|
||||||
Nmaterialpoints = count(material_homogenizationAt == h)
|
Nmaterialpoints = count(material_homogenizationAt == h)
|
||||||
damageState(h)%sizeState = 1
|
damageState(h)%sizeState = 1
|
||||||
allocate(damageState(h)%state0 (1,Nmaterialpoints), source=damage_initialPhi(h))
|
allocate(damageState(h)%state0 (1,Nmaterialpoints), source=1.0_pReal)
|
||||||
allocate(damageState(h)%subState0(1,Nmaterialpoints), source=damage_initialPhi(h))
|
allocate(damageState(h)%subState0(1,Nmaterialpoints), source=1.0_pReal)
|
||||||
allocate(damageState(h)%state (1,Nmaterialpoints), source=damage_initialPhi(h))
|
allocate(damageState(h)%state (1,Nmaterialpoints), source=1.0_pReal)
|
||||||
|
|
||||||
nullify(damageMapping(h)%p)
|
|
||||||
damageMapping(h)%p => material_homogenizationMemberAt
|
damageMapping(h)%p => material_homogenizationMemberAt
|
||||||
deallocate(damage(h)%p)
|
|
||||||
damage(h)%p => damageState(h)%state(1,:)
|
damage(h)%p => damageState(h)%state(1,:)
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
|
@ -3,6 +3,7 @@
|
||||||
!> @brief material subroutine for constant damage field
|
!> @brief material subroutine for constant damage field
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module damage_none
|
module damage_none
|
||||||
|
use prec
|
||||||
use config
|
use config
|
||||||
use material
|
use material
|
||||||
|
|
||||||
|
@ -29,8 +30,8 @@ subroutine damage_none_init
|
||||||
allocate(damageState(h)%subState0(0,Nmaterialpoints))
|
allocate(damageState(h)%subState0(0,Nmaterialpoints))
|
||||||
allocate(damageState(h)%state (0,Nmaterialpoints))
|
allocate(damageState(h)%state (0,Nmaterialpoints))
|
||||||
|
|
||||||
deallocate(damage(h)%p)
|
damageMapping(h)%p => material_homogenizationMemberAt
|
||||||
allocate (damage(h)%p(1), source=damage_initialPhi(h))
|
allocate (damage(h)%p(Nmaterialpoints), source=1.0_pReal)
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
|
|
@ -78,13 +78,11 @@ subroutine damage_nonlocal_init
|
||||||
|
|
||||||
Nmaterialpoints = count(material_homogenizationAt == h)
|
Nmaterialpoints = count(material_homogenizationAt == h)
|
||||||
damageState(h)%sizeState = 1
|
damageState(h)%sizeState = 1
|
||||||
allocate(damageState(h)%state0 (1,Nmaterialpoints), source=damage_initialPhi(h))
|
allocate(damageState(h)%state0 (1,Nmaterialpoints), source=1.0_pReal)
|
||||||
allocate(damageState(h)%subState0(1,Nmaterialpoints), source=damage_initialPhi(h))
|
allocate(damageState(h)%subState0(1,Nmaterialpoints), source=1.0_pReal)
|
||||||
allocate(damageState(h)%state (1,Nmaterialpoints), source=damage_initialPhi(h))
|
allocate(damageState(h)%state (1,Nmaterialpoints), source=1.0_pReal)
|
||||||
|
|
||||||
nullify(damageMapping(h)%p)
|
|
||||||
damageMapping(h)%p => material_homogenizationMemberAt
|
damageMapping(h)%p => material_homogenizationMemberAt
|
||||||
deallocate(damage(h)%p)
|
|
||||||
damage(h)%p => damageState(h)%state(1,:)
|
damage(h)%p => damageState(h)%state(1,:)
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
|
@ -131,8 +131,7 @@ subroutine grid_thermal_spectral_init
|
||||||
cell = 0
|
cell = 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)
|
||||||
cell = cell + 1
|
cell = cell + 1
|
||||||
T_current(i,j,k) = temperature(material_homogenizationAt(cell))% &
|
T_current(i,j,k) = temperature(material_homogenizationAt(cell))%p(material_homogenizationMemberAt(1,cell))
|
||||||
p(thermalMapping(material_homogenizationAt(cell))%p(1,cell))
|
|
||||||
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
|
||||||
|
|
|
@ -126,8 +126,8 @@ module subroutine kinematics_thermal_expansion_LiAndItsTangent(Li, dLi_dTstar, i
|
||||||
|
|
||||||
phase = material_phaseAt(ipc,el)
|
phase = material_phaseAt(ipc,el)
|
||||||
homog = material_homogenizationAt(el)
|
homog = material_homogenizationAt(el)
|
||||||
T = temperature(homog)%p(thermalMapping(homog)%p(ip,el))
|
T = temperature(homog)%p(material_homogenizationMemberAt(ip,el))
|
||||||
TDot = temperatureRate(homog)%p(thermalMapping(homog)%p(ip,el))
|
TDot = temperatureRate(homog)%p(material_homogenizationMemberAt(ip,el))
|
||||||
|
|
||||||
associate(prm => param(kinematics_thermal_expansion_instance(phase)))
|
associate(prm => param(kinematics_thermal_expansion_instance(phase)))
|
||||||
Li = TDot * ( &
|
Li = TDot * ( &
|
||||||
|
|
|
@ -64,17 +64,16 @@ module material
|
||||||
homogenization_type !< type of each homogenization
|
homogenization_type !< type of each homogenization
|
||||||
|
|
||||||
integer, public, protected :: &
|
integer, public, protected :: &
|
||||||
homogenization_maxNconstituents !< max number of grains in any USED homogenization
|
homogenization_maxNconstituents !< max number of grains in any USED homogenization
|
||||||
|
|
||||||
integer, dimension(:), allocatable, public, protected :: &
|
integer, dimension(:), allocatable, public, protected :: &
|
||||||
homogenization_Nconstituents, & !< number of grains in each homogenization
|
homogenization_Nconstituents, & !< number of grains in each homogenization
|
||||||
homogenization_typeInstance, & !< instance of particular type of each homogenization
|
homogenization_typeInstance, & !< instance of particular type of each homogenization
|
||||||
thermal_typeInstance, & !< instance of particular type of each thermal transport
|
thermal_typeInstance, & !< instance of particular type of each thermal transport
|
||||||
damage_typeInstance !< instance of particular type of each nonlocal damage
|
damage_typeInstance !< instance of particular type of each nonlocal damage
|
||||||
|
|
||||||
real(pReal), dimension(:), allocatable, public, protected :: &
|
real(pReal), dimension(:), allocatable, public, protected :: &
|
||||||
thermal_initialT, & !< initial temperature per each homogenization
|
thermal_initialT !< initial temperature per each homogenization
|
||||||
damage_initialPhi !< initial damage per each homogenization
|
|
||||||
|
|
||||||
integer, dimension(:), allocatable, public, protected :: & ! (elem)
|
integer, dimension(:), allocatable, public, protected :: & ! (elem)
|
||||||
material_homogenizationAt !< homogenization ID of each element
|
material_homogenizationAt !< homogenization ID of each element
|
||||||
|
@ -93,12 +92,7 @@ module material
|
||||||
type(Rotation), dimension(:,:,:), allocatable, public, protected :: &
|
type(Rotation), dimension(:,:,:), allocatable, public, protected :: &
|
||||||
material_orientation0 !< initial orientation of each grain,IP,element
|
material_orientation0 !< initial orientation of each grain,IP,element
|
||||||
|
|
||||||
! BEGIN DEPRECATED
|
|
||||||
integer, dimension(:,:), allocatable, private, target :: mappingHomogenizationConst !< mapping from material points to offset in constant state/field
|
|
||||||
! END DEPRECATED
|
|
||||||
|
|
||||||
type(tHomogMapping), allocatable, dimension(:), public :: &
|
type(tHomogMapping), allocatable, dimension(:), public :: &
|
||||||
thermalMapping, & !< mapping for thermal state/fields
|
|
||||||
damageMapping !< mapping for damage state/fields
|
damageMapping !< mapping for damage state/fields
|
||||||
|
|
||||||
type(group_float), allocatable, dimension(:), public :: &
|
type(group_float), allocatable, dimension(:), public :: &
|
||||||
|
@ -165,7 +159,6 @@ subroutine material_init(restart)
|
||||||
allocate(thermalState (size(material_name_homogenization)))
|
allocate(thermalState (size(material_name_homogenization)))
|
||||||
allocate(damageState (size(material_name_homogenization)))
|
allocate(damageState (size(material_name_homogenization)))
|
||||||
|
|
||||||
allocate(thermalMapping (size(material_name_homogenization)))
|
|
||||||
allocate(damageMapping (size(material_name_homogenization)))
|
allocate(damageMapping (size(material_name_homogenization)))
|
||||||
|
|
||||||
allocate(temperature (size(material_name_homogenization)))
|
allocate(temperature (size(material_name_homogenization)))
|
||||||
|
@ -181,20 +174,6 @@ subroutine material_init(restart)
|
||||||
call results_closeJobFile
|
call results_closeJobFile
|
||||||
endif
|
endif
|
||||||
|
|
||||||
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
|
||||||
! BEGIN DEPRECATED
|
|
||||||
allocate(mappingHomogenizationConst( discretization_nIPs,discretization_Nelems),source=1)
|
|
||||||
|
|
||||||
! hack needed to initialize field values used during constitutive initialization
|
|
||||||
do myHomog = 1, size(material_name_homogenization)
|
|
||||||
thermalMapping (myHomog)%p => mappingHomogenizationConst
|
|
||||||
damageMapping (myHomog)%p => mappingHomogenizationConst
|
|
||||||
allocate(temperature (myHomog)%p(1), source=thermal_initialT(myHomog))
|
|
||||||
allocate(damage (myHomog)%p(1), source=damage_initialPhi(myHomog))
|
|
||||||
allocate(temperatureRate (myHomog)%p(1), source=0.0_pReal)
|
|
||||||
enddo
|
|
||||||
! END DEPRECATED
|
|
||||||
|
|
||||||
end subroutine material_init
|
end subroutine material_init
|
||||||
|
|
||||||
|
|
||||||
|
@ -222,7 +201,6 @@ subroutine material_parseHomogenization
|
||||||
allocate(thermal_typeInstance(size(material_name_homogenization)), source=0)
|
allocate(thermal_typeInstance(size(material_name_homogenization)), source=0)
|
||||||
allocate(damage_typeInstance(size(material_name_homogenization)), source=0)
|
allocate(damage_typeInstance(size(material_name_homogenization)), source=0)
|
||||||
allocate(thermal_initialT(size(material_name_homogenization)), source=300.0_pReal)
|
allocate(thermal_initialT(size(material_name_homogenization)), source=300.0_pReal)
|
||||||
allocate(damage_initialPhi(size(material_name_homogenization)), source=1.0_pReal)
|
|
||||||
|
|
||||||
do h=1, size(material_name_homogenization)
|
do h=1, size(material_name_homogenization)
|
||||||
homog => material_homogenization%get(h)
|
homog => material_homogenization%get(h)
|
||||||
|
@ -258,7 +236,6 @@ subroutine material_parseHomogenization
|
||||||
|
|
||||||
if(homog%contains('damage')) then
|
if(homog%contains('damage')) then
|
||||||
homogDamage => homog%get('damage')
|
homogDamage => homog%get('damage')
|
||||||
damage_initialPhi(h) = homogDamage%get_asFloat('phi_0',defaultVal=1.0_pReal)
|
|
||||||
select case (homogDamage%get_asString('type'))
|
select case (homogDamage%get_asString('type'))
|
||||||
case('none')
|
case('none')
|
||||||
damage_type(h) = DAMAGE_none_ID
|
damage_type(h) = DAMAGE_none_ID
|
||||||
|
|
|
@ -72,12 +72,9 @@ subroutine thermal_adiabatic_init
|
||||||
allocate(thermalState(h)%state0 (1,Nmaterialpoints), source=thermal_initialT(h))
|
allocate(thermalState(h)%state0 (1,Nmaterialpoints), source=thermal_initialT(h))
|
||||||
allocate(thermalState(h)%subState0(1,Nmaterialpoints), source=thermal_initialT(h))
|
allocate(thermalState(h)%subState0(1,Nmaterialpoints), source=thermal_initialT(h))
|
||||||
allocate(thermalState(h)%state (1,Nmaterialpoints), source=thermal_initialT(h))
|
allocate(thermalState(h)%state (1,Nmaterialpoints), source=thermal_initialT(h))
|
||||||
|
|
||||||
thermalMapping(h)%p => material_homogenizationMemberAt
|
|
||||||
deallocate(temperature(h)%p)
|
|
||||||
temperature(h)%p => thermalState(h)%state(1,:)
|
temperature(h)%p => thermalState(h)%state(1,:)
|
||||||
deallocate(temperatureRate(h)%p)
|
allocate(temperatureRate(h)%p(Nmaterialpoints),source = 0.0_pReal)
|
||||||
allocate (temperatureRate(h)%p(Nmaterialpoints), source=0.0_pReal)
|
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
enddo
|
enddo
|
||||||
|
@ -117,8 +114,8 @@ function thermal_adiabatic_updateState(subdt, ip, el)
|
||||||
<= 1.0e-6_pReal*abs(thermalState(homog)%state(1,offset)), &
|
<= 1.0e-6_pReal*abs(thermalState(homog)%state(1,offset)), &
|
||||||
.true.]
|
.true.]
|
||||||
|
|
||||||
temperature (homog)%p(thermalMapping(homog)%p(ip,el)) = T
|
temperature (homog)%p(material_homogenizationMemberAt(ip,el)) = T
|
||||||
temperatureRate(homog)%p(thermalMapping(homog)%p(ip,el)) = &
|
temperatureRate(homog)%p(material_homogenizationMemberAt(ip,el)) = &
|
||||||
(thermalState(homog)%state(1,offset) - thermalState(homog)%subState0(1,offset))/(subdt+tiny(0.0_pReal))
|
(thermalState(homog)%state(1,offset) - thermalState(homog)%subState0(1,offset))/(subdt+tiny(0.0_pReal))
|
||||||
|
|
||||||
end function thermal_adiabatic_updateState
|
end function thermal_adiabatic_updateState
|
||||||
|
|
|
@ -71,10 +71,7 @@ subroutine thermal_conduction_init
|
||||||
allocate(thermalState(h)%subState0(0,Nmaterialpoints))
|
allocate(thermalState(h)%subState0(0,Nmaterialpoints))
|
||||||
allocate(thermalState(h)%state (0,Nmaterialpoints))
|
allocate(thermalState(h)%state (0,Nmaterialpoints))
|
||||||
|
|
||||||
thermalMapping(h)%p => material_homogenizationMemberAt
|
|
||||||
deallocate(temperature (h)%p)
|
|
||||||
allocate (temperature (h)%p(Nmaterialpoints), source=thermal_initialT(h))
|
allocate (temperature (h)%p(Nmaterialpoints), source=thermal_initialT(h))
|
||||||
deallocate(temperatureRate(h)%p)
|
|
||||||
allocate (temperatureRate(h)%p(Nmaterialpoints), source=0.0_pReal)
|
allocate (temperatureRate(h)%p(Nmaterialpoints), source=0.0_pReal)
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
@ -205,7 +202,7 @@ subroutine thermal_conduction_putTemperatureAndItsRate(T,Tdot,ip,el)
|
||||||
offset
|
offset
|
||||||
|
|
||||||
homog = material_homogenizationAt(el)
|
homog = material_homogenizationAt(el)
|
||||||
offset = thermalMapping(homog)%p(ip,el)
|
offset = material_homogenizationMemberAt(ip,el)
|
||||||
temperature (homog)%p(offset) = T
|
temperature (homog)%p(offset) = T
|
||||||
temperatureRate(homog)%p(offset) = Tdot
|
temperatureRate(homog)%p(offset) = Tdot
|
||||||
|
|
||||||
|
|
|
@ -3,6 +3,7 @@
|
||||||
!> @brief material subroutine for isothermal temperature field
|
!> @brief material subroutine for isothermal temperature field
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module thermal_isothermal
|
module thermal_isothermal
|
||||||
|
use prec
|
||||||
use config
|
use config
|
||||||
use material
|
use material
|
||||||
|
|
||||||
|
@ -29,10 +30,8 @@ subroutine thermal_isothermal_init
|
||||||
allocate(thermalState(h)%subState0(0,Nmaterialpoints))
|
allocate(thermalState(h)%subState0(0,Nmaterialpoints))
|
||||||
allocate(thermalState(h)%state (0,Nmaterialpoints))
|
allocate(thermalState(h)%state (0,Nmaterialpoints))
|
||||||
|
|
||||||
deallocate(temperature (h)%p)
|
allocate(temperature (h)%p(Nmaterialpoints),source=thermal_initialT(h))
|
||||||
allocate (temperature (h)%p(1), source=thermal_initialT(h))
|
allocate(temperatureRate(h)%p(Nmaterialpoints),source = 0.0_pReal)
|
||||||
deallocate(temperatureRate(h)%p)
|
|
||||||
allocate (temperatureRate(h)%p(1))
|
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue