temperature initialised to value from load case file

This commit is contained in:
Pratheek Shanthraj 2014-10-13 17:54:27 +00:00
parent 45dffc704c
commit a057c540e0
5 changed files with 35 additions and 27 deletions

View File

@ -97,8 +97,8 @@ subroutine CPFEM_initAll(temperature,el,ip)
call FE_init call FE_init
call mesh_init(ip, el) ! pass on coordinates to alter calcMode of first ip call mesh_init(ip, el) ! pass on coordinates to alter calcMode of first ip
call lattice_init call lattice_init
call material_init call material_init(temperature)
call constitutive_init call constitutive_init(temperature)
call crystallite_init call crystallite_init
call homogenization_init call homogenization_init
call CPFEM_init call CPFEM_init

View File

@ -53,7 +53,7 @@ contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief allocates arrays pointing to array of the various constitutive modules !> @brief allocates arrays pointing to array of the various constitutive modules
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine constitutive_init subroutine constitutive_init(temperature_init)
#ifdef HDF #ifdef HDF
use hdf5, only: & use hdf5, only: &
HID_T HID_T
@ -158,9 +158,10 @@ subroutine constitutive_init
use vacancy_generation use vacancy_generation
implicit none implicit none
real(pReal), intent(in) :: temperature_init !< initial temperature
integer(pInt), parameter :: FILEUNIT = 200_pInt integer(pInt), parameter :: FILEUNIT = 200_pInt
integer(pInt) :: & integer(pInt) :: &
e, & !< maximum number of elements e, & !< maximum number of elements
phase, & phase, &
instance instance
@ -201,8 +202,8 @@ 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_isothermal_ID)) call thermal_isothermal_init(FILEUNIT) if (any(phase_thermal == LOCAL_THERMAL_isothermal_ID)) call thermal_isothermal_init(FILEUNIT,temperature_init)
if (any(phase_thermal == LOCAL_THERMAL_adiabatic_ID)) call thermal_adiabatic_init(FILEUNIT) if (any(phase_thermal == LOCAL_THERMAL_adiabatic_ID)) call thermal_adiabatic_init(FILEUNIT,temperature_init)
close(FILEUNIT) close(FILEUNIT)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
@ -351,7 +352,7 @@ subroutine constitutive_init
end select end select
if (knownVacancy) then if (knownVacancy) then
write(FILEUNIT,'(a)') '(vacancy)'//char(9)//trim(outputName) write(FILEUNIT,'(a)') '(vacancy)'//char(9)//trim(outputName)
if (phase_vacancy(phase) /= LOCAL_VACANCY_generation_ID) then if (phase_vacancy(phase) /= LOCAL_VACANCY_constant_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
@ -1067,11 +1068,12 @@ function constitutive_getAdiabaticTemperature(ipc, ip, el)
material_phase, & material_phase, &
LOCAL_THERMAL_isothermal_ID, & LOCAL_THERMAL_isothermal_ID, &
LOCAL_THERMAL_adiabatic_ID, & LOCAL_THERMAL_adiabatic_ID, &
phase_thermal phase_thermal, &
phase_thermalInstance
use thermal_isothermal, only: &
thermal_isothermal_temperature
use thermal_adiabatic, only: & use thermal_adiabatic, only: &
thermal_adiabatic_getTemperature thermal_adiabatic_getTemperature
use lattice, only: &
lattice_referenceTemperature
implicit none implicit none
integer(pInt), intent(in) :: & integer(pInt), intent(in) :: &
@ -1082,7 +1084,8 @@ function constitutive_getAdiabaticTemperature(ipc, ip, el)
select case (phase_thermal(material_phase(ipc,ip,el))) select case (phase_thermal(material_phase(ipc,ip,el)))
case (LOCAL_THERMAL_isothermal_ID) case (LOCAL_THERMAL_isothermal_ID)
constitutive_getAdiabaticTemperature = lattice_referenceTemperature(material_phase(ipc,ip,el)) constitutive_getAdiabaticTemperature = &
thermal_isothermal_temperature(phase_thermalInstance(material_phase(ipc,ip,el)))
case (LOCAL_THERMAL_adiabatic_ID) case (LOCAL_THERMAL_adiabatic_ID)
constitutive_getAdiabaticTemperature = thermal_adiabatic_getTemperature(ipc, ip, el) constitutive_getAdiabaticTemperature = thermal_adiabatic_getTemperature(ipc, ip, el)

View File

@ -271,7 +271,7 @@ contains
!> @details figures out if solverJobName.materialConfig is present, if not looks for !> @details figures out if solverJobName.materialConfig is present, if not looks for
!> material.config !> material.config
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine material_init subroutine material_init(temperature_init)
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 IO, only: & use IO, only: &
IO_error, & IO_error, &
@ -293,6 +293,7 @@ subroutine material_init
worldrank worldrank
implicit none implicit none
real(pReal), intent(in) :: temperature_init !< initial field temperature
integer(pInt), parameter :: FILEUNIT = 200_pInt integer(pInt), parameter :: FILEUNIT = 200_pInt
integer(pInt) :: m,c,h, myDebug, myHomog integer(pInt) :: m,c,h, myDebug, myHomog
integer(pInt) :: & integer(pInt) :: &
@ -419,14 +420,13 @@ subroutine material_init
case (FIELD_THERMAL_local_ID) case (FIELD_THERMAL_local_ID)
fieldThermal(homog)%sizeField = 0_pInt fieldThermal(homog)%sizeField = 0_pInt
fieldThermal(homog)%sizePostResults = 0_pInt fieldThermal(homog)%sizePostResults = 0_pInt
allocate(fieldThermal(homog)%field(fieldThermal(homog)%sizeField,NofMyField), & allocate(fieldThermal(homog)%field(fieldThermal(homog)%sizeField,NofMyField))
source = 300.0_pReal) ! ToDo: temporary fix for now
case (FIELD_THERMAL_nonlocal_ID) case (FIELD_THERMAL_nonlocal_ID)
fieldThermal(homog)%sizeField = 1_pInt fieldThermal(homog)%sizeField = 1_pInt
fieldThermal(homog)%sizePostResults = 1_pInt fieldThermal(homog)%sizePostResults = 1_pInt
allocate(fieldThermal(homog)%field(fieldThermal(homog)%sizeField,NofMyField), & allocate(fieldThermal(homog)%field(fieldThermal(homog)%sizeField,NofMyField), &
source = 300.0_pReal) ! ToDo: temporary fix for now source = temperature_init)
end select end select
enddo enddo

View File

@ -24,7 +24,7 @@ module thermal_adiabatic
integer(pInt), dimension(:), allocatable, target, public :: & integer(pInt), dimension(:), allocatable, target, public :: &
thermal_adiabatic_Noutput !< number of outputs per instance of this damage thermal_adiabatic_Noutput !< number of outputs per instance of this damage
real(pReal), dimension(:), allocatable, public :: & real(pReal), dimension(:), allocatable, public :: &
thermal_adiabatic_aTol thermal_adiabatic_aTol
enum, bind(c) enum, bind(c)
@ -51,7 +51,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_adiabatic_init(fileUnit) subroutine thermal_adiabatic_init(fileUnit,temperature_init)
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,&
@ -88,6 +88,7 @@ subroutine thermal_adiabatic_init(fileUnit)
numerics_integrator numerics_integrator
implicit none implicit none
real(pReal), intent(in) :: temperature_init !< initial temperature
integer(pInt), intent(in) :: fileUnit integer(pInt), intent(in) :: fileUnit
integer(pInt), parameter :: MAXNCHUNKS = 7_pInt integer(pInt), parameter :: MAXNCHUNKS = 7_pInt
@ -117,7 +118,7 @@ subroutine thermal_adiabatic_init(fileUnit)
thermal_adiabatic_output = '' thermal_adiabatic_output = ''
allocate(thermal_adiabatic_outputID(maxval(phase_Noutput),maxNinstance), source=undefined_ID) allocate(thermal_adiabatic_outputID(maxval(phase_Noutput),maxNinstance), source=undefined_ID)
allocate(thermal_adiabatic_Noutput(maxNinstance), source=0_pInt) allocate(thermal_adiabatic_Noutput(maxNinstance), source=0_pInt)
allocate(thermal_adiabatic_aTol(maxNinstance), source=0.0_pReal) allocate(thermal_adiabatic_aTol(maxNinstance), source=0.0_pReal)
rewind(fileUnit) rewind(fileUnit)
phase = 0_pInt phase = 0_pInt
@ -202,7 +203,7 @@ subroutine thermal_adiabatic_init(fileUnit)
if (any(numerics_integrator == 5_pInt)) & if (any(numerics_integrator == 5_pInt)) &
allocate(thermalState(phase)%RKCK45dotState (6,sizeDotState,NofMyPhase),source=0.0_pReal) allocate(thermalState(phase)%RKCK45dotState (6,sizeDotState,NofMyPhase),source=0.0_pReal)
call thermal_adiabatic_stateInit(phase,instance) call thermal_adiabatic_stateInit(phase,temperature_init)
call thermal_adiabatic_aTolState(phase,instance) call thermal_adiabatic_aTolState(phase,instance)
endif endif
@ -212,19 +213,17 @@ end subroutine thermal_adiabatic_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief sets the relevant NEW state values for a given instance of this thermal !> @brief sets the relevant NEW state values for a given instance of this thermal
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine thermal_adiabatic_stateInit(phase,instance) subroutine thermal_adiabatic_stateInit(phase,temperature_init)
use material, only: & use material, only: &
thermalState thermalState
use lattice, only: &
lattice_referenceTemperature
implicit none implicit none
integer(pInt), intent(in) :: instance !< number specifying the instance of the thermal
integer(pInt), intent(in) :: phase !< number specifying the phase of the thermal integer(pInt), intent(in) :: phase !< number specifying the phase of the thermal
real(pReal), intent(in) :: temperature_init !< initial temperature
real(pReal), dimension(thermalState(phase)%sizeState) :: tempState real(pReal), dimension(thermalState(phase)%sizeState) :: tempState
tempState(1) = lattice_referenceTemperature(phase) tempState(1) = temperature_init
thermalState(phase)%state = spread(tempState,2,size(thermalState(phase)%state(1,:))) thermalState(phase)%state = spread(tempState,2,size(thermalState(phase)%state(1,:)))
thermalState(phase)%state0 = thermalState(phase)%state thermalState(phase)%state0 = thermalState(phase)%state
thermalState(phase)%partionedState0 = thermalState(phase)%state thermalState(phase)%partionedState0 = thermalState(phase)%state
@ -243,7 +242,7 @@ subroutine thermal_adiabatic_aTolState(phase,instance)
instance ! number specifying the current instance of the thermal instance ! number specifying the current instance of the thermal
real(pReal), dimension(thermalState(phase)%sizeState) :: tempTol real(pReal), dimension(thermalState(phase)%sizeState) :: tempTol
tempTol = thermal_adiabatic_aTol tempTol = thermal_adiabatic_aTol(instance)
thermalState(phase)%aTolState = tempTol thermalState(phase)%aTolState = tempTol
end subroutine thermal_adiabatic_aTolState end subroutine thermal_adiabatic_aTolState

View File

@ -7,7 +7,8 @@
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module thermal_isothermal module thermal_isothermal
use prec, only: & use prec, only: &
pInt pInt, &
pReal
implicit none implicit none
private private
@ -17,6 +18,9 @@ module thermal_isothermal
integer(pInt), dimension(:,:), allocatable, target, public :: & integer(pInt), dimension(:,:), allocatable, target, public :: &
thermal_isothermal_sizePostResult !< size of each post result output thermal_isothermal_sizePostResult !< size of each post result output
real(pReal), dimension(:), allocatable, public :: &
thermal_isothermal_temperature
public :: & public :: &
thermal_isothermal_init thermal_isothermal_init
@ -27,7 +31,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_isothermal_init(fileUnit) subroutine thermal_isothermal_init(fileUnit,temperature_init)
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, &
@ -49,6 +53,7 @@ subroutine thermal_isothermal_init(fileUnit)
implicit none implicit none
real(pReal), intent(in) :: temperature_init !< initial temperature
integer(pInt), intent(in) :: fileUnit integer(pInt), intent(in) :: fileUnit
integer(pInt) :: & integer(pInt) :: &
maxNinstance, & maxNinstance, &
@ -98,6 +103,7 @@ subroutine thermal_isothermal_init(fileUnit)
endif endif
enddo initializeInstances enddo initializeInstances
allocate(thermal_isothermal_sizePostResults(maxNinstance), source=0_pInt) allocate(thermal_isothermal_sizePostResults(maxNinstance), source=0_pInt)
allocate(thermal_isothermal_temperature(maxNinstance), source=temperature_init)
end subroutine thermal_isothermal_init end subroutine thermal_isothermal_init