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:
Christoph Kords 2009-06-10 15:08:33 +00:00
parent a8ff024d97
commit caf568eb89
6 changed files with 14758 additions and 17523 deletions

View File

@ -48,9 +48,7 @@ MODULE crystallite
logical, dimension (:,:,:), allocatable :: crystallite_localConstitution, & ! indicates this grain to have purely local constitutive law logical, dimension (:,:,:), allocatable :: crystallite_localConstitution, & ! indicates this grain to have purely local constitutive law
crystallite_requested, & ! flag to request crystallite calculation crystallite_requested, & ! flag to request crystallite calculation
crystallite_onTrack, & ! flag to indicate ongoing calculation crystallite_onTrack, & ! flag to indicate ongoing calculation
crystallite_converged, & ! convergence flag crystallite_converged ! convergence flag
crystallite_stressConverged, & ! convergence flag for stress
crystallite_stateConverged ! convergence flag for state
CONTAINS CONTAINS
@ -155,8 +153,6 @@ MODULE crystallite
allocate(crystallite_localConstitution(gMax,iMax,eMax)); allocate(crystallite_localConstitution(gMax,iMax,eMax));
allocate(crystallite_requested(gMax,iMax,eMax)); crystallite_requested = .false. allocate(crystallite_requested(gMax,iMax,eMax)); crystallite_requested = .false.
allocate(crystallite_onTrack(gMax,iMax,eMax)); crystallite_onTrack = .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. allocate(crystallite_converged(gMax,iMax,eMax)); crystallite_converged = .true.
!$OMP PARALLEL DO !$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_localConstitution: ', shape(crystallite_localConstitution)
write(6,'(a32,x,7(i5,x))') 'crystallite_requested: ', shape(crystallite_requested) 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_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,'(a32,x,7(i5,x))') 'crystallite_converged: ', shape(crystallite_converged)
write(6,*) write(6,*)
write(6,*) 'Number of non-local grains: ',count(.not. crystallite_localConstitution) write(6,*) 'Number of non-local grains: ',count(.not. crystallite_localConstitution)
@ -315,8 +309,6 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
! crystallite_localConstitution ! crystallite_localConstitution
! crystallite_requested ! crystallite_requested
! crystallite_onTrack ! crystallite_onTrack
! crystallite_stressConverged
! crystallite_stateConverged
! crystallite_converged ! crystallite_converged
!*** global functions or subroutines ***! !*** global functions or subroutines ***!
@ -355,7 +347,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
enddo enddo
!$OMPEND PARALLEL DO !$OMPEND PARALLEL DO
! ------ cutback loop ------ ! --+>> crystallite loop <<+--
NiterationCrystallite = 0_pInt NiterationCrystallite = 0_pInt
@ -424,24 +416,14 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
enddo enddo
!$OMPEND PARALLEL DO !$OMPEND PARALLEL DO
! ------ convergence loop for stress and state ------ ! --+>> preguess for 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 <<+--
! !
! incrementing by crystallite_subdt ! incrementing by crystallite_subdt
! based on constitutive_subState0 ! based on constitutive_subState0
! results in constitutive_state ! results in constitutive_state
if (debugger) write(6,*) 'state integration started'
!$OMP PARALLEL DO !$OMP PARALLEL DO
do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over elements to be processed do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over elements to be processed
myNgrains = homogenization_Ngrains(mesh_element(3,e)) myNgrains = homogenization_Ngrains(mesh_element(3,e))
@ -449,13 +431,26 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
do g = 1,myNgrains do g = 1,myNgrains
if ( crystallite_requested(g,i,e) & if ( crystallite_requested(g,i,e) &
.and. crystallite_onTrack(g,i,e) & .and. crystallite_onTrack(g,i,e) &
.and. .not. crystallite_converged(g,i,e)) & ! all undone crystallites .and. .not. crystallite_converged(g,i,e)) then ! all undone crystallites
crystallite_stateConverged(g,i,e) = crystallite_updateState(g,i,e) 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 enddo
enddo enddo
!$OMPEND PARALLEL DO !$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 <<+-- ! --+>> stress integration <<+--
! !
! incrementing by crystallite_subdt ! incrementing by crystallite_subdt
@ -464,6 +459,26 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
! to account for substepping within _integrateStress ! to account for substepping within _integrateStress
! results in crystallite_Fp,.._Lp ! 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 !$OMP PARALLEL DO
do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over elements to be processed do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over elements to be processed
myNgrains = homogenization_Ngrains(mesh_element(3,e)) myNgrains = homogenization_Ngrains(mesh_element(3,e))
@ -472,9 +487,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
if ( crystallite_requested(g,i,e) & if ( crystallite_requested(g,i,e) &
.and. crystallite_onTrack(g,i,e) & .and. crystallite_onTrack(g,i,e) &
.and. .not. crystallite_converged(g,i,e)) then ! all undone crystallites .and. .not. crystallite_converged(g,i,e)) then ! all undone crystallites
crystallite_stressConverged(g,i,e) = crystallite_integrateStress(g,i,e) crystallite_converged(g,i,e) = crystallite_updateState(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)
if (crystallite_converged(g,i,e)) then if (crystallite_converged(g,i,e)) then
!$OMP CRITICAL (distributionState) !$OMP CRITICAL (distributionState)
debug_StateLoopDistribution(NiterationState) = debug_StateLoopDistribution(NiterationState) + 1 debug_StateLoopDistribution(NiterationState) = debug_StateLoopDistribution(NiterationState) + 1
@ -520,7 +533,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
enddo enddo
!$OMPEND PARALLEL DO !$OMPEND PARALLEL DO
! ------ stiffness calculation ------ ! --+>> stiffness calculation <<+--
if(updateJaco) then ! Jacobian required if(updateJaco) then ! Jacobian required
if (debugger) write (6,*) 'Stiffness calculation started' if (debugger) write (6,*) 'Stiffness calculation started'
@ -551,21 +564,20 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
do l = 1,3 ! ...components do l = 1,3 ! ...components
crystallite_subF(:,:,g,i,e) = myF ! initialize perturbed F to match converged 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 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 if (debugger) then
write (6,*) '=============' write (6,*) '============='
write (6,'(i1,x,i1)') k,l write (6,'(i1,x,i1)') k,l
write (6,*) '=============' write (6,*) '============='
write (6,'(a,/,3(3(f12.6,x)/))') 'pertF of 1 1 1',crystallite_subF(1:3,:,g,i,e) write (6,'(a,/,3(3(f12.6,x)/))') 'pertF of 1 1 1',crystallite_subF(1:3,:,g,i,e)
endif endif
onTrack = .true.
converged = .false.
NiterationState = 0_pInt
do while(.not. converged .and. onTrack .and. NiterationState < nState) ! keep cycling until done (potentially non-converged) do while(.not. converged .and. onTrack .and. NiterationState < nState) ! keep cycling until done (potentially non-converged)
NiterationState = NiterationState + 1_pInt NiterationState = NiterationState + 1_pInt
if (debugger) write (6,'(a4,x,i6)') 'loop',NiterationState 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) 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 if (debugger) then
write (6,*) '-------------' write (6,*) '-------------'
write (6,'(l,x,l)') onTrack,converged write (6,'(l,x,l)') onTrack,converged

View File

@ -9,8 +9,8 @@
/Keywords () /Keywords ()
/Creator (FreeHEP Graphics2D Driver) /Creator (FreeHEP Graphics2D Driver)
/Producer (org.freehep.graphicsio.pdf.PDFGraphics2D Revision: 10516 ) /Producer (org.freehep.graphicsio.pdf.PDFGraphics2D Revision: 10516 )
/CreationDate (D:20090609115952+02'00') /CreationDate (D:20090610154844+02'00')
/ModDate (D:20090609115952+02'00') /ModDate (D:20090610154844+02'00')
/Trapped /False /Trapped /False
>> >>
endobj endobj

View File

@ -32,21 +32,21 @@
<qFalse> <qFalse>
</qFalse> </qFalse>
</alternative> </alternative>
<call text="&#34;crystallite_updateState&#34;" comment="&#34;&#34;" color="ffffff"></call>
<instruction text="&#34;NiterationState = 0&#34;" comment="" color="ffffff" rotated="0"></instruction> <instruction text="&#34;NiterationState = 0&#34;" comment="" color="ffffff" rotated="0"></instruction>
<for text="&#34;STATE LOOP: any: crystallite_requested .and. crystallite_onTrack .and. .not. crystallite_converged&#34;,&#34; .and. NiterationState &#60; ncryst&#34;" comment="" color="ffffff"> <for text="&#34;STATE LOOP: any: crystallite_requested .and. crystallite_onTrack .and. .not. crystallite_converged&#34;,&#34; .and. NiterationState &#60; ncryst&#34;" comment="" color="ffffff">
<qFor> <qFor>
<instruction text="&#34;NiterationState = NiterationState + 1&#34;" comment="" color="ffffff" rotated="0"></instruction> <instruction text="&#34;NiterationState = NiterationState + 1&#34;" comment="" color="ffffff" rotated="0"></instruction>
<alternative text="&#34;crystallite_requested .and. crystallite_onTrack .and. .not. crystallite_converged&#34;" comment="&#34;&#34;" color="ffffff"> <alternative text="&#34;crystallite_requested .and. crystallite_onTrack .and. .not. crystallite_converged&#34;" comment="" color="ffffff">
<qTrue> <qTrue>
<call text="&#34;crystallite_stateConverged = crystallite_updateState&#34;" comment="&#34;&#34;" color="ffffff"></call> <call text="&#34;crystallite_onTrack = crystallite_integrateStress&#34;" comment="&#34;&#34;" color="ffffff"></call>
</qTrue> </qTrue>
<qFalse> <qFalse>
</qFalse> </qFalse>
</alternative> </alternative>
<alternative text="&#34;crystallite_requested .and. crystallite_onTrack .and. .not. crystallite_converged&#34;" comment="&#34;&#34;" color="ffffff"> <alternative text="&#34;crystallite_requested .and. crystallite_onTrack .and. .not. crystallite_converged&#34;" comment="" color="ffffff">
<qTrue> <qTrue>
<call text="&#34;crystallite_stressConverged = crystallite_integrateStress&#34;" comment="&#34;&#34;" color="ffffff"></call> <call text="&#34;crystallite_converged = crystallite_updateState&#34;" comment="&#34;&#34;" color="ffffff"></call>
<instruction text="&#34;crystallite_onTrack = crystallite_stressConverged&#34;,&#34;crystallite_converged = crystallite_stateConverged .and. crystallite_stressConverged&#34;" comment="&#34;&#34;" color="ffffff" rotated="0"></instruction>
</qTrue> </qTrue>
<qFalse> <qFalse>
</qFalse> </qFalse>

View File

@ -13,9 +13,14 @@
<for text="&#34;STIFFNESS LOOP: .not. converged .and. onTrack .and. NiterationState &#60; nState&#34;" comment="" color="ffffff"> <for text="&#34;STIFFNESS LOOP: .not. converged .and. onTrack .and. NiterationState &#60; nState&#34;" comment="" color="ffffff">
<qFor> <qFor>
<instruction text="&#34;NiterationState = NiterationState + 1&#34;" comment="" color="ffffff" rotated="0"></instruction> <instruction text="&#34;NiterationState = NiterationState + 1&#34;" comment="" color="ffffff" rotated="0"></instruction>
<call text="&#34;converged = crystallite_updateState&#34;" comment="" color="ffffff"></call>
<call text="&#34;onTrack = crystallite_integrateStress&#34;" comment="" color="ffffff"></call> <call text="&#34;onTrack = crystallite_integrateStress&#34;" comment="" color="ffffff"></call>
<instruction text="&#34;converged = onTrack .and. converged&#34;" comment="&#34;&#34;" color="ffffff" rotated="0"></instruction> <alternative text="&#34;onTrack&#34;" comment="&#34;&#34;" color="ffffff">
<qTrue>
<call text="&#34;converged = crystallite_updateState&#34;" comment="" color="ffffff"></call>
</qTrue>
<qFalse>
</qFalse>
</alternative>
</qFor> </qFor>
</for> </for>
<alternative text="&#34;converged&#34;" comment="" color="ffffff"> <alternative text="&#34;converged&#34;" comment="" color="ffffff">