This commit is contained in:
Martin Diehl 2020-06-11 08:51:17 +02:00
parent 579ced6a52
commit e5c9380bac
3 changed files with 7 additions and 25 deletions

View File

@ -43,7 +43,6 @@ module CPFEM
theTime = 0.0_pReal, & !< needs description theTime = 0.0_pReal, & !< needs description
theDelta = 0.0_pReal theDelta = 0.0_pReal
logical, public :: & logical, public :: &
outdatedFFN1 = .false., & !< needs description
lastIncConverged = .false., & !< needs description lastIncConverged = .false., & !< needs description
outdatedByNewInc = .false. !< needs description outdatedByNewInc = .false. !< needs description
@ -68,12 +67,9 @@ contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief call (thread safe) all module initializations !> @brief call all module initializations
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine CPFEM_initAll(el,ip) subroutine CPFEM_initAll
integer(pInt), intent(in) :: el, & !< FE el number
ip !< FE integration point number
CPFEM_init_done = .true. CPFEM_init_done = .true.
call DAMASK_interface_init call DAMASK_interface_init
@ -88,7 +84,7 @@ subroutine CPFEM_initAll(el,ip)
call YAML_init call YAML_init
call HDF5_utilities_init call HDF5_utilities_init
call results_init(.false.) call results_init(.false.)
call discretization_marc_init(ip, el) call discretization_marc_init
call lattice_init call lattice_init
call material_init(.false.) call material_init(.false.)
call constitutive_init call constitutive_init
@ -187,7 +183,7 @@ subroutine CPFEM_general(mode, ffn, ffn1, temperature_inp, dt, elFE, ip, cauchyS
if (iand(mode, CPFEM_CALCRESULTS) /= 0_pInt) then if (iand(mode, CPFEM_CALCRESULTS) /= 0_pInt) then
!*** deformation gradient outdated or any actual deformation gradient differs more than relevantStrain from the stored one !*** deformation gradient outdated or any actual deformation gradient differs more than relevantStrain from the stored one
validCalculation: if (terminallyIll .or. outdatedFFN1) then validCalculation: if (terminallyIll) then
call random_number(rnd) call random_number(rnd)
if (rnd < 0.5_pReal) rnd = rnd - 1.0_pReal if (rnd < 0.5_pReal) rnd = rnd - 1.0_pReal
CPFEM_cs(1:6,ip,elCP) = ODD_STRESS * rnd CPFEM_cs(1:6,ip,elCP) = ODD_STRESS * rnd

View File

@ -43,9 +43,6 @@ module DAMASK_interface
logical, protected, public :: symmetricSolver logical, protected, public :: symmetricSolver
character(len=*), parameter, public :: INPUTFILEEXTENSION = '.dat' character(len=*), parameter, public :: INPUTFILEEXTENSION = '.dat'
logical, dimension(:,:), public, allocatable :: &
calcMode !< calculate or collect (ping pong scheme)
public :: & public :: &
DAMASK_interface_init, & DAMASK_interface_init, &
getSolverJobName getSolverJobName
@ -263,7 +260,7 @@ subroutine hypela2(d,g,e,de,s,t,dt,ngens,m,nn,kcus,matus,ndi,nshear,disp, &
!$ defaultNumThreadsInt = omp_get_num_threads() ! remember number of threads set by Marc !$ defaultNumThreadsInt = omp_get_num_threads() ! remember number of threads set by Marc
!$ call omp_set_num_threads(1) ! set number of threads for parallel execution set by DAMASK_NUM_THREADS !$ call omp_set_num_threads(1) ! set number of threads for parallel execution set by DAMASK_NUM_THREADS
if (.not. CPFEM_init_done) call CPFEM_initAll(m(1),nn) if (.not. CPFEM_init_done) call CPFEM_initAll
computationMode = 0 ! save initialization value, since it does not result in any calculation computationMode = 0 ! save initialization value, since it does not result in any calculation
if (lovl == 4 ) then ! jacobian requested by marc if (lovl == 4 ) then ! jacobian requested by marc
@ -277,20 +274,17 @@ subroutine hypela2(d,g,e,de,s,t,dt,ngens,m,nn,kcus,matus,ndi,nshear,disp, &
if (inc == 0) then ! >> start of analysis << if (inc == 0) then ! >> start of analysis <<
lastIncConverged = .false. ! no Jacobian backup lastIncConverged = .false. ! no Jacobian backup
outdatedByNewInc = .false. ! no aging of state outdatedByNewInc = .false. ! no aging of state
calcMode = .false. ! pretend last step was collection
lastLovl = lovl ! pretend that this is NOT the first after a lovl change lastLovl = lovl ! pretend that this is NOT the first after a lovl change
write(6,'(a,i6,1x,i2)') '<< HYPELA2 >> start of analysis..! ',m(1),nn write(6,'(a,i6,1x,i2)') '<< HYPELA2 >> start of analysis..! ',m(1),nn
flush(6) flush(6)
else if (inc - theInc > 1) then ! >> restart of broken analysis << else if (inc - theInc > 1) then ! >> restart of broken analysis <<
lastIncConverged = .false. ! no Jacobian backup lastIncConverged = .false. ! no Jacobian backup
outdatedByNewInc = .false. ! no aging of state outdatedByNewInc = .false. ! no aging of state
calcMode = .true. ! pretend last step was calculation
write(6,'(a,i6,1x,i2)') '<< HYPELA2 >> restart of analysis..! ',m(1),nn write(6,'(a,i6,1x,i2)') '<< HYPELA2 >> restart of analysis..! ',m(1),nn
flush(6) flush(6)
else ! >> just the next inc << else ! >> just the next inc <<
lastIncConverged = .true. ! request Jacobian backup lastIncConverged = .true. ! request Jacobian backup
outdatedByNewInc = .true. ! request aging of state outdatedByNewInc = .true. ! request aging of state
calcMode = .true. ! assure last step was calculation
write(6,'(a,i6,1x,i2)') '<< HYPELA2 >> new increment..! ',m(1),nn write(6,'(a,i6,1x,i2)') '<< HYPELA2 >> new increment..! ',m(1),nn
flush(6) flush(6)
endif endif
@ -299,7 +293,6 @@ subroutine hypela2(d,g,e,de,s,t,dt,ngens,m,nn,kcus,matus,ndi,nshear,disp, &
outdatedByNewInc = .false. ! no aging of state outdatedByNewInc = .false. ! no aging of state
terminallyIll = .false. terminallyIll = .false.
cycleCounter = -1 ! first calc step increments this to cycle = 0 cycleCounter = -1 ! first calc step increments this to cycle = 0
calcMode = .true. ! pretend last step was calculation
write(6,'(a,i6,1x,i2)') '<< HYPELA2 >> cutback detected..! ',m(1),nn write(6,'(a,i6,1x,i2)') '<< HYPELA2 >> cutback detected..! ',m(1),nn
flush(6) flush(6)
endif ! convergence treatment end endif ! convergence treatment end
@ -307,7 +300,6 @@ subroutine hypela2(d,g,e,de,s,t,dt,ngens,m,nn,kcus,matus,ndi,nshear,disp, &
computationMode = CPFEM_CALCRESULTS ! always calc computationMode = CPFEM_CALCRESULTS ! always calc
if (lastLovl /= lovl) then if (lastLovl /= lovl) then
outdatedFFN1 = .false.
cycleCounter = cycleCounter + 1 cycleCounter = cycleCounter + 1
!mesh_cellnode = mesh_build_cellnodes() ! update cell node coordinates !mesh_cellnode = mesh_build_cellnodes() ! update cell node coordinates
!call mesh_build_ipCoordinates() ! update ip coordinates !call mesh_build_ipCoordinates() ! update ip coordinates

View File

@ -45,9 +45,7 @@ contains
!> @brief initializes the mesh by calling all necessary private routines the mesh module !> @brief initializes the mesh by calling all necessary private routines the mesh module
!! Order and routines strongly depend on type of solver !! Order and routines strongly depend on type of solver
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine discretization_marc_init(ip,el) subroutine discretization_marc_init
integer, intent(in) :: el, ip
real(pReal), dimension(:,:), allocatable :: & real(pReal), dimension(:,:), allocatable :: &
node0_elem, & !< node x,y,z coordinates (initially!) node0_elem, & !< node x,y,z coordinates (initially!)
@ -70,7 +68,7 @@ subroutine discretization_marc_init(ip,el)
real(pReal), dimension(:,:,:,:),allocatable :: & real(pReal), dimension(:,:,:,:),allocatable :: &
unscaledNormals unscaledNormals
write(6,'(/,a)') ' <<<+- mesh init -+>>>'; flush(6) write(6,'(/,a)') ' <<<+- discretization_marc init -+>>>'; flush(6)
mesh_unitlength = numerics_unitlength ! set physical extent of a length unit in mesh mesh_unitlength = numerics_unitlength ! set physical extent of a length unit in mesh
@ -83,10 +81,6 @@ subroutine discretization_marc_init(ip,el)
FEsolving_execElem = [1,nElems] FEsolving_execElem = [1,nElems]
FEsolving_execIP = [1,elem%nIPs] FEsolving_execIP = [1,elem%nIPs]
allocate(calcMode(elem%nIPs,nElems),source=.false.) ! pretend to have collected what first call is asking (F = I)
calcMode(ip,mesh_FEM2DAMASK_elem(el)) = .true. ! first ip,el needs to be already pingponged to "calc"
allocate(cellNodeDefinition(elem%nNodes-1)) allocate(cellNodeDefinition(elem%nNodes-1))
allocate(connectivity_cell(elem%NcellNodesPerCell,elem%nIPs,nElems)) allocate(connectivity_cell(elem%NcellNodesPerCell,elem%nIPs,nElems))
call buildCells(connectivity_cell,cellNodeDefinition,& call buildCells(connectivity_cell,cellNodeDefinition,&