do not clutter the code with use statements
This commit is contained in:
parent
0db4264265
commit
a5c6e4b17c
|
@ -14,7 +14,11 @@
|
|||
#define PETSC_MAJOR 3
|
||||
#define PETSC_MINOR_MIN 10
|
||||
#define PETSC_MINOR_MAX 11
|
||||
|
||||
module DAMASK_interface
|
||||
use, intrinsic :: iso_fortran_env
|
||||
use PETScSys
|
||||
|
||||
use prec
|
||||
use system_routines
|
||||
|
||||
|
@ -50,9 +54,6 @@ contains
|
|||
!! information on computation to screen
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine DAMASK_interface_init
|
||||
use, intrinsic :: iso_fortran_env
|
||||
use PETScSys
|
||||
|
||||
#include <petsc/finclude/petscsys.h>
|
||||
#if defined(__GFORTRAN__) && __GNUC__<GCC_MIN
|
||||
===================================================================================================
|
||||
|
|
|
@ -8,6 +8,8 @@ module HDF5_utilities
|
|||
use prec
|
||||
use IO
|
||||
use HDF5
|
||||
use rotations
|
||||
use numerics
|
||||
#ifdef PETSc
|
||||
use PETSC
|
||||
#endif
|
||||
|
@ -1676,8 +1678,6 @@ end subroutine HDF5_write_int7
|
|||
! ToDo: We could optionally write out other representations (axis angle, euler, ...)
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine HDF5_write_rotation(loc_id,dataset,datasetName,parallel)
|
||||
use rotations, only: &
|
||||
rotation
|
||||
|
||||
type(rotation), intent(in), dimension(:) :: dataset
|
||||
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
||||
|
@ -1754,9 +1754,6 @@ end subroutine HDF5_write_rotation
|
|||
subroutine initialize_read(dset_id, filespace_id, memspace_id, plist_id, aplist_id, &
|
||||
myStart, globalShape, &
|
||||
loc_id,localShape,datasetName,parallel)
|
||||
use numerics, only: &
|
||||
worldrank, &
|
||||
worldsize
|
||||
|
||||
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
||||
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
||||
|
@ -1850,9 +1847,6 @@ end subroutine finalize_read
|
|||
subroutine initialize_write(dset_id, filespace_id, memspace_id, plist_id, &
|
||||
myStart, totalShape, &
|
||||
loc_id,myShape,datasetName,datatype,parallel)
|
||||
use numerics, only: &
|
||||
worldrank, &
|
||||
worldsize
|
||||
|
||||
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
||||
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
||||
|
|
|
@ -11,6 +11,10 @@ module damage_nonlocal
|
|||
use crystallite
|
||||
use lattice
|
||||
use mesh
|
||||
use source_damage_isoBrittle
|
||||
use source_damage_isoDuctile
|
||||
use source_damage_anisoBrittle
|
||||
use source_damage_anisoDuctile
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
@ -119,18 +123,11 @@ subroutine damage_nonlocal_init
|
|||
enddo
|
||||
end subroutine damage_nonlocal_init
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief calculates homogenized damage driving forces
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine damage_nonlocal_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el)
|
||||
use source_damage_isoBrittle, only: &
|
||||
source_damage_isobrittle_getRateAndItsTangent
|
||||
use source_damage_isoDuctile, only: &
|
||||
source_damage_isoductile_getRateAndItsTangent
|
||||
use source_damage_anisoBrittle, only: &
|
||||
source_damage_anisobrittle_getRateAndItsTangent
|
||||
use source_damage_anisoDuctile, only: &
|
||||
source_damage_anisoductile_getRateAndItsTangent
|
||||
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
|
|
|
@ -16,6 +16,12 @@ module homogenization
|
|||
use crystallite
|
||||
use mesh
|
||||
use FEsolving
|
||||
use thermal_isothermal
|
||||
use thermal_adiabatic
|
||||
use thermal_conduction
|
||||
use damage_none
|
||||
use damage_local
|
||||
use damage_nonlocal
|
||||
#if defined(PETSc) || defined(DAMASK_HDF5)
|
||||
use results
|
||||
use HDF5_utilities
|
||||
|
@ -131,12 +137,6 @@ contains
|
|||
!> @brief module initialization
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine homogenization_init
|
||||
use thermal_isothermal
|
||||
use thermal_adiabatic
|
||||
use thermal_conduction
|
||||
use damage_none
|
||||
use damage_local
|
||||
use damage_nonlocal
|
||||
|
||||
integer, parameter :: FILEUNIT = 200
|
||||
integer :: e,i,p
|
||||
|
@ -668,10 +668,6 @@ end subroutine partitionDeformation
|
|||
!> "happy" with result
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function updateState(ip,el)
|
||||
use thermal_adiabatic, only: &
|
||||
thermal_adiabatic_updateState
|
||||
use damage_local, only: &
|
||||
damage_local_updateState
|
||||
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point
|
||||
|
@ -753,14 +749,6 @@ end subroutine averageStressAndItsTangent
|
|||
!> if homogenization_sizePostResults(i,e) > 0 !!
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function postResults(ip,el)
|
||||
use thermal_adiabatic, only: &
|
||||
thermal_adiabatic_postResults
|
||||
use thermal_conduction, only: &
|
||||
thermal_conduction_postResults
|
||||
use damage_local, only: &
|
||||
damage_local_postResults
|
||||
use damage_nonlocal, only: &
|
||||
damage_nonlocal_postResults
|
||||
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point
|
||||
|
|
34
src/list.f90
34
src/list.f90
|
@ -3,8 +3,8 @@
|
|||
!> @brief linked list
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module list
|
||||
use prec, only: &
|
||||
pReal
|
||||
use prec
|
||||
use IO
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
@ -65,10 +65,6 @@ contains
|
|||
!! to lower case. The data is not stored in the new element but in the current.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine add(this,string)
|
||||
use IO, only: &
|
||||
IO_isBlank, &
|
||||
IO_lc, &
|
||||
IO_stringPos
|
||||
|
||||
class(tPartitionedStringList), target, intent(in) :: this
|
||||
character(len=*), intent(in) :: string
|
||||
|
@ -157,8 +153,6 @@ end subroutine finalizeArray
|
|||
!> @brief reports wether a given key (string value at first position) exists in the list
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
logical function keyExists(this,key)
|
||||
use IO, only: &
|
||||
IO_stringValue
|
||||
|
||||
class(tPartitionedStringList), target, intent(in) :: this
|
||||
character(len=*), intent(in) :: key
|
||||
|
@ -180,8 +174,6 @@ end function keyExists
|
|||
!> @details traverses list and counts each occurrence of specified key
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
integer function countKeys(this,key)
|
||||
use IO, only: &
|
||||
IO_stringValue
|
||||
|
||||
class(tPartitionedStringList), target, intent(in) :: this
|
||||
character(len=*), intent(in) :: key
|
||||
|
@ -205,10 +197,6 @@ end function countKeys
|
|||
!! error unless default is given
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
real(pReal) function getFloat(this,key,defaultVal)
|
||||
use IO, only : &
|
||||
IO_error, &
|
||||
IO_stringValue, &
|
||||
IO_FloatValue
|
||||
|
||||
class(tPartitionedStringList), target, intent(in) :: this
|
||||
character(len=*), intent(in) :: key
|
||||
|
@ -241,10 +229,6 @@ end function getFloat
|
|||
!! error unless default is given
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
integer function getInt(this,key,defaultVal)
|
||||
use IO, only: &
|
||||
IO_error, &
|
||||
IO_stringValue, &
|
||||
IO_IntValue
|
||||
|
||||
class(tPartitionedStringList), target, intent(in) :: this
|
||||
character(len=*), intent(in) :: key
|
||||
|
@ -278,9 +262,6 @@ end function getInt
|
|||
!! the individual chunks are returned
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
character(len=65536) function getString(this,key,defaultVal,raw)
|
||||
use IO, only: &
|
||||
IO_error, &
|
||||
IO_stringValue
|
||||
|
||||
class(tPartitionedStringList), target, intent(in) :: this
|
||||
character(len=*), intent(in) :: key
|
||||
|
@ -327,10 +308,6 @@ end function getString
|
|||
!! values from the last occurrence. If key is not found exits with error unless default is given.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function getFloats(this,key,defaultVal,requiredSize)
|
||||
use IO, only: &
|
||||
IO_error, &
|
||||
IO_stringValue, &
|
||||
IO_FloatValue
|
||||
|
||||
real(pReal), dimension(:), allocatable :: getFloats
|
||||
class(tPartitionedStringList), target, intent(in) :: this
|
||||
|
@ -376,10 +353,6 @@ end function getFloats
|
|||
!! values from the last occurrence. If key is not found exits with error unless default is given.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function getInts(this,key,defaultVal,requiredSize)
|
||||
use IO, only: &
|
||||
IO_error, &
|
||||
IO_stringValue, &
|
||||
IO_IntValue
|
||||
|
||||
integer, dimension(:), allocatable :: getInts
|
||||
class(tPartitionedStringList), target, intent(in) :: this
|
||||
|
@ -426,9 +399,6 @@ end function getInts
|
|||
!! If raw is true, the the complete string is returned, otherwise the individual chunks are returned
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function getStrings(this,key,defaultVal,raw)
|
||||
use IO, only: &
|
||||
IO_error, &
|
||||
IO_StringValue
|
||||
|
||||
character(len=65536),dimension(:), allocatable :: getStrings
|
||||
class(tPartitionedStringList),target, intent(in) :: this
|
||||
|
|
|
@ -5,6 +5,9 @@
|
|||
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module results
|
||||
use DAMASK_interface
|
||||
use rotations
|
||||
use numerics
|
||||
use HDF5_utilities
|
||||
#ifdef PETSc
|
||||
use PETSC
|
||||
|
@ -55,8 +58,6 @@ module results
|
|||
contains
|
||||
|
||||
subroutine results_init
|
||||
use DAMASK_interface, only: &
|
||||
getSolverJobName
|
||||
|
||||
character(len=pStringLen) :: commandLine
|
||||
|
||||
|
@ -83,9 +84,6 @@ end subroutine results_init
|
|||
!> @brief opens the results file to append data
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine results_openJobFile
|
||||
use DAMASK_interface, only: &
|
||||
getSolverJobName
|
||||
|
||||
|
||||
resultsFile = HDF5_openFile(trim(getSolverJobName())//'.hdf5','a',.true.)
|
||||
|
||||
|
@ -396,8 +394,6 @@ end subroutine results_writeTensorDataset_int
|
|||
!> @brief stores a scalar dataset in a group
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine results_writeScalarDataset_rotation(group,dataset,label,description,lattice_structure)
|
||||
use rotations, only: &
|
||||
rotation
|
||||
|
||||
character(len=*), intent(in) :: label,group,description
|
||||
character(len=*), intent(in), optional :: lattice_structure
|
||||
|
@ -428,9 +424,6 @@ end subroutine results_writeScalarDataset_rotation
|
|||
!> @brief adds the unique mapping from spatial position and constituent ID to results
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine results_mapping_constituent(phaseAt,memberAt,label)
|
||||
use numerics, only: &
|
||||
worldrank, &
|
||||
worldsize
|
||||
|
||||
integer, dimension(:,:), intent(in) :: phaseAt !< phase section at (constituent,element)
|
||||
integer, dimension(:,:,:), intent(in) :: memberAt !< phase member at (constituent,IP,element)
|
||||
|
@ -566,9 +559,6 @@ end subroutine results_mapping_constituent
|
|||
!> @brief adds the unique mapping from spatial position and constituent ID to results
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine results_mapping_materialpoint(homogenizationAt,memberAt,label)
|
||||
use numerics, only: &
|
||||
worldrank, &
|
||||
worldsize
|
||||
|
||||
integer, dimension(:), intent(in) :: homogenizationAt !< homogenization section at (element)
|
||||
integer, dimension(:,:), intent(in) :: memberAt !< homogenization member at (IP,element)
|
||||
|
|
|
@ -6,9 +6,16 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
module source_damage_anisoBrittle
|
||||
use prec
|
||||
use debug
|
||||
use IO
|
||||
use math
|
||||
use material
|
||||
use config
|
||||
use lattice
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
||||
integer, dimension(:), allocatable, public, protected :: &
|
||||
source_damage_anisoBrittle_offset, & !< which source is my current source mechanism?
|
||||
source_damage_anisoBrittle_instance !< instance of source mechanism
|
||||
|
@ -19,7 +26,7 @@ module source_damage_anisoBrittle
|
|||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
source_damage_anisoBrittle_output !< name of each post result output
|
||||
|
||||
integer, dimension(:,:), allocatable, private :: &
|
||||
integer, dimension(:,:), allocatable :: &
|
||||
source_damage_anisoBrittle_Ncleavage !< number of cleavage systems per family
|
||||
|
||||
enum, bind(c)
|
||||
|
@ -28,7 +35,7 @@ module source_damage_anisoBrittle
|
|||
end enum
|
||||
|
||||
|
||||
type, private :: tParameters !< container type for internal constitutive parameters
|
||||
type :: tParameters !< container type for internal constitutive parameters
|
||||
real(pReal) :: &
|
||||
aTol, &
|
||||
sdot_0, &
|
||||
|
@ -46,7 +53,7 @@ module source_damage_anisoBrittle
|
|||
outputID !< ID of each post result output
|
||||
end type tParameters
|
||||
|
||||
type(tParameters), dimension(:), allocatable, private :: param !< containers of constitutive parameters (len Ninstance)
|
||||
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstance)
|
||||
|
||||
|
||||
public :: &
|
||||
|
@ -63,29 +70,6 @@ contains
|
|||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_damage_anisoBrittle_init
|
||||
use debug, only: &
|
||||
debug_level,&
|
||||
debug_constitutive,&
|
||||
debug_levelBasic
|
||||
use IO, only: &
|
||||
IO_error
|
||||
use math, only: &
|
||||
math_expand
|
||||
use material, only: &
|
||||
material_allocateSourceState, &
|
||||
phase_source, &
|
||||
phase_Nsources, &
|
||||
phase_Noutput, &
|
||||
SOURCE_damage_anisoBrittle_label, &
|
||||
SOURCE_damage_anisoBrittle_ID, &
|
||||
material_phase, &
|
||||
sourceState
|
||||
use config, only: &
|
||||
config_phase, &
|
||||
material_Nphase
|
||||
use lattice, only: &
|
||||
lattice_SchmidMatrix_cleavage, &
|
||||
lattice_maxNcleavageFamily
|
||||
|
||||
integer :: Ninstance,phase,instance,source,sourceOffset
|
||||
integer :: NofMyPhase,p ,i
|
||||
|
@ -193,25 +177,13 @@ subroutine source_damage_anisoBrittle_init
|
|||
source_damage_anisoBrittle_Ncleavage(1:size(param(instance)%Ncleavage),instance) = param(instance)%Ncleavage
|
||||
enddo
|
||||
|
||||
|
||||
end subroutine source_damage_anisoBrittle_init
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief calculates derived quantities from state
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_damage_anisoBrittle_dotState(S, ipc, ip, el)
|
||||
use math, only: &
|
||||
math_mul33xx33
|
||||
use material, only: &
|
||||
phaseAt, phasememberAt, &
|
||||
sourceState, &
|
||||
material_homogenizationAt, &
|
||||
damage, &
|
||||
damageMapping
|
||||
use lattice, only: &
|
||||
lattice_Scleavage, &
|
||||
lattice_maxNcleavageFamily, &
|
||||
lattice_NcleavageSystem
|
||||
|
||||
integer, intent(in) :: &
|
||||
ipc, & !< component-ID of integration point
|
||||
|
@ -265,12 +237,11 @@ subroutine source_damage_anisoBrittle_dotState(S, ipc, ip, el)
|
|||
|
||||
end subroutine source_damage_anisoBrittle_dotState
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns local part of nonlocal damage driving force
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_damage_anisobrittle_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, phase, constituent)
|
||||
use material, only: &
|
||||
sourceState
|
||||
|
||||
integer, intent(in) :: &
|
||||
phase, &
|
||||
|
@ -292,16 +263,16 @@ subroutine source_damage_anisobrittle_getRateAndItsTangent(localphiDot, dLocalph
|
|||
|
||||
end subroutine source_damage_anisobrittle_getRateAndItsTangent
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief return array of local damage results
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function source_damage_anisoBrittle_postResults(phase, constituent)
|
||||
use material, only: &
|
||||
sourceState
|
||||
|
||||
integer, intent(in) :: &
|
||||
phase, &
|
||||
constituent
|
||||
|
||||
real(pReal), dimension(sum(source_damage_anisoBrittle_sizePostResult(:, &
|
||||
source_damage_anisoBrittle_instance(phase)))) :: &
|
||||
source_damage_anisoBrittle_postResults
|
||||
|
|
|
@ -5,11 +5,14 @@
|
|||
!> @details to be done
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module source_thermal_dissipation
|
||||
use prec, only: &
|
||||
pReal
|
||||
use prec
|
||||
use debug
|
||||
use material
|
||||
use config
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
||||
integer, dimension(:), allocatable, public, protected :: &
|
||||
source_thermal_dissipation_offset, & !< which source is my current thermal dissipation mechanism?
|
||||
source_thermal_dissipation_instance !< instance of thermal dissipation source mechanism
|
||||
|
@ -20,12 +23,12 @@ module source_thermal_dissipation
|
|||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
source_thermal_dissipation_output !< name of each post result output
|
||||
|
||||
type, private :: tParameters !< container type for internal constitutive parameters
|
||||
type :: tParameters !< container type for internal constitutive parameters
|
||||
real(pReal) :: &
|
||||
kappa
|
||||
end type tParameters
|
||||
|
||||
type(tParameters), dimension(:), allocatable, private :: param !< containers of constitutive parameters (len Ninstance)
|
||||
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstance)
|
||||
|
||||
|
||||
public :: &
|
||||
|
@ -40,21 +43,6 @@ contains
|
|||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_thermal_dissipation_init
|
||||
use debug, only: &
|
||||
debug_level,&
|
||||
debug_constitutive,&
|
||||
debug_levelBasic
|
||||
use material, only: &
|
||||
material_allocateSourceState, &
|
||||
phase_source, &
|
||||
phase_Nsources, &
|
||||
phase_Noutput, &
|
||||
SOURCE_thermal_dissipation_label, &
|
||||
SOURCE_thermal_dissipation_ID, &
|
||||
material_phase
|
||||
use config, only: &
|
||||
config_phase, &
|
||||
material_Nphase
|
||||
|
||||
integer :: Ninstance,instance,source,sourceOffset
|
||||
integer :: NofMyPhase,p
|
||||
|
|
|
@ -5,11 +5,14 @@
|
|||
!> @brief material subroutine for variable heat source
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module source_thermal_externalheat
|
||||
use prec, only: &
|
||||
pReal
|
||||
use prec
|
||||
use debug
|
||||
use material
|
||||
use config
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
||||
integer, dimension(:), allocatable, public, protected :: &
|
||||
source_thermal_externalheat_offset, & !< which source is my current thermal dissipation mechanism?
|
||||
source_thermal_externalheat_instance !< instance of thermal dissipation source mechanism
|
||||
|
@ -23,7 +26,7 @@ module source_thermal_externalheat
|
|||
integer, dimension(:), allocatable, target, public :: &
|
||||
source_thermal_externalheat_Noutput !< number of outputs per instance of this source
|
||||
|
||||
type, private :: tParameters !< container type for internal constitutive parameters
|
||||
type :: tParameters !< container type for internal constitutive parameters
|
||||
real(pReal), dimension(:), allocatable :: &
|
||||
time, &
|
||||
heat_rate
|
||||
|
@ -31,7 +34,7 @@ module source_thermal_externalheat
|
|||
nIntervals
|
||||
end type tParameters
|
||||
|
||||
type(tParameters), dimension(:), allocatable, private :: param !< containers of constitutive parameters (len Ninstance)
|
||||
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstance)
|
||||
|
||||
|
||||
public :: &
|
||||
|
@ -47,22 +50,6 @@ contains
|
|||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_thermal_externalheat_init
|
||||
use debug, only: &
|
||||
debug_level,&
|
||||
debug_constitutive,&
|
||||
debug_levelBasic
|
||||
use material, only: &
|
||||
material_allocateSourceState, &
|
||||
material_phase, &
|
||||
phase_source, &
|
||||
phase_Nsources, &
|
||||
phase_Noutput, &
|
||||
SOURCE_thermal_externalheat_label, &
|
||||
SOURCE_thermal_externalheat_ID
|
||||
use config, only: &
|
||||
config_phase, &
|
||||
material_Nphase
|
||||
|
||||
|
||||
integer :: maxNinstance,instance,source,sourceOffset,NofMyPhase,p
|
||||
|
||||
|
@ -116,8 +103,6 @@ end subroutine source_thermal_externalheat_init
|
|||
!> @details state only contains current time to linearly interpolate given heat powers
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_thermal_externalheat_dotState(phase, of)
|
||||
use material, only: &
|
||||
sourceState
|
||||
|
||||
integer, intent(in) :: &
|
||||
phase, &
|
||||
|
@ -135,8 +120,6 @@ end subroutine source_thermal_externalheat_dotState
|
|||
!> @brief returns local heat generation rate
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_thermal_externalheat_getRateAndItsTangent(TDot, dTDot_dT, phase, of)
|
||||
use material, only: &
|
||||
sourceState
|
||||
|
||||
integer, intent(in) :: &
|
||||
phase, &
|
||||
|
|
|
@ -3,8 +3,15 @@
|
|||
!> @brief material subroutine for adiabatic temperature evolution
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module thermal_adiabatic
|
||||
use prec, only: &
|
||||
pReal
|
||||
use prec
|
||||
use config
|
||||
use numerics
|
||||
use material
|
||||
use source_thermal_dissipation
|
||||
use source_thermal_externalheat
|
||||
use crystallite
|
||||
use lattice
|
||||
use mesh
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
@ -21,7 +28,7 @@ module thermal_adiabatic
|
|||
enumerator :: undefined_ID, &
|
||||
temperature_ID
|
||||
end enum
|
||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
||||
integer(kind(undefined_ID)), dimension(:,:), allocatable :: &
|
||||
thermal_adiabatic_outputID !< ID of each post result output
|
||||
|
||||
|
||||
|
@ -41,21 +48,6 @@ contains
|
|||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine thermal_adiabatic_init
|
||||
use material, only: &
|
||||
thermal_type, &
|
||||
thermal_typeInstance, &
|
||||
homogenization_Noutput, &
|
||||
THERMAL_ADIABATIC_label, &
|
||||
THERMAL_adiabatic_ID, &
|
||||
material_homogenizationAt, &
|
||||
mappingHomogenization, &
|
||||
thermalState, &
|
||||
thermalMapping, &
|
||||
thermal_initialT, &
|
||||
temperature, &
|
||||
temperatureRate
|
||||
use config, only: &
|
||||
config_homogenization
|
||||
|
||||
integer :: maxNinstance,section,instance,i,sizeState,NofMyHomog
|
||||
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
|
||||
|
@ -112,16 +104,6 @@ end subroutine thermal_adiabatic_init
|
|||
!> @brief calculates adiabatic change in temperature based on local heat generation model
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function thermal_adiabatic_updateState(subdt, ip, el)
|
||||
use numerics, only: &
|
||||
err_thermal_tolAbs, &
|
||||
err_thermal_tolRel
|
||||
use material, only: &
|
||||
material_homogenizationAt, &
|
||||
mappingHomogenization, &
|
||||
thermalState, &
|
||||
temperature, &
|
||||
temperatureRate, &
|
||||
thermalMapping
|
||||
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
|
@ -156,27 +138,11 @@ function thermal_adiabatic_updateState(subdt, ip, el)
|
|||
|
||||
end function thermal_adiabatic_updateState
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns heat generation rate
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine thermal_adiabatic_getSourceAndItsTangent(Tdot, dTdot_dT, T, ip, el)
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_homogenizationAt, &
|
||||
phaseAt, &
|
||||
phasememberAt, &
|
||||
thermal_typeInstance, &
|
||||
phase_Nsources, &
|
||||
phase_source, &
|
||||
SOURCE_thermal_dissipation_ID, &
|
||||
SOURCE_thermal_externalheat_ID
|
||||
use source_thermal_dissipation, only: &
|
||||
source_thermal_dissipation_getRateAndItsTangent
|
||||
use source_thermal_externalheat, only: &
|
||||
source_thermal_externalheat_getRateAndItsTangent
|
||||
use crystallite, only: &
|
||||
crystallite_S, &
|
||||
crystallite_Lp
|
||||
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
|
@ -230,17 +196,11 @@ subroutine thermal_adiabatic_getSourceAndItsTangent(Tdot, dTdot_dT, T, ip, el)
|
|||
|
||||
end subroutine thermal_adiabatic_getSourceAndItsTangent
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns homogenized specific heat capacity
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function thermal_adiabatic_getSpecificHeat(ip,el)
|
||||
use lattice, only: &
|
||||
lattice_specificHeat
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_phase
|
||||
use mesh, only: &
|
||||
mesh_element
|
||||
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
|
@ -269,13 +229,6 @@ end function thermal_adiabatic_getSpecificHeat
|
|||
!> @brief returns homogenized mass density
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function thermal_adiabatic_getMassDensity(ip,el)
|
||||
use lattice, only: &
|
||||
lattice_massDensity
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_phase
|
||||
use mesh, only: &
|
||||
mesh_element
|
||||
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
|
@ -303,8 +256,6 @@ end function thermal_adiabatic_getMassDensity
|
|||
!> @brief return array of thermal results
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function thermal_adiabatic_postResults(homog,instance,of) result(postResults)
|
||||
use material, only: &
|
||||
temperature
|
||||
|
||||
integer, intent(in) :: &
|
||||
homog, &
|
||||
|
|
Loading…
Reference in New Issue