renamed get/put thermal to get/put temperature and thermal_none to thermal_isothermal
This commit is contained in:
parent
d4076e4db9
commit
dabfa6d2e6
|
@ -84,7 +84,7 @@ end module DAMASK_interface
|
||||||
#include "lattice.f90"
|
#include "lattice.f90"
|
||||||
#include "damage_none.f90"
|
#include "damage_none.f90"
|
||||||
#include "damage_brittle.f90"
|
#include "damage_brittle.f90"
|
||||||
#include "thermal_none.f90"
|
#include "thermal_isothermal.f90"
|
||||||
#include "thermal_adiabatic.f90"
|
#include "thermal_adiabatic.f90"
|
||||||
#include "constitutive_none.f90"
|
#include "constitutive_none.f90"
|
||||||
#include "constitutive_j2.f90"
|
#include "constitutive_j2.f90"
|
||||||
|
|
|
@ -84,7 +84,7 @@ end module DAMASK_interface
|
||||||
#include "lattice.f90"
|
#include "lattice.f90"
|
||||||
#include "damage_none.f90"
|
#include "damage_none.f90"
|
||||||
#include "damage_brittle.f90"
|
#include "damage_brittle.f90"
|
||||||
#include "thermal_none.f90"
|
#include "thermal_isothermal.f90"
|
||||||
#include "thermal_adiabatic.f90"
|
#include "thermal_adiabatic.f90"
|
||||||
#include "constitutive_none.f90"
|
#include "constitutive_none.f90"
|
||||||
#include "constitutive_j2.f90"
|
#include "constitutive_j2.f90"
|
||||||
|
|
|
@ -113,7 +113,7 @@ end module DAMASK_interface
|
||||||
#include "lattice.f90"
|
#include "lattice.f90"
|
||||||
#include "damage_none.f90"
|
#include "damage_none.f90"
|
||||||
#include "damage_brittle.f90"
|
#include "damage_brittle.f90"
|
||||||
#include "thermal_none.f90"
|
#include "thermal_isothermal.f90"
|
||||||
#include "thermal_adiabatic.f90"
|
#include "thermal_adiabatic.f90"
|
||||||
#include "constitutive_none.f90"
|
#include "constitutive_none.f90"
|
||||||
#include "constitutive_j2.f90"
|
#include "constitutive_j2.f90"
|
||||||
|
|
|
@ -109,12 +109,12 @@ subroutine constitutive_init
|
||||||
LOCAL_DAMAGE_NONE_ID, &
|
LOCAL_DAMAGE_NONE_ID, &
|
||||||
LOCAL_DAMAGE_BRITTLE_ID, &
|
LOCAL_DAMAGE_BRITTLE_ID, &
|
||||||
LOCAL_DAMAGE_DUCTILE_ID, &
|
LOCAL_DAMAGE_DUCTILE_ID, &
|
||||||
LOCAL_THERMAL_none_ID, &
|
LOCAL_THERMAL_ISOTHERMAL_ID, &
|
||||||
LOCAL_THERMAL_HEATGEN_ID, &
|
LOCAL_THERMAL_HEATGEN_ID, &
|
||||||
LOCAL_DAMAGE_NONE_label, &
|
LOCAL_DAMAGE_NONE_label, &
|
||||||
LOCAL_DAMAGE_BRITTLE_label, &
|
LOCAL_DAMAGE_BRITTLE_label, &
|
||||||
LOCAL_DAMAGE_DUCTILE_label, &
|
LOCAL_DAMAGE_DUCTILE_label, &
|
||||||
LOCAL_THERMAL_none_label, &
|
LOCAL_THERMAL_ISOTHERMAL_label, &
|
||||||
LOCAL_THERMAL_HEATGEN_label, &
|
LOCAL_THERMAL_HEATGEN_label, &
|
||||||
plasticState, &
|
plasticState, &
|
||||||
damageState, &
|
damageState, &
|
||||||
|
@ -132,7 +132,7 @@ subroutine constitutive_init
|
||||||
use damage_none
|
use damage_none
|
||||||
use damage_brittle
|
use damage_brittle
|
||||||
use damage_ductile
|
use damage_ductile
|
||||||
use thermal_none
|
use thermal_isothermal
|
||||||
use thermal_adiabatic
|
use thermal_adiabatic
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt), parameter :: FILEUNIT = 200_pInt
|
integer(pInt), parameter :: FILEUNIT = 200_pInt
|
||||||
|
@ -177,7 +177,7 @@ subroutine constitutive_init
|
||||||
! parse thermal from config file
|
! parse thermal from config file
|
||||||
if (.not. IO_open_jobFile_stat(FILEUNIT,material_localFileExt)) & ! no local material configuration present...
|
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
|
call IO_open_file(FILEUNIT,material_configFile) ! ... open material.config file
|
||||||
if (any(phase_thermal == LOCAL_THERMAL_none_ID)) call thermal_none_init(FILEUNIT)
|
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_HEATGEN_ID)) call thermal_heatgen_init(FILEUNIT)
|
||||||
close(FILEUNIT)
|
close(FILEUNIT)
|
||||||
|
|
||||||
|
@ -273,8 +273,8 @@ subroutine constitutive_init
|
||||||
instance = phase_thermalInstance(phase) ! which instance is present phase
|
instance = phase_thermalInstance(phase) ! which instance is present phase
|
||||||
knownThermal = .true.
|
knownThermal = .true.
|
||||||
select case(phase_thermal(phase)) ! split per constititution
|
select case(phase_thermal(phase)) ! split per constititution
|
||||||
case (LOCAL_THERMAL_none_ID)
|
case (LOCAL_THERMAL_ISOTHERMAL_ID)
|
||||||
outputName = LOCAL_THERMAL_NONE_label
|
outputName = LOCAL_THERMAL_ISOTHERMAL_label
|
||||||
thisNoutput => null()
|
thisNoutput => null()
|
||||||
thisOutput => null()
|
thisOutput => null()
|
||||||
thisSize => null()
|
thisSize => null()
|
||||||
|
@ -288,7 +288,7 @@ subroutine constitutive_init
|
||||||
end select
|
end select
|
||||||
if (knownThermal) then
|
if (knownThermal) then
|
||||||
write(FILEUNIT,'(a)') '(thermal)'//char(9)//trim(outputName)
|
write(FILEUNIT,'(a)') '(thermal)'//char(9)//trim(outputName)
|
||||||
if (phase_thermal(phase) /= LOCAL_THERMAL_none_ID) then
|
if (phase_thermal(phase) /= LOCAL_THERMAL_ISOTHERMAL_ID) then
|
||||||
do e = 1_pInt,thisNoutput(instance)
|
do e = 1_pInt,thisNoutput(instance)
|
||||||
write(FILEUNIT,'(a,i4)') trim(thisOutput(e,instance))//char(9),thisSize(e,instance)
|
write(FILEUNIT,'(a,i4)') trim(thisOutput(e,instance))//char(9),thisSize(e,instance)
|
||||||
enddo
|
enddo
|
||||||
|
@ -917,7 +917,7 @@ function constitutive_getAdiabaticThermal(ipc, ip, el)
|
||||||
pReal
|
pReal
|
||||||
use material, only: &
|
use material, only: &
|
||||||
material_phase, &
|
material_phase, &
|
||||||
LOCAL_THERMAL_none_ID, &
|
LOCAL_THERMAL_ISOTHERMAL_ID, &
|
||||||
LOCAL_THERMAL_HEATGEN_ID, &
|
LOCAL_THERMAL_HEATGEN_ID, &
|
||||||
phase_thermal
|
phase_thermal
|
||||||
use thermal_adiabatic, only: &
|
use thermal_adiabatic, only: &
|
||||||
|
@ -933,7 +933,7 @@ function constitutive_getAdiabaticThermal(ipc, ip, el)
|
||||||
real(pReal) :: constitutive_getAdiabaticThermal
|
real(pReal) :: constitutive_getAdiabaticThermal
|
||||||
|
|
||||||
select case (phase_thermal(material_phase(ipc,ip,el)))
|
select case (phase_thermal(material_phase(ipc,ip,el)))
|
||||||
case (LOCAL_THERMAL_none_ID)
|
case (LOCAL_THERMAL_ISOTHERMAL_ID)
|
||||||
constitutive_getAdiabaticThermal = lattice_referenceTemperature(material_phase(ipc,ip,el))
|
constitutive_getAdiabaticThermal = lattice_referenceTemperature(material_phase(ipc,ip,el))
|
||||||
|
|
||||||
case (LOCAL_THERMAL_HEATGEN_ID)
|
case (LOCAL_THERMAL_HEATGEN_ID)
|
||||||
|
|
|
@ -64,10 +64,10 @@ module homogenization
|
||||||
public :: &
|
public :: &
|
||||||
homogenization_init, &
|
homogenization_init, &
|
||||||
materialpoint_stressAndItsTangent, &
|
materialpoint_stressAndItsTangent, &
|
||||||
field_getDAMAGE, &
|
field_getLocalDamage, &
|
||||||
field_putDAMAGE, &
|
field_putFieldDamage, &
|
||||||
field_getThermal, &
|
field_getLocalTemperature, &
|
||||||
field_putThermal, &
|
field_putFieldTemperature, &
|
||||||
field_getDamageMobility, &
|
field_getDamageMobility, &
|
||||||
field_getDamageDiffusion33, &
|
field_getDamageDiffusion33, &
|
||||||
field_getThermalConductivity33, &
|
field_getThermalConductivity33, &
|
||||||
|
@ -1129,7 +1129,7 @@ end function field_getDamageMobility
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief ToDo
|
!> @brief ToDo
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
real(pReal) function field_getDAMAGE(ip,el)
|
real(pReal) function field_getLocalDamage(ip,el)
|
||||||
use mesh, only: &
|
use mesh, only: &
|
||||||
mesh_element
|
mesh_element
|
||||||
use material, only: &
|
use material, only: &
|
||||||
|
@ -1146,20 +1146,20 @@ real(pReal) function field_getDAMAGE(ip,el)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! computing the damage value needed to be passed to field solver
|
! computing the damage value needed to be passed to field solver
|
||||||
field_getDAMAGE =0.0_pReal
|
field_getLocalDamage =0.0_pReal
|
||||||
|
|
||||||
do ipc = 1, homogenization_Ngrains(mesh_element(3,el))
|
do ipc = 1, homogenization_Ngrains(mesh_element(3,el))
|
||||||
field_getDAMAGE = field_getDAMAGE + constitutive_getLocalDamage(ipc,ip,el)
|
field_getLocalDamage = field_getLocalDamage + constitutive_getLocalDamage(ipc,ip,el)
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
field_getDAMAGE = field_getDAMAGE /homogenization_Ngrains(mesh_element(3,el))
|
field_getLocalDamage = field_getLocalDamage /homogenization_Ngrains(mesh_element(3,el))
|
||||||
|
|
||||||
end function field_getDAMAGE
|
end function field_getLocalDamage
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Sets the regularised damage value in field state
|
!> @brief Sets the regularised damage value in field state
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine field_putDAMAGE(ip,el,fieldDamageValue) ! naming scheme
|
subroutine field_putFieldDamage(ip,el,fieldDamageValue) ! naming scheme
|
||||||
use material, only: &
|
use material, only: &
|
||||||
fieldDamage, &
|
fieldDamage, &
|
||||||
material_homog, &
|
material_homog, &
|
||||||
|
@ -1181,12 +1181,12 @@ subroutine field_putDAMAGE(ip,el,fieldDamageValue) ! naming scheme
|
||||||
|
|
||||||
end select
|
end select
|
||||||
|
|
||||||
end subroutine field_putDAMAGE
|
end subroutine field_putFieldDamage
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief ToDo
|
!> @brief ToDo
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
real(pReal) function field_getThermal(ip,el)
|
real(pReal) function field_getLocalTemperature(ip,el)
|
||||||
use mesh, only: &
|
use mesh, only: &
|
||||||
mesh_element
|
mesh_element
|
||||||
use material, only: &
|
use material, only: &
|
||||||
|
@ -1202,18 +1202,18 @@ real(pReal) function field_getThermal(ip,el)
|
||||||
ipc
|
ipc
|
||||||
|
|
||||||
|
|
||||||
field_getThermal = 0.0_pReal
|
field_getLocalTemperature = 0.0_pReal
|
||||||
do ipc = 1, homogenization_Ngrains(mesh_element(3,el))
|
do ipc = 1, homogenization_Ngrains(mesh_element(3,el))
|
||||||
field_getThermal = field_getThermal + constitutive_getAdiabaticThermal(ipc,ip,el) ! array/function/subroutine which is faster
|
field_getLocalTemperature = field_getLocalTemperature + constitutive_getAdiabaticThermal(ipc,ip,el) ! array/function/subroutine which is faster
|
||||||
enddo
|
enddo
|
||||||
field_getThermal = field_getThermal /homogenization_Ngrains(mesh_element(3,el))
|
field_getLocalTemperature = field_getLocalTemperature /homogenization_Ngrains(mesh_element(3,el))
|
||||||
|
|
||||||
end function field_getThermal
|
end function field_getLocalTemperature
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Sets the regularised temperature value in field state
|
!> @brief Sets the regularised temperature value in field state
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine field_putThermal(ip,el,fieldThermalValue)
|
subroutine field_putFieldTemperature(ip,el,fieldThermalValue)
|
||||||
use material, only: &
|
use material, only: &
|
||||||
material_homog, &
|
material_homog, &
|
||||||
fieldThermal, &
|
fieldThermal, &
|
||||||
|
@ -1235,7 +1235,7 @@ subroutine field_putThermal(ip,el,fieldThermalValue)
|
||||||
|
|
||||||
end select
|
end select
|
||||||
|
|
||||||
end subroutine field_putThermal
|
end subroutine field_putFieldTemperature
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief return array of homogenization results for post file inclusion. call only,
|
!> @brief return array of homogenization results for post file inclusion. call only,
|
||||||
|
|
|
@ -30,7 +30,7 @@ module material
|
||||||
LOCAL_DAMAGE_NONE_label = 'none', &
|
LOCAL_DAMAGE_NONE_label = 'none', &
|
||||||
LOCAL_DAMAGE_BRITTLE_label = 'brittle', &
|
LOCAL_DAMAGE_BRITTLE_label = 'brittle', &
|
||||||
LOCAL_DAMAGE_DUCTILE_label = 'ductile', &
|
LOCAL_DAMAGE_DUCTILE_label = 'ductile', &
|
||||||
LOCAL_THERMAL_NONE_label = 'none', &
|
LOCAL_THERMAL_ISOTHERMAL_label = 'isothermal', &
|
||||||
LOCAL_THERMAL_HEATGEN_label = 'heatgen', &
|
LOCAL_THERMAL_HEATGEN_label = 'heatgen', &
|
||||||
FIELD_DAMAGE_LOCAL_label = 'local', &
|
FIELD_DAMAGE_LOCAL_label = 'local', &
|
||||||
FIELD_DAMAGE_NONLOCAL_label = 'nonlocal', &
|
FIELD_DAMAGE_NONLOCAL_label = 'nonlocal', &
|
||||||
|
@ -64,7 +64,7 @@ module material
|
||||||
end enum
|
end enum
|
||||||
|
|
||||||
enum, bind(c)
|
enum, bind(c)
|
||||||
enumerator :: LOCAL_THERMAL_NONE_ID, &
|
enumerator :: LOCAL_THERMAL_ISOTHERMAL_ID, &
|
||||||
LOCAL_THERMAL_HEATGEN_ID
|
LOCAL_THERMAL_HEATGEN_ID
|
||||||
end enum
|
end enum
|
||||||
enum, bind(c)
|
enum, bind(c)
|
||||||
|
@ -98,7 +98,7 @@ module material
|
||||||
phase_plasticity !< plasticity of each phase
|
phase_plasticity !< plasticity of each phase
|
||||||
integer(kind(LOCAL_DAMAGE_none_ID)), dimension(:), allocatable, public, protected :: &
|
integer(kind(LOCAL_DAMAGE_none_ID)), dimension(:), allocatable, public, protected :: &
|
||||||
phase_damage !< local damage of each phase
|
phase_damage !< local damage of each phase
|
||||||
integer(kind(LOCAL_THERMAL_none_ID)), dimension(:), allocatable, public, protected :: &
|
integer(kind(LOCAL_THERMAL_isothermal_ID)), dimension(:), allocatable, public, protected :: &
|
||||||
phase_thermal !< local thermal of each phase
|
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
|
field_damage_type !< field damage of each phase
|
||||||
|
@ -216,7 +216,7 @@ module material
|
||||||
LOCAL_DAMAGE_none_ID, &
|
LOCAL_DAMAGE_none_ID, &
|
||||||
LOCAL_DAMAGE_brittle_ID, &
|
LOCAL_DAMAGE_brittle_ID, &
|
||||||
LOCAL_DAMAGE_ductile_ID, &
|
LOCAL_DAMAGE_ductile_ID, &
|
||||||
LOCAL_THERMAL_none_ID, &
|
LOCAL_THERMAL_isothermal_ID, &
|
||||||
LOCAL_THERMAL_heatgen_ID, &
|
LOCAL_THERMAL_heatgen_ID, &
|
||||||
FIELD_DAMAGE_LOCAL_ID, &
|
FIELD_DAMAGE_LOCAL_ID, &
|
||||||
FIELD_DAMAGE_NONLOCAL_ID, &
|
FIELD_DAMAGE_NONLOCAL_ID, &
|
||||||
|
@ -717,7 +717,7 @@ subroutine material_parsePhase(fileUnit,myPart)
|
||||||
allocate(phase_plasticityInstance(Nsections), source=0_pInt)
|
allocate(phase_plasticityInstance(Nsections), source=0_pInt)
|
||||||
allocate(phase_damage(Nsections) , source=LOCAL_DAMAGE_none_ID)
|
allocate(phase_damage(Nsections) , source=LOCAL_DAMAGE_none_ID)
|
||||||
allocate(phase_damageInstance(Nsections), source=0_pInt)
|
allocate(phase_damageInstance(Nsections), source=0_pInt)
|
||||||
allocate(phase_thermal(Nsections) , source=LOCAL_THERMAL_none_ID)
|
allocate(phase_thermal(Nsections) , source=LOCAL_THERMAL_isothermal_ID)
|
||||||
allocate(phase_thermalInstance(Nsections), source=0_pInt)
|
allocate(phase_thermalInstance(Nsections), source=0_pInt)
|
||||||
allocate(phase_Noutput(Nsections), source=0_pInt)
|
allocate(phase_Noutput(Nsections), source=0_pInt)
|
||||||
allocate(phase_localPlasticity(Nsections), source=.false.)
|
allocate(phase_localPlasticity(Nsections), source=.false.)
|
||||||
|
@ -791,8 +791,8 @@ subroutine material_parsePhase(fileUnit,myPart)
|
||||||
phase_damageInstance(section) = count(phase_damage(1:section) == phase_damage(section)) ! count instances
|
phase_damageInstance(section) = count(phase_damage(1:section) == phase_damage(section)) ! count instances
|
||||||
case ('thermal')
|
case ('thermal')
|
||||||
select case (IO_lc(IO_stringValue(line,positions,2_pInt)))
|
select case (IO_lc(IO_stringValue(line,positions,2_pInt)))
|
||||||
case (LOCAL_THERMAL_NONE_label)
|
case (LOCAL_THERMAL_ISOTHERMAL_label)
|
||||||
phase_thermal(section) = LOCAL_THERMAL_none_ID
|
phase_thermal(section) = LOCAL_THERMAL_isothermal_ID
|
||||||
case (LOCAL_THERMAL_HEATGEN_label)
|
case (LOCAL_THERMAL_HEATGEN_label)
|
||||||
phase_thermal(section) = LOCAL_THERMAL_HEATGEN_ID
|
phase_thermal(section) = LOCAL_THERMAL_HEATGEN_ID
|
||||||
case default
|
case default
|
||||||
|
|
|
@ -1,24 +1,24 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! $Id: thermal_none.f90 3148 2014-05-27 14:46:03Z MPIE\m.diehl $
|
! $Id: thermal_isothermal.f90 3148 2014-05-27 14:46:03Z MPIE\m.diehl $
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
!> @brief material subroutine for purely elastic material
|
!> @brief material subroutine for purely elastic material
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module thermal_none
|
module thermal_isothermal
|
||||||
use prec, only: &
|
use prec, only: &
|
||||||
pInt
|
pInt
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||||
thermal_none_sizePostResults
|
thermal_isothermal_sizePostResults
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||||
thermal_none_sizePostResult !< size of each post result output
|
thermal_isothermal_sizePostResult !< size of each post result output
|
||||||
|
|
||||||
public :: &
|
public :: &
|
||||||
thermal_none_init
|
thermal_isothermal_init
|
||||||
|
|
||||||
contains
|
contains
|
||||||
|
|
||||||
|
@ -27,7 +27,7 @@ contains
|
||||||
!> @brief module initialization
|
!> @brief module initialization
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine thermal_none_init(fileUnit)
|
subroutine thermal_isothermal_init(fileUnit)
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
||||||
use debug, only: &
|
use debug, only: &
|
||||||
debug_level, &
|
debug_level, &
|
||||||
|
@ -40,8 +40,8 @@ subroutine thermal_none_init(fileUnit)
|
||||||
use material, only: &
|
use material, only: &
|
||||||
phase_thermal, &
|
phase_thermal, &
|
||||||
phase_Noutput, &
|
phase_Noutput, &
|
||||||
LOCAL_THERMAL_NONE_label, &
|
LOCAL_THERMAL_ISOTHERMAL_label, &
|
||||||
LOCAL_THERMAL_NONE_ID, &
|
LOCAL_THERMAL_ISOTHERMAL_ID, &
|
||||||
material_phase, &
|
material_phase, &
|
||||||
thermalState, &
|
thermalState, &
|
||||||
MATERIAL_partPhase
|
MATERIAL_partPhase
|
||||||
|
@ -56,12 +56,12 @@ subroutine thermal_none_init(fileUnit)
|
||||||
sizeState, &
|
sizeState, &
|
||||||
sizeDotState
|
sizeDotState
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- thermal_'//LOCAL_THERMAL_NONE_label//' init -+>>>'
|
write(6,'(/,a)') ' <<<+- thermal_'//LOCAL_THERMAL_ISOTHERMAL_label//' init -+>>>'
|
||||||
write(6,'(a)') ' $Id: thermal_none.f90 3148 2014-05-27 14:46:03Z MPIE\m.diehl $'
|
write(6,'(a)') ' $Id: thermal_isothermal.f90 3148 2014-05-27 14:46:03Z MPIE\m.diehl $'
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||||
#include "compilation_info.f90"
|
#include "compilation_info.f90"
|
||||||
|
|
||||||
maxNinstance = int(count(phase_thermal == LOCAL_THERMAL_NONE_ID),pInt)
|
maxNinstance = int(count(phase_thermal == LOCAL_THERMAL_ISOTHERMAL_ID),pInt)
|
||||||
if (maxNinstance == 0_pInt) return
|
if (maxNinstance == 0_pInt) return
|
||||||
|
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
|
||||||
|
@ -70,7 +70,7 @@ subroutine thermal_none_init(fileUnit)
|
||||||
initializeInstances: do phase = 1_pInt, size(phase_thermal)
|
initializeInstances: do phase = 1_pInt, size(phase_thermal)
|
||||||
NofMyPhase=count(material_phase==phase)
|
NofMyPhase=count(material_phase==phase)
|
||||||
|
|
||||||
if (phase_thermal(phase) == LOCAL_THERMAL_none_ID) then
|
if (phase_thermal(phase) == LOCAL_THERMAL_ISOTHERMAL_ID) then
|
||||||
sizeState = 0_pInt
|
sizeState = 0_pInt
|
||||||
thermalState(phase)%sizeState = sizeState
|
thermalState(phase)%sizeState = sizeState
|
||||||
sizeDotState = sizeState
|
sizeDotState = sizeState
|
||||||
|
@ -94,8 +94,8 @@ subroutine thermal_none_init(fileUnit)
|
||||||
allocate(thermalState(phase)%RKCK45dotState (6,sizeDotState,NofMyPhase))
|
allocate(thermalState(phase)%RKCK45dotState (6,sizeDotState,NofMyPhase))
|
||||||
endif
|
endif
|
||||||
enddo initializeInstances
|
enddo initializeInstances
|
||||||
allocate(thermal_none_sizePostResults(maxNinstance), source=0_pInt)
|
allocate(thermal_isothermal_sizePostResults(maxNinstance), source=0_pInt)
|
||||||
|
|
||||||
end subroutine thermal_none_init
|
end subroutine thermal_isothermal_init
|
||||||
|
|
||||||
end module thermal_none
|
end module thermal_isothermal
|
||||||
|
|
Loading…
Reference in New Issue