more sensible location

This commit is contained in:
Martin Diehl 2021-01-25 15:13:17 +01:00
parent 2533e0616d
commit 8b11af0d84
3 changed files with 74 additions and 76 deletions

View File

@ -14,26 +14,17 @@ module damage_nonlocal
implicit none
private
type :: tParameters
character(len=pStringLen), allocatable, dimension(:) :: &
output
end type tParameters
type, private :: tNumerics
real(pReal) :: &
charLength !< characteristic length scale for gradient problems
end type tNumerics
type(tparameters), dimension(:), allocatable :: &
param
type(tNumerics), private :: &
num
public :: &
damage_nonlocal_init, &
damage_nonlocal_getDiffusion, &
damage_nonlocal_putNonLocalDamage, &
damage_nonlocal_results
damage_nonlocal_getDiffusion
contains
@ -46,9 +37,7 @@ subroutine damage_nonlocal_init
integer :: Ninstances,Nmaterialpoints,h
class(tNode), pointer :: &
num_generic, &
material_homogenization, &
homog, &
homogDamage
material_homogenization
print'(/,a)', ' <<<+- damage_nonlocal init -+>>>'; flush(6)
@ -58,20 +47,10 @@ subroutine damage_nonlocal_init
num%charLength = num_generic%get_asFloat('charLength',defaultVal=1.0_pReal)
Ninstances = count(damage_type == DAMAGE_nonlocal_ID)
allocate(param(Ninstances))
material_homogenization => config_material%get('homogenization')
do h = 1, material_homogenization%length
if (damage_type(h) /= DAMAGE_NONLOCAL_ID) cycle
homog => material_homogenization%get(h)
homogDamage => homog%get('damage')
associate(prm => param(damage_typeInstance(h)))
#if defined (__GFORTRAN__)
prm%output = output_asStrings(homogDamage)
#else
prm%output = homogDamage%get_asStrings('output',defaultVal=emptyStringArray)
#endif
Nmaterialpoints = count(material_homogenizationAt == h)
damageState_h(h)%sizeState = 1
@ -81,7 +60,6 @@ subroutine damage_nonlocal_init
damage(h)%p => damageState_h(h)%state(1,:)
end associate
enddo
end subroutine damage_nonlocal_init
@ -114,47 +92,4 @@ function damage_nonlocal_getDiffusion(ip,el)
end function damage_nonlocal_getDiffusion
!--------------------------------------------------------------------------------------------------
!> @brief updated nonlocal damage field with solution from damage phase field PDE
!--------------------------------------------------------------------------------------------------
subroutine damage_nonlocal_putNonLocalDamage(phi,ip,el)
integer, intent(in) :: &
ip, & !< integration point number
el !< element number
real(pReal), intent(in) :: &
phi
integer :: &
homog, &
offset
homog = material_homogenizationAt(el)
offset = material_homogenizationMemberAt(ip,el)
damage(homog)%p(offset) = phi
end subroutine damage_nonlocal_putNonLocalDamage
!--------------------------------------------------------------------------------------------------
!> @brief writes results to HDF5 output file
!--------------------------------------------------------------------------------------------------
subroutine damage_nonlocal_results(homog,group)
integer, intent(in) :: homog
character(len=*), intent(in) :: group
integer :: o
associate(prm => param(damage_typeInstance(homog)))
outputsLoop: do o = 1,size(prm%output)
select case(prm%output(o))
case ('phi')
call results_writeDataset(group,damage(homog)%p,prm%output(o),&
'damage indicator','-')
end select
enddo outputsLoop
end associate
end subroutine damage_nonlocal_results
end module damage_nonlocal

View File

@ -154,16 +154,34 @@ module homogenization
real(pReal) :: M
end function damage_nonlocal_getMobility
module subroutine damage_nonlocal_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el)
module subroutine damage_nonlocal_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el)
integer, intent(in) :: &
ip, & !< integration point number
el !< element number
real(pReal), intent(in) :: &
phi
real(pReal) :: &
phiDot, dPhiDot_dPhi
end subroutine damage_nonlocal_getSourceAndItsTangent
integer, intent(in) :: &
ip, & !< integration point number
el !< element number
real(pReal), intent(in) :: &
phi
real(pReal) :: &
phiDot, dPhiDot_dPhi
end subroutine damage_nonlocal_getSourceAndItsTangent
module subroutine damage_nonlocal_putNonLocalDamage(phi,ip,el)
integer, intent(in) :: &
ip, & !< integration point number
el !< element number
real(pReal), intent(in) :: &
phi
end subroutine damage_nonlocal_putNonLocalDamage
module subroutine damage_nonlocal_results(homog,group)
integer, intent(in) :: homog
character(len=*), intent(in) :: group
end subroutine damage_nonlocal_results
end interface
public :: &
@ -175,6 +193,7 @@ end subroutine damage_nonlocal_getSourceAndItsTangent
thermal_conduction_getSource, &
damage_nonlocal_getMobility, &
damage_nonlocal_getSourceAndItsTangent, &
damage_nonlocal_putNonLocalDamage, &
homogenization_thermal_setfield, &
homogenization_thermal_T, &
homogenization_forward, &

View File

@ -126,4 +126,48 @@ module subroutine damage_nonlocal_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, p
end subroutine damage_nonlocal_getSourceAndItsTangent
!--------------------------------------------------------------------------------------------------
!> @brief updated nonlocal damage field with solution from damage phase field PDE
!--------------------------------------------------------------------------------------------------
module subroutine damage_nonlocal_putNonLocalDamage(phi,ip,el)
integer, intent(in) :: &
ip, & !< integration point number
el !< element number
real(pReal), intent(in) :: &
phi
integer :: &
homog, &
offset
homog = material_homogenizationAt(el)
offset = material_homogenizationMemberAt(ip,el)
damage(homog)%p(offset) = phi
end subroutine damage_nonlocal_putNonLocalDamage
!--------------------------------------------------------------------------------------------------
!> @brief writes results to HDF5 output file
!--------------------------------------------------------------------------------------------------
module subroutine damage_nonlocal_results(homog,group)
integer, intent(in) :: homog
character(len=*), intent(in) :: group
integer :: o
associate(prm => param(damage_typeInstance(homog)))
outputsLoop: do o = 1,size(prm%output)
select case(prm%output(o))
case ('phi')
call results_writeDataset(group,damage(homog)%p,prm%output(o),&
'damage indicator','-')
end select
enddo outputsLoop
end associate
end subroutine damage_nonlocal_results
end submodule homogenization_damage