further improvements on implementing the plain mode
This commit is contained in:
parent
d751283b4a
commit
8b2d9d8155
|
@ -39,7 +39,7 @@ module CPFEM
|
||||||
logical :: CPFEM_init_done = .false., & !< remember whether init has been done already
|
logical :: CPFEM_init_done = .false., & !< remember whether init has been done already
|
||||||
CPFEM_init_inProgress = .false., & !< remember whether first IP is currently performing init
|
CPFEM_init_inProgress = .false., & !< remember whether first IP is currently performing init
|
||||||
CPFEM_calc_done = .false. !< remember whether first IP has already calced the results
|
CPFEM_calc_done = .false. !< remember whether first IP has already calced the results
|
||||||
logical, public, protected :: usePingPong = .false.
|
logical, private :: parallelExecution = .false.
|
||||||
integer(pInt), parameter, public :: &
|
integer(pInt), parameter, public :: &
|
||||||
CPFEM_CALCRESULTS = 2_pInt**0_pInt, &
|
CPFEM_CALCRESULTS = 2_pInt**0_pInt, &
|
||||||
CPFEM_AGERESULTS = 2_pInt**1_pInt, &
|
CPFEM_AGERESULTS = 2_pInt**1_pInt, &
|
||||||
|
@ -144,20 +144,19 @@ subroutine CPFEM_init
|
||||||
IO_timeStamp, &
|
IO_timeStamp, &
|
||||||
IO_error
|
IO_error
|
||||||
use numerics, only: &
|
use numerics, only: &
|
||||||
DAMASK_NumThreadsInt
|
DAMASK_NumThreadsInt, &
|
||||||
|
usePingPong
|
||||||
use debug, only: &
|
use debug, only: &
|
||||||
debug_level, &
|
debug_level, &
|
||||||
debug_CPFEM, &
|
debug_CPFEM, &
|
||||||
debug_levelBasic, &
|
debug_levelBasic, &
|
||||||
debug_levelExtensive
|
debug_levelExtensive
|
||||||
use FEsolving, only: &
|
use FEsolving, only: &
|
||||||
parallelExecution, &
|
|
||||||
symmetricSolver, &
|
symmetricSolver, &
|
||||||
restartRead, &
|
restartRead, &
|
||||||
modelName
|
modelName
|
||||||
use mesh, only: &
|
use mesh, only: &
|
||||||
mesh_NcpElems, &
|
mesh_NcpElems, &
|
||||||
mesh_Nelems, &
|
|
||||||
mesh_maxNips
|
mesh_maxNips
|
||||||
use material, only: &
|
use material, only: &
|
||||||
homogenization_maxNgrains, &
|
homogenization_maxNgrains, &
|
||||||
|
@ -183,10 +182,6 @@ subroutine CPFEM_init
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||||
#include "compilation_info.f90"
|
#include "compilation_info.f90"
|
||||||
|
|
||||||
if (any(.not. crystallite_localPlasticity) .and. (mesh_Nelems /= mesh_NcpElems)) call IO_error(600)
|
|
||||||
if ((DAMASK_NumThreadsInt > 1_pInt) .and. (mesh_Nelems /= mesh_NcpElems)) call IO_error(601)
|
|
||||||
usePingPong = (any(.not. crystallite_localPlasticity) .or. (DAMASK_NumThreadsInt > 1_pInt))
|
|
||||||
|
|
||||||
! initialize stress and jacobian to zero
|
! initialize stress and jacobian to zero
|
||||||
allocate(CPFEM_cs(6,mesh_maxNips,mesh_NcpElems)) ; CPFEM_cs = 0.0_pReal
|
allocate(CPFEM_cs(6,mesh_maxNips,mesh_NcpElems)) ; CPFEM_cs = 0.0_pReal
|
||||||
allocate(CPFEM_dcsdE(6,6,mesh_maxNips,mesh_NcpElems)) ; CPFEM_dcsdE = 0.0_pReal
|
allocate(CPFEM_dcsdE(6,6,mesh_maxNips,mesh_NcpElems)) ; CPFEM_dcsdE = 0.0_pReal
|
||||||
|
@ -269,7 +264,8 @@ end subroutine CPFEM_init
|
||||||
subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchyStress, jacobian)
|
subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchyStress, jacobian)
|
||||||
! note: cauchyStress = Cauchy stress cs(6) and jacobian = Consistent tangent dcs/dE
|
! note: cauchyStress = Cauchy stress cs(6) and jacobian = Consistent tangent dcs/dE
|
||||||
use numerics, only: defgradTolerance, &
|
use numerics, only: defgradTolerance, &
|
||||||
iJacoStiffness
|
iJacoStiffness, &
|
||||||
|
usePingPong
|
||||||
use debug, only: debug_level, &
|
use debug, only: debug_level, &
|
||||||
debug_CPFEM, &
|
debug_CPFEM, &
|
||||||
debug_levelBasic, &
|
debug_levelBasic, &
|
||||||
|
@ -285,8 +281,7 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt
|
||||||
debug_stressMin, &
|
debug_stressMin, &
|
||||||
debug_jacobianMax, &
|
debug_jacobianMax, &
|
||||||
debug_jacobianMin
|
debug_jacobianMin
|
||||||
use FEsolving, only: parallelExecution, &
|
use FEsolving, only: outdatedFFN1, &
|
||||||
outdatedFFN1, &
|
|
||||||
terminallyIll, &
|
terminallyIll, &
|
||||||
cycleCounter, &
|
cycleCounter, &
|
||||||
theInc, &
|
theInc, &
|
||||||
|
@ -377,6 +372,8 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt
|
||||||
!$OMP END CRITICAL (write2out)
|
!$OMP END CRITICAL (write2out)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
|
parallelExecution = usePingPong .and. .not. (iand(mode, CPFEM_EXPLICIT) /= 0_pInt)
|
||||||
|
|
||||||
if (iand(mode, CPFEM_AGERESULTS) /= 0_pInt) then
|
if (iand(mode, CPFEM_AGERESULTS) /= 0_pInt) then
|
||||||
crystallite_F0 = crystallite_partionedF ! crystallite deformation (_subF is perturbed...)
|
crystallite_F0 = crystallite_partionedF ! crystallite deformation (_subF is perturbed...)
|
||||||
crystallite_Fp0 = crystallite_Fp ! crystallite plastic deformation
|
crystallite_Fp0 = crystallite_Fp ! crystallite plastic deformation
|
||||||
|
@ -513,6 +510,14 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt
|
||||||
!$OMP END CRITICAL (write2out)
|
!$OMP END CRITICAL (write2out)
|
||||||
endif
|
endif
|
||||||
call materialpoint_stressAndItsTangent(updateJaco, dt) ! calculate stress and its tangent
|
call materialpoint_stressAndItsTangent(updateJaco, dt) ! calculate stress and its tangent
|
||||||
|
!$OMP CRITICAL (write2out)
|
||||||
|
write(6,'(a,i8,1x,i2)') '<< CPFEM >> calculation for el ip ',cp_en,IP
|
||||||
|
flush(6)
|
||||||
|
!$OMP END CRITICAL (write2out)
|
||||||
|
!$OMP CRITICAL (write2out)
|
||||||
|
write(6,'(a,i8,1x,i2)') '<< CPFEM >> calculation for el ip ',cp_en,IP
|
||||||
|
flush(6)
|
||||||
|
!$OMP END CRITICAL (write2out)
|
||||||
call materialpoint_postResults(dt) ! post results
|
call materialpoint_postResults(dt) ! post results
|
||||||
endif
|
endif
|
||||||
|
|
||||||
|
@ -559,7 +564,7 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt
|
||||||
0.5_pReal * (math_I3(i,k) * Kirchhoff(j,l) + math_I3(j,l) * Kirchhoff(i,k) + &
|
0.5_pReal * (math_I3(i,k) * Kirchhoff(j,l) + math_I3(j,l) * Kirchhoff(i,k) + &
|
||||||
math_I3(i,l) * Kirchhoff(j,k) + math_I3(j,k) * Kirchhoff(i,l))
|
math_I3(i,l) * Kirchhoff(j,k) + math_I3(j,k) * Kirchhoff(i,l))
|
||||||
enddo; enddo; enddo; enddo; enddo; enddo
|
enddo; enddo; enddo; enddo; enddo; enddo
|
||||||
do i=1,3; do j=1,3; do k=1,3; do l=1,3
|
do i=1,3; do j=1,3; do k=1,3; do l=1,3 !< @ToDo use forall
|
||||||
H_sym(i,j,k,l) = 0.25_pReal * (H(i,j,k,l) + H(j,i,k,l) + H(i,j,l,k) + H(j,i,l,k))
|
H_sym(i,j,k,l) = 0.25_pReal * (H(i,j,k,l) + H(j,i,k,l) + H(i,j,l,k) + H(j,i,l,k))
|
||||||
enddo; enddo; enddo; enddo
|
enddo; enddo; enddo; enddo
|
||||||
CPFEM_dcsde(1:6,1:6,IP,cp_en) = math_Mandel3333to66(J_inverse * H_sym)
|
CPFEM_dcsde(1:6,1:6,IP,cp_en) = math_Mandel3333to66(J_inverse * H_sym)
|
||||||
|
@ -589,7 +594,7 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt
|
||||||
Temperature = materialpoint_Temperature(IP,cp_en) ! homogenized result except for potentially non-isothermal starting condition.
|
Temperature = materialpoint_Temperature(IP,cp_en) ! homogenized result except for potentially non-isothermal starting condition.
|
||||||
endif
|
endif
|
||||||
|
|
||||||
if (mode < 3 .and. iand(debug_level(debug_CPFEM), debug_levelExtensive) /= 0_pInt &
|
if (mode < 3 .and. iand(debug_level(debug_CPFEM), debug_levelExtensive) /= 0_pInt & !< @ToDo mode 3 doesn't exist any more
|
||||||
.and. ((debug_e == cp_en .and. debug_i == IP) &
|
.and. ((debug_e == cp_en .and. debug_i == IP) &
|
||||||
.or. .not. iand(debug_level(debug_CPFEM), debug_levelSelective) /= 0_pInt)) then
|
.or. .not. iand(debug_level(debug_CPFEM), debug_levelSelective) /= 0_pInt)) then
|
||||||
!$OMP CRITICAL (write2out)
|
!$OMP CRITICAL (write2out)
|
||||||
|
|
|
@ -45,7 +45,6 @@ module FEsolving
|
||||||
restartWrite = .false., & !< write current state to enable restart
|
restartWrite = .false., & !< write current state to enable restart
|
||||||
restartRead = .false., & !< restart information to continue calculation from saved state
|
restartRead = .false., & !< restart information to continue calculation from saved state
|
||||||
terminallyIll = .false., & !< at least one material point is terminally ill
|
terminallyIll = .false., & !< at least one material point is terminally ill
|
||||||
parallelExecution = .true., & !< OpenMP multicore calculation
|
|
||||||
lastMode = .true., & !< toDo
|
lastMode = .true., & !< toDo
|
||||||
lastIncConverged = .false., & !< toDo
|
lastIncConverged = .false., & !< toDo
|
||||||
outdatedByNewInc = .false. !< toDo
|
outdatedByNewInc = .false. !< toDo
|
||||||
|
|
|
@ -1515,9 +1515,9 @@ subroutine IO_error(error_ID,e,i,g,ext_msg)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! user errors
|
! user errors
|
||||||
case (600_pInt)
|
case (600_pInt)
|
||||||
msg = 'Cannot combine Non-local plasticity and non-DAMASK elements'
|
msg = 'Ping-Pong not possible when using non-DAMASK elements'
|
||||||
case (601_pInt)
|
case (601_pInt)
|
||||||
msg = 'Cannot combine OpenMP threading and non-DAMASK elements'
|
msg = 'Ping-Pong needed when using non-local plasticity'
|
||||||
|
|
||||||
!-------------------------------------------------------------------------------------------------
|
!-------------------------------------------------------------------------------------------------
|
||||||
! DAMASK_marc errors
|
! DAMASK_marc errors
|
||||||
|
|
|
@ -127,6 +127,8 @@ subroutine crystallite_init(Temperature)
|
||||||
debug_level, &
|
debug_level, &
|
||||||
debug_crystallite, &
|
debug_crystallite, &
|
||||||
debug_levelBasic
|
debug_levelBasic
|
||||||
|
use numerics, only: &
|
||||||
|
usePingPong
|
||||||
use math, only: math_I3, &
|
use math, only: math_I3, &
|
||||||
math_EulerToR, &
|
math_EulerToR, &
|
||||||
math_inv33, &
|
math_inv33, &
|
||||||
|
@ -335,6 +337,9 @@ do e = FEsolving_execElem(1),FEsolving_execElem(2)
|
||||||
crystallite_requested(g,i,e) = .true.
|
crystallite_requested(g,i,e) = .true.
|
||||||
endforall
|
endforall
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
if(any(.not. crystallite_localPlasticity) .and. .not. usePingPong) call IO_error(601)
|
||||||
|
|
||||||
crystallite_partionedTemperature0 = Temperature ! isothermal assumption
|
crystallite_partionedTemperature0 = Temperature ! isothermal assumption
|
||||||
crystallite_partionedFp0 = crystallite_Fp0
|
crystallite_partionedFp0 = crystallite_Fp0
|
||||||
crystallite_partionedF0 = crystallite_F0
|
crystallite_partionedF0 = crystallite_F0
|
||||||
|
@ -1158,7 +1163,7 @@ if(updateJaco) then
|
||||||
|
|
||||||
do e = FEsolving_execElem(1),FEsolving_execElem(2)
|
do e = FEsolving_execElem(1),FEsolving_execElem(2)
|
||||||
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
||||||
select case(perturbation)
|
select case(perturbation) !< @ToDo: what's going on here
|
||||||
case(1_pInt)
|
case(1_pInt)
|
||||||
forall (i = FEsolving_execIP(1,e):FEsolving_execIP(2,e), g = 1:myNgrains, &
|
forall (i = FEsolving_execIP(1,e):FEsolving_execIP(2,e), g = 1:myNgrains, &
|
||||||
crystallite_requested(g,i,e) .and. crystallite_converged(g,i,e)) & ! converged state warrants stiffness update
|
crystallite_requested(g,i,e) .and. crystallite_converged(g,i,e)) & ! converged state warrants stiffness update
|
||||||
|
|
|
@ -468,6 +468,7 @@ subroutine mesh_init(ip,el)
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
||||||
use IO, only: &
|
use IO, only: &
|
||||||
IO_timeStamp, &
|
IO_timeStamp, &
|
||||||
|
IO_error, &
|
||||||
#ifdef Abaqus
|
#ifdef Abaqus
|
||||||
IO_abaqus_hasNoPart, &
|
IO_abaqus_hasNoPart, &
|
||||||
#endif
|
#endif
|
||||||
|
@ -478,9 +479,9 @@ subroutine mesh_init(ip,el)
|
||||||
#else
|
#else
|
||||||
IO_open_InputFile
|
IO_open_InputFile
|
||||||
#endif
|
#endif
|
||||||
|
use numerics, only: &
|
||||||
|
usePingPong
|
||||||
use FEsolving, only: &
|
use FEsolving, only: &
|
||||||
parallelExecution, &
|
|
||||||
FEsolving_execElem, &
|
FEsolving_execElem, &
|
||||||
FEsolving_execIP, &
|
FEsolving_execIP, &
|
||||||
calcMode, &
|
calcMode, &
|
||||||
|
@ -590,7 +591,7 @@ subroutine mesh_init(ip,el)
|
||||||
call mesh_build_ipNeighborhood
|
call mesh_build_ipNeighborhood
|
||||||
call mesh_tell_statistics
|
call mesh_tell_statistics
|
||||||
|
|
||||||
parallelExecution = (parallelExecution .and. (mesh_Nelems == mesh_NcpElems)) ! plus potential killer from non-local constitutive
|
if (usePingPong .and. (mesh_Nelems /= mesh_NcpElems)) call IO_error(600_pInt) ! ping-pong must be disabled when havin non-DAMASK-elements
|
||||||
|
|
||||||
FEsolving_execElem = [ 1_pInt,mesh_NcpElems ]
|
FEsolving_execElem = [ 1_pInt,mesh_NcpElems ]
|
||||||
if (allocated(FEsolving_execIP)) deallocate(FEsolving_execIP)
|
if (allocated(FEsolving_execIP)) deallocate(FEsolving_execIP)
|
||||||
|
|
|
@ -78,6 +78,7 @@ module numerics
|
||||||
volDiscrPow_RGC = 5.0_pReal !< powerlaw penalty for volume discrepancy
|
volDiscrPow_RGC = 5.0_pReal !< powerlaw penalty for volume discrepancy
|
||||||
logical, protected, public :: &
|
logical, protected, public :: &
|
||||||
analyticJaco = .false., & !< use analytic Jacobian or perturbation, Default .false.: calculate Jacobian using perturbations
|
analyticJaco = .false., & !< use analytic Jacobian or perturbation, Default .false.: calculate Jacobian using perturbations
|
||||||
|
usePingPong = .true., &
|
||||||
numerics_timeSyncing = .false. !< flag indicating if time synchronization in crystallite is used for nonlocal plasticity
|
numerics_timeSyncing = .false. !< flag indicating if time synchronization in crystallite is used for nonlocal plasticity
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
|
Loading…
Reference in New Issue