parallelExecution flag now passed as input variable by CPFEM_general; flag is set on the solver level (DAMASK_abaqus_exp.f, DAMASK_marc.f90, etc.)

This commit is contained in:
Christoph Kords 2013-08-02 11:20:11 +00:00
parent 4f9dbfa193
commit 7d2206356e
5 changed files with 27 additions and 24 deletions

View File

@ -39,14 +39,12 @@ module CPFEM
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_calc_done = .false. !< remember whether first IP has already calced the results
logical, private :: parallelExecution = .false.
integer(pInt), parameter, public :: &
CPFEM_CALCRESULTS = 2_pInt**0_pInt, &
CPFEM_AGERESULTS = 2_pInt**1_pInt, &
CPFEM_BACKUPJACOBIAN = 2_pInt**2_pInt, &
CPFEM_RESTOREJACOBIAN = 2_pInt**3_pInt, &
CPFEM_COLLECT = 2_pInt**4_pInt, &
CPFEM_EXPLICIT = 2_pInt**5_pInt
CPFEM_COLLECT = 2_pInt**4_pInt
public ::CPFEM_general, &
CPFEM_initAll
@ -144,8 +142,7 @@ subroutine CPFEM_init
IO_timeStamp, &
IO_error
use numerics, only: &
DAMASK_NumThreadsInt, &
usePingPong
DAMASK_NumThreadsInt
use debug, only: &
debug_level, &
debug_CPFEM, &
@ -250,7 +247,6 @@ subroutine CPFEM_init
write(6,'(a32,1x,6(i8,1x))') 'CPFEM_dcsdE: ', shape(CPFEM_dcsdE)
write(6,'(a32,1x,6(i8,1x))') 'CPFEM_dcsdE_knownGood: ', shape(CPFEM_dcsdE_knownGood)
write(6,*)
write(6,*) 'parallelExecution: ', parallelExecution
write(6,*) 'symmetricSolver: ', symmetricSolver
endif
flush(6)
@ -261,11 +257,10 @@ end subroutine CPFEM_init
!--------------------------------------------------------------------------------------------------
!> @brief perform initialization at first call, update variables and call the actual material model
!--------------------------------------------------------------------------------------------------
subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchyStress, jacobian)
subroutine CPFEM_general(mode, parallelExecution, ffn, ffn1, Temperature, dt, element, IP, cauchyStress, jacobian)
! note: cauchyStress = Cauchy stress cs(6) and jacobian = Consistent tangent dcs/dE
use numerics, only: defgradTolerance, &
iJacoStiffness, &
usePingPong
iJacoStiffness
use debug, only: debug_level, &
debug_CPFEM, &
debug_levelBasic, &
@ -341,6 +336,7 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt
real(pReal), dimension (3,3), intent(in) :: ffn, & !< deformation gradient for t=t0
ffn1 !< deformation gradient for t=t1
integer(pInt), intent(in) :: mode !< computation mode 1: regular computation plus aging of results
logical, intent(in) :: parallelExecution !< flag indicating parallel computation of requested IPs
real(pReal), dimension(6), intent(out), optional :: cauchyStress !< stress vector in Mandel notation
real(pReal), dimension(6,6), intent(out), optional :: jacobian !< jacobian in Mandel notation
@ -359,9 +355,12 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt
cp_en = mesh_FEasCP('elem',element)
if (iand(debug_level(debug_CPFEM), debug_levelBasic) /= 0_pInt .and. cp_en == 1 .and. IP == 1) then
if (iand(debug_level(debug_CPFEM), debug_levelBasic) /= 0_pInt &
.and. cp_en == debug_e .and. IP == debug_i) then
!$OMP CRITICAL (write2out)
write(6,'(/,a)') '#############################################'
write(6,'(a1,a22,1x,i8,a13)') '#','element', cp_en, '#'
write(6,'(a1,a22,1x,i8,a13)') '#','IP', IP, '#'
write(6,'(a1,a22,1x,f15.7,a6)') '#','theTime', theTime, '#'
write(6,'(a1,a22,1x,f15.7,a6)') '#','theDelta', theDelta, '#'
write(6,'(a1,a22,1x,i8,a13)') '#','theInc', theInc, '#'
@ -372,7 +371,6 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt
!$OMP END CRITICAL (write2out)
endif
parallelExecution = usePingPong .and. .not. (iand(mode, CPFEM_EXPLICIT) /= 0_pInt)
if (iand(mode, CPFEM_AGERESULTS) /= 0_pInt) then
crystallite_F0 = crystallite_partionedF ! crystallite deformation (_subF is perturbed...)

View File

@ -147,8 +147,7 @@ subroutine vumat(nBlock, nDir, nshr, nStateV, nFieldV, nProps, lAnneal, &
CPFEM_init_done, &
CPFEM_initAll, &
CPFEM_CALCRESULTS, &
CPFEM_AGERESULTS, &
CPFEM_EXPLICIT
CPFEM_AGERESULTS
use homogenization, only: &
materialpoint_sizeResults, &
materialpoint_results
@ -211,7 +210,7 @@ subroutine vumat(nBlock, nDir, nshr, nStateV, nFieldV, nProps, lAnneal, &
real(pReal) :: temp, timeInc
integer(pInt) :: computationMode, n, i, cp_en
computationMode = ior(CPFEM_CALCRESULTS,CPFEM_EXPLICIT) ! always calculate, always explicit
computationMode = CPFEM_CALCRESULTS ! always calculate
do n = 1,nblock(1) ! loop over vector of IPs
temp = tempOld(n)
if ( .not. CPFEM_init_done ) then
@ -284,7 +283,7 @@ subroutine vumat(nBlock, nDir, nshr, nStateV, nFieldV, nProps, lAnneal, &
cp_en = mesh_FEasCP('elem',nBlock(4_pInt+n))
mesh_ipCoordinates(1:3,n,cp_en) = mesh_unitlength * coordMp(n,1:3)
call CPFEM_general(computationMode,defgrd0,defgrd1,temp,timeInc,cp_en,nBlock(2),stress,ddsdde)
call CPFEM_general(computationMode,.false.,defgrd0,defgrd1,temp,timeInc,cp_en,nBlock(2),stress,ddsdde)
! Mandel: 11, 22, 33, SQRT(2)*12, SQRT(2)*23, SQRT(2)*13
! straight: 11, 22, 33, 12, 23, 13

View File

@ -122,6 +122,8 @@ subroutine UMAT(STRESS,STATEV,DDSDDE,SSE,SPD,SCD,&
use prec, only: &
pReal, &
pInt
use numerics, only: &
usePingPong
use FEsolving, only: &
cycleCounter, &
theInc, &
@ -311,7 +313,7 @@ subroutine UMAT(STRESS,STATEV,DDSDDE,SSE,SPD,SCD,&
!$OMP END CRITICAL (write2out)
endif
call CPFEM_general(computationMode,dfgrd0,dfgrd1,temperature,dtime,noel,npt,stress_h,ddsdde_h)
call CPFEM_general(computationMode,usePingPong,dfgrd0,dfgrd1,temperature,dtime,noel,npt,stress_h,ddsdde_h)
! Mandel: 11, 22, 33, SQRT(2)*12, SQRT(2)*23, SQRT(2)*13
! straight: 11, 22, 33, 12, 23, 13

View File

@ -173,7 +173,8 @@ subroutine hypela2(d,g,e,de,s,t,dt,ngens,m,nn,kcus,matus,ndi,nshear,disp, &
pInt
use numerics, only: &
!$ DAMASK_NumThreadsInt, &
numerics_unitlength
numerics_unitlength, &
usePingPong
use FEsolving, only: &
cycleCounter, &
theInc, &
@ -298,9 +299,10 @@ subroutine hypela2(d,g,e,de,s,t,dt,ngens,m,nn,kcus,matus,ndi,nshear,disp, &
!$ call omp_set_num_threads(DAMASK_NumThreadsInt) ! set number of threads for parallel execution set by DAMASK_NUM_THREADS
computationMode = 0_pInt ! save initialization value, since does not result in any calculation
if (lovl == 4 ) then
if(timinc < theDelta .and. theInc == inc ) computationMode = CPFEM_RESTOREJACOBIAN ! first after cutback
else ! stress requested (lovl == 6)
if (lovl == 4 ) then ! jacobian requested by marc
if (timinc < theDelta .and. theInc == inc) &
computationMode = CPFEM_RESTOREJACOBIAN ! first after cutback
else ! (lovl == 6) ! stress requested by marc
cp_en = mesh_FEasCP('elem',m(1))
if (cptim > theTime .or. inc /= theInc) then ! reached "convergence"
terminallyIll = .false.
@ -360,7 +362,7 @@ subroutine hypela2(d,g,e,de,s,t,dt,ngens,m,nn,kcus,matus,ndi,nshear,disp, &
computationMode = CPFEM_CALCRESULTS
endif
else ! now --- COLLECT ---
if ( lastMode /= calcMode(nn,cp_en) .and. & .not. terminallyIll) call debug_info() ! first after ping pong reports (meaningful) debugging
if ( lastMode /= calcMode(nn,cp_en) .and. & .not. terminallyIll) call debug_info() ! first after ping pong reports (meaningful) debugging
if ( lastIncConverged ) then
computationMode = ior(CPFEM_COLLECT,CPFEM_BACKUPJACOBIAN) ! collect and backup Jacobian after convergence
lastIncConverged = .false. ! reset flag
@ -379,7 +381,7 @@ subroutine hypela2(d,g,e,de,s,t,dt,ngens,m,nn,kcus,matus,ndi,nshear,disp, &
lastMode = calcMode(nn,cp_en) ! record calculationMode
endif
call CPFEM_general(computationMode,ffn,ffn1,t(1),timinc,m(1),nn,stress,ddsdde)
call CPFEM_general(computationMode,usePingPong,ffn,ffn1,t(1),timinc,m(1),nn,stress,ddsdde)
! Mandel: 11, 22, 33, SQRT(2)*12, SQRT(2)*23, SQRT(2)*13
! Marc: 11, 22, 33, 12, 23, 13

View File

@ -803,6 +803,8 @@ subroutine utilities_constitutiveResponse(F_lastInc,F,temperature,timeinc,&
use debug, only: &
debug_reset, &
debug_info
use numerics, only: &
usePingPong
use math, only: &
math_transpose33, &
math_rotate_forward33, &
@ -856,7 +858,7 @@ subroutine utilities_constitutiveResponse(F_lastInc,F,temperature,timeinc,&
calcMode = iand(calcMode, not(CPFEM_AGERESULTS))
endif
call CPFEM_general(collectMode,F_lastInc(1:3,1:3,1,1,1),F(1:3,1:3,1,1,1), & ! collect mode handles Jacobian backup / restoration
call CPFEM_general(collectMode,usePingPong,F_lastInc(1:3,1:3,1,1,1),F(1:3,1:3,1,1,1), & ! collect mode handles Jacobian backup / restoration
temperature,timeinc,1_pInt,1_pInt)
materialpoint_F0 = reshape(F_lastInc, [3,3,1,product(grid)])
@ -880,7 +882,7 @@ subroutine utilities_constitutiveResponse(F_lastInc,F,temperature,timeinc,&
flush(6)
endif
call CPFEM_general(calcMode,F_lastInc(1:3,1:3,1,1,1), F(1:3,1:3,1,1,1), & ! first call calculates everything
call CPFEM_general(calcMode,usePingPong,F_lastInc(1:3,1:3,1,1,1), F(1:3,1:3,1,1,1), & ! first call calculates everything
temperature,timeinc,1_pInt,1_pInt)
max_dPdF = 0.0_pReal