harmonize status reporting

This commit is contained in:
Martin Diehl 2024-01-09 12:03:25 +01:00
parent 70e720c032
commit 845d3eed33
No known key found for this signature in database
GPG Key ID: 1FD50837275A0A9B
5 changed files with 29 additions and 21 deletions

View File

@ -20,6 +20,7 @@ module materialpoint_Marc
use material
use phase
use homogenization
use constants
use discretization
use discretization_Marc
@ -27,18 +28,18 @@ module materialpoint_Marc
implicit none(type,external)
private
real(pREAL), dimension (:,:,:), allocatable, private :: &
real(pREAL), dimension (:,:,:), allocatable :: &
materialpoint_cs !< Cauchy stress
real(pREAL), dimension (:,:,:,:), allocatable, private :: &
real(pREAL), dimension (:,:,:,:), allocatable :: &
materialpoint_dcsdE, & !< Cauchy stress tangent
materialpoint_F !< deformation gradient
real(pREAL), dimension (:,:,:,:), allocatable, private :: &
real(pREAL), dimension (:,:,:,:), allocatable :: &
materialpoint_dcsdE_knownGood !< known good tangent
integer, public :: &
cycleCounter = 0 !< needs description
logical, public :: &
broken = .false. !< needs description
integer(kind(STATUS_OK)) :: &
status
integer, parameter, public :: &
materialpoint_CALCRESULTS = 2**0, &
@ -150,17 +151,17 @@ subroutine materialpoint_general(mode, ffn, ffn1, temperature_inp, dt, elFE, ip,
if (iand(mode, materialpoint_CALCRESULTS) /= 0) then
validCalculation: if (broken) then
validCalculation: if (status /= STATUS_OK) then
call random_number(rnd)
if (rnd < 0.5_pREAL) rnd = rnd - 1.0_pREAL
materialpoint_cs(1:6,ip,elCP) = ODD_STRESS * rnd
materialpoint_dcsde(1:6,1:6,ip,elCP) = ODD_JACOBIAN * math_eye(6)
else validCalculation
call homogenization_mechanical_response(broken, &
call homogenization_mechanical_response(status, &
dt,(elCP-1)*discretization_nIPs + ip, (elCP-1)*discretization_nIPs + ip)
terminalIllness: if (broken) then
terminalIllness: if (status /= STATUS_OK) then
call random_number(rnd)
if (rnd < 0.5_pREAL) rnd = rnd - 1.0_pREAL

View File

@ -26,7 +26,9 @@ module constants
STATUS_FAILED_PHASE_DELTASTATE, &
STATUS_FAILED_PHASE_STRESS, &
STATUS_FAILED_DAMAGE_STATE, &
STATUS_FAILED_DAMAGE_DELTASTATE
STATUS_FAILED_DAMAGE_DELTASTATE, &
STATUS_FAILED_DAMAGE, &
STATUS_FAILED_MECHANICAL
end enum
end module constants

View File

@ -18,7 +18,7 @@ module grid_mech_utilities
use discretization
use spectral_utilities
use homogenization
use constants
#if (PETSC_VERSION_MAJOR==3 && PETSC_VERSION_MINOR>14) && !defined(PETSC_HAVE_MPI_F90MODULE_VISIBILITY)
implicit none(type,external)
@ -129,6 +129,7 @@ subroutine utilities_constitutiveResponse(broken, P,P_av,C_volAvg,C_minmaxAvg,&
real(pREAL), dimension(3,3,3,3) :: dPdF_max, dPdF_min
real(pREAL) :: dPdF_norm_max, dPdF_norm_min
real(pREAL), dimension(2) :: valueAndRank !< pair of min/max norm of dPdF to synchronize min/max of dPdF
integer(kind(STATUS_OK)) :: status
print'(/,1x,a)', '... evaluating constitutive response ......................................'
@ -136,7 +137,8 @@ subroutine utilities_constitutiveResponse(broken, P,P_av,C_volAvg,C_minmaxAvg,&
homogenization_F = reshape(F,[3,3,product(cells(1:2))*cells3]) ! set materialpoint target F to estimated field
call homogenization_mechanical_response(broken,Delta_t,1,product(cells(1:2))*cells3) ! calculate P field
call homogenization_mechanical_response(status,Delta_t,1,product(cells(1:2))*cells3) ! calculate P field
broken = STATUS_OK /= status
P = reshape(homogenization_P, [3,3,cells(1),cells(2),cells3])
P_av = sum(sum(sum(P,dim=5),dim=4),dim=3) * wgt

View File

@ -210,9 +210,9 @@ end subroutine homogenization_init
!--------------------------------------------------------------------------------------------------
!> @brief
!--------------------------------------------------------------------------------------------------
subroutine homogenization_mechanical_response(broken,Delta_t,cell_start,cell_end)
subroutine homogenization_mechanical_response(status,Delta_t,cell_start,cell_end)
logical, intent(out) :: broken
integer(kind(STATUS_OK)), intent(out) :: status
real(pREAL), intent(in) :: Delta_t !< time increment
integer, intent(in) :: &
cell_start, cell_end
@ -224,7 +224,7 @@ subroutine homogenization_mechanical_response(broken,Delta_t,cell_start,cell_end
doneAndHappy
broken = .false.
status = STATUS_OK
!$OMP PARALLEL DO PRIVATE(en,ho,co,converged,doneAndHappy)
do ce = cell_start, cell_end
@ -239,7 +239,7 @@ subroutine homogenization_mechanical_response(broken,Delta_t,cell_start,cell_end
doneAndHappy = [.false.,.true.]
convergenceLooping: do while (.not. (broken .or. doneAndHappy(1)))
convergenceLooping: do while (.not. (status /= STATUS_OK .or. doneAndHappy(1)))
call mechanical_partition(homogenization_F(1:3,1:3,ce),ce)
converged = all([(phase_mechanical_constitutive(Delta_t,co,ce),co=1,homogenization_Nconstituents(ho))])
@ -251,19 +251,19 @@ subroutine homogenization_mechanical_response(broken,Delta_t,cell_start,cell_end
end if
end do convergenceLooping
if (.not. converged) then
if (.not. broken) print*, ' Cell ', ce, ' failed (mechanics)'
broken = .true.
if (status == STATUS_OK) print*, ' Cell ', ce, ' failed (mechanics)'
status = STATUS_FAILED_MECHANICAL
end if
converged = converged .and. all([(phase_damage_constitutive(Delta_t,co,ce),co=1,homogenization_Nconstituents(ho))])
if (.not. converged) then
if (.not. broken) print*, ' Cell ', ce, ' failed (damage)'
broken = .true.
if (status == STATUS_OK) print*, ' Cell ', ce, ' failed (damage)'
status = STATUS_FAILED_DAMAGE
end if
end do
!$OMP END PARALLEL DO
if (broken) return
if (status /= STATUS_OK) return
!$OMP PARALLEL DO PRIVATE(ho)
do ce = cell_start, cell_end

View File

@ -22,6 +22,7 @@ module FEM_utilities
use discretization_mesh
use homogenization
use FEM_quadrature
use constants
#if (PETSC_VERSION_MAJOR==3 && PETSC_VERSION_MINOR>14) && !defined(PETSC_HAVE_MPI_F90MODULE_VISIBILITY)
implicit none(type,external)
@ -128,11 +129,13 @@ subroutine utilities_constitutiveResponse(broken, Delta_t,P_av,forwardData)
real(pREAL),intent(out), dimension(3,3) :: P_av !< average PK stress
integer(MPI_INTEGER_KIND) :: err_MPI
integer(kind(STATUS_OK)) :: status
print'(/,1x,a)', '... evaluating constitutive response ......................................'
call homogenization_mechanical_response(broken,Delta_t,1,mesh_maxNips*mesh_NcpElems) ! calculate P field
call homogenization_mechanical_response(status,Delta_t,1,mesh_maxNips*mesh_NcpElems) ! calculate P field
broken = STATUS_OK /= status
cutBack = .false.
P_av = sum(homogenization_P,dim=3) * wgt