last remaining outputID enums removed

This commit is contained in:
Martin Diehl 2020-02-28 11:06:21 +01:00
parent 11d456bcd7
commit 15712d7ebb
2 changed files with 66 additions and 98 deletions

View File

@ -16,24 +16,18 @@ module damage_local
implicit none implicit none
private private
enum, bind(c)
enumerator :: &
undefined_ID, &
damage_ID
end enum
type :: tParameters type :: tParameters
integer(kind(undefined_ID)), dimension(:), allocatable :: & character(len=pStringLen), allocatable, dimension(:) :: &
outputID output
end type tParameters end type tParameters
type(tparameters), dimension(:), allocatable :: & type(tparameters), dimension(:), allocatable :: &
param param
public :: & public :: &
damage_local_init, & damage_local_init, &
damage_local_updateState, & damage_local_updateState, &
damage_local_Results damage_local_results
contains contains
@ -43,41 +37,32 @@ contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine damage_local_init subroutine damage_local_init
integer :: maxNinstance,o,NofMyHomog,h integer :: maxNinstance,NofMyHomog,h
character(len=pStringLen), dimension(:), allocatable :: outputs
write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_local_label//' init -+>>>'; flush(6)
write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_local_label//' init -+>>>'; flush(6)
maxNinstance = count(damage_type == DAMAGE_local_ID) maxNinstance = count(damage_type == DAMAGE_local_ID)
if (maxNinstance == 0) return if (maxNinstance == 0) return
allocate(param(maxNinstance)) allocate(param(maxNinstance))
do h = 1, size(damage_type) do h = 1, size(damage_type)
if (damage_type(h) /= DAMAGE_LOCAL_ID) cycle if (damage_type(h) /= DAMAGE_LOCAL_ID) cycle
associate(prm => param(damage_typeInstance(h)),config => config_homogenization(h)) associate(prm => param(damage_typeInstance(h)),config => config_homogenization(h))
outputs = config%getStrings('(output)',defaultVal=emptyStringArray) prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
allocate(prm%outputID(0))
do o=1, size(outputs)
select case(outputs(o))
case ('damage')
prm%outputID = [prm%outputID , damage_ID]
end select
enddo
NofMyHomog = count(material_homogenizationAt == h) NofMyHomog = count(material_homogenizationAt == h)
damageState(h)%sizeState = 1 damageState(h)%sizeState = 1
allocate(damageState(h)%state0 (1,NofMyHomog), source=damage_initialPhi(h)) allocate(damageState(h)%state0 (1,NofMyHomog), source=damage_initialPhi(h))
allocate(damageState(h)%subState0(1,NofMyHomog), source=damage_initialPhi(h)) allocate(damageState(h)%subState0(1,NofMyHomog), source=damage_initialPhi(h))
allocate(damageState(h)%state (1,NofMyHomog), source=damage_initialPhi(h)) allocate(damageState(h)%state (1,NofMyHomog), source=damage_initialPhi(h))
nullify(damageMapping(h)%p) nullify(damageMapping(h)%p)
damageMapping(h)%p => material_homogenizationMemberAt damageMapping(h)%p => material_homogenizationMemberAt
deallocate(damage(h)%p) deallocate(damage(h)%p)
damage(h)%p => damageState(h)%state(1,:) damage(h)%p => damageState(h)%state(1,:)
end associate end associate
enddo enddo
@ -85,10 +70,10 @@ end subroutine damage_local_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates local change in damage field !> @brief calculates local change in damage field
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function damage_local_updateState(subdt, ip, el) function damage_local_updateState(subdt, ip, el)
integer, intent(in) :: & integer, intent(in) :: &
ip, & !< integration point number ip, & !< integration point number
el !< element number el !< element number
@ -100,30 +85,30 @@ function damage_local_updateState(subdt, ip, el)
homog, & homog, &
offset offset
real(pReal) :: & real(pReal) :: &
phi, phiDot, dPhiDot_dPhi phi, phiDot, dPhiDot_dPhi
homog = material_homogenizationAt(el) homog = material_homogenizationAt(el)
offset = material_homogenizationMemberAt(ip,el) offset = material_homogenizationMemberAt(ip,el)
phi = damageState(homog)%subState0(1,offset) phi = damageState(homog)%subState0(1,offset)
call damage_local_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el) call damage_local_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el)
phi = max(residualStiffness,min(1.0_pReal,phi + subdt*phiDot)) phi = max(residualStiffness,min(1.0_pReal,phi + subdt*phiDot))
damage_local_updateState = [ abs(phi - damageState(homog)%state(1,offset)) & damage_local_updateState = [ abs(phi - damageState(homog)%state(1,offset)) &
<= err_damage_tolAbs & <= err_damage_tolAbs &
.or. abs(phi - damageState(homog)%state(1,offset)) & .or. abs(phi - damageState(homog)%state(1,offset)) &
<= err_damage_tolRel*abs(damageState(homog)%state(1,offset)), & <= err_damage_tolRel*abs(damageState(homog)%state(1,offset)), &
.true.] .true.]
damageState(homog)%state(1,offset) = phi damageState(homog)%state(1,offset) = phi
end function damage_local_updateState end function damage_local_updateState
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates homogenized local damage driving forces !> @brief calculates homogenized local damage driving forces
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine damage_local_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el) subroutine damage_local_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el)
integer, intent(in) :: & integer, intent(in) :: &
ip, & !< integration point number ip, & !< integration point number
el !< element number el !< element number
@ -135,7 +120,7 @@ subroutine damage_local_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el
source, & source, &
constituent constituent
real(pReal) :: & real(pReal) :: &
phiDot, dPhiDot_dPhi, localphiDot, dLocalphiDot_dPhi phiDot, dPhiDot_dPhi, localphiDot, dLocalphiDot_dPhi
phiDot = 0.0_pReal phiDot = 0.0_pReal
dPhiDot_dPhi = 0.0_pReal dPhiDot_dPhi = 0.0_pReal
@ -143,7 +128,7 @@ subroutine damage_local_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el
phase = material_phaseAt(grain,el) phase = material_phaseAt(grain,el)
constituent = material_phasememberAt(grain,ip,el) constituent = material_phasememberAt(grain,ip,el)
do source = 1, phase_Nsources(phase) do source = 1, phase_Nsources(phase)
select case(phase_source(source,phase)) select case(phase_source(source,phase))
case (SOURCE_damage_isoBrittle_ID) case (SOURCE_damage_isoBrittle_ID)
call source_damage_isobrittle_getRateAndItsTangent (localphiDot, dLocalphiDot_dPhi, phi, phase, constituent) call source_damage_isobrittle_getRateAndItsTangent (localphiDot, dLocalphiDot_dPhi, phi, phase, constituent)
@ -163,12 +148,12 @@ subroutine damage_local_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el
end select end select
phiDot = phiDot + localphiDot phiDot = phiDot + localphiDot
dPhiDot_dPhi = dPhiDot_dPhi + dLocalphiDot_dPhi dPhiDot_dPhi = dPhiDot_dPhi + dLocalphiDot_dPhi
enddo enddo
enddo enddo
phiDot = phiDot/real(homogenization_Ngrains(material_homogenizationAt(el)),pReal) phiDot = phiDot/real(homogenization_Ngrains(material_homogenizationAt(el)),pReal)
dPhiDot_dPhi = dPhiDot_dPhi/real(homogenization_Ngrains(material_homogenizationAt(el)),pReal) dPhiDot_dPhi = dPhiDot_dPhi/real(homogenization_Ngrains(material_homogenizationAt(el)),pReal)
end subroutine damage_local_getSourceAndItsTangent end subroutine damage_local_getSourceAndItsTangent
@ -179,14 +164,13 @@ subroutine damage_local_results(homog,group)
integer, intent(in) :: homog integer, intent(in) :: homog
character(len=*), intent(in) :: group character(len=*), intent(in) :: group
integer :: o
associate(prm => param(damage_typeInstance(homog)))
outputsLoop: do o = 1,size(prm%outputID) integer :: o
select case(prm%outputID(o))
associate(prm => param(damage_typeInstance(homog)))
case (damage_ID) outputsLoop: do o = 1,size(prm%output)
select case(prm%output(o))
case ('damage')
call results_writeDataset(group,damage(homog)%p,'phi',& call results_writeDataset(group,damage(homog)%p,'phi',&
'damage indicator','-') 'damage indicator','-')
end select end select

View File

@ -18,17 +18,11 @@ module damage_nonlocal
implicit none implicit none
private private
enum, bind(c)
enumerator :: &
undefined_ID, &
damage_ID
end enum
type :: tParameters type :: tParameters
integer(kind(undefined_ID)), dimension(:), allocatable :: & character(len=pStringLen), allocatable, dimension(:) :: &
outputID output
end type tParameters end type tParameters
type(tparameters), dimension(:), allocatable :: & type(tparameters), dimension(:), allocatable :: &
param param
@ -38,7 +32,7 @@ module damage_nonlocal
damage_nonlocal_getDiffusion33, & damage_nonlocal_getDiffusion33, &
damage_nonlocal_getMobility, & damage_nonlocal_getMobility, &
damage_nonlocal_putNonLocalDamage, & damage_nonlocal_putNonLocalDamage, &
damage_nonlocal_Results damage_nonlocal_results
contains contains
@ -48,29 +42,20 @@ contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine damage_nonlocal_init subroutine damage_nonlocal_init
integer :: maxNinstance,o,NofMyHomog,h integer :: maxNinstance,NofMyHomog,h
character(len=pStringLen), dimension(:), allocatable :: outputs
write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_nonlocal_label//' init -+>>>'; flush(6)
write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_nonlocal_label//' init -+>>>'; flush(6)
maxNinstance = count(damage_type == DAMAGE_nonlocal_ID) maxNinstance = count(damage_type == DAMAGE_nonlocal_ID)
if (maxNinstance == 0) return if (maxNinstance == 0) return
allocate(param(maxNinstance)) allocate(param(maxNinstance))
do h = 1, size(damage_type) do h = 1, size(damage_type)
if (damage_type(h) /= DAMAGE_NONLOCAL_ID) cycle if (damage_type(h) /= DAMAGE_NONLOCAL_ID) cycle
associate(prm => param(damage_typeInstance(h)),config => config_homogenization(h)) associate(prm => param(damage_typeInstance(h)),config => config_homogenization(h))
outputs = config%getStrings('(output)',defaultVal=emptyStringArray) prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
allocate(prm%outputID(0))
do o=1, size(outputs)
select case(outputs(o))
case ('damage')
prm%outputID = [prm%outputID, damage_ID]
end select
enddo
NofMyHomog = count(material_homogenizationAt == h) NofMyHomog = count(material_homogenizationAt == h)
damageState(h)%sizeState = 1 damageState(h)%sizeState = 1
@ -82,7 +67,7 @@ subroutine damage_nonlocal_init
damageMapping(h)%p => material_homogenizationMemberAt damageMapping(h)%p => material_homogenizationMemberAt
deallocate(damage(h)%p) deallocate(damage(h)%p)
damage(h)%p => damageState(h)%state(1,:) damage(h)%p => damageState(h)%state(1,:)
end associate end associate
enddo enddo
@ -90,10 +75,10 @@ end subroutine damage_nonlocal_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates homogenized damage driving forces !> @brief calculates homogenized damage driving forces
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine damage_nonlocal_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el) subroutine damage_nonlocal_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el)
integer, intent(in) :: & integer, intent(in) :: &
ip, & !< integration point number ip, & !< integration point number
el !< element number el !< element number
@ -105,7 +90,7 @@ subroutine damage_nonlocal_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip,
source, & source, &
constituent constituent
real(pReal) :: & real(pReal) :: &
phiDot, dPhiDot_dPhi, localphiDot, dLocalphiDot_dPhi phiDot, dPhiDot_dPhi, localphiDot, dLocalphiDot_dPhi
phiDot = 0.0_pReal phiDot = 0.0_pReal
dPhiDot_dPhi = 0.0_pReal dPhiDot_dPhi = 0.0_pReal
@ -113,7 +98,7 @@ subroutine damage_nonlocal_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip,
phase = material_phaseAt(grain,el) phase = material_phaseAt(grain,el)
constituent = material_phasememberAt(grain,ip,el) constituent = material_phasememberAt(grain,ip,el)
do source = 1, phase_Nsources(phase) do source = 1, phase_Nsources(phase)
select case(phase_source(source,phase)) select case(phase_source(source,phase))
case (SOURCE_damage_isoBrittle_ID) case (SOURCE_damage_isoBrittle_ID)
call source_damage_isobrittle_getRateAndItsTangent (localphiDot, dLocalphiDot_dPhi, phi, phase, constituent) call source_damage_isobrittle_getRateAndItsTangent (localphiDot, dLocalphiDot_dPhi, phi, phase, constituent)
@ -133,12 +118,12 @@ subroutine damage_nonlocal_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip,
end select end select
phiDot = phiDot + localphiDot phiDot = phiDot + localphiDot
dPhiDot_dPhi = dPhiDot_dPhi + dLocalphiDot_dPhi dPhiDot_dPhi = dPhiDot_dPhi + dLocalphiDot_dPhi
enddo enddo
enddo enddo
phiDot = phiDot/real(homogenization_Ngrains(material_homogenizationAt(el)),pReal) phiDot = phiDot/real(homogenization_Ngrains(material_homogenizationAt(el)),pReal)
dPhiDot_dPhi = dPhiDot_dPhi/real(homogenization_Ngrains(material_homogenizationAt(el)),pReal) dPhiDot_dPhi = dPhiDot_dPhi/real(homogenization_Ngrains(material_homogenizationAt(el)),pReal)
end subroutine damage_nonlocal_getSourceAndItsTangent end subroutine damage_nonlocal_getSourceAndItsTangent
@ -155,9 +140,9 @@ function damage_nonlocal_getDiffusion33(ip,el)
integer :: & integer :: &
homog, & homog, &
grain grain
homog = material_homogenizationAt(el) homog = material_homogenizationAt(el)
damage_nonlocal_getDiffusion33 = 0.0_pReal damage_nonlocal_getDiffusion33 = 0.0_pReal
do grain = 1, homogenization_Ngrains(homog) do grain = 1, homogenization_Ngrains(homog)
damage_nonlocal_getDiffusion33 = damage_nonlocal_getDiffusion33 + & damage_nonlocal_getDiffusion33 = damage_nonlocal_getDiffusion33 + &
crystallite_push33ToRef(grain,ip,el,lattice_DamageDiffusion33(1:3,1:3,material_phaseAt(grain,el))) crystallite_push33ToRef(grain,ip,el,lattice_DamageDiffusion33(1:3,1:3,material_phaseAt(grain,el)))
@ -165,12 +150,12 @@ function damage_nonlocal_getDiffusion33(ip,el)
damage_nonlocal_getDiffusion33 = & damage_nonlocal_getDiffusion33 = &
charLength**2*damage_nonlocal_getDiffusion33/real(homogenization_Ngrains(homog),pReal) charLength**2*damage_nonlocal_getDiffusion33/real(homogenization_Ngrains(homog),pReal)
end function damage_nonlocal_getDiffusion33 end function damage_nonlocal_getDiffusion33
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief Returns homogenized nonlocal damage mobility !> @brief Returns homogenized nonlocal damage mobility
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
real(pReal) function damage_nonlocal_getMobility(ip,el) real(pReal) function damage_nonlocal_getMobility(ip,el)
@ -179,9 +164,9 @@ real(pReal) function damage_nonlocal_getMobility(ip,el)
el !< element number el !< element number
integer :: & integer :: &
ipc ipc
damage_nonlocal_getMobility = 0.0_pReal damage_nonlocal_getMobility = 0.0_pReal
do ipc = 1, homogenization_Ngrains(material_homogenizationAt(el)) do ipc = 1, homogenization_Ngrains(material_homogenizationAt(el))
damage_nonlocal_getMobility = damage_nonlocal_getMobility + lattice_DamageMobility(material_phaseAt(ipc,el)) damage_nonlocal_getMobility = damage_nonlocal_getMobility + lattice_DamageMobility(material_phaseAt(ipc,el))
enddo enddo
@ -205,7 +190,7 @@ subroutine damage_nonlocal_putNonLocalDamage(phi,ip,el)
integer :: & integer :: &
homog, & homog, &
offset offset
homog = material_homogenizationAt(el) homog = material_homogenizationAt(el)
offset = damageMapping(homog)%p(ip,el) offset = damageMapping(homog)%p(ip,el)
damage(homog)%p(offset) = phi damage(homog)%p(offset) = phi
@ -220,14 +205,13 @@ subroutine damage_nonlocal_results(homog,group)
integer, intent(in) :: homog integer, intent(in) :: homog
character(len=*), intent(in) :: group character(len=*), intent(in) :: group
integer :: o
associate(prm => param(damage_typeInstance(homog)))
outputsLoop: do o = 1,size(prm%outputID) integer :: o
select case(prm%outputID(o))
associate(prm => param(damage_typeInstance(homog)))
case (damage_ID) outputsLoop: do o = 1,size(prm%output)
select case(prm%output(o))
case ('damage')
call results_writeDataset(group,damage(homog)%p,'phi',& call results_writeDataset(group,damage(homog)%p,'phi',&
'damage indicator','-') 'damage indicator','-')
end select end select