simplified and unified style
This commit is contained in:
parent
7e30c10e82
commit
73491f3be9
|
@ -21,14 +21,14 @@ module source_damage_anisoBrittle
|
||||||
integer, dimension(:), allocatable :: &
|
integer, dimension(:), allocatable :: &
|
||||||
source_damage_anisoBrittle_offset, & !< which source is my current source mechanism?
|
source_damage_anisoBrittle_offset, & !< which source is my current source mechanism?
|
||||||
source_damage_anisoBrittle_instance !< instance of source mechanism
|
source_damage_anisoBrittle_instance !< instance of source mechanism
|
||||||
|
|
||||||
integer, dimension(:,:), allocatable :: &
|
integer, dimension(:,:), allocatable :: &
|
||||||
source_damage_anisoBrittle_Ncleavage !< number of cleavage systems per family
|
source_damage_anisoBrittle_Ncleavage !< number of cleavage systems per family
|
||||||
|
|
||||||
enum, bind(c)
|
enum, bind(c)
|
||||||
enumerator :: undefined_ID, &
|
enumerator :: undefined_ID, &
|
||||||
damage_drivingforce_ID
|
damage_drivingforce_ID
|
||||||
end enum
|
end enum
|
||||||
|
|
||||||
|
|
||||||
type :: tParameters !< container type for internal constitutive parameters
|
type :: tParameters !< container type for internal constitutive parameters
|
||||||
|
@ -67,68 +67,64 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_damage_anisoBrittle_init
|
subroutine source_damage_anisoBrittle_init
|
||||||
|
|
||||||
integer :: Ninstance,phase,instance,source,sourceOffset
|
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p,i
|
||||||
integer :: NofMyPhase,p ,i
|
|
||||||
integer(kind(undefined_ID)) :: &
|
integer(kind(undefined_ID)) :: &
|
||||||
outputID
|
outputID
|
||||||
|
|
||||||
character(len=pStringLen) :: &
|
character(len=pStringLen) :: &
|
||||||
extmsg = ''
|
extmsg = ''
|
||||||
character(len=pStringLen), dimension(:), allocatable :: &
|
character(len=pStringLen), dimension(:), allocatable :: &
|
||||||
outputs
|
outputs
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISOBRITTLE_LABEL//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISOBRITTLE_LABEL//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
Ninstance = count(phase_source == SOURCE_damage_anisoBrittle_ID)
|
Ninstance = count(phase_source == SOURCE_DAMAGE_ANISOBRITTLE_ID)
|
||||||
if (Ninstance == 0) return
|
|
||||||
|
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
||||||
|
|
||||||
allocate(source_damage_anisoBrittle_offset(material_Nphase), source=0)
|
allocate(source_damage_anisoBrittle_offset (size(config_phase)), source=0)
|
||||||
allocate(source_damage_anisoBrittle_instance(material_Nphase), source=0)
|
allocate(source_damage_anisoBrittle_instance(size(config_phase)), source=0)
|
||||||
do phase = 1, material_Nphase
|
allocate(param(Ninstance))
|
||||||
source_damage_anisoBrittle_instance(phase) = count(phase_source(:,1:phase) == source_damage_anisoBrittle_ID)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
if (phase_source(source,phase) == source_damage_anisoBrittle_ID) &
|
|
||||||
source_damage_anisoBrittle_offset(phase) = source
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(source_damage_anisoBrittle_Ncleavage(lattice_maxNcleavageFamily,Ninstance), source=0)
|
allocate(source_damage_anisoBrittle_Ncleavage(lattice_maxNcleavageFamily,Ninstance), source=0)
|
||||||
|
|
||||||
allocate(param(Ninstance))
|
do p = 1, size(config_phase)
|
||||||
|
source_damage_anisoBrittle_instance(p) = count(phase_source(:,1:p) == SOURCE_DAMAGE_ANISOBRITTLE_ID)
|
||||||
do p=1, size(config_phase)
|
do source = 1, phase_Nsources(p)
|
||||||
|
if (phase_source(source,p) == SOURCE_DAMAGE_ANISOBRITTLE_ID) &
|
||||||
|
source_damage_anisoBrittle_offset(p) = source
|
||||||
|
enddo
|
||||||
|
|
||||||
if (all(phase_source(:,p) /= SOURCE_DAMAGE_ANISOBRITTLE_ID)) cycle
|
if (all(phase_source(:,p) /= SOURCE_DAMAGE_ANISOBRITTLE_ID)) cycle
|
||||||
|
|
||||||
associate(prm => param(source_damage_anisoBrittle_instance(p)), &
|
associate(prm => param(source_damage_anisoBrittle_instance(p)), &
|
||||||
config => config_phase(p))
|
config => config_phase(p))
|
||||||
|
|
||||||
prm%aTol = config%getFloat('anisobrittle_atol',defaultVal = 1.0e-3_pReal)
|
prm%aTol = config%getFloat('anisobrittle_atol',defaultVal = 1.0e-3_pReal)
|
||||||
|
|
||||||
prm%N = config%getFloat('anisobrittle_ratesensitivity')
|
prm%N = config%getFloat('anisobrittle_ratesensitivity')
|
||||||
prm%sdot_0 = config%getFloat('anisobrittle_sdot0')
|
prm%sdot_0 = config%getFloat('anisobrittle_sdot0')
|
||||||
|
|
||||||
! sanity checks
|
! sanity checks
|
||||||
if (prm%aTol < 0.0_pReal) extmsg = trim(extmsg)//' anisobrittle_atol'
|
if (prm%aTol < 0.0_pReal) extmsg = trim(extmsg)//' anisobrittle_atol'
|
||||||
|
|
||||||
if (prm%N <= 0.0_pReal) extmsg = trim(extmsg)//' anisobrittle_ratesensitivity'
|
if (prm%N <= 0.0_pReal) extmsg = trim(extmsg)//' anisobrittle_ratesensitivity'
|
||||||
if (prm%sdot_0 <= 0.0_pReal) extmsg = trim(extmsg)//' anisobrittle_sdot0'
|
if (prm%sdot_0 <= 0.0_pReal) extmsg = trim(extmsg)//' anisobrittle_sdot0'
|
||||||
|
|
||||||
prm%Ncleavage = config%getInts('ncleavage',defaultVal=emptyIntArray)
|
prm%Ncleavage = config%getInts('ncleavage',defaultVal=emptyIntArray)
|
||||||
|
|
||||||
prm%critDisp = config%getFloats('anisobrittle_criticaldisplacement',requiredSize=size(prm%Ncleavage))
|
prm%critDisp = config%getFloats('anisobrittle_criticaldisplacement',requiredSize=size(prm%Ncleavage))
|
||||||
prm%critLoad = config%getFloats('anisobrittle_criticalload', requiredSize=size(prm%Ncleavage))
|
prm%critLoad = config%getFloats('anisobrittle_criticalload', requiredSize=size(prm%Ncleavage))
|
||||||
|
|
||||||
prm%cleavage_systems = lattice_SchmidMatrix_cleavage (prm%Ncleavage,config%getString('lattice_structure'),&
|
prm%cleavage_systems = lattice_SchmidMatrix_cleavage (prm%Ncleavage,config%getString('lattice_structure'),&
|
||||||
config%getFloat('c/a',defaultVal=0.0_pReal))
|
config%getFloat('c/a',defaultVal=0.0_pReal))
|
||||||
|
|
||||||
! expand: family => system
|
! expand: family => system
|
||||||
prm%critDisp = math_expand(prm%critDisp, prm%Ncleavage)
|
prm%critDisp = math_expand(prm%critDisp, prm%Ncleavage)
|
||||||
prm%critLoad = math_expand(prm%critLoad, prm%Ncleavage)
|
prm%critLoad = math_expand(prm%critLoad, prm%Ncleavage)
|
||||||
|
|
||||||
if (any(prm%critLoad < 0.0_pReal)) extmsg = trim(extmsg)//' anisobrittle_criticalload'
|
if (any(prm%critLoad < 0.0_pReal)) extmsg = trim(extmsg)//' anisobrittle_criticalload'
|
||||||
if (any(prm%critDisp < 0.0_pReal)) extmsg = trim(extmsg)//' anisobrittle_criticaldisplacement'
|
if (any(prm%critDisp < 0.0_pReal)) extmsg = trim(extmsg)//' anisobrittle_criticaldisplacement'
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! exit if any parameter is out of range
|
! exit if any parameter is out of range
|
||||||
if (extmsg /= '') &
|
if (extmsg /= '') &
|
||||||
|
@ -141,7 +137,7 @@ subroutine source_damage_anisoBrittle_init
|
||||||
do i=1, size(outputs)
|
do i=1, size(outputs)
|
||||||
outputID = undefined_ID
|
outputID = undefined_ID
|
||||||
select case(outputs(i))
|
select case(outputs(i))
|
||||||
|
|
||||||
case ('anisobrittle_drivingforce')
|
case ('anisobrittle_drivingforce')
|
||||||
prm%outputID = [prm%outputID, damage_drivingforce_ID]
|
prm%outputID = [prm%outputID, damage_drivingforce_ID]
|
||||||
|
|
||||||
|
@ -150,16 +146,13 @@ subroutine source_damage_anisoBrittle_init
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
phase = p
|
|
||||||
NofMyPhase=count(material_phaseAt==phase) * discretization_nIP
|
|
||||||
instance = source_damage_anisoBrittle_instance(phase)
|
|
||||||
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
|
||||||
|
|
||||||
|
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
|
||||||
|
instance = source_damage_anisoBrittle_instance(p)
|
||||||
|
sourceOffset = source_damage_anisoBrittle_offset(p)
|
||||||
|
|
||||||
call material_allocateSourceState(phase,sourceOffset,NofMyPhase,1,1,0)
|
call material_allocateSourceState(p,sourceOffset,NofMyPhase,1,1,0)
|
||||||
sourceState(phase)%p(sourceOffset)%aTolState=param(instance)%aTol
|
sourceState(p)%p(sourceOffset)%aTolState=param(instance)%aTol
|
||||||
|
|
||||||
|
|
||||||
source_damage_anisoBrittle_Ncleavage(1:size(param(instance)%Ncleavage),instance) = param(instance)%Ncleavage
|
source_damage_anisoBrittle_Ncleavage(1:size(param(instance)%Ncleavage),instance) = param(instance)%Ncleavage
|
||||||
enddo
|
enddo
|
||||||
|
@ -195,9 +188,9 @@ subroutine source_damage_anisoBrittle_dotState(S, ipc, ip, el)
|
||||||
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
||||||
homog = material_homogenizationAt(el)
|
homog = material_homogenizationAt(el)
|
||||||
damageOffset = damageMapping(homog)%p(ip,el)
|
damageOffset = damageMapping(homog)%p(ip,el)
|
||||||
|
|
||||||
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) = 0.0_pReal
|
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) = 0.0_pReal
|
||||||
|
|
||||||
index = 1
|
index = 1
|
||||||
do f = 1,lattice_maxNcleavageFamily
|
do f = 1,lattice_maxNcleavageFamily
|
||||||
index_myFamily = sum(lattice_NcleavageSystem(1:f-1,phase)) ! at which index starts my family
|
index_myFamily = sum(lattice_NcleavageSystem(1:f-1,phase)) ! at which index starts my family
|
||||||
|
@ -206,7 +199,7 @@ subroutine source_damage_anisoBrittle_dotState(S, ipc, ip, el)
|
||||||
traction_d = math_mul33xx33(S,lattice_Scleavage(1:3,1:3,1,index_myFamily+i,phase))
|
traction_d = math_mul33xx33(S,lattice_Scleavage(1:3,1:3,1,index_myFamily+i,phase))
|
||||||
traction_t = math_mul33xx33(S,lattice_Scleavage(1:3,1:3,2,index_myFamily+i,phase))
|
traction_t = math_mul33xx33(S,lattice_Scleavage(1:3,1:3,2,index_myFamily+i,phase))
|
||||||
traction_n = math_mul33xx33(S,lattice_Scleavage(1:3,1:3,3,index_myFamily+i,phase))
|
traction_n = math_mul33xx33(S,lattice_Scleavage(1:3,1:3,3,index_myFamily+i,phase))
|
||||||
|
|
||||||
traction_crit = param(instance)%critLoad(index)* &
|
traction_crit = param(instance)%critLoad(index)* &
|
||||||
damage(homog)%p(damageOffset)*damage(homog)%p(damageOffset)
|
damage(homog)%p(damageOffset)*damage(homog)%p(damageOffset)
|
||||||
|
|
||||||
|
@ -242,12 +235,12 @@ subroutine source_damage_anisobrittle_getRateAndItsTangent(localphiDot, dLocalph
|
||||||
sourceOffset
|
sourceOffset
|
||||||
|
|
||||||
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
||||||
|
|
||||||
localphiDot = 1.0_pReal &
|
localphiDot = 1.0_pReal &
|
||||||
- sourceState(phase)%p(sourceOffset)%state(1,constituent)*phi
|
- sourceState(phase)%p(sourceOffset)%state(1,constituent)*phi
|
||||||
|
|
||||||
dLocalphiDot_dPhi = -sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
dLocalphiDot_dPhi = -sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
||||||
|
|
||||||
end subroutine source_damage_anisoBrittle_getRateAndItsTangent
|
end subroutine source_damage_anisoBrittle_getRateAndItsTangent
|
||||||
|
|
||||||
|
|
||||||
|
@ -257,9 +250,9 @@ end subroutine source_damage_anisoBrittle_getRateAndItsTangent
|
||||||
subroutine source_damage_anisoBrittle_results(phase,group)
|
subroutine source_damage_anisoBrittle_results(phase,group)
|
||||||
|
|
||||||
integer, intent(in) :: phase
|
integer, intent(in) :: phase
|
||||||
character(len=*), intent(in) :: group
|
character(len=*), intent(in) :: group
|
||||||
integer :: sourceOffset, o, instance
|
integer :: sourceOffset, o, instance
|
||||||
|
|
||||||
instance = source_damage_anisoBrittle_instance(phase)
|
instance = source_damage_anisoBrittle_instance(phase)
|
||||||
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
||||||
|
|
||||||
|
|
|
@ -13,20 +13,20 @@ module source_damage_anisoDuctile
|
||||||
use material
|
use material
|
||||||
use config
|
use config
|
||||||
use results
|
use results
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
|
||||||
integer, dimension(:), allocatable :: &
|
integer, dimension(:), allocatable :: &
|
||||||
source_damage_anisoDuctile_offset, & !< which source is my current damage mechanism?
|
source_damage_anisoDuctile_offset, & !< which source is my current damage mechanism?
|
||||||
source_damage_anisoDuctile_instance !< instance of damage source mechanism
|
source_damage_anisoDuctile_instance !< instance of damage source mechanism
|
||||||
|
|
||||||
enum, bind(c)
|
enum, bind(c)
|
||||||
enumerator :: undefined_ID, &
|
enumerator :: undefined_ID, &
|
||||||
damage_drivingforce_ID
|
damage_drivingforce_ID
|
||||||
end enum
|
end enum
|
||||||
|
|
||||||
|
|
||||||
type, private :: tParameters !< container type for internal constitutive parameters
|
type, private :: tParameters !< container type for internal constitutive parameters
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
aTol, &
|
aTol, &
|
||||||
|
@ -40,10 +40,10 @@ module source_damage_anisoDuctile
|
||||||
integer(kind(undefined_ID)), allocatable, dimension(:) :: &
|
integer(kind(undefined_ID)), allocatable, dimension(:) :: &
|
||||||
outputID
|
outputID
|
||||||
end type tParameters
|
end type tParameters
|
||||||
|
|
||||||
type(tParameters), dimension(:), allocatable, private :: param !< containers of constitutive parameters (len Ninstance)
|
type(tParameters), dimension(:), allocatable, private :: param !< containers of constitutive parameters (len Ninstance)
|
||||||
|
|
||||||
|
|
||||||
public :: &
|
public :: &
|
||||||
source_damage_anisoDuctile_init, &
|
source_damage_anisoDuctile_init, &
|
||||||
source_damage_anisoDuctile_dotState, &
|
source_damage_anisoDuctile_dotState, &
|
||||||
|
@ -58,61 +58,54 @@ contains
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_damage_anisoDuctile_init
|
subroutine source_damage_anisoDuctile_init
|
||||||
|
|
||||||
integer :: Ninstance,phase,instance,source,sourceOffset
|
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p,i
|
||||||
integer :: NofMyPhase,p ,i
|
|
||||||
|
|
||||||
integer(kind(undefined_ID)) :: &
|
integer(kind(undefined_ID)) :: &
|
||||||
outputID
|
outputID
|
||||||
|
|
||||||
character(len=pStringLen) :: &
|
character(len=pStringLen) :: &
|
||||||
extmsg = ''
|
extmsg = ''
|
||||||
character(len=pStringLen), dimension(:), allocatable :: &
|
character(len=pStringLen), dimension(:), allocatable :: &
|
||||||
outputs
|
outputs
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISODUCTILE_LABEL//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISODUCTILE_LABEL//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
Ninstance = count(phase_source == SOURCE_damage_anisoDuctile_ID)
|
Ninstance = count(phase_source == SOURCE_DAMAGE_ANISODUCTILE_ID)
|
||||||
if (Ninstance == 0) return
|
|
||||||
|
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
||||||
|
|
||||||
allocate(source_damage_anisoDuctile_offset(size(config_phase)), source=0)
|
allocate(source_damage_anisoDuctile_offset (size(config_phase)), source=0)
|
||||||
allocate(source_damage_anisoDuctile_instance(size(config_phase)), source=0)
|
allocate(source_damage_anisoDuctile_instance(size(config_phase)), source=0)
|
||||||
do phase = 1, size(config_phase)
|
|
||||||
source_damage_anisoDuctile_instance(phase) = count(phase_source(:,1:phase) == source_damage_anisoDuctile_ID)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
if (phase_source(source,phase) == source_damage_anisoDuctile_ID) &
|
|
||||||
source_damage_anisoDuctile_offset(phase) = source
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(param(Ninstance))
|
allocate(param(Ninstance))
|
||||||
|
|
||||||
do p=1, size(config_phase)
|
do p = 1, size(config_phase)
|
||||||
|
source_damage_anisoDuctile_instance(p) = count(phase_source(:,1:p) == SOURCE_DAMAGE_ANISODUCTILE_ID)
|
||||||
|
do source = 1, phase_Nsources(p)
|
||||||
|
if (phase_source(source,p) == SOURCE_DAMAGE_ANISODUCTILE_ID) &
|
||||||
|
source_damage_anisoDuctile_offset(p) = source
|
||||||
|
enddo
|
||||||
|
|
||||||
if (all(phase_source(:,p) /= SOURCE_DAMAGE_ANISODUCTILE_ID)) cycle
|
if (all(phase_source(:,p) /= SOURCE_DAMAGE_ANISODUCTILE_ID)) cycle
|
||||||
|
|
||||||
associate(prm => param(source_damage_anisoDuctile_instance(p)), &
|
associate(prm => param(source_damage_anisoDuctile_instance(p)), &
|
||||||
config => config_phase(p))
|
config => config_phase(p))
|
||||||
|
|
||||||
prm%aTol = config%getFloat('anisoductile_atol',defaultVal = 1.0e-3_pReal)
|
prm%aTol = config%getFloat('anisoductile_atol',defaultVal = 1.0e-3_pReal)
|
||||||
|
|
||||||
prm%N = config%getFloat('anisoductile_ratesensitivity')
|
prm%N = config%getFloat('anisoductile_ratesensitivity')
|
||||||
prm%totalNslip = sum(prm%Nslip)
|
prm%totalNslip = sum(prm%Nslip)
|
||||||
! sanity checks
|
! sanity checks
|
||||||
if (prm%aTol < 0.0_pReal) extmsg = trim(extmsg)//' anisoductile_atol'
|
if (prm%aTol < 0.0_pReal) extmsg = trim(extmsg)//' anisoductile_atol'
|
||||||
|
|
||||||
if (prm%N <= 0.0_pReal) extmsg = trim(extmsg)//' anisoductile_ratesensitivity'
|
if (prm%N <= 0.0_pReal) extmsg = trim(extmsg)//' anisoductile_ratesensitivity'
|
||||||
|
|
||||||
prm%Nslip = config%getInts('nslip',defaultVal=emptyIntArray)
|
prm%Nslip = config%getInts('nslip',defaultVal=emptyIntArray)
|
||||||
|
|
||||||
prm%critPlasticStrain = config%getFloats('anisoductile_criticalplasticstrain',requiredSize=size(prm%Nslip))
|
prm%critPlasticStrain = config%getFloats('anisoductile_criticalplasticstrain',requiredSize=size(prm%Nslip))
|
||||||
|
|
||||||
! expand: family => system
|
! expand: family => system
|
||||||
prm%critPlasticStrain = math_expand(prm%critPlasticStrain, prm%Nslip)
|
prm%critPlasticStrain = math_expand(prm%critPlasticStrain, prm%Nslip)
|
||||||
|
|
||||||
if (any(prm%critPlasticStrain < 0.0_pReal)) extmsg = trim(extmsg)//' anisoductile_criticalplasticstrain'
|
if (any(prm%critPlasticStrain < 0.0_pReal)) extmsg = trim(extmsg)//' anisoductile_criticalplasticstrain'
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! exit if any parameter is out of range
|
! exit if any parameter is out of range
|
||||||
if (extmsg /= '') call IO_error(211,ext_msg=trim(extmsg)//'('//SOURCE_DAMAGE_ANISODUCTILE_LABEL//')')
|
if (extmsg /= '') call IO_error(211,ext_msg=trim(extmsg)//'('//SOURCE_DAMAGE_ANISODUCTILE_LABEL//')')
|
||||||
|
@ -124,27 +117,25 @@ subroutine source_damage_anisoDuctile_init
|
||||||
do i=1, size(outputs)
|
do i=1, size(outputs)
|
||||||
outputID = undefined_ID
|
outputID = undefined_ID
|
||||||
select case(outputs(i))
|
select case(outputs(i))
|
||||||
|
|
||||||
case ('anisoductile_drivingforce')
|
case ('anisoductile_drivingforce')
|
||||||
prm%outputID = [prm%outputID, damage_drivingforce_ID]
|
prm%outputID = [prm%outputID, damage_drivingforce_ID]
|
||||||
|
|
||||||
end select
|
end select
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
phase = p
|
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
|
||||||
|
instance = source_damage_anisoDuctile_instance(p)
|
||||||
NofMyPhase=count(material_phaseAt==phase) * discretization_nIP
|
sourceOffset = source_damage_anisoDuctile_offset(p)
|
||||||
instance = source_damage_anisoDuctile_instance(phase)
|
|
||||||
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
call material_allocateSourceState(p,sourceOffset,NofMyPhase,1,1,0)
|
||||||
|
sourceState(p)%p(sourceOffset)%aTolState=param(instance)%aTol
|
||||||
call material_allocateSourceState(phase,sourceOffset,NofMyPhase,1,1,0)
|
|
||||||
sourceState(phase)%p(sourceOffset)%aTolState=param(instance)%aTol
|
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end subroutine source_damage_anisoDuctile_init
|
end subroutine source_damage_anisoDuctile_init
|
||||||
|
|
||||||
|
|
||||||
|
@ -164,22 +155,22 @@ subroutine source_damage_anisoDuctile_dotState(ipc, ip, el)
|
||||||
homog, damageOffset, &
|
homog, damageOffset, &
|
||||||
instance, &
|
instance, &
|
||||||
i
|
i
|
||||||
|
|
||||||
phase = material_phaseAt(ipc,el)
|
phase = material_phaseAt(ipc,el)
|
||||||
constituent = material_phasememberAt(ipc,ip,el)
|
constituent = material_phasememberAt(ipc,ip,el)
|
||||||
instance = source_damage_anisoDuctile_instance(phase)
|
instance = source_damage_anisoDuctile_instance(phase)
|
||||||
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
||||||
homog = material_homogenizationAt(el)
|
homog = material_homogenizationAt(el)
|
||||||
damageOffset = damageMapping(homog)%p(ip,el)
|
damageOffset = damageMapping(homog)%p(ip,el)
|
||||||
|
|
||||||
|
|
||||||
do i = 1, param(instance)%totalNslip
|
do i = 1, param(instance)%totalNslip
|
||||||
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) = &
|
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) = &
|
||||||
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) + &
|
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) + &
|
||||||
plasticState(phase)%slipRate(i,constituent)/ &
|
plasticState(phase)%slipRate(i,constituent)/ &
|
||||||
((damage(homog)%p(damageOffset))**param(instance)%N)/param(instance)%critPlasticStrain(i)
|
((damage(homog)%p(damageOffset))**param(instance)%N)/param(instance)%critPlasticStrain(i)
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end subroutine source_damage_anisoDuctile_dotState
|
end subroutine source_damage_anisoDuctile_dotState
|
||||||
|
|
||||||
|
|
||||||
|
@ -198,14 +189,14 @@ subroutine source_damage_anisoDuctile_getRateAndItsTangent(localphiDot, dLocalph
|
||||||
dLocalphiDot_dPhi
|
dLocalphiDot_dPhi
|
||||||
integer :: &
|
integer :: &
|
||||||
sourceOffset
|
sourceOffset
|
||||||
|
|
||||||
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
||||||
|
|
||||||
localphiDot = 1.0_pReal &
|
localphiDot = 1.0_pReal &
|
||||||
- sourceState(phase)%p(sourceOffset)%state(1,constituent) * phi
|
- sourceState(phase)%p(sourceOffset)%state(1,constituent) * phi
|
||||||
|
|
||||||
dLocalphiDot_dPhi = -sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
dLocalphiDot_dPhi = -sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
||||||
|
|
||||||
end subroutine source_damage_anisoDuctile_getRateAndItsTangent
|
end subroutine source_damage_anisoDuctile_getRateAndItsTangent
|
||||||
|
|
||||||
|
|
||||||
|
@ -217,7 +208,7 @@ subroutine source_damage_anisoDuctile_results(phase,group)
|
||||||
integer, intent(in) :: phase
|
integer, intent(in) :: phase
|
||||||
character(len=*), intent(in) :: group
|
character(len=*), intent(in) :: group
|
||||||
integer :: sourceOffset, o, instance
|
integer :: sourceOffset, o, instance
|
||||||
|
|
||||||
instance = source_damage_anisoDuctile_instance(phase)
|
instance = source_damage_anisoDuctile_instance(phase)
|
||||||
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
||||||
|
|
||||||
|
|
|
@ -20,7 +20,7 @@ module source_damage_isoBrittle
|
||||||
source_damage_isoBrittle_offset, &
|
source_damage_isoBrittle_offset, &
|
||||||
source_damage_isoBrittle_instance
|
source_damage_isoBrittle_instance
|
||||||
|
|
||||||
enum, bind(c)
|
enum, bind(c)
|
||||||
enumerator :: &
|
enumerator :: &
|
||||||
undefined_ID, &
|
undefined_ID, &
|
||||||
damage_drivingforce_ID
|
damage_drivingforce_ID
|
||||||
|
@ -54,52 +54,47 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_damage_isoBrittle_init
|
subroutine source_damage_isoBrittle_init
|
||||||
|
|
||||||
integer :: Ninstance,phase,instance,source,sourceOffset
|
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p,i
|
||||||
integer :: NofMyPhase,p,i
|
|
||||||
integer(kind(undefined_ID)) :: &
|
integer(kind(undefined_ID)) :: &
|
||||||
outputID
|
outputID
|
||||||
|
|
||||||
character(len=pStringLen) :: &
|
character(len=pStringLen) :: &
|
||||||
extmsg = ''
|
extmsg = ''
|
||||||
character(len=pStringLen), dimension(:), allocatable :: &
|
character(len=pStringLen), dimension(:), allocatable :: &
|
||||||
outputs
|
outputs
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISOBRITTLE_LABEL//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISOBRITTLE_LABEL//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
Ninstance = count(phase_source == SOURCE_damage_isoBrittle_ID)
|
Ninstance = count(phase_source == SOURCE_DAMAGE_ISOBRITTLE_ID)
|
||||||
if (Ninstance == 0) return
|
|
||||||
|
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
||||||
|
|
||||||
allocate(source_damage_isoBrittle_offset(material_Nphase), source=0)
|
allocate(source_damage_isoBrittle_offset (size(config_phase)), source=0)
|
||||||
allocate(source_damage_isoBrittle_instance(material_Nphase), source=0)
|
allocate(source_damage_isoBrittle_instance(size(config_phase)), source=0)
|
||||||
do phase = 1, material_Nphase
|
|
||||||
source_damage_isoBrittle_instance(phase) = count(phase_source(:,1:phase) == source_damage_isoBrittle_ID)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
if (phase_source(source,phase) == source_damage_isoBrittle_ID) &
|
|
||||||
source_damage_isoBrittle_offset(phase) = source
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(param(Ninstance))
|
allocate(param(Ninstance))
|
||||||
|
|
||||||
do p=1, size(config_phase)
|
do p = 1, size(config_phase)
|
||||||
|
source_damage_isoBrittle_instance(p) = count(phase_source(:,1:p) == SOURCE_DAMAGE_ISOBRITTLE_ID)
|
||||||
|
do source = 1, phase_Nsources(p)
|
||||||
|
if (phase_source(source,p) == SOURCE_DAMAGE_ISOBRITTLE_ID) &
|
||||||
|
source_damage_isoBrittle_offset(p) = source
|
||||||
|
enddo
|
||||||
|
|
||||||
if (all(phase_source(:,p) /= SOURCE_DAMAGE_ISOBRITTLE_ID)) cycle
|
if (all(phase_source(:,p) /= SOURCE_DAMAGE_ISOBRITTLE_ID)) cycle
|
||||||
|
|
||||||
associate(prm => param(source_damage_isoBrittle_instance(p)), &
|
associate(prm => param(source_damage_isoBrittle_instance(p)), &
|
||||||
config => config_phase(p))
|
config => config_phase(p))
|
||||||
|
|
||||||
prm%aTol = config%getFloat('isobrittle_atol',defaultVal = 1.0e-3_pReal)
|
prm%aTol = config%getFloat('isobrittle_atol',defaultVal = 1.0e-3_pReal)
|
||||||
|
|
||||||
prm%N = config%getFloat('isobrittle_n')
|
prm%N = config%getFloat('isobrittle_n')
|
||||||
prm%critStrainEnergy = config%getFloat('isobrittle_criticalstrainenergy')
|
prm%critStrainEnergy = config%getFloat('isobrittle_criticalstrainenergy')
|
||||||
|
|
||||||
! sanity checks
|
! sanity checks
|
||||||
if (prm%aTol < 0.0_pReal) extmsg = trim(extmsg)//' isobrittle_atol'
|
if (prm%aTol < 0.0_pReal) extmsg = trim(extmsg)//' isobrittle_atol'
|
||||||
|
|
||||||
if (prm%N <= 0.0_pReal) extmsg = trim(extmsg)//' isobrittle_n'
|
if (prm%N <= 0.0_pReal) extmsg = trim(extmsg)//' isobrittle_n'
|
||||||
if (prm%critStrainEnergy <= 0.0_pReal) extmsg = trim(extmsg)//' isobrittle_criticalstrainenergy'
|
if (prm%critStrainEnergy <= 0.0_pReal) extmsg = trim(extmsg)//' isobrittle_criticalstrainenergy'
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! exit if any parameter is out of range
|
! exit if any parameter is out of range
|
||||||
if (extmsg /= '') &
|
if (extmsg /= '') &
|
||||||
|
@ -112,27 +107,25 @@ subroutine source_damage_isoBrittle_init
|
||||||
do i=1, size(outputs)
|
do i=1, size(outputs)
|
||||||
outputID = undefined_ID
|
outputID = undefined_ID
|
||||||
select case(outputs(i))
|
select case(outputs(i))
|
||||||
|
|
||||||
case ('isobrittle_drivingforce')
|
case ('isobrittle_drivingforce')
|
||||||
prm%outputID = [prm%outputID, damage_drivingforce_ID]
|
prm%outputID = [prm%outputID, damage_drivingforce_ID]
|
||||||
|
|
||||||
end select
|
end select
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
phase = p
|
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
|
||||||
|
instance = source_damage_isoBrittle_instance(p)
|
||||||
NofMyPhase = count(material_phaseAt==phase) * discretization_nIP
|
sourceOffset = source_damage_isoBrittle_offset(p)
|
||||||
instance = source_damage_isoBrittle_instance(phase)
|
|
||||||
sourceOffset = source_damage_isoBrittle_offset(phase)
|
call material_allocateSourceState(p,sourceOffset,NofMyPhase,1,1,1)
|
||||||
|
sourceState(p)%p(sourceOffset)%aTolState=param(instance)%aTol
|
||||||
call material_allocateSourceState(phase,sourceOffset,NofMyPhase,1,1,1)
|
|
||||||
sourceState(phase)%p(sourceOffset)%aTolState=param(instance)%aTol
|
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end subroutine source_damage_isoBrittle_init
|
end subroutine source_damage_isoBrittle_init
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -160,12 +153,12 @@ subroutine source_damage_isoBrittle_deltaState(C, Fe, ipc, ip, el)
|
||||||
instance = source_damage_isoBrittle_instance(phase) !< instance of damage_isoBrittle source
|
instance = source_damage_isoBrittle_instance(phase) !< instance of damage_isoBrittle source
|
||||||
sourceOffset = source_damage_isoBrittle_offset(phase)
|
sourceOffset = source_damage_isoBrittle_offset(phase)
|
||||||
|
|
||||||
|
|
||||||
strain = 0.5_pReal*math_sym33to6(matmul(transpose(Fe),Fe)-math_I3)
|
strain = 0.5_pReal*math_sym33to6(matmul(transpose(Fe),Fe)-math_I3)
|
||||||
|
|
||||||
strainenergy = 2.0_pReal*sum(strain*matmul(C,strain))/param(instance)%critStrainEnergy
|
strainenergy = 2.0_pReal*sum(strain*matmul(C,strain))/param(instance)%critStrainEnergy
|
||||||
! ToDo: check strainenergy = 2.0_pReal*dot_product(strain,matmul(C,strain))/param(instance)%critStrainEnergy
|
! ToDo: check strainenergy = 2.0_pReal*dot_product(strain,matmul(C,strain))/param(instance)%critStrainEnergy
|
||||||
|
|
||||||
if (strainenergy > sourceState(phase)%p(sourceOffset)%subState0(1,constituent)) then
|
if (strainenergy > sourceState(phase)%p(sourceOffset)%subState0(1,constituent)) then
|
||||||
sourceState(phase)%p(sourceOffset)%deltaState(1,constituent) = &
|
sourceState(phase)%p(sourceOffset)%deltaState(1,constituent) = &
|
||||||
strainenergy - sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
strainenergy - sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
||||||
|
@ -174,9 +167,9 @@ subroutine source_damage_isoBrittle_deltaState(C, Fe, ipc, ip, el)
|
||||||
sourceState(phase)%p(sourceOffset)%subState0(1,constituent) - &
|
sourceState(phase)%p(sourceOffset)%subState0(1,constituent) - &
|
||||||
sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
end subroutine source_damage_isoBrittle_deltaState
|
end subroutine source_damage_isoBrittle_deltaState
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief returns local part of nonlocal damage driving force
|
!> @brief returns local part of nonlocal damage driving force
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -195,13 +188,13 @@ subroutine source_damage_isoBrittle_getRateAndItsTangent(localphiDot, dLocalphiD
|
||||||
|
|
||||||
instance = source_damage_isoBrittle_instance(phase)
|
instance = source_damage_isoBrittle_instance(phase)
|
||||||
sourceOffset = source_damage_isoBrittle_offset(phase)
|
sourceOffset = source_damage_isoBrittle_offset(phase)
|
||||||
|
|
||||||
localphiDot = (1.0_pReal - phi)**(param(instance)%N - 1.0_pReal) - &
|
localphiDot = (1.0_pReal - phi)**(param(instance)%N - 1.0_pReal) - &
|
||||||
phi*sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
phi*sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
||||||
dLocalphiDot_dPhi = - (param(instance)%N - 1.0_pReal)* &
|
dLocalphiDot_dPhi = - (param(instance)%N - 1.0_pReal)* &
|
||||||
(1.0_pReal - phi)**max(0.0_pReal,param(instance)%N - 2.0_pReal) &
|
(1.0_pReal - phi)**max(0.0_pReal,param(instance)%N - 2.0_pReal) &
|
||||||
- sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
- sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
||||||
|
|
||||||
end subroutine source_damage_isoBrittle_getRateAndItsTangent
|
end subroutine source_damage_isoBrittle_getRateAndItsTangent
|
||||||
|
|
||||||
|
|
||||||
|
@ -211,9 +204,9 @@ end subroutine source_damage_isoBrittle_getRateAndItsTangent
|
||||||
subroutine source_damage_isoBrittle_results(phase,group)
|
subroutine source_damage_isoBrittle_results(phase,group)
|
||||||
|
|
||||||
integer, intent(in) :: phase
|
integer, intent(in) :: phase
|
||||||
character(len=*), intent(in) :: group
|
character(len=*), intent(in) :: group
|
||||||
integer :: sourceOffset, o, instance
|
integer :: sourceOffset, o, instance
|
||||||
|
|
||||||
instance = source_damage_isoBrittle_instance(phase)
|
instance = source_damage_isoBrittle_instance(phase)
|
||||||
sourceOffset = source_damage_isoBrittle_offset(phase)
|
sourceOffset = source_damage_isoBrittle_offset(phase)
|
||||||
|
|
||||||
|
|
|
@ -19,7 +19,7 @@ module source_damage_isoDuctile
|
||||||
source_damage_isoDuctile_offset, & !< which source is my current damage mechanism?
|
source_damage_isoDuctile_offset, & !< which source is my current damage mechanism?
|
||||||
source_damage_isoDuctile_instance !< instance of damage source mechanism
|
source_damage_isoDuctile_instance !< instance of damage source mechanism
|
||||||
|
|
||||||
enum, bind(c)
|
enum, bind(c)
|
||||||
enumerator :: undefined_ID, &
|
enumerator :: undefined_ID, &
|
||||||
damage_drivingforce_ID
|
damage_drivingforce_ID
|
||||||
end enum !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ToDo
|
end enum !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ToDo
|
||||||
|
@ -51,52 +51,47 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_damage_isoDuctile_init
|
subroutine source_damage_isoDuctile_init
|
||||||
|
|
||||||
integer :: Ninstance,phase,instance,source,sourceOffset
|
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p,i
|
||||||
integer :: NofMyPhase,p,i
|
|
||||||
integer(kind(undefined_ID)) :: &
|
integer(kind(undefined_ID)) :: &
|
||||||
outputID
|
outputID
|
||||||
|
|
||||||
character(len=pStringLen) :: &
|
character(len=pStringLen) :: &
|
||||||
extmsg = ''
|
extmsg = ''
|
||||||
character(len=pStringLen), dimension(:), allocatable :: &
|
character(len=pStringLen), dimension(:), allocatable :: &
|
||||||
outputs
|
outputs
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISODUCTILE_LABEL//' init -+>>>'
|
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISODUCTILE_LABEL//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
Ninstance = count(phase_source == SOURCE_damage_isoDuctile_ID)
|
Ninstance = count(phase_source == SOURCE_DAMAGE_ISODUCTILE_ID)
|
||||||
if (Ninstance == 0) return
|
|
||||||
|
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
||||||
|
|
||||||
allocate(source_damage_isoDuctile_offset(material_Nphase), source=0)
|
|
||||||
allocate(source_damage_isoDuctile_instance(material_Nphase), source=0)
|
|
||||||
do phase = 1, material_Nphase
|
|
||||||
source_damage_isoDuctile_instance(phase) = count(phase_source(:,1:phase) == source_damage_isoDuctile_ID)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
if (phase_source(source,phase) == source_damage_isoDuctile_ID) &
|
|
||||||
source_damage_isoDuctile_offset(phase) = source
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
|
allocate(source_damage_isoDuctile_offset (size(config_phase)), source=0)
|
||||||
|
allocate(source_damage_isoDuctile_instance(size(config_phase)), source=0)
|
||||||
allocate(param(Ninstance))
|
allocate(param(Ninstance))
|
||||||
|
|
||||||
do p=1, size(config_phase)
|
do p = 1, size(config_phase)
|
||||||
|
source_damage_isoDuctile_instance(p) = count(phase_source(:,1:p) == SOURCE_DAMAGE_ISODUCTILE_ID)
|
||||||
|
do source = 1, phase_Nsources(p)
|
||||||
|
if (phase_source(source,p) == SOURCE_DAMAGE_ISODUCTILE_ID) &
|
||||||
|
source_damage_isoDuctile_offset(p) = source
|
||||||
|
enddo
|
||||||
|
|
||||||
if (all(phase_source(:,p) /= SOURCE_DAMAGE_ISODUCTILE_ID)) cycle
|
if (all(phase_source(:,p) /= SOURCE_DAMAGE_ISODUCTILE_ID)) cycle
|
||||||
|
|
||||||
associate(prm => param(source_damage_isoDuctile_instance(p)), &
|
associate(prm => param(source_damage_isoDuctile_instance(p)), &
|
||||||
config => config_phase(p))
|
config => config_phase(p))
|
||||||
|
|
||||||
prm%aTol = config%getFloat('isoductile_atol',defaultVal = 1.0e-3_pReal)
|
prm%aTol = config%getFloat('isoductile_atol',defaultVal = 1.0e-3_pReal)
|
||||||
|
|
||||||
prm%N = config%getFloat('isoductile_ratesensitivity')
|
prm%N = config%getFloat('isoductile_ratesensitivity')
|
||||||
prm%critPlasticStrain = config%getFloat('isoductile_criticalplasticstrain')
|
prm%critPlasticStrain = config%getFloat('isoductile_criticalplasticstrain')
|
||||||
|
|
||||||
! sanity checks
|
! sanity checks
|
||||||
if (prm%aTol < 0.0_pReal) extmsg = trim(extmsg)//' isoductile_atol'
|
if (prm%aTol < 0.0_pReal) extmsg = trim(extmsg)//' isoductile_atol'
|
||||||
|
|
||||||
if (prm%N <= 0.0_pReal) extmsg = trim(extmsg)//' isoductile_ratesensitivity'
|
if (prm%N <= 0.0_pReal) extmsg = trim(extmsg)//' isoductile_ratesensitivity'
|
||||||
if (prm%critPlasticStrain <= 0.0_pReal) extmsg = trim(extmsg)//' isoductile_criticalplasticstrain'
|
if (prm%critPlasticStrain <= 0.0_pReal) extmsg = trim(extmsg)//' isoductile_criticalplasticstrain'
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! exit if any parameter is out of range
|
! exit if any parameter is out of range
|
||||||
if (extmsg /= '') &
|
if (extmsg /= '') &
|
||||||
|
@ -109,7 +104,7 @@ subroutine source_damage_isoDuctile_init
|
||||||
do i=1, size(outputs)
|
do i=1, size(outputs)
|
||||||
outputID = undefined_ID
|
outputID = undefined_ID
|
||||||
select case(outputs(i))
|
select case(outputs(i))
|
||||||
|
|
||||||
case ('isoductile_drivingforce')
|
case ('isoductile_drivingforce')
|
||||||
prm%outputID = [prm%outputID, damage_drivingforce_ID]
|
prm%outputID = [prm%outputID, damage_drivingforce_ID]
|
||||||
|
|
||||||
|
@ -118,17 +113,17 @@ subroutine source_damage_isoDuctile_init
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
phase = p
|
|
||||||
NofMyPhase=count(material_phaseAt==phase) * discretization_nIP
|
|
||||||
instance = source_damage_isoDuctile_instance(phase)
|
|
||||||
sourceOffset = source_damage_isoDuctile_offset(phase)
|
|
||||||
|
|
||||||
call material_allocateSourceState(phase,sourceOffset,NofMyPhase,1,1,0)
|
|
||||||
sourceState(phase)%p(sourceOffset)%aTolState=param(instance)%aTol
|
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
|
||||||
|
instance = source_damage_isoDuctile_instance(p)
|
||||||
|
sourceOffset = source_damage_isoDuctile_offset(p)
|
||||||
|
|
||||||
|
call material_allocateSourceState(p,sourceOffset,NofMyPhase,1,1,0)
|
||||||
|
sourceState(p)%p(sourceOffset)%aTolState=param(instance)%aTol
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end subroutine source_damage_isoDuctile_init
|
end subroutine source_damage_isoDuctile_init
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -152,11 +147,11 @@ subroutine source_damage_isoDuctile_dotState(ipc, ip, el)
|
||||||
|
|
||||||
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) = &
|
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) = &
|
||||||
sum(plasticState(phase)%slipRate(:,constituent))/ &
|
sum(plasticState(phase)%slipRate(:,constituent))/ &
|
||||||
((damage(homog)%p(damageOffset))**param(instance)%N)/ &
|
((damage(homog)%p(damageOffset))**param(instance)%N)/ &
|
||||||
param(instance)%critPlasticStrain
|
param(instance)%critPlasticStrain
|
||||||
|
|
||||||
end subroutine source_damage_isoDuctile_dotState
|
end subroutine source_damage_isoDuctile_dotState
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief returns local part of nonlocal damage driving force
|
!> @brief returns local part of nonlocal damage driving force
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -174,12 +169,12 @@ subroutine source_damage_isoDuctile_getRateAndItsTangent(localphiDot, dLocalphiD
|
||||||
sourceOffset
|
sourceOffset
|
||||||
|
|
||||||
sourceOffset = source_damage_isoDuctile_offset(phase)
|
sourceOffset = source_damage_isoDuctile_offset(phase)
|
||||||
|
|
||||||
localphiDot = 1.0_pReal &
|
localphiDot = 1.0_pReal &
|
||||||
- sourceState(phase)%p(sourceOffset)%state(1,constituent) * phi
|
- sourceState(phase)%p(sourceOffset)%state(1,constituent) * phi
|
||||||
|
|
||||||
dLocalphiDot_dPhi = -sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
dLocalphiDot_dPhi = -sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
||||||
|
|
||||||
end subroutine source_damage_isoDuctile_getRateAndItsTangent
|
end subroutine source_damage_isoDuctile_getRateAndItsTangent
|
||||||
|
|
||||||
|
|
||||||
|
@ -189,9 +184,9 @@ end subroutine source_damage_isoDuctile_getRateAndItsTangent
|
||||||
subroutine source_damage_isoDuctile_results(phase,group)
|
subroutine source_damage_isoDuctile_results(phase,group)
|
||||||
|
|
||||||
integer, intent(in) :: phase
|
integer, intent(in) :: phase
|
||||||
character(len=*), intent(in) :: group
|
character(len=*), intent(in) :: group
|
||||||
integer :: sourceOffset, o, instance
|
integer :: sourceOffset, o, instance
|
||||||
|
|
||||||
instance = source_damage_isoDuctile_instance(phase)
|
instance = source_damage_isoDuctile_instance(phase)
|
||||||
sourceOffset = source_damage_isoDuctile_offset(phase)
|
sourceOffset = source_damage_isoDuctile_offset(phase)
|
||||||
|
|
||||||
|
|
|
@ -10,26 +10,26 @@ module source_thermal_dissipation
|
||||||
use discretization
|
use discretization
|
||||||
use material
|
use material
|
||||||
use config
|
use config
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
|
||||||
integer, dimension(:), allocatable :: &
|
integer, dimension(:), allocatable :: &
|
||||||
source_thermal_dissipation_offset, & !< which source is my current thermal dissipation mechanism?
|
source_thermal_dissipation_offset, & !< which source is my current thermal dissipation mechanism?
|
||||||
source_thermal_dissipation_instance !< instance of thermal dissipation source mechanism
|
source_thermal_dissipation_instance !< instance of thermal dissipation source mechanism
|
||||||
|
|
||||||
type :: tParameters !< container type for internal constitutive parameters
|
type :: tParameters !< container type for internal constitutive parameters
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
kappa
|
kappa
|
||||||
end type tParameters
|
end type tParameters
|
||||||
|
|
||||||
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstance)
|
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstance)
|
||||||
|
|
||||||
|
|
||||||
public :: &
|
public :: &
|
||||||
source_thermal_dissipation_init, &
|
source_thermal_dissipation_init, &
|
||||||
source_thermal_dissipation_getRateAndItsTangent
|
source_thermal_dissipation_getRateAndItsTangent
|
||||||
|
|
||||||
contains
|
contains
|
||||||
|
|
||||||
|
|
||||||
|
@ -38,45 +38,42 @@ contains
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_thermal_dissipation_init
|
subroutine source_thermal_dissipation_init
|
||||||
|
|
||||||
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p
|
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_thermal_dissipation_label//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- source_'//SOURCE_thermal_dissipation_label//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
|
Ninstance = count(phase_source == SOURCE_THERMAL_DISSIPATION_ID)
|
||||||
Ninstance = count(phase_source == SOURCE_thermal_dissipation_ID)
|
|
||||||
if (Ninstance == 0) return
|
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
||||||
|
|
||||||
allocate(source_thermal_dissipation_offset(material_Nphase), source=0)
|
allocate(source_thermal_dissipation_offset (size(config_phase)), source=0)
|
||||||
allocate(source_thermal_dissipation_instance(material_Nphase), source=0)
|
allocate(source_thermal_dissipation_instance(size(config_phase)), source=0)
|
||||||
allocate(param(Ninstance))
|
allocate(param(Ninstance))
|
||||||
|
|
||||||
do p = 1, material_Nphase
|
do p = 1, size(config_phase)
|
||||||
source_thermal_dissipation_instance(p) = count(phase_source(:,1:p) == SOURCE_thermal_dissipation_ID)
|
source_thermal_dissipation_instance(p) = count(phase_source(:,1:p) == SOURCE_THERMAL_DISSIPATION_ID)
|
||||||
do source = 1, phase_Nsources(p)
|
do source = 1, phase_Nsources(p)
|
||||||
if (phase_source(source,p) == SOURCE_thermal_dissipation_ID) &
|
if (phase_source(source,p) == SOURCE_THERMAL_DISSIPATION_ID) &
|
||||||
source_thermal_dissipation_offset(p) = source
|
source_thermal_dissipation_offset(p) = source
|
||||||
enddo
|
enddo
|
||||||
enddo
|
|
||||||
|
|
||||||
do p=1, size(config_phase)
|
|
||||||
if (all(phase_source(:,p) /= SOURCE_THERMAL_DISSIPATION_ID)) cycle
|
if (all(phase_source(:,p) /= SOURCE_THERMAL_DISSIPATION_ID)) cycle
|
||||||
|
|
||||||
instance = source_thermal_dissipation_instance(p)
|
instance = source_thermal_dissipation_instance(p)
|
||||||
param(instance)%kappa = config_phase(p)%getFloat('dissipation_coldworkcoeff')
|
param(instance)%kappa = config_phase(p)%getFloat('dissipation_coldworkcoeff')
|
||||||
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
|
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
|
||||||
sourceOffset = source_thermal_dissipation_offset(p)
|
sourceOffset = source_thermal_dissipation_offset(p)
|
||||||
|
|
||||||
call material_allocateSourceState(p,sourceOffset,NofMyPhase,0,0,0)
|
call material_allocateSourceState(p,sourceOffset,NofMyPhase,0,0,0)
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end subroutine source_thermal_dissipation_init
|
end subroutine source_thermal_dissipation_init
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief returns dissipation rate
|
!> @brief Ninstances dissipation rate
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_thermal_dissipation_getRateAndItsTangent(TDot, dTDOT_dT, Tstar, Lp, phase)
|
subroutine source_thermal_dissipation_getRateAndItsTangent(TDot, dTDOT_dT, Tstar, Lp, phase)
|
||||||
|
|
||||||
|
@ -91,12 +88,12 @@ subroutine source_thermal_dissipation_getRateAndItsTangent(TDot, dTDOT_dT, Tstar
|
||||||
dTDOT_dT
|
dTDOT_dT
|
||||||
integer :: &
|
integer :: &
|
||||||
instance
|
instance
|
||||||
|
|
||||||
instance = source_thermal_dissipation_instance(phase)
|
instance = source_thermal_dissipation_instance(phase)
|
||||||
|
|
||||||
TDot = param(instance)%kappa*sum(abs(Tstar*Lp))
|
TDot = param(instance)%kappa*sum(abs(Tstar*Lp))
|
||||||
dTDOT_dT = 0.0_pReal
|
dTDOT_dT = 0.0_pReal
|
||||||
|
|
||||||
end subroutine source_thermal_dissipation_getRateAndItsTangent
|
end subroutine source_thermal_dissipation_getRateAndItsTangent
|
||||||
|
|
||||||
end module source_thermal_dissipation
|
end module source_thermal_dissipation
|
||||||
|
|
|
@ -42,44 +42,40 @@ contains
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_thermal_externalheat_init
|
subroutine source_thermal_externalheat_init
|
||||||
|
|
||||||
integer :: maxNinstance,instance,source,sourceOffset,NofMyPhase,p
|
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_thermal_externalheat_label//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- source_'//SOURCE_thermal_externalheat_label//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
|
Ninstance = count(phase_source == SOURCE_thermal_externalheat_ID)
|
||||||
maxNinstance = count(phase_source == SOURCE_thermal_externalheat_ID)
|
|
||||||
if (maxNinstance == 0) return
|
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
||||||
|
|
||||||
allocate(source_thermal_externalheat_offset(material_Nphase), source=0)
|
allocate(source_thermal_externalheat_offset (size(config_phase)), source=0)
|
||||||
allocate(source_thermal_externalheat_instance(material_Nphase), source=0)
|
allocate(source_thermal_externalheat_instance(size(config_phase)), source=0)
|
||||||
|
allocate(param(Ninstance))
|
||||||
do p = 1, material_Nphase
|
|
||||||
|
do p = 1, size(config_phase)
|
||||||
source_thermal_externalheat_instance(p) = count(phase_source(:,1:p) == SOURCE_thermal_externalheat_ID)
|
source_thermal_externalheat_instance(p) = count(phase_source(:,1:p) == SOURCE_thermal_externalheat_ID)
|
||||||
do source = 1, phase_Nsources(p)
|
do source = 1, phase_Nsources(p)
|
||||||
if (phase_source(source,p) == SOURCE_thermal_externalheat_ID) &
|
if (phase_source(source,p) == SOURCE_thermal_externalheat_ID) &
|
||||||
source_thermal_externalheat_offset(p) = source
|
source_thermal_externalheat_offset(p) = source
|
||||||
enddo
|
enddo
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(param(maxNinstance))
|
|
||||||
|
|
||||||
do p=1, size(config_phase)
|
|
||||||
if (all(phase_source(:,p) /= SOURCE_thermal_externalheat_ID)) cycle
|
if (all(phase_source(:,p) /= SOURCE_thermal_externalheat_ID)) cycle
|
||||||
|
|
||||||
instance = source_thermal_externalheat_instance(p)
|
instance = source_thermal_externalheat_instance(p)
|
||||||
sourceOffset = source_thermal_externalheat_offset(p)
|
sourceOffset = source_thermal_externalheat_offset(p)
|
||||||
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
|
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
|
||||||
|
|
||||||
param(instance)%time = config_phase(p)%getFloats('externalheat_time')
|
param(instance)%time = config_phase(p)%getFloats('externalheat_time')
|
||||||
param(instance)%nIntervals = size(param(instance)%time) - 1
|
param(instance)%nIntervals = size(param(instance)%time) - 1
|
||||||
|
|
||||||
|
|
||||||
param(instance)%heat_rate = config_phase(p)%getFloats('externalheat_rate',requiredSize = size(param(instance)%time))
|
param(instance)%heat_rate = config_phase(p)%getFloats('externalheat_rate',requiredSize = size(param(instance)%time))
|
||||||
|
|
||||||
call material_allocateSourceState(p,sourceOffset,NofMyPhase,1,1,0)
|
call material_allocateSourceState(p,sourceOffset,NofMyPhase,1,1,0)
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end subroutine source_thermal_externalheat_init
|
end subroutine source_thermal_externalheat_init
|
||||||
|
@ -90,25 +86,25 @@ end subroutine source_thermal_externalheat_init
|
||||||
!> @details state only contains current time to linearly interpolate given heat powers
|
!> @details state only contains current time to linearly interpolate given heat powers
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_thermal_externalheat_dotState(phase, of)
|
subroutine source_thermal_externalheat_dotState(phase, of)
|
||||||
|
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
phase, &
|
phase, &
|
||||||
of
|
of
|
||||||
integer :: &
|
integer :: &
|
||||||
sourceOffset
|
sourceOffset
|
||||||
|
|
||||||
sourceOffset = source_thermal_externalheat_offset(phase)
|
sourceOffset = source_thermal_externalheat_offset(phase)
|
||||||
|
|
||||||
sourceState(phase)%p(sourceOffset)%dotState(1,of) = 1.0_pReal ! state is current time
|
sourceState(phase)%p(sourceOffset)%dotState(1,of) = 1.0_pReal ! state is current time
|
||||||
|
|
||||||
end subroutine source_thermal_externalheat_dotState
|
end subroutine source_thermal_externalheat_dotState
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief returns local heat generation rate
|
!> @brief returns local heat generation rate
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_thermal_externalheat_getRateAndItsTangent(TDot, dTDot_dT, phase, of)
|
subroutine source_thermal_externalheat_getRateAndItsTangent(TDot, dTDot_dT, phase, of)
|
||||||
|
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
phase, &
|
phase, &
|
||||||
of
|
of
|
||||||
|
@ -118,11 +114,11 @@ subroutine source_thermal_externalheat_getRateAndItsTangent(TDot, dTDot_dT, phas
|
||||||
integer :: &
|
integer :: &
|
||||||
instance, sourceOffset, interval
|
instance, sourceOffset, interval
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
frac_time
|
frac_time
|
||||||
|
|
||||||
instance = source_thermal_externalheat_instance(phase)
|
instance = source_thermal_externalheat_instance(phase)
|
||||||
sourceOffset = source_thermal_externalheat_offset(phase)
|
sourceOffset = source_thermal_externalheat_offset(phase)
|
||||||
|
|
||||||
do interval = 1, param(instance)%nIntervals ! scan through all rate segments
|
do interval = 1, param(instance)%nIntervals ! scan through all rate segments
|
||||||
frac_time = (sourceState(phase)%p(sourceOffset)%state(1,of) - param(instance)%time(interval)) &
|
frac_time = (sourceState(phase)%p(sourceOffset)%state(1,of) - param(instance)%time(interval)) &
|
||||||
/ (param(instance)%time(interval+1) - param(instance)%time(interval)) ! fractional time within segment
|
/ (param(instance)%time(interval+1) - param(instance)%time(interval)) ! fractional time within segment
|
||||||
|
@ -134,7 +130,7 @@ subroutine source_thermal_externalheat_getRateAndItsTangent(TDot, dTDot_dT, phas
|
||||||
! ...or extrapolate if outside of bounds
|
! ...or extrapolate if outside of bounds
|
||||||
enddo
|
enddo
|
||||||
dTDot_dT = 0.0
|
dTDot_dT = 0.0
|
||||||
|
|
||||||
end subroutine source_thermal_externalheat_getRateAndItsTangent
|
end subroutine source_thermal_externalheat_getRateAndItsTangent
|
||||||
|
|
||||||
end module source_thermal_externalheat
|
end module source_thermal_externalheat
|
||||||
|
|
Loading…
Reference in New Issue