better name
This commit is contained in:
parent
c8f426a875
commit
550b6510a5
|
@ -613,7 +613,7 @@ pure function constitutive_initialFi(ipc, ip, el)
|
|||
math_I3
|
||||
use material, only: &
|
||||
material_phase, &
|
||||
material_homog, &
|
||||
material_homogenizationAt, &
|
||||
thermalMapping, &
|
||||
phase_kinematics, &
|
||||
phase_Nkinematics, &
|
||||
|
@ -641,7 +641,7 @@ pure function constitutive_initialFi(ipc, ip, el)
|
|||
KinematicsLoop: do k = 1_pInt, phase_Nkinematics(phase) !< Warning: small initial strain assumption
|
||||
kinematicsType: select case (phase_kinematics(k,phase))
|
||||
case (KINEMATICS_thermal_expansion_ID) kinematicsType
|
||||
homog = material_homog(ip,el)
|
||||
homog = material_homogenizationAt(el)
|
||||
offset = thermalMapping(homog)%p(ip,el)
|
||||
constitutive_initialFi = &
|
||||
constitutive_initialFi + kinematics_thermal_expansion_initialStrain(homog,phase,offset)
|
||||
|
|
|
@ -53,7 +53,7 @@ subroutine damage_local_init
|
|||
homogenization_Noutput, &
|
||||
DAMAGE_local_label, &
|
||||
DAMAGE_local_ID, &
|
||||
material_homog, &
|
||||
material_homogenizationAt, &
|
||||
mappingHomogenization, &
|
||||
damageState, &
|
||||
damageMapping, &
|
||||
|
@ -111,7 +111,7 @@ subroutine damage_local_init
|
|||
|
||||
homog = h
|
||||
|
||||
NofMyHomog = count(material_homog == homog)
|
||||
NofMyHomog = count(material_homogenizationAt == homog)
|
||||
instance = damage_typeInstance(homog)
|
||||
|
||||
|
||||
|
|
|
@ -22,7 +22,7 @@ subroutine damage_none_init()
|
|||
damage_initialPhi, &
|
||||
damage, &
|
||||
damage_type, &
|
||||
material_homog, &
|
||||
material_homogenizationAt, &
|
||||
damageState, &
|
||||
DAMAGE_NONE_LABEL, &
|
||||
DAMAGE_NONE_ID
|
||||
|
@ -37,7 +37,7 @@ subroutine damage_none_init()
|
|||
initializeInstances: do homog = 1, size(config_homogenization)
|
||||
|
||||
myhomog: if (damage_type(homog) == DAMAGE_NONE_ID) then
|
||||
NofMyHomog = count(material_homog == homog)
|
||||
NofMyHomog = count(material_homogenizationAt == homog)
|
||||
damageState(homog)%sizeState = 0
|
||||
damageState(homog)%sizePostResults = 0
|
||||
allocate(damageState(homog)%state0 (0,NofMyHomog))
|
||||
|
|
|
@ -53,7 +53,7 @@ subroutine damage_nonlocal_init
|
|||
homogenization_Noutput, &
|
||||
DAMAGE_nonlocal_label, &
|
||||
DAMAGE_nonlocal_ID, &
|
||||
material_homog, &
|
||||
material_homogenizationAt, &
|
||||
mappingHomogenization, &
|
||||
damageState, &
|
||||
damageMapping, &
|
||||
|
@ -109,7 +109,7 @@ subroutine damage_nonlocal_init
|
|||
|
||||
homog = h
|
||||
|
||||
NofMyHomog = count(material_homog == homog)
|
||||
NofMyHomog = count(material_homogenizationAt == homog)
|
||||
instance = damage_typeInstance(homog)
|
||||
|
||||
|
||||
|
@ -274,7 +274,7 @@ end function damage_nonlocal_getMobility
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine damage_nonlocal_putNonLocalDamage(phi,ip,el)
|
||||
use material, only: &
|
||||
material_homog, &
|
||||
material_homogenizationAt, &
|
||||
damageMapping, &
|
||||
damage
|
||||
|
||||
|
@ -288,7 +288,7 @@ subroutine damage_nonlocal_putNonLocalDamage(phi,ip,el)
|
|||
homog, &
|
||||
offset
|
||||
|
||||
homog = material_homog(ip,el)
|
||||
homog = material_homogenizationAt(el)
|
||||
offset = damageMapping(homog)%p(ip,el)
|
||||
damage(homog)%p(offset) = phi
|
||||
|
||||
|
|
|
@ -118,7 +118,7 @@ subroutine homogenization_init
|
|||
mainProcess2: if (worldrank == 0) then
|
||||
call IO_write_jobFile(FILEUNIT,'outputHomogenization')
|
||||
do p = 1,size(config_homogenization)
|
||||
if (any(material_homog == p)) then
|
||||
if (any(material_homogenizationAt == p)) then
|
||||
i = homogenization_typeInstance(p) ! which instance of this homogenization type
|
||||
valid = .true. ! assume valid
|
||||
select case(homogenization_type(p)) ! split per homogenization type
|
||||
|
|
|
@ -107,11 +107,10 @@ subroutine homogenization_RGC_init()
|
|||
IO_error
|
||||
use material, only: &
|
||||
#ifdef DEBUG
|
||||
material_homogenizationAt, &
|
||||
mappingHomogenization, &
|
||||
#endif
|
||||
homogenization_type, &
|
||||
material_homog, &
|
||||
material_homogenizationAt, &
|
||||
homogState, &
|
||||
HOMOGENIZATION_RGC_ID, &
|
||||
HOMOGENIZATION_RGC_LABEL, &
|
||||
|
@ -217,7 +216,7 @@ subroutine homogenization_RGC_init()
|
|||
|
||||
enddo
|
||||
|
||||
NofMyHomog = count(material_homog == h)
|
||||
NofMyHomog = count(material_homogenizationAt == h)
|
||||
nIntFaceTot = 3_pInt*( (prm%Nconstituents(1)-1_pInt)*prm%Nconstituents(2)*prm%Nconstituents(3) &
|
||||
+ prm%Nconstituents(1)*(prm%Nconstituents(2)-1_pInt)*prm%Nconstituents(3) &
|
||||
+ prm%Nconstituents(1)*prm%Nconstituents(2)*(prm%Nconstituents(3)-1_pInt))
|
||||
|
|
|
@ -44,7 +44,7 @@ subroutine homogenization_isostrain_init()
|
|||
IO_error
|
||||
use material, only: &
|
||||
homogenization_type, &
|
||||
material_homog, &
|
||||
material_homogenizationAt, &
|
||||
homogState, &
|
||||
HOMOGENIZATION_ISOSTRAIN_ID, &
|
||||
HOMOGENIZATION_ISOSTRAIN_LABEL, &
|
||||
|
@ -85,7 +85,7 @@ subroutine homogenization_isostrain_init()
|
|||
call IO_error(211_pInt,ext_msg=trim(tag)//' ('//HOMOGENIZATION_isostrain_label//')')
|
||||
end select
|
||||
|
||||
NofMyHomog = count(material_homog == h)
|
||||
NofMyHomog = count(material_homogenizationAt == h)
|
||||
homogState(h)%sizeState = 0_pInt
|
||||
homogState(h)%sizePostResults = 0_pInt
|
||||
allocate(homogState(h)%state0 (0_pInt,NofMyHomog))
|
||||
|
|
|
@ -26,7 +26,7 @@ subroutine homogenization_none_init()
|
|||
config_homogenization
|
||||
use material, only: &
|
||||
homogenization_type, &
|
||||
material_homog, &
|
||||
material_homogenizationAt, &
|
||||
homogState, &
|
||||
HOMOGENIZATION_NONE_LABEL, &
|
||||
HOMOGENIZATION_NONE_ID
|
||||
|
@ -46,7 +46,7 @@ subroutine homogenization_none_init()
|
|||
do h = 1, size(homogenization_type)
|
||||
if (homogenization_type(h) /= HOMOGENIZATION_NONE_ID) cycle
|
||||
|
||||
NofMyHomog = count(material_homog == h)
|
||||
NofMyHomog = count(material_homogenizationAt == h)
|
||||
homogState(h)%sizeState = 0
|
||||
homogState(h)%sizePostResults = 0
|
||||
allocate(homogState(h)%state0 (0,NofMyHomog))
|
||||
|
|
|
@ -54,11 +54,6 @@ contains
|
|||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine kinematics_cleavage_opening_init()
|
||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||
use, intrinsic :: iso_fortran_env, only: &
|
||||
compiler_version, &
|
||||
compiler_options
|
||||
#endif
|
||||
use debug, only: &
|
||||
debug_level,&
|
||||
debug_constitutive,&
|
||||
|
@ -66,9 +61,7 @@ subroutine kinematics_cleavage_opening_init()
|
|||
use config, only: &
|
||||
config_phase
|
||||
use IO, only: &
|
||||
IO_warning, &
|
||||
IO_error, &
|
||||
IO_timeStamp
|
||||
IO_error
|
||||
use material, only: &
|
||||
phase_kinematics, &
|
||||
KINEMATICS_cleavage_opening_label, &
|
||||
|
@ -84,8 +77,6 @@ subroutine kinematics_cleavage_opening_init()
|
|||
integer(pInt) :: maxNinstance,p,instance,kinematics
|
||||
|
||||
write(6,'(/,a)') ' <<<+- kinematics_'//KINEMATICS_cleavage_opening_LABEL//' init -+>>>'
|
||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||
#include "compilation_info.f90"
|
||||
|
||||
maxNinstance = int(count(phase_kinematics == KINEMATICS_cleavage_opening_ID),pInt)
|
||||
if (maxNinstance == 0_pInt) return
|
||||
|
@ -145,7 +136,7 @@ subroutine kinematics_cleavage_opening_LiAndItsTangent(Ld, dLd_dTstar, S, ipc, i
|
|||
math_mul33xx33
|
||||
use material, only: &
|
||||
material_phase, &
|
||||
material_homog, &
|
||||
material_homogenizationAt, &
|
||||
damage, &
|
||||
damageMapping
|
||||
use lattice, only: &
|
||||
|
@ -174,7 +165,7 @@ subroutine kinematics_cleavage_opening_LiAndItsTangent(Ld, dLd_dTstar, S, ipc, i
|
|||
|
||||
phase = material_phase(ipc,ip,el)
|
||||
instance = kinematics_cleavage_opening_instance(phase)
|
||||
homog = material_homog(ip,el)
|
||||
homog = material_homogenizationAt(el)
|
||||
damageOffset = damageMapping(homog)%p(ip,el)
|
||||
|
||||
Ld = 0.0_pReal
|
||||
|
|
|
@ -121,7 +121,7 @@ subroutine kinematics_slipplane_opening_LiAndItsTangent(Ld, dLd_dTstar, S, ipc,
|
|||
math_outer
|
||||
use material, only: &
|
||||
material_phase, &
|
||||
material_homog, &
|
||||
material_homogenizationAt, &
|
||||
damage, &
|
||||
damageMapping
|
||||
|
||||
|
@ -148,7 +148,7 @@ subroutine kinematics_slipplane_opening_LiAndItsTangent(Ld, dLd_dTstar, S, ipc,
|
|||
|
||||
phase = material_phase(ipc,ip,el)
|
||||
instance = kinematics_slipplane_opening_instance(phase)
|
||||
homog = material_homog(ip,el)
|
||||
homog = material_homogenizationAt(el)
|
||||
damageOffset = damageMapping(homog)%p(ip,el)
|
||||
|
||||
associate(prm => param(instance))
|
||||
|
|
|
@ -112,7 +112,7 @@ end function kinematics_thermal_expansion_initialStrain
|
|||
subroutine kinematics_thermal_expansion_LiAndItsTangent(Li, dLi_dTstar, ipc, ip, el)
|
||||
use material, only: &
|
||||
material_phase, &
|
||||
material_homog, &
|
||||
material_homogenizationAt, &
|
||||
temperature, &
|
||||
temperatureRate, &
|
||||
thermalMapping
|
||||
|
@ -136,7 +136,7 @@ subroutine kinematics_thermal_expansion_LiAndItsTangent(Li, dLi_dTstar, ipc, ip,
|
|||
T, TRef, TDot
|
||||
|
||||
phase = material_phase(ipc,ip,el)
|
||||
homog = material_homog(ip,el)
|
||||
homog = material_homogenizationAt(el)
|
||||
offset = thermalMapping(homog)%p(ip,el)
|
||||
T = temperature(homog)%p(offset)
|
||||
TDot = temperatureRate(homog)%p(offset)
|
||||
|
|
|
@ -162,10 +162,6 @@ module material
|
|||
! DEPRECATED: use material_phaseAt
|
||||
integer(pInt), dimension(:,:,:), allocatable, public :: &
|
||||
material_phase !< phase (index) of each grain,IP,element
|
||||
! DEPRECATED: use material_homogenizationAt
|
||||
integer(pInt), dimension(:,:), allocatable, public :: &
|
||||
material_homog !< homogenization (index) of each IP,element
|
||||
! END DEPRECATED
|
||||
|
||||
type(tPlasticState), allocatable, dimension(:), public :: &
|
||||
plasticState
|
||||
|
@ -1050,18 +1046,12 @@ subroutine material_populateGrains
|
|||
|
||||
allocate(material_volume(homogenization_maxNgrains,theMesh%elem%nIPs,theMesh%Nelems), source=0.0_pReal)
|
||||
allocate(material_phase(homogenization_maxNgrains,theMesh%elem%nIPs,theMesh%Nelems), source=0_pInt)
|
||||
allocate(material_homog(theMesh%elem%nIPs,theMesh%Nelems), source=0_pInt)
|
||||
allocate(material_texture(homogenization_maxNgrains,theMesh%elem%nIPs,theMesh%Nelems), source=0_pInt)
|
||||
allocate(material_EulerAngles(3,homogenization_maxNgrains,theMesh%elem%nIPs,theMesh%Nelems),source=0.0_pReal)
|
||||
|
||||
allocate(Ngrains(size(config_homogenization),size(config_microstructure)), source=0_pInt)
|
||||
allocate(Nelems (size(config_homogenization),size(config_microstructure)), source=0_pInt)
|
||||
|
||||
! populating homogenization schemes in each
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
do e = 1_pInt, theMesh%Nelems
|
||||
material_homog(1_pInt:theMesh%elem%nIPs,e) = theMesh%homogenizationAt(e)
|
||||
enddo
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! precounting of elements for each homog/micro pair
|
||||
|
|
|
@ -205,7 +205,7 @@ subroutine source_damage_anisoBrittle_dotState(S, ipc, ip, el)
|
|||
use material, only: &
|
||||
phaseAt, phasememberAt, &
|
||||
sourceState, &
|
||||
material_homog, &
|
||||
material_homogenizationAt, &
|
||||
damage, &
|
||||
damageMapping
|
||||
use lattice, only: &
|
||||
|
@ -235,7 +235,7 @@ subroutine source_damage_anisoBrittle_dotState(S, ipc, ip, el)
|
|||
constituent = phasememberAt(ipc,ip,el)
|
||||
instance = source_damage_anisoBrittle_instance(phase)
|
||||
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
||||
homog = material_homog(ip,el)
|
||||
homog = material_homogenizationAt(el)
|
||||
damageOffset = damageMapping(homog)%p(ip,el)
|
||||
|
||||
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) = 0.0_pReal
|
||||
|
|
|
@ -190,7 +190,7 @@ subroutine source_damage_anisoDuctile_dotState(ipc, ip, el)
|
|||
phaseAt, phasememberAt, &
|
||||
plasticState, &
|
||||
sourceState, &
|
||||
material_homog, &
|
||||
material_homogenizationAt, &
|
||||
damage, &
|
||||
damageMapping
|
||||
|
||||
|
@ -211,7 +211,7 @@ subroutine source_damage_anisoDuctile_dotState(ipc, ip, el)
|
|||
constituent = phasememberAt(ipc,ip,el)
|
||||
instance = source_damage_anisoDuctile_instance(phase)
|
||||
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
||||
homog = material_homog(ip,el)
|
||||
homog = material_homogenizationAt(el)
|
||||
damageOffset = damageMapping(homog)%p(ip,el)
|
||||
|
||||
|
||||
|
|
|
@ -173,7 +173,7 @@ subroutine source_damage_isoDuctile_dotState(ipc, ip, el)
|
|||
phaseAt, phasememberAt, &
|
||||
plasticState, &
|
||||
sourceState, &
|
||||
material_homog, &
|
||||
material_homogenizationAt, &
|
||||
damage, &
|
||||
damageMapping
|
||||
|
||||
|
@ -189,7 +189,7 @@ subroutine source_damage_isoDuctile_dotState(ipc, ip, el)
|
|||
constituent = phasememberAt(ipc,ip,el)
|
||||
instance = source_damage_isoDuctile_instance(phase)
|
||||
sourceOffset = source_damage_isoDuctile_offset(phase)
|
||||
homog = material_homog(ip,el)
|
||||
homog = material_homogenizationAt(el)
|
||||
damageOffset = damageMapping(homog)%p(ip,el)
|
||||
|
||||
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) = &
|
||||
|
|
|
@ -49,7 +49,7 @@ subroutine thermal_adiabatic_init
|
|||
homogenization_Noutput, &
|
||||
THERMAL_ADIABATIC_label, &
|
||||
THERMAL_adiabatic_ID, &
|
||||
material_homog, &
|
||||
material_homogenizationAt, &
|
||||
mappingHomogenization, &
|
||||
thermalState, &
|
||||
thermalMapping, &
|
||||
|
@ -80,7 +80,7 @@ subroutine thermal_adiabatic_init
|
|||
|
||||
initializeInstances: do section = 1_pInt, size(thermal_type)
|
||||
if (thermal_type(section) /= THERMAL_adiabatic_ID) cycle
|
||||
NofMyHomog=count(material_homog==section)
|
||||
NofMyHomog=count(material_homogenizationAt==section)
|
||||
instance = thermal_typeInstance(section)
|
||||
outputs = config_homogenization(section)%getStrings('(output)',defaultVal=emptyStringArray)
|
||||
do i=1_pInt, size(outputs)
|
||||
|
@ -120,6 +120,7 @@ function thermal_adiabatic_updateState(subdt, ip, el)
|
|||
err_thermal_tolAbs, &
|
||||
err_thermal_tolRel
|
||||
use material, only: &
|
||||
material_homogenizationAt, &
|
||||
mappingHomogenization, &
|
||||
thermalState, &
|
||||
temperature, &
|
||||
|
@ -140,7 +141,7 @@ function thermal_adiabatic_updateState(subdt, ip, el)
|
|||
real(pReal) :: &
|
||||
T, Tdot, dTdot_dT
|
||||
|
||||
homog = mappingHomogenization(2,ip,el)
|
||||
homog = material_homogenizationAt(el)
|
||||
offset = mappingHomogenization(1,ip,el)
|
||||
|
||||
T = thermalState(homog)%subState0(1,offset)
|
||||
|
|
|
@ -50,7 +50,7 @@ subroutine thermal_conduction_init
|
|||
homogenization_Noutput, &
|
||||
THERMAL_conduction_label, &
|
||||
THERMAL_conduction_ID, &
|
||||
material_homog, &
|
||||
material_homogenizationAt, &
|
||||
mappingHomogenization, &
|
||||
thermalState, &
|
||||
thermalMapping, &
|
||||
|
@ -81,7 +81,7 @@ subroutine thermal_conduction_init
|
|||
|
||||
initializeInstances: do section = 1_pInt, size(thermal_type)
|
||||
if (thermal_type(section) /= THERMAL_conduction_ID) cycle
|
||||
NofMyHomog=count(material_homog==section)
|
||||
NofMyHomog=count(material_homogenizationAt==section)
|
||||
instance = thermal_typeInstance(section)
|
||||
outputs = config_homogenization(section)%getStrings('(output)',defaultVal=emptyStringArray)
|
||||
do i=1_pInt, size(outputs)
|
||||
|
|
|
@ -16,38 +16,28 @@ contains
|
|||
!> @brief allocates all neccessary fields, reads information from material configuration file
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine thermal_isothermal_init()
|
||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||
use, intrinsic :: iso_fortran_env, only: &
|
||||
compiler_version, &
|
||||
compiler_options
|
||||
#endif
|
||||
use prec, only: &
|
||||
pReal, &
|
||||
pInt
|
||||
use IO, only: &
|
||||
IO_timeStamp
|
||||
pReal
|
||||
use config, only: &
|
||||
material_Nhomogenization
|
||||
use material
|
||||
|
||||
implicit none
|
||||
integer(pInt) :: &
|
||||
integer :: &
|
||||
homog, &
|
||||
NofMyHomog
|
||||
|
||||
write(6,'(/,a)') ' <<<+- thermal_'//THERMAL_isothermal_label//' init -+>>>'
|
||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||
#include "compilation_info.f90"
|
||||
|
||||
initializeInstances: do homog = 1_pInt, material_Nhomogenization
|
||||
initializeInstances: do homog = 1, material_Nhomogenization
|
||||
|
||||
if (thermal_type(homog) /= THERMAL_isothermal_ID) cycle
|
||||
NofMyHomog = count(material_homog == homog)
|
||||
thermalState(homog)%sizeState = 0_pInt
|
||||
thermalState(homog)%sizePostResults = 0_pInt
|
||||
allocate(thermalState(homog)%state0 (0_pInt,NofMyHomog), source=0.0_pReal)
|
||||
allocate(thermalState(homog)%subState0(0_pInt,NofMyHomog), source=0.0_pReal)
|
||||
allocate(thermalState(homog)%state (0_pInt,NofMyHomog), source=0.0_pReal)
|
||||
NofMyHomog = count(material_homogenizationAt == homog)
|
||||
thermalState(homog)%sizeState = 0
|
||||
thermalState(homog)%sizePostResults = 0
|
||||
allocate(thermalState(homog)%state0 (0,NofMyHomog), source=0.0_pReal)
|
||||
allocate(thermalState(homog)%subState0(0,NofMyHomog), source=0.0_pReal)
|
||||
allocate(thermalState(homog)%state (0,NofMyHomog), source=0.0_pReal)
|
||||
|
||||
deallocate(temperature (homog)%p)
|
||||
allocate (temperature (homog)%p(1), source=thermal_initialT(homog))
|
||||
|
|
Loading…
Reference in New Issue