changed thermal heatGen to thermal adiabatic

This commit is contained in:
Luv Sharma 2014-10-09 14:08:32 +00:00
parent fc57c6e572
commit 2eadb0a178
8 changed files with 124 additions and 124 deletions

View File

@ -86,7 +86,7 @@ end module DAMASK_interface
#include "damage_brittle.f90"
#include "damage_ductile.f90"
#include "thermal_isothermal.f90"
#include "thermal_heatGen.f90"
#include "thermal_adiabatic.f90"
#include "constitutive_none.f90"
#include "constitutive_j2.f90"
#include "constitutive_phenopowerlaw.f90"

View File

@ -86,7 +86,7 @@ end module DAMASK_interface
#include "damage_brittle.f90"
#include "damage_ductile.f90"
#include "thermal_isothermal.f90"
#include "thermal_heatGen.f90"
#include "thermal_adiabatic.f90"
#include "constitutive_none.f90"
#include "constitutive_j2.f90"
#include "constitutive_phenopowerlaw.f90"

View File

@ -115,7 +115,7 @@ end module DAMASK_interface
#include "damage_brittle.f90"
#include "damage_ductile.f90"
#include "thermal_isothermal.f90"
#include "thermal_heatGen.f90"
#include "thermal_adiabatic.f90"
#include "constitutive_none.f90"
#include "constitutive_j2.f90"
#include "constitutive_phenopowerlaw.f90"

View File

@ -329,7 +329,7 @@ DAMAGE_FILES = \
damage_none.o damage_brittle.o damage_ductile.o
THERMAL_FILES = \
thermal_isothermal.o thermal_heatGen.o
thermal_isothermal.o thermal_adiabatic.o
CONSTITUTIVE_FILES = \
constitutive_dislotwin.o constitutive_dislokmc.o constitutive_j2.o constitutive_phenopowerlaw.o \
@ -486,7 +486,7 @@ damage_ductile.o: damage_ductile.f90 \
thermal_isothermal.o: thermal_isothermal.f90 \
lattice.o
thermal_heatGen.o: thermal_heatGen.f90 \
thermal_adiabatic.o: thermal_adiabatic.f90 \
lattice.o
lattice.o: lattice.f90 \

View File

@ -90,14 +90,14 @@ subroutine constitutive_init
phase_Noutput, &
homogenization_Ngrains, &
homogenization_maxNgrains, &
ELASTICITY_HOOKE_ID, &
PLASTICITY_NONE_ID, &
PLASTICITY_J2_ID, &
PLASTICITY_PHENOPOWERLAW_ID, &
PLASTICITY_DISLOTWIN_ID, &
PLASTICITY_DISLOKMC_ID, &
PLASTICITY_TITANMOD_ID, &
PLASTICITY_NONLOCAL_ID ,&
ELASTICITY_hooke_ID, &
PLASTICITY_none_ID, &
PLASTICITY_j2_ID, &
PLASTICITY_phenopowerlaw_ID, &
PLASTICITY_dislotwin_ID, &
PLASTICITY_dislokmc_ID, &
PLASTICITY_titanmod_ID, &
PLASTICITY_nonlocal_ID ,&
ELASTICITY_HOOKE_label, &
PLASTICITY_NONE_label, &
PLASTICITY_J2_label, &
@ -106,16 +106,16 @@ subroutine constitutive_init
PLASTICITY_DISLOKMC_label, &
PLASTICITY_TITANMOD_label, &
PLASTICITY_NONLOCAL_label, &
LOCAL_DAMAGE_NONE_ID, &
LOCAL_DAMAGE_BRITTLE_ID, &
LOCAL_DAMAGE_DUCTILE_ID, &
LOCAL_THERMAL_ISOTHERMAL_ID, &
LOCAL_THERMAL_HEATGEN_ID, &
LOCAL_DAMAGE_none_ID, &
LOCAL_DAMAGE_brittle_ID, &
LOCAL_DAMAGE_ductile_ID, &
LOCAL_THERMAL_isothermal_ID, &
LOCAL_THERMAL_adiabatic_ID, &
LOCAL_DAMAGE_NONE_label, &
LOCAL_DAMAGE_BRITTLE_label, &
LOCAL_DAMAGE_DUCTILE_label, &
LOCAL_THERMAL_ISOTHERMAL_label, &
LOCAL_THERMAL_HEATGEN_label, &
LOCAL_THERMAL_ADIABATIC_label, &
plasticState, &
damageState, &
thermalState, &
@ -133,7 +133,7 @@ subroutine constitutive_init
use damage_brittle
use damage_ductile
use thermal_isothermal
use thermal_heatGen
use thermal_adiabatic
implicit none
integer(pInt), parameter :: FILEUNIT = 200_pInt
integer(pInt) :: &
@ -178,7 +178,7 @@ subroutine constitutive_init
if (.not. IO_open_jobFile_stat(FILEUNIT,material_localFileExt)) & ! no local material configuration present...
call IO_open_file(FILEUNIT,material_configFile) ! ... open material.config file
if (any(phase_thermal == LOCAL_THERMAL_ISOTHERMAL_ID)) call thermal_isothermal_init(FILEUNIT)
if (any(phase_thermal == LOCAL_THERMAL_HEATGEN_ID)) call thermal_heatGen_init(FILEUNIT)
if (any(phase_thermal == LOCAL_THERMAL_adiabatic_ID)) call thermal_adiabatic_init(FILEUNIT)
close(FILEUNIT)
write(6,'(/,a)') ' <<<+- constitutive init -+>>>'
@ -278,17 +278,17 @@ subroutine constitutive_init
thisNoutput => null()
thisOutput => null()
thisSize => null()
case (LOCAL_THERMAL_heatgen_ID)
outputName = LOCAL_THERMAL_HEATGEN_label
thisNoutput => thermal_heatGen_Noutput
thisOutput => thermal_heatGen_output
thisSize => thermal_heatGen_sizePostResult
case (LOCAL_THERMAL_adiabatic_ID)
outputName = LOCAL_THERMAL_ADIABATIC_label
thisNoutput => thermal_adiabatic_Noutput
thisOutput => thermal_adiabatic_output
thisSize => thermal_adiabatic_sizePostResult
case default
knownThermal = .false.
end select
if (knownThermal) then
write(FILEUNIT,'(a)') '(thermal)'//char(9)//trim(outputName)
if (phase_thermal(phase) /= LOCAL_THERMAL_ISOTHERMAL_ID) then
if (phase_thermal(phase) /= LOCAL_THERMAL_isothermal_ID) then
do e = 1_pInt,thisNoutput(instance)
write(FILEUNIT,'(a,i4)') trim(thisOutput(e,instance))//char(9),thisSize(e,instance)
enddo
@ -652,16 +652,16 @@ subroutine constitutive_collectDotState(Tstar_v, Lp, FeArray, FpArray, Temperatu
phase_thermal, &
material_phase, &
homogenization_maxNgrains, &
PLASTICITY_NONE_ID, &
PLASTICITY_J2_ID, &
PLASTICITY_PHENOPOWERLAW_ID, &
PLASTICITY_DISLOTWIN_ID, &
PLASTICITY_DISLOKMC_ID, &
PLASTICITY_TITANMOD_ID, &
PLASTICITY_NONLOCAL_ID, &
LOCAL_DAMAGE_BRITTLE_ID, &
LOCAL_DAMAGE_DUCTILE_ID, &
LOCAL_THERMAL_HEATGEN_ID
PLASTICITY_none_ID, &
PLASTICITY_j2_ID, &
PLASTICITY_phenopowerlaw_ID, &
PLASTICITY_dislotwin_ID, &
PLASTICITY_dislokmc_ID, &
PLASTICITY_titanmod_ID, &
PLASTICITY_nonlocal_ID, &
LOCAL_DAMAGE_brittle_ID, &
LOCAL_DAMAGE_ductile_ID, &
LOCAL_THERMAL_adiabatic_ID
use constitutive_j2, only: &
constitutive_j2_dotState
use constitutive_phenopowerlaw, only: &
@ -678,8 +678,8 @@ subroutine constitutive_collectDotState(Tstar_v, Lp, FeArray, FpArray, Temperatu
damage_brittle_dotState
use damage_ductile, only: &
damage_ductile_dotState
use thermal_heatGen, only: &
thermal_heatGen_dotState
use thermal_adiabatic, only: &
thermal_adiabatic_dotState
implicit none
integer(pInt), intent(in) :: &
@ -731,8 +731,8 @@ subroutine constitutive_collectDotState(Tstar_v, Lp, FeArray, FpArray, Temperatu
end select
select case (phase_thermal(material_phase(ipc,ip,el)))
case (LOCAL_THERMAL_HEATGEN_ID)
call thermal_heatGen_dotState(Tstar_v, Lp, ipc, ip, el)
case (LOCAL_THERMAL_adiabatic_ID)
call thermal_adiabatic_dotState(Tstar_v, Lp, ipc, ip, el)
end select
if (iand(debug_level(debug_constitutive), debug_levelBasic) /= 0_pInt) then
@ -920,11 +920,11 @@ function constitutive_getAdiabaticTemperature(ipc, ip, el)
pReal
use material, only: &
material_phase, &
LOCAL_THERMAL_ISOTHERMAL_ID, &
LOCAL_THERMAL_HEATGEN_ID, &
LOCAL_THERMAL_isothermal_ID, &
LOCAL_THERMAL_adiabatic_ID, &
phase_thermal
use thermal_heatGen, only: &
thermal_heatGen_getTemperature
use thermal_adiabatic, only: &
thermal_adiabatic_getTemperature
use lattice, only: &
lattice_referenceTemperature
@ -939,8 +939,8 @@ function constitutive_getAdiabaticTemperature(ipc, ip, el)
case (LOCAL_THERMAL_ISOTHERMAL_ID)
constitutive_getAdiabaticTemperature = lattice_referenceTemperature(material_phase(ipc,ip,el))
case (LOCAL_THERMAL_HEATGEN_ID)
constitutive_getAdiabaticTemperature = thermal_heatGen_getTemperature(ipc, ip, el)
case (LOCAL_THERMAL_adiabatic_ID)
constitutive_getAdiabaticTemperature = thermal_adiabatic_getTemperature(ipc, ip, el)
end select
end function constitutive_getAdiabaticTemperature
@ -953,10 +953,10 @@ subroutine constitutive_putAdiabaticTemperature(ipc, ip, el, localTemperature)
pReal
use material, only: &
material_phase, &
LOCAL_THERMAL_HEATGEN_ID, &
LOCAL_THERMAL_adiabatic_ID, &
phase_thermal
use thermal_heatGen, only: &
thermal_heatGen_putTemperature
use thermal_adiabatic, only: &
thermal_adiabatic_putTemperature
implicit none
integer(pInt), intent(in) :: &
@ -967,8 +967,8 @@ subroutine constitutive_putAdiabaticTemperature(ipc, ip, el, localTemperature)
localTemperature
select case (phase_thermal(material_phase(ipc,ip,el)))
case (LOCAL_THERMAL_HEATGEN_ID)
call thermal_heatGen_putTemperature(ipc, ip, el, localTemperature)
case (LOCAL_THERMAL_adiabatic_ID)
call thermal_adiabatic_putTemperature(ipc, ip, el, localTemperature)
end select
@ -985,8 +985,8 @@ function constitutive_getTemperature(ipc, ip, el)
material_phase, &
fieldThermal, &
field_thermal_type, &
FIELD_THERMAL_ADIABATIC_ID, &
FIELD_THERMAL_CONDUCTION_ID, &
FIELD_THERMAL_local_ID, &
FIELD_THERMAL_nonlocal_ID, &
material_homog
use lattice, only: &
lattice_referenceTemperature
@ -999,10 +999,10 @@ function constitutive_getTemperature(ipc, ip, el)
select case(field_thermal_type(material_homog(ip,el)))
case (FIELD_THERMAL_ADIABATIC_ID)
case (FIELD_THERMAL_local_ID)
constitutive_getTemperature = constitutive_getAdiabaticTemperature(ipc, ip, el)
case (FIELD_THERMAL_CONDUCTION_ID)
case (FIELD_THERMAL_nonlocal_ID)
constitutive_getTemperature = fieldThermal(material_homog(ip,el))% &
field(1,mappingHomogenization(1,ip,el)) ! Taylor type
@ -1036,7 +1036,7 @@ function constitutive_postResults(Tstar_v, FeArray, temperature, ipc, ip, el)
PLASTICITY_NONLOCAL_ID, &
LOCAL_DAMAGE_BRITTLE_ID, &
LOCAL_DAMAGE_DUCTILE_ID, &
LOCAL_THERMAL_HEATGEN_ID
LOCAL_THERMAL_ADIABATIC_ID
use constitutive_j2, only: &
#ifdef HDF
constitutive_j2_postResults2,&
@ -1057,8 +1057,8 @@ function constitutive_postResults(Tstar_v, FeArray, temperature, ipc, ip, el)
damage_brittle_postResults
use damage_ductile, only: &
damage_ductile_postResults
use thermal_heatGen, only: &
thermal_heatGen_postResults
use thermal_adiabatic, only: &
thermal_adiabatic_postResults
#endif
implicit none
@ -1123,8 +1123,8 @@ function constitutive_postResults(Tstar_v, FeArray, temperature, ipc, ip, el)
startPos = endPos + 1_pInt
endPos = endPos + thermalState(material_phase(ipc,ip,el))%sizePostResults
select case (phase_thermal(material_phase(ipc,ip,el)))
case (LOCAL_THERMAL_HEATGEN_ID)
constitutive_postResults(startPos:endPos) = thermal_heatGen_postResults(ipc, ip, el)
case (LOCAL_THERMAL_ADIABATIC_ID)
constitutive_postResults(startPos:endPos) = thermal_adiabatic_postResults(ipc, ip, el)
end select
#endif

View File

@ -314,7 +314,7 @@ subroutine damage_ductile_microstructure(ipc, ip, el)
constituent = mappingConstitutive(1,ipc,ip,el)
damageState(phase)%state(3,constituent) = min(damageState(phase)%state(3,constituent), &
damage_ductile_critpStrain(phase)/ &
damageState(phase)%state(2,constituent)) !< akin to damage surface
damageState(phase)%state(2,constituent)) !< akin to damage surface
end subroutine damage_ductile_microstructure

View File

@ -927,8 +927,8 @@ function field_getSpecificHeat(ip,el)
material_phase, &
material_homog, &
field_thermal_type, &
FIELD_THERMAL_ADIABATIC_ID, &
FIELD_THERMAL_CONDUCTION_ID, &
FIELD_THERMAL_local_ID, &
FIELD_THERMAL_nonlocal_ID, &
homogenization_Ngrains
implicit none
@ -943,10 +943,10 @@ function field_getSpecificHeat(ip,el)
select case(field_thermal_type(material_homog(ip,el)))
case (FIELD_THERMAL_ADIABATIC_ID)
case (FIELD_THERMAL_local_ID)
field_getSpecificHeat = 0.0_pReal
case (FIELD_THERMAL_CONDUCTION_ID)
case (FIELD_THERMAL_nonlocal_ID)
do ipc = 1, homogenization_Ngrains(mesh_element(3,el))
field_getSpecificHeat = field_getSpecificHeat + lattice_specificHeat(material_phase(ipc,ip,el))
enddo
@ -969,8 +969,8 @@ function field_getMassDensity(ip,el)
material_phase, &
material_homog, &
field_thermal_type, &
FIELD_THERMAL_ADIABATIC_ID, &
FIELD_THERMAL_CONDUCTION_ID, &
FIELD_THERMAL_local_ID, &
FIELD_THERMAL_nonlocal_ID, &
homogenization_Ngrains
@ -986,10 +986,10 @@ function field_getMassDensity(ip,el)
select case(field_thermal_type(material_homog(ip,el)))
case (FIELD_THERMAL_ADIABATIC_ID)
case (FIELD_THERMAL_local_ID)
field_getMassDensity = 0.0_pReal
case (FIELD_THERMAL_CONDUCTION_ID)
case (FIELD_THERMAL_nonlocal_ID)
do ipc = 1, homogenization_Ngrains(mesh_element(3,el))
field_getMassDensity = field_getMassDensity + lattice_massDensity(material_phase(ipc,ip,el))
enddo
@ -1011,8 +1011,8 @@ function field_getThermalConductivity33(ip,el)
material_phase, &
material_homog, &
field_thermal_type, &
FIELD_THERMAL_ADIABATIC_ID, &
FIELD_THERMAL_CONDUCTION_ID, &
FIELD_THERMAL_local_ID, &
FIELD_THERMAL_nonlocal_ID, &
homogenization_Ngrains
use crystallite, only: &
crystallite_push33ToRef
@ -1030,10 +1030,10 @@ function field_getThermalConductivity33(ip,el)
select case(field_thermal_type(material_homog(ip,el)))
case (FIELD_THERMAL_ADIABATIC_ID)
case (FIELD_THERMAL_local_ID)
field_getThermalConductivity33 = 0.0_pReal
case (FIELD_THERMAL_CONDUCTION_ID)
case (FIELD_THERMAL_nonlocal_ID)
do ipc = 1, homogenization_Ngrains(mesh_element(3,el))
field_getThermalConductivity33 = field_getThermalConductivity33 + &
crystallite_push33ToRef(ipc,ip,el,lattice_thermalConductivity33(:,:,material_phase(ipc,ip,el)))
@ -1220,7 +1220,7 @@ subroutine field_putFieldTemperature(ip,el,fieldThermalValue)
fieldThermal, &
mappingHomogenization, &
field_thermal_type, &
FIELD_THERMAL_CONDUCTION_ID
FIELD_THERMAL_nonlocal_ID
implicit none
integer(pInt), intent(in) :: &
@ -1230,7 +1230,7 @@ subroutine field_putFieldTemperature(ip,el,fieldThermalValue)
fieldThermalValue
select case(field_thermal_type(material_homog(ip,el)))
case (FIELD_THERMAL_CONDUCTION_ID)
case (FIELD_THERMAL_nonlocal_ID)
fieldThermal(material_homog(ip,el))% &
field(1,mappingHomogenization(1,ip,el)) = fieldThermalValue

View File

@ -19,26 +19,26 @@ module material
implicit none
private
character(len=*), parameter, public :: &
ELASTICITY_HOOKE_label = 'hooke', &
PLASTICITY_NONE_label = 'none', &
PLASTICITY_J2_label = 'j2', &
PLASTICITY_PHENOPOWERLAW_label = 'phenopowerlaw', &
PLASTICITY_DISLOTWIN_label = 'dislotwin', &
PLASTICITY_DISLOKMC_label = 'dislokmc', &
PLASTICITY_TITANMOD_label = 'titanmod', &
PLASTICITY_NONLOCAL_label = 'nonlocal', &
LOCAL_DAMAGE_NONE_label = 'none', &
LOCAL_DAMAGE_BRITTLE_label = 'brittle', &
LOCAL_DAMAGE_DUCTILE_label = 'ductile', &
LOCAL_THERMAL_ISOTHERMAL_label = 'isothermal', &
LOCAL_THERMAL_HEATGEN_label = 'heatgen', &
FIELD_DAMAGE_LOCAL_label = 'local', &
FIELD_DAMAGE_NONLOCAL_label = 'nonlocal', &
FIELD_THERMAL_ADIABATIC_label = 'adiabatic', &
FIELD_THERMAL_CONDUCTION_label = 'conduction', &
HOMOGENIZATION_NONE_label = 'none', &
HOMOGENIZATION_ISOSTRAIN_label = 'isostrain', &
HOMOGENIZATION_RGC_label = 'rgc'
ELASTICITY_hooke_label = 'hooke', &
PLASTICITY_none_label = 'none', &
PLASTICITY_j2_label = 'j2', &
PLASTICITY_phenopowerlaw_label = 'phenopowerlaw', &
PLASTICITY_dislotwin_label = 'dislotwin', &
PLASTICITY_dislokmc_label = 'dislokmc', &
PLASTICITY_titanmod_label = 'titanmod', &
PLASTICITY_nonlocal_label = 'nonlocal', &
LOCAL_DAMAGE_none_label = 'none', &
LOCAL_DAMAGE_brittle_label = 'brittle', &
LOCAL_DAMAGE_ductile_label = 'ductile', &
LOCAL_THERMAL_isothermal_label = 'isothermal', &
LOCAL_THERMAL_adiabatic_label = 'adiabatic', &
FIELD_DAMAGE_local_label = 'local', &
FIELD_DAMAGE_nonlocal_label = 'nonlocal', &
FIELD_THERMAL_local_label = 'local', &
FIELD_THERMAL_nonlocal_label = 'nonlocal', &
HOMOGENIZATION_none_label = 'none', &
HOMOGENIZATION_isostrain_label = 'isostrain', &
HOMOGENIZATION_rgc_label = 'rgc'
@ -49,7 +49,7 @@ module material
enum, bind(c)
enumerator :: PLASTICITY_undefined_ID, &
PLASTICITY_none_ID, &
PLASTICITY_J2_ID, &
PLASTICITY_j2_ID, &
PLASTICITY_phenopowerlaw_ID, &
PLASTICITY_dislotwin_ID, &
PLASTICITY_dislokmc_ID, &
@ -58,29 +58,29 @@ module material
end enum
enum, bind(c)
enumerator :: LOCAL_DAMAGE_NONE_ID, &
LOCAL_DAMAGE_BRITTLE_ID, &
LOCAL_DAMAGE_DUCTILE_ID
enumerator :: LOCAL_DAMAGE_none_ID, &
LOCAL_DAMAGE_brittle_ID, &
LOCAL_DAMAGE_ductile_ID
end enum
enum, bind(c)
enumerator :: LOCAL_THERMAL_ISOTHERMAL_ID, &
LOCAL_THERMAL_HEATGEN_ID
enumerator :: LOCAL_THERMAL_isothermal_ID, &
LOCAL_THERMAL_adiabatic_ID
end enum
enum, bind(c)
enumerator :: FIELD_DAMAGE_LOCAL_ID ,&
FIELD_DAMAGE_NONLOCAL_ID
enumerator :: FIELD_DAMAGE_local_ID ,&
FIELD_DAMAGE_nonlocal_ID
end enum
enum, bind(c)
enumerator :: FIELD_THERMAL_ADIABATIC_ID, &
FIELD_THERMAL_CONDUCTION_ID
enumerator :: FIELD_THERMAL_local_ID, &
FIELD_THERMAL_nonlocal_ID
end enum
enum, bind(c)
enumerator :: HOMOGENIZATION_undefined_ID, &
HOMOGENIZATION_none_ID, &
HOMOGENIZATION_isostrain_ID, &
HOMOGENIZATION_RGC_ID
HOMOGENIZATION_rgc_ID
end enum
character(len=*), parameter, public :: &
@ -100,9 +100,9 @@ module material
phase_damage !< local damage of each phase
integer(kind(LOCAL_THERMAL_isothermal_ID)), dimension(:), allocatable, public, protected :: &
phase_thermal !< local thermal of each phase
integer(kind(FIELD_DAMAGE_LOCAL_ID)), dimension(:), allocatable, public, protected :: &
integer(kind(FIELD_DAMAGE_local_ID)), dimension(:), allocatable, public, protected :: &
field_damage_type !< field damage of each phase
integer(kind(FIELD_THERMAL_ADIABATIC_ID)), dimension(:), allocatable, public, protected :: &
integer(kind(FIELD_THERMAL_local_ID)), dimension(:), allocatable, public, protected :: &
field_thermal_type !< field thermal of each phase
integer(kind(HOMOGENIZATION_undefined_ID)), dimension(:), allocatable, public, protected :: &
@ -217,11 +217,11 @@ module material
LOCAL_DAMAGE_brittle_ID, &
LOCAL_DAMAGE_ductile_ID, &
LOCAL_THERMAL_isothermal_ID, &
LOCAL_THERMAL_heatgen_ID, &
FIELD_DAMAGE_LOCAL_ID, &
FIELD_DAMAGE_NONLOCAL_ID, &
FIELD_THERMAL_ADIABATIC_ID, &
FIELD_THERMAL_CONDUCTION_ID, &
LOCAL_THERMAL_adiabatic_ID, &
FIELD_DAMAGE_local_ID, &
FIELD_DAMAGE_nonlocal_ID, &
FIELD_THERMAL_local_ID, &
FIELD_THERMAL_nonlocal_ID, &
HOMOGENIZATION_none_ID, &
HOMOGENIZATION_isostrain_ID, &
#ifdef HDF
@ -384,13 +384,13 @@ subroutine material_init
do homog = 1,material_Nhomogenization
NofMyField=count(material_homog==homog)
select case(field_thermal_type(homog))
case (FIELD_THERMAL_ADIABATIC_ID)
case (FIELD_THERMAL_local_ID)
fieldThermal(homog)%sizeField = 0_pInt
fieldThermal(homog)%sizePostResults = 0_pInt
allocate(fieldThermal(homog)%field(fieldThermal(homog)%sizeField,NofMyField), &
source = 300.0_pReal) ! ToDo: temporary fix for now
case (FIELD_THERMAL_CONDUCTION_ID)
case (FIELD_THERMAL_nonlocal_ID)
fieldThermal(homog)%sizeField = 1_pInt
fieldThermal(homog)%sizePostResults = 1_pInt
allocate(fieldThermal(homog)%field(fieldThermal(homog)%sizeField,NofMyField), &
@ -441,8 +441,8 @@ subroutine material_parseHomogenization(fileUnit,myPart)
allocate(homogenization_name(Nsections)); homogenization_name = ''
allocate(homogenization_type(Nsections), source=HOMOGENIZATION_undefined_ID)
allocate(FIELD_DAMAGE_type(Nsections), source=FIELD_DAMAGE_LOCAL_ID)
allocate(FIELD_THERMAL_type(Nsections), source=FIELD_THERMAL_ADIABATIC_ID)
allocate(FIELD_DAMAGE_type(Nsections), source=FIELD_DAMAGE_local_ID)
allocate(FIELD_THERMAL_type(Nsections), source=FIELD_THERMAL_local_ID)
allocate(homogenization_typeInstance(Nsections), source=0_pInt)
allocate(homogenization_Ngrains(Nsections), source=0_pInt)
allocate(homogenization_Noutput(Nsections), source=0_pInt)
@ -501,10 +501,10 @@ subroutine material_parseHomogenization(fileUnit,myPart)
case ('field_thermal')
select case (IO_lc(IO_stringValue(line,positions,2_pInt)))
case(FIELD_THERMAL_ADIABATIC_label)
FIELD_THERMAL_type(section) = FIELD_THERMAL_ADIABATIC_ID
case(FIELD_THERMAL_CONDUCTION_label)
FIELD_THERMAL_type(section) = FIELD_THERMAL_CONDUCTION_ID
case(FIELD_THERMAL_local_label)
FIELD_THERMAL_type(section) = FIELD_THERMAL_local_ID
case(FIELD_THERMAL_nonlocal_label)
FIELD_THERMAL_type(section) = FIELD_THERMAL_nonlocal_ID
case default
call IO_error(500_pInt,ext_msg=trim(IO_stringValue(line,positions,2_pInt)))
end select
@ -793,8 +793,8 @@ subroutine material_parsePhase(fileUnit,myPart)
select case (IO_lc(IO_stringValue(line,positions,2_pInt)))
case (LOCAL_THERMAL_ISOTHERMAL_label)
phase_thermal(section) = LOCAL_THERMAL_isothermal_ID
case (LOCAL_THERMAL_HEATGEN_label)
phase_thermal(section) = LOCAL_THERMAL_HEATGEN_ID
case (LOCAL_THERMAL_ADIABATIC_label)
phase_thermal(section) = LOCAL_THERMAL_adiabatic_ID
case default
call IO_error(200_pInt,ext_msg=trim(IO_stringValue(line,positions,2_pInt)))
end select