adapted crystallite_stressAndItsTangent to do a pre-guess for the state before the actual state loop (with order stress integration, state update)
This commit is contained in:
parent
a8ff024d97
commit
caf568eb89
|
@ -48,9 +48,7 @@ MODULE crystallite
|
|||
logical, dimension (:,:,:), allocatable :: crystallite_localConstitution, & ! indicates this grain to have purely local constitutive law
|
||||
crystallite_requested, & ! flag to request crystallite calculation
|
||||
crystallite_onTrack, & ! flag to indicate ongoing calculation
|
||||
crystallite_converged, & ! convergence flag
|
||||
crystallite_stressConverged, & ! convergence flag for stress
|
||||
crystallite_stateConverged ! convergence flag for state
|
||||
crystallite_converged ! convergence flag
|
||||
|
||||
|
||||
CONTAINS
|
||||
|
@ -155,8 +153,6 @@ MODULE crystallite
|
|||
allocate(crystallite_localConstitution(gMax,iMax,eMax));
|
||||
allocate(crystallite_requested(gMax,iMax,eMax)); crystallite_requested = .false.
|
||||
allocate(crystallite_onTrack(gMax,iMax,eMax)); crystallite_onTrack = .false.
|
||||
allocate(crystallite_stressConverged(gMax,iMax,eMax)); crystallite_stressConverged = .false.
|
||||
allocate(crystallite_stateConverged(gMax,iMax,eMax)); crystallite_stateConverged = .false.
|
||||
allocate(crystallite_converged(gMax,iMax,eMax)); crystallite_converged = .true.
|
||||
|
||||
!$OMP PARALLEL DO
|
||||
|
@ -211,8 +207,6 @@ MODULE crystallite
|
|||
write(6,'(a32,x,7(i5,x))') 'crystallite_localConstitution: ', shape(crystallite_localConstitution)
|
||||
write(6,'(a32,x,7(i5,x))') 'crystallite_requested: ', shape(crystallite_requested)
|
||||
write(6,'(a32,x,7(i5,x))') 'crystallite_onTrack: ', shape(crystallite_onTrack)
|
||||
write(6,'(a32,x,7(i5,x))') 'crystallite_stressConverged: ', shape(crystallite_stressConverged)
|
||||
write(6,'(a32,x,7(i5,x))') 'crystallite_stateConverged: ', shape(crystallite_stateConverged)
|
||||
write(6,'(a32,x,7(i5,x))') 'crystallite_converged: ', shape(crystallite_converged)
|
||||
write(6,*)
|
||||
write(6,*) 'Number of non-local grains: ',count(.not. crystallite_localConstitution)
|
||||
|
@ -315,8 +309,6 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
|||
! crystallite_localConstitution
|
||||
! crystallite_requested
|
||||
! crystallite_onTrack
|
||||
! crystallite_stressConverged
|
||||
! crystallite_stateConverged
|
||||
! crystallite_converged
|
||||
|
||||
!*** global functions or subroutines ***!
|
||||
|
@ -355,7 +347,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
|||
enddo
|
||||
!$OMPEND PARALLEL DO
|
||||
|
||||
! ------ cutback loop ------
|
||||
! --+>> crystallite loop <<+--
|
||||
|
||||
NiterationCrystallite = 0_pInt
|
||||
|
||||
|
@ -424,24 +416,14 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
|||
enddo
|
||||
!$OMPEND PARALLEL DO
|
||||
|
||||
! ------ convergence loop for stress and state ------
|
||||
|
||||
NiterationState = 1_pInt
|
||||
if (debugger) write(6,*) 'state integration started'
|
||||
|
||||
do while (any( crystallite_requested(:,:,FEsolving_execELem(1):FEsolving_execElem(2)) &
|
||||
.and. crystallite_onTrack(:,:,FEsolving_execELem(1):FEsolving_execElem(2)) &
|
||||
.and. .not. crystallite_converged(:,:,FEsolving_execELem(1):FEsolving_execElem(2)) &
|
||||
) .and. NiterationState < nState) ! convergence loop for crystallite
|
||||
|
||||
NiterationState = NiterationState + 1
|
||||
|
||||
! --+>> state integration <<+--
|
||||
! --+>> preguess for state <<+--
|
||||
!
|
||||
! incrementing by crystallite_subdt
|
||||
! based on constitutive_subState0
|
||||
! results in constitutive_state
|
||||
|
||||
if (debugger) write(6,*) 'state integration started'
|
||||
|
||||
!$OMP PARALLEL DO
|
||||
do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over elements to be processed
|
||||
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
||||
|
@ -449,13 +431,26 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
|||
do g = 1,myNgrains
|
||||
if ( crystallite_requested(g,i,e) &
|
||||
.and. crystallite_onTrack(g,i,e) &
|
||||
.and. .not. crystallite_converged(g,i,e)) & ! all undone crystallites
|
||||
crystallite_stateConverged(g,i,e) = crystallite_updateState(g,i,e)
|
||||
.and. .not. crystallite_converged(g,i,e)) then ! all undone crystallites
|
||||
crystallite_converged(g,i,e) = crystallite_updateState(g,i,e)
|
||||
crystallite_converged(g,i,e) = .false. ! force at least one iteration step even if state already converged
|
||||
endif
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
!$OMPEND PARALLEL DO
|
||||
|
||||
! --+>> state loop <<+--
|
||||
|
||||
NiterationState = 0_pInt
|
||||
|
||||
do while ( any( crystallite_requested(:,:,FEsolving_execELem(1):FEsolving_execElem(2)) &
|
||||
.and. crystallite_onTrack(:,:,FEsolving_execELem(1):FEsolving_execElem(2)) &
|
||||
.and. .not. crystallite_converged(:,:,FEsolving_execELem(1):FEsolving_execElem(2)) ) &
|
||||
.and. NiterationState < nState) ! convergence loop for crystallite
|
||||
|
||||
NiterationState = NiterationState + 1_pInt
|
||||
|
||||
! --+>> stress integration <<+--
|
||||
!
|
||||
! incrementing by crystallite_subdt
|
||||
|
@ -464,6 +459,26 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
|||
! to account for substepping within _integrateStress
|
||||
! results in crystallite_Fp,.._Lp
|
||||
|
||||
!$OMP PARALLEL DO
|
||||
do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over elements to be processed
|
||||
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
||||
do i = FEsolving_execIP(1,e),FEsolving_execIP(2,e) ! iterate over IPs of this element to be processed
|
||||
do g = 1,myNgrains
|
||||
if ( crystallite_requested(g,i,e) &
|
||||
.and. crystallite_onTrack(g,i,e) &
|
||||
.and. .not. crystallite_converged(g,i,e) ) & ! all undone crystallites
|
||||
crystallite_onTrack(g,i,e) = crystallite_integrateStress(g,i,e)
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
!$OMPEND PARALLEL DO
|
||||
|
||||
! --+>> state integration <<+--
|
||||
!
|
||||
! incrementing by crystallite_subdt
|
||||
! based on constitutive_subState0
|
||||
! results in constitutive_state
|
||||
|
||||
!$OMP PARALLEL DO
|
||||
do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over elements to be processed
|
||||
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
||||
|
@ -472,9 +487,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
|||
if ( crystallite_requested(g,i,e) &
|
||||
.and. crystallite_onTrack(g,i,e) &
|
||||
.and. .not. crystallite_converged(g,i,e)) then ! all undone crystallites
|
||||
crystallite_stressConverged(g,i,e) = crystallite_integrateStress(g,i,e)
|
||||
crystallite_onTrack(g,i,e) = crystallite_stressConverged(g,i,e)
|
||||
crystallite_converged(g,i,e) = crystallite_stateConverged(g,i,e) .and. crystallite_stressConverged(g,i,e)
|
||||
crystallite_converged(g,i,e) = crystallite_updateState(g,i,e)
|
||||
if (crystallite_converged(g,i,e)) then
|
||||
!$OMP CRITICAL (distributionState)
|
||||
debug_StateLoopDistribution(NiterationState) = debug_StateLoopDistribution(NiterationState) + 1
|
||||
|
@ -520,7 +533,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
|||
enddo
|
||||
!$OMPEND PARALLEL DO
|
||||
|
||||
! ------ stiffness calculation ------
|
||||
! --+>> stiffness calculation <<+--
|
||||
|
||||
if(updateJaco) then ! Jacobian required
|
||||
if (debugger) write (6,*) 'Stiffness calculation started'
|
||||
|
@ -551,21 +564,20 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
|
|||
do l = 1,3 ! ...components
|
||||
crystallite_subF(:,:,g,i,e) = myF ! initialize perturbed F to match converged
|
||||
crystallite_subF(k,l,g,i,e) = crystallite_subF(k,l,g,i,e) + pert_Fg ! perturb single component
|
||||
onTrack = .true.
|
||||
converged = .false.
|
||||
NiterationState = 0_pInt
|
||||
if (debugger) then
|
||||
write (6,*) '============='
|
||||
write (6,'(i1,x,i1)') k,l
|
||||
write (6,*) '============='
|
||||
write (6,'(a,/,3(3(f12.6,x)/))') 'pertF of 1 1 1',crystallite_subF(1:3,:,g,i,e)
|
||||
endif
|
||||
onTrack = .true.
|
||||
converged = .false.
|
||||
NiterationState = 0_pInt
|
||||
do while(.not. converged .and. onTrack .and. NiterationState < nState) ! keep cycling until done (potentially non-converged)
|
||||
NiterationState = NiterationState + 1_pInt
|
||||
if (debugger) write (6,'(a4,x,i6)') 'loop',NiterationState
|
||||
converged = crystallite_updateState(g,i,e) ! update state
|
||||
onTrack = crystallite_integrateStress(g,i,e) ! stress of perturbed situation (overwrites _P,_Tstar_v,_Fp,_Lp,_Fe)
|
||||
converged = converged .and. onTrack
|
||||
if (onTrack) converged = crystallite_updateState(g,i,e) ! update state
|
||||
if (debugger) then
|
||||
write (6,*) '-------------'
|
||||
write (6,'(l,x,l)') onTrack,converged
|
||||
|
|
|
@ -9,8 +9,8 @@
|
|||
/Keywords ()
|
||||
/Creator (FreeHEP Graphics2D Driver)
|
||||
/Producer (org.freehep.graphicsio.pdf.PDFGraphics2D Revision: 10516 )
|
||||
/CreationDate (D:20090609115952+02'00')
|
||||
/ModDate (D:20090609115952+02'00')
|
||||
/CreationDate (D:20090610154844+02'00')
|
||||
/ModDate (D:20090610154844+02'00')
|
||||
/Trapped /False
|
||||
>>
|
||||
endobj
|
||||
|
|
|
@ -32,21 +32,21 @@
|
|||
<qFalse>
|
||||
</qFalse>
|
||||
</alternative>
|
||||
<call text=""crystallite_updateState"" comment="""" color="ffffff"></call>
|
||||
<instruction text=""NiterationState = 0"" comment="" color="ffffff" rotated="0"></instruction>
|
||||
<for text=""STATE LOOP: any: crystallite_requested .and. crystallite_onTrack .and. .not. crystallite_converged"," .and. NiterationState < ncryst"" comment="" color="ffffff">
|
||||
<qFor>
|
||||
<instruction text=""NiterationState = NiterationState + 1"" comment="" color="ffffff" rotated="0"></instruction>
|
||||
<alternative text=""crystallite_requested .and. crystallite_onTrack .and. .not. crystallite_converged"" comment="""" color="ffffff">
|
||||
<alternative text=""crystallite_requested .and. crystallite_onTrack .and. .not. crystallite_converged"" comment="" color="ffffff">
|
||||
<qTrue>
|
||||
<call text=""crystallite_stateConverged = crystallite_updateState"" comment="""" color="ffffff"></call>
|
||||
<call text=""crystallite_onTrack = crystallite_integrateStress"" comment="""" color="ffffff"></call>
|
||||
</qTrue>
|
||||
<qFalse>
|
||||
</qFalse>
|
||||
</alternative>
|
||||
<alternative text=""crystallite_requested .and. crystallite_onTrack .and. .not. crystallite_converged"" comment="""" color="ffffff">
|
||||
<alternative text=""crystallite_requested .and. crystallite_onTrack .and. .not. crystallite_converged"" comment="" color="ffffff">
|
||||
<qTrue>
|
||||
<call text=""crystallite_stressConverged = crystallite_integrateStress"" comment="""" color="ffffff"></call>
|
||||
<instruction text=""crystallite_onTrack = crystallite_stressConverged","crystallite_converged = crystallite_stateConverged .and. crystallite_stressConverged"" comment="""" color="ffffff" rotated="0"></instruction>
|
||||
<call text=""crystallite_converged = crystallite_updateState"" comment="""" color="ffffff"></call>
|
||||
</qTrue>
|
||||
<qFalse>
|
||||
</qFalse>
|
||||
|
|
File diff suppressed because it is too large
Load Diff
|
@ -13,9 +13,14 @@
|
|||
<for text=""STIFFNESS LOOP: .not. converged .and. onTrack .and. NiterationState < nState"" comment="" color="ffffff">
|
||||
<qFor>
|
||||
<instruction text=""NiterationState = NiterationState + 1"" comment="" color="ffffff" rotated="0"></instruction>
|
||||
<call text=""converged = crystallite_updateState"" comment="" color="ffffff"></call>
|
||||
<call text=""onTrack = crystallite_integrateStress"" comment="" color="ffffff"></call>
|
||||
<instruction text=""converged = onTrack .and. converged"" comment="""" color="ffffff" rotated="0"></instruction>
|
||||
<alternative text=""onTrack"" comment="""" color="ffffff">
|
||||
<qTrue>
|
||||
<call text=""converged = crystallite_updateState"" comment="" color="ffffff"></call>
|
||||
</qTrue>
|
||||
<qFalse>
|
||||
</qFalse>
|
||||
</alternative>
|
||||
</qFor>
|
||||
</for>
|
||||
<alternative text=""converged"" comment="" color="ffffff">
|
||||
|
|
File diff suppressed because it is too large
Load Diff
Loading…
Reference in New Issue