store damage parameter like temperature

This commit is contained in:
Martin Diehl 2021-01-24 18:20:47 +01:00
parent 26c7969837
commit b58465415b
3 changed files with 66 additions and 11 deletions

View File

@ -198,7 +198,6 @@ function grid_damage_spectral_solution(timeinc) result(solution)
do k = 1, grid3; do j = 1, grid(2); do i = 1,grid(1) do k = 1, grid3; do j = 1, grid(2); do i = 1,grid(1)
cell = cell + 1 cell = cell + 1
call damage_nonlocal_putNonLocalDamage(phi_current(i,j,k),1,cell) call damage_nonlocal_putNonLocalDamage(phi_current(i,j,k),1,cell)
homogenization_phi(cell) = phi_current(i,j,k)
enddo; enddo; enddo enddo; enddo; enddo
call VecMin(solution_vec,devNull,phi_min,ierr); CHKERRQ(ierr) call VecMin(solution_vec,devNull,phi_min,ierr); CHKERRQ(ierr)
@ -236,7 +235,6 @@ subroutine grid_damage_spectral_forward(cutBack)
do k = 1, grid3; do j = 1, grid(2); do i = 1,grid(1) do k = 1, grid3; do j = 1, grid(2); do i = 1,grid(1)
cell = cell + 1 cell = cell + 1
call damage_nonlocal_putNonLocalDamage(phi_current(i,j,k),1,cell) call damage_nonlocal_putNonLocalDamage(phi_current(i,j,k),1,cell)
homogenization_phi(cell) = phi_current(i,j,k)
enddo; enddo; enddo enddo; enddo; enddo
else else
phi_lastInc = phi_current phi_lastInc = phi_current

View File

@ -25,9 +25,6 @@ module homogenization
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! General variables for the homogenization at a material point ! General variables for the homogenization at a material point
real(pReal), dimension(:), allocatable, public :: &
homogenization_phi, &
homogenization_dot_phi
real(pReal), dimension(:,:,:), allocatable, public :: & real(pReal), dimension(:,:,:), allocatable, public :: &
homogenization_F0, & !< def grad of IP at start of FE increment homogenization_F0, & !< def grad of IP at start of FE increment
homogenization_F !< def grad of IP to be reached at end of FE increment homogenization_F !< def grad of IP to be reached at end of FE increment
@ -75,8 +72,7 @@ module homogenization
integer, intent(in) :: ce integer, intent(in) :: ce
end subroutine thermal_partition end subroutine thermal_partition
module subroutine damage_partition(phi,ce) module subroutine damage_partition(ce)
real(pReal), intent(in) :: phi
integer, intent(in) :: ce integer, intent(in) :: ce
end subroutine damage_partition end subroutine damage_partition
@ -330,6 +326,26 @@ subroutine materialpoint_stressAndItsTangent(dt,FEsolving_execIP,FEsolving_execE
enddo enddo
!$OMP END DO !$OMP END DO
!$OMP DO PRIVATE(ho,ph,ce)
do el = FEsolving_execElem(1),FEsolving_execElem(2)
if (terminallyIll) continue
ho = material_homogenizationAt(el)
do ip = FEsolving_execIP(1),FEsolving_execIP(2)
ce = (el-1)*discretization_nIPs + ip
call damage_partition(ce)
! do co = 1, homogenization_Nconstituents(ho)
! ph = material_phaseAt(co,el)
! if (.not. thermal_stress(dt,ph,material_phaseMemberAt(co,ip,el))) then
! if (.not. terminallyIll) & ! so first signals terminally ill...
! print*, ' Integration point ', ip,' at element ', el, ' terminally ill'
! terminallyIll = .true. ! ...and kills all others
! endif
! call thermal_homogenize(ip,el)
! enddo
enddo
enddo
!$OMP END DO
!$OMP DO PRIVATE(ho) !$OMP DO PRIVATE(ho)
elementLooping3: do el = FEsolving_execElem(1),FEsolving_execElem(2) elementLooping3: do el = FEsolving_execElem(1),FEsolving_execElem(2)
ho = material_homogenizationAt(el) ho = material_homogenizationAt(el)

View File

@ -3,19 +3,58 @@
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
submodule(homogenization) homogenization_damage submodule(homogenization) homogenization_damage
type :: tDataContainer
real(pReal), dimension(:), allocatable :: phi
end type tDataContainer
type(tDataContainer), dimension(:), allocatable :: current
type :: tParameters
character(len=pStringLen), allocatable, dimension(:) :: &
output
end type tParameters
type(tparameters), dimension(:), allocatable :: &
param
contains contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief Allocate variables and set parameters. !> @brief Allocate variables and set parameters.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine damage_init() module subroutine damage_init()
class(tNode), pointer :: &
configHomogenizations, &
configHomogenization, &
configHomogenizationDamage
integer :: ho
print'(/,a)', ' <<<+- homogenization_damage init -+>>>' print'(/,a)', ' <<<+- homogenization_damage init -+>>>'
allocate(homogenization_phi(discretization_nIPs*discretization_Nelems))
allocate(homogenization_dot_phi(discretization_nIPs*discretization_Nelems)) configHomogenizations => config_material%get('homogenization')
allocate(param(configHomogenizations%length))
allocate(current(configHomogenizations%length))
do ho = 1, configHomogenizations%length
allocate(current(ho)%phi(count(material_homogenizationAt2==ho)), source=1.0_pReal)
configHomogenization => configHomogenizations%get(ho)
associate(prm => param(ho))
if (configHomogenization%contains('damage')) then
configHomogenizationDamage => configHomogenization%get('damage')
#if defined (__GFORTRAN__)
prm%output = output_asStrings(configHomogenizationDamage)
#else
prm%output = configHomogenizationDamage%get_asStrings('output',defaultVal=emptyStringArray)
#endif
else
prm%output = emptyStringArray
endif
end associate
enddo
end subroutine damage_init end subroutine damage_init
@ -23,13 +62,15 @@ end subroutine damage_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief Partition temperature onto the individual constituents. !> @brief Partition temperature onto the individual constituents.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine damage_partition(phi,ce) module subroutine damage_partition(ce)
real(pReal), intent(in) :: phi real(pReal) :: phi
integer, intent(in) :: ce integer, intent(in) :: ce
integer :: co integer :: co
phi = current(material_homogenizationAt2(ce))%phi(material_homogenizationMemberAt2(ce))
do co = 1, homogenization_Nconstituents(material_homogenizationAt2(ce)) do co = 1, homogenization_Nconstituents(material_homogenizationAt2(ce))
call constitutive_damage_set_phi(phi,co,ce) call constitutive_damage_set_phi(phi,co,ce)
enddo enddo