use already known mappings
This commit is contained in:
parent
5af53f0be7
commit
b5efaa08a4
|
@ -709,12 +709,14 @@ end subroutine constitutive_hooke_SandItsTangents
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief contains the constitutive equation for calculating the rate of change of microstructure
|
!> @brief contains the constitutive equation for calculating the rate of change of microstructure
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function constitutive_collectDotState(S, FArray, Fi, FpArray, subdt, ipc, ip, el) result(broken)
|
function constitutive_collectDotState(S, FArray, Fi, FpArray, subdt, ipc, ip, el,phase,of) result(broken)
|
||||||
|
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
ipc, & !< component-ID of integration point
|
ipc, & !< component-ID of integration point
|
||||||
ip, & !< integration point
|
ip, & !< integration point
|
||||||
el !< element
|
el, & !< element
|
||||||
|
phase, &
|
||||||
|
of
|
||||||
real(pReal), intent(in) :: &
|
real(pReal), intent(in) :: &
|
||||||
subdt !< timestep
|
subdt !< timestep
|
||||||
real(pReal), intent(in), dimension(3,3,homogenization_maxNgrains,discretization_nIP,discretization_nElem) :: &
|
real(pReal), intent(in), dimension(3,3,homogenization_maxNgrains,discretization_nIP,discretization_nElem) :: &
|
||||||
|
@ -727,17 +729,14 @@ function constitutive_collectDotState(S, FArray, Fi, FpArray, subdt, ipc, ip, el
|
||||||
real(pReal), dimension(3,3) :: &
|
real(pReal), dimension(3,3) :: &
|
||||||
Mp
|
Mp
|
||||||
integer :: &
|
integer :: &
|
||||||
phase, &
|
|
||||||
ho, & !< homogenization
|
ho, & !< homogenization
|
||||||
tme, & !< thermal member position
|
tme, & !< thermal member position
|
||||||
i, & !< counter in source loop
|
i, & !< counter in source loop
|
||||||
instance, of
|
instance
|
||||||
logical :: broken
|
logical :: broken
|
||||||
|
|
||||||
ho = material_homogenizationAt(el)
|
ho = material_homogenizationAt(el)
|
||||||
tme = thermalMapping(ho)%p(ip,el)
|
tme = thermalMapping(ho)%p(ip,el)
|
||||||
of = material_phasememberAt(ipc,ip,el)
|
|
||||||
phase = material_phaseAt(ipc,el)
|
|
||||||
instance = phase_plasticityInstance(phase)
|
instance = phase_plasticityInstance(phase)
|
||||||
|
|
||||||
Mp = matmul(matmul(transpose(Fi),Fi),S)
|
Mp = matmul(matmul(transpose(Fi),Fi),S)
|
||||||
|
@ -794,12 +793,14 @@ end function constitutive_collectDotState
|
||||||
!> @brief for constitutive models having an instantaneous change of state
|
!> @brief for constitutive models having an instantaneous change of state
|
||||||
!> will return false if delta state is not needed/supported by the constitutive model
|
!> will return false if delta state is not needed/supported by the constitutive model
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function constitutive_deltaState(S, Fe, Fi, ipc, ip, el) result(broken)
|
function constitutive_deltaState(S, Fe, Fi, ipc, ip, el, phase, of) result(broken)
|
||||||
|
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
ipc, & !< component-ID of integration point
|
ipc, & !< component-ID of integration point
|
||||||
ip, & !< integration point
|
ip, & !< integration point
|
||||||
el !< element
|
el, & !< element
|
||||||
|
phase, &
|
||||||
|
of
|
||||||
real(pReal), intent(in), dimension(3,3) :: &
|
real(pReal), intent(in), dimension(3,3) :: &
|
||||||
S, & !< 2nd Piola Kirchhoff stress
|
S, & !< 2nd Piola Kirchhoff stress
|
||||||
Fe, & !< elastic deformation gradient
|
Fe, & !< elastic deformation gradient
|
||||||
|
@ -808,27 +809,28 @@ function constitutive_deltaState(S, Fe, Fi, ipc, ip, el) result(broken)
|
||||||
Mp
|
Mp
|
||||||
integer :: &
|
integer :: &
|
||||||
i, &
|
i, &
|
||||||
instance, of, &
|
instance
|
||||||
phase
|
|
||||||
logical :: &
|
logical :: &
|
||||||
broken
|
broken
|
||||||
|
|
||||||
|
|
||||||
Mp = matmul(matmul(transpose(Fi),Fi),S)
|
Mp = matmul(matmul(transpose(Fi),Fi),S)
|
||||||
of = material_phasememberAt(ipc,ip,el)
|
instance = phase_plasticityInstance(phase)
|
||||||
phase = material_phaseAt(ipc,el)
|
|
||||||
instance = phase_plasticityInstance(material_phaseAt(ipc,el))
|
|
||||||
|
|
||||||
plasticityType: select case (phase_plasticity(phase))
|
plasticityType: select case (phase_plasticity(phase))
|
||||||
|
|
||||||
case (PLASTICITY_KINEHARDENING_ID) plasticityType
|
case (PLASTICITY_KINEHARDENING_ID) plasticityType
|
||||||
call plastic_kinehardening_deltaState(Mp,instance,of)
|
call plastic_kinehardening_deltaState(Mp,instance,of)
|
||||||
|
broken = any(IEEE_is_NaN(plasticState(phase)%deltaState(:,of)))
|
||||||
|
|
||||||
case (PLASTICITY_NONLOCAL_ID) plasticityType
|
case (PLASTICITY_NONLOCAL_ID) plasticityType
|
||||||
call plastic_nonlocal_deltaState(Mp,instance,of,ip,el)
|
call plastic_nonlocal_deltaState(Mp,instance,of,ip,el)
|
||||||
|
broken = any(IEEE_is_NaN(plasticState(phase)%deltaState(:,of)))
|
||||||
|
|
||||||
|
case default
|
||||||
|
broken = .false.
|
||||||
|
|
||||||
end select plasticityType
|
end select plasticityType
|
||||||
broken = any(IEEE_is_NaN(plasticState(phase)%deltaState(:,of)))
|
|
||||||
|
|
||||||
sourceLoop: do i = 1, phase_Nsources(phase)
|
sourceLoop: do i = 1, phase_Nsources(phase)
|
||||||
|
|
||||||
|
@ -837,11 +839,10 @@ function constitutive_deltaState(S, Fe, Fi, ipc, ip, el) result(broken)
|
||||||
case (SOURCE_damage_isoBrittle_ID) sourceType
|
case (SOURCE_damage_isoBrittle_ID) sourceType
|
||||||
call source_damage_isoBrittle_deltaState (constitutive_homogenizedC(ipc,ip,el), Fe, &
|
call source_damage_isoBrittle_deltaState (constitutive_homogenizedC(ipc,ip,el), Fe, &
|
||||||
ipc, ip, el)
|
ipc, ip, el)
|
||||||
|
broken = broken .or. any(IEEE_is_NaN(sourceState(phase)%p(i)%deltaState(:,of)))
|
||||||
|
|
||||||
end select sourceType
|
end select sourceType
|
||||||
|
|
||||||
broken = broken .or. any(IEEE_is_NaN(sourceState(phase)%p(i)%deltaState(:,of)))
|
|
||||||
|
|
||||||
enddo SourceLoop
|
enddo SourceLoop
|
||||||
|
|
||||||
end function constitutive_deltaState
|
end function constitutive_deltaState
|
||||||
|
|
|
@ -1038,7 +1038,7 @@ subroutine integrateStateFPI(todo)
|
||||||
crystallite_partionedF0, &
|
crystallite_partionedF0, &
|
||||||
crystallite_Fi(1:3,1:3,g,i,e), &
|
crystallite_Fi(1:3,1:3,g,i,e), &
|
||||||
crystallite_partionedFp0, &
|
crystallite_partionedFp0, &
|
||||||
crystallite_subdt(g,i,e), g,i,e)
|
crystallite_subdt(g,i,e), g,i,e,p,c)
|
||||||
|
|
||||||
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
||||||
if(broken) cycle
|
if(broken) cycle
|
||||||
|
@ -1073,7 +1073,7 @@ subroutine integrateStateFPI(todo)
|
||||||
crystallite_partionedF0, &
|
crystallite_partionedF0, &
|
||||||
crystallite_Fi(1:3,1:3,g,i,e), &
|
crystallite_Fi(1:3,1:3,g,i,e), &
|
||||||
crystallite_partionedFp0, &
|
crystallite_partionedFp0, &
|
||||||
crystallite_subdt(g,i,e), g,i,e)
|
crystallite_subdt(g,i,e), g,i,e,p,c)
|
||||||
if(broken) exit iteration
|
if(broken) exit iteration
|
||||||
|
|
||||||
sizeDotState = plasticState(p)%sizeDotState
|
sizeDotState = plasticState(p)%sizeDotState
|
||||||
|
@ -1107,7 +1107,7 @@ subroutine integrateStateFPI(todo)
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
if(crystallite_converged(g,i,e)) then
|
if(crystallite_converged(g,i,e)) then
|
||||||
broken = stateJump(g,i,e)
|
broken = stateJump(g,i,e,p,c)
|
||||||
exit iteration
|
exit iteration
|
||||||
endif
|
endif
|
||||||
|
|
||||||
|
@ -1177,7 +1177,7 @@ subroutine integrateStateEuler(todo)
|
||||||
crystallite_partionedF0, &
|
crystallite_partionedF0, &
|
||||||
crystallite_Fi(1:3,1:3,g,i,e), &
|
crystallite_Fi(1:3,1:3,g,i,e), &
|
||||||
crystallite_partionedFp0, &
|
crystallite_partionedFp0, &
|
||||||
crystallite_subdt(g,i,e), g,i,e)
|
crystallite_subdt(g,i,e), g,i,e,p,c)
|
||||||
|
|
||||||
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
||||||
if(broken) cycle
|
if(broken) cycle
|
||||||
|
@ -1193,7 +1193,7 @@ subroutine integrateStateEuler(todo)
|
||||||
* crystallite_subdt(g,i,e)
|
* crystallite_subdt(g,i,e)
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
broken = stateJump(g,i,e)
|
broken = stateJump(g,i,e,p,c)
|
||||||
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
||||||
if(broken) cycle
|
if(broken) cycle
|
||||||
|
|
||||||
|
@ -1246,7 +1246,7 @@ subroutine integrateStateAdaptiveEuler(todo)
|
||||||
crystallite_partionedF0, &
|
crystallite_partionedF0, &
|
||||||
crystallite_Fi(1:3,1:3,g,i,e), &
|
crystallite_Fi(1:3,1:3,g,i,e), &
|
||||||
crystallite_partionedFp0, &
|
crystallite_partionedFp0, &
|
||||||
crystallite_subdt(g,i,e), g,i,e)
|
crystallite_subdt(g,i,e), g,i,e,p,c)
|
||||||
|
|
||||||
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
||||||
if(broken) cycle
|
if(broken) cycle
|
||||||
|
@ -1265,7 +1265,7 @@ subroutine integrateStateAdaptiveEuler(todo)
|
||||||
+ sourceState(p)%p(s)%dotstate(1:sizeDotState,c) * crystallite_subdt(g,i,e)
|
+ sourceState(p)%p(s)%dotstate(1:sizeDotState,c) * crystallite_subdt(g,i,e)
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
broken = stateJump(g,i,e)
|
broken = stateJump(g,i,e,p,c)
|
||||||
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
||||||
if(broken) cycle
|
if(broken) cycle
|
||||||
|
|
||||||
|
@ -1277,7 +1277,7 @@ subroutine integrateStateAdaptiveEuler(todo)
|
||||||
crystallite_partionedF0, &
|
crystallite_partionedF0, &
|
||||||
crystallite_Fi(1:3,1:3,g,i,e), &
|
crystallite_Fi(1:3,1:3,g,i,e), &
|
||||||
crystallite_partionedFp0, &
|
crystallite_partionedFp0, &
|
||||||
crystallite_subdt(g,i,e), g,i,e)
|
crystallite_subdt(g,i,e), g,i,e,p,c)
|
||||||
|
|
||||||
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
||||||
if(broken) cycle
|
if(broken) cycle
|
||||||
|
@ -1357,7 +1357,7 @@ subroutine integrateStateRK4(todo)
|
||||||
crystallite_partionedF0, &
|
crystallite_partionedF0, &
|
||||||
crystallite_Fi(1:3,1:3,g,i,e), &
|
crystallite_Fi(1:3,1:3,g,i,e), &
|
||||||
crystallite_partionedFp0, &
|
crystallite_partionedFp0, &
|
||||||
crystallite_subdt(g,i,e), g,i,e)
|
crystallite_subdt(g,i,e), g,i,e,p,c)
|
||||||
|
|
||||||
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
||||||
if(broken) cycle
|
if(broken) cycle
|
||||||
|
@ -1401,7 +1401,7 @@ subroutine integrateStateRK4(todo)
|
||||||
crystallite_partionedF0, &
|
crystallite_partionedF0, &
|
||||||
crystallite_Fi(1:3,1:3,g,i,e), &
|
crystallite_Fi(1:3,1:3,g,i,e), &
|
||||||
crystallite_partionedFp0, &
|
crystallite_partionedFp0, &
|
||||||
crystallite_subdt(g,i,e)*CC(stage), g,i,e)
|
crystallite_subdt(g,i,e)*CC(stage), g,i,e,p,c)
|
||||||
if(broken) exit
|
if(broken) exit
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
@ -1428,7 +1428,7 @@ subroutine integrateStateRK4(todo)
|
||||||
* crystallite_subdt(g,i,e)
|
* crystallite_subdt(g,i,e)
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
broken = stateJump(g,i,e)
|
broken = stateJump(g,i,e,p,c)
|
||||||
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
||||||
if(broken) cycle
|
if(broken) cycle
|
||||||
|
|
||||||
|
@ -1502,7 +1502,7 @@ subroutine integrateStateRKCK45(todo)
|
||||||
crystallite_partionedF0, &
|
crystallite_partionedF0, &
|
||||||
crystallite_Fi(1:3,1:3,g,i,e), &
|
crystallite_Fi(1:3,1:3,g,i,e), &
|
||||||
crystallite_partionedFp0, &
|
crystallite_partionedFp0, &
|
||||||
crystallite_subdt(g,i,e), g,i,e)
|
crystallite_subdt(g,i,e), g,i,e,p,c)
|
||||||
|
|
||||||
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
||||||
if(broken) cycle
|
if(broken) cycle
|
||||||
|
@ -1546,7 +1546,7 @@ subroutine integrateStateRKCK45(todo)
|
||||||
crystallite_partionedF0, &
|
crystallite_partionedF0, &
|
||||||
crystallite_Fi(1:3,1:3,g,i,e), &
|
crystallite_Fi(1:3,1:3,g,i,e), &
|
||||||
crystallite_partionedFp0, &
|
crystallite_partionedFp0, &
|
||||||
crystallite_subdt(g,i,e)*CC(stage), g,i,e)
|
crystallite_subdt(g,i,e)*CC(stage), g,i,e,p,c)
|
||||||
if(broken) exit
|
if(broken) exit
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
@ -1582,7 +1582,7 @@ subroutine integrateStateRKCK45(todo)
|
||||||
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
||||||
if(broken) cycle
|
if(broken) cycle
|
||||||
|
|
||||||
broken = stateJump(g,i,e)
|
broken = stateJump(g,i,e,p,c)
|
||||||
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
if(broken .and. plasticState(p)%nonlocal) nonlocalBroken = .true.
|
||||||
if(broken) cycle
|
if(broken) cycle
|
||||||
|
|
||||||
|
@ -1631,7 +1631,7 @@ end function converged
|
||||||
!> @brief calculates a jump in the state according to the current state and the current stress
|
!> @brief calculates a jump in the state according to the current state and the current stress
|
||||||
!> returns true, if state jump was successfull or not needed. false indicates NaN in delta state
|
!> returns true, if state jump was successfull or not needed. false indicates NaN in delta state
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function stateJump(ipc,ip,el) result(broken)
|
function stateJump(ipc,ip,el,p,c) result(broken)
|
||||||
|
|
||||||
integer, intent(in):: &
|
integer, intent(in):: &
|
||||||
el, & ! element index
|
el, & ! element index
|
||||||
|
@ -1646,13 +1646,10 @@ function stateJump(ipc,ip,el) result(broken)
|
||||||
mySize
|
mySize
|
||||||
logical :: broken
|
logical :: broken
|
||||||
|
|
||||||
c = material_phaseMemberAt(ipc,ip,el)
|
|
||||||
p = material_phaseAt(ipc,el)
|
|
||||||
|
|
||||||
broken = constitutive_deltaState(crystallite_S(1:3,1:3,ipc,ip,el), &
|
broken = constitutive_deltaState(crystallite_S(1:3,1:3,ipc,ip,el), &
|
||||||
crystallite_Fe(1:3,1:3,ipc,ip,el), &
|
crystallite_Fe(1:3,1:3,ipc,ip,el), &
|
||||||
crystallite_Fi(1:3,1:3,ipc,ip,el), &
|
crystallite_Fi(1:3,1:3,ipc,ip,el), &
|
||||||
ipc,ip,el)
|
ipc,ip,el,p,c)
|
||||||
if(broken) return
|
if(broken) return
|
||||||
|
|
||||||
myOffset = plasticState(p)%offsetDeltaState
|
myOffset = plasticState(p)%offsetDeltaState
|
||||||
|
|
Loading…
Reference in New Issue