Merge branch '32_NewStyleNonlocal-4' into development

This commit is contained in:
Martin Diehl 2019-02-25 20:06:20 +01:00
commit d83847446d
5 changed files with 1475 additions and 2262 deletions

View File

@ -137,11 +137,6 @@ subroutine constitutive_init()
logical :: knownPlasticity, knownSource, nonlocalConstitutionPresent logical :: knownPlasticity, knownSource, nonlocalConstitutionPresent
nonlocalConstitutionPresent = .false. nonlocalConstitutionPresent = .false.
!--------------------------------------------------------------------------------------------------
! open material.config
if (.not. IO_open_jobFile_stat(FILEUNIT,material_localFileExt)) & ! no local material configuration present...
call IO_open_file(FILEUNIT,material_configFile) ! ... open material.config file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! parse plasticities from config file ! parse plasticities from config file
if (any(phase_plasticity == PLASTICITY_NONE_ID)) call plastic_none_init if (any(phase_plasticity == PLASTICITY_NONE_ID)) call plastic_none_init
@ -150,14 +145,16 @@ subroutine constitutive_init()
if (any(phase_plasticity == PLASTICITY_KINEHARDENING_ID)) call plastic_kinehardening_init if (any(phase_plasticity == PLASTICITY_KINEHARDENING_ID)) call plastic_kinehardening_init
if (any(phase_plasticity == PLASTICITY_DISLOTWIN_ID)) call plastic_dislotwin_init if (any(phase_plasticity == PLASTICITY_DISLOTWIN_ID)) call plastic_dislotwin_init
if (any(phase_plasticity == PLASTICITY_DISLOUCLA_ID)) call plastic_disloucla_init if (any(phase_plasticity == PLASTICITY_DISLOUCLA_ID)) call plastic_disloucla_init
if (any(phase_plasticity == PLASTICITY_NONLOCAL_ID)) then if (any(phase_plasticity == PLASTICITY_NONLOCAL_ID)) call plastic_nonlocal_init
call plastic_nonlocal_init(FILEUNIT)
call plastic_nonlocal_stateInit()
endif !--------------------------------------------------------------------------------------------------
! open material.config
if (.not. IO_open_jobFile_stat(FILEUNIT,material_localFileExt)) & ! no local material configuration present...
call IO_open_file(FILEUNIT,material_configFile) ! ... open material.config file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! parse source mechanisms from config file ! parse source mechanisms from config file
call IO_checkAndRewind(FILEUNIT)
if (any(phase_source == SOURCE_thermal_dissipation_ID)) call source_thermal_dissipation_init(FILEUNIT) if (any(phase_source == SOURCE_thermal_dissipation_ID)) call source_thermal_dissipation_init(FILEUNIT)
if (any(phase_source == SOURCE_thermal_externalheat_ID)) call source_thermal_externalheat_init(FILEUNIT) if (any(phase_source == SOURCE_thermal_externalheat_ID)) call source_thermal_externalheat_init(FILEUNIT)
if (any(phase_source == SOURCE_damage_isoBrittle_ID)) call source_damage_isoBrittle_init if (any(phase_source == SOURCE_damage_isoBrittle_ID)) call source_damage_isoBrittle_init
@ -176,8 +173,6 @@ subroutine constitutive_init()
call config_deallocate('material.config/phase') call config_deallocate('material.config/phase')
write(6,'(/,a)') ' <<<+- constitutive init -+>>>' write(6,'(/,a)') ' <<<+- constitutive init -+>>>'
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
#include "compilation_info.f90"
mainProcess: if (worldrank == 0) then mainProcess: if (worldrank == 0) then
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
@ -360,7 +355,7 @@ subroutine constitutive_microstructure(Fe, Fp, ipc, ip, el)
PLASTICITY_disloucla_ID, & PLASTICITY_disloucla_ID, &
PLASTICITY_nonlocal_ID PLASTICITY_nonlocal_ID
use plastic_nonlocal, only: & use plastic_nonlocal, only: &
plastic_nonlocal_microstructure plastic_nonlocal_dependentState
use plastic_dislotwin, only: & use plastic_dislotwin, only: &
plastic_dislotwin_dependentState plastic_dislotwin_dependentState
use plastic_disloUCLA, only: & use plastic_disloUCLA, only: &
@ -392,7 +387,7 @@ subroutine constitutive_microstructure(Fe, Fp, ipc, ip, el)
instance = phase_plasticityInstance(material_phase(ipc,ip,el)) instance = phase_plasticityInstance(material_phase(ipc,ip,el))
call plastic_disloUCLA_dependentState(instance,of) call plastic_disloUCLA_dependentState(instance,of)
case (PLASTICITY_NONLOCAL_ID) plasticityType case (PLASTICITY_NONLOCAL_ID) plasticityType
call plastic_nonlocal_microstructure (Fe,Fp,ip,el) call plastic_nonlocal_dependentState (Fe,Fp,ip,el)
end select plasticityType end select plasticityType
end subroutine constitutive_microstructure end subroutine constitutive_microstructure
@ -400,15 +395,15 @@ end subroutine constitutive_microstructure
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief contains the constitutive equation for calculating the velocity gradient !> @brief contains the constitutive equation for calculating the velocity gradient
! ToDo: Discuss wheter it makes sense if crystallite handles the configuration conversion, i.e.
! Mp in, dLp_dMp out
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine constitutive_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, S6, Fi, ipc, ip, el) subroutine constitutive_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, &
S, Fi, ipc, ip, el)
use prec, only: & use prec, only: &
pReal pReal
use math, only: & use math, only: &
math_mul33x33, & math_mul33x33
math_6toSym33, &
math_sym33to6, &
math_99to3333
use material, only: & use material, only: &
phasememberAt, & phasememberAt, &
phase_plasticity, & phase_plasticity, &
@ -424,6 +419,8 @@ subroutine constitutive_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, S6, Fi, ipc, ip, e
PLASTICITY_DISLOTWIN_ID, & PLASTICITY_DISLOTWIN_ID, &
PLASTICITY_DISLOUCLA_ID, & PLASTICITY_DISLOUCLA_ID, &
PLASTICITY_NONLOCAL_ID PLASTICITY_NONLOCAL_ID
use mesh, only: &
mesh_ipVolume
use plastic_isotropic, only: & use plastic_isotropic, only: &
plastic_isotropic_LpAndItsTangent plastic_isotropic_LpAndItsTangent
use plastic_phenopowerlaw, only: & use plastic_phenopowerlaw, only: &
@ -442,9 +439,8 @@ subroutine constitutive_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, S6, Fi, ipc, ip, e
ipc, & !< component-ID of integration point ipc, & !< component-ID of integration point
ip, & !< integration point ip, & !< integration point
el !< element el !< element
real(pReal), intent(in), dimension(6) :: &
S6 !< 2nd Piola-Kirchhoff stress (vector notation)
real(pReal), intent(in), dimension(3,3) :: & real(pReal), intent(in), dimension(3,3) :: &
S, & !< 2nd Piola-Kirchhoff stress
Fi !< intermediate deformation gradient Fi !< intermediate deformation gradient
real(pReal), intent(out), dimension(3,3) :: & real(pReal), intent(out), dimension(3,3) :: &
Lp !< plastic velocity gradient Lp !< plastic velocity gradient
@ -453,11 +449,8 @@ subroutine constitutive_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, S6, Fi, ipc, ip, e
dLp_dFi !< derivative of Lp with respect to Fi dLp_dFi !< derivative of Lp with respect to Fi
real(pReal), dimension(3,3,3,3) :: & real(pReal), dimension(3,3,3,3) :: &
dLp_dMp !< derivative of Lp with respect to Mandel stress dLp_dMp !< derivative of Lp with respect to Mandel stress
real(pReal), dimension(9,9) :: &
dLp_dMp99 !< derivative of Lp with respect to Mstar (matrix notation)
real(pReal), dimension(3,3) :: & real(pReal), dimension(3,3) :: &
Mp, & !< Mandel stress work conjugate with Lp Mp !< Mandel stress work conjugate with Lp
S !< 2nd Piola-Kirchhoff stress
integer(pInt) :: & integer(pInt) :: &
ho, & !< homogenization ho, & !< homogenization
tme !< thermal member position tme !< thermal member position
@ -467,7 +460,6 @@ subroutine constitutive_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, S6, Fi, ipc, ip, e
ho = material_homogenizationAt(el) ho = material_homogenizationAt(el)
tme = thermalMapping(ho)%p(ip,el) tme = thermalMapping(ho)%p(ip,el)
S = math_6toSym33(S6)
Mp = math_mul33x33(math_mul33x33(transpose(Fi),Fi),S) Mp = math_mul33x33(math_mul33x33(transpose(Fi),Fi),S)
plasticityType: select case (phase_plasticity(material_phase(ipc,ip,el))) plasticityType: select case (phase_plasticity(material_phase(ipc,ip,el)))
@ -492,9 +484,8 @@ subroutine constitutive_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, S6, Fi, ipc, ip, e
call plastic_kinehardening_LpAndItsTangent (Lp,dLp_dMp,Mp,instance,of) call plastic_kinehardening_LpAndItsTangent (Lp,dLp_dMp,Mp,instance,of)
case (PLASTICITY_NONLOCAL_ID) plasticityType case (PLASTICITY_NONLOCAL_ID) plasticityType
call plastic_nonlocal_LpAndItsTangent (Lp,dLp_dMp99, math_sym33to6(Mp), & call plastic_nonlocal_LpAndItsTangent (Lp,dLp_dMp,Mp, &
temperature(ho)%p(tme),ip,el) temperature(ho)%p(tme),mesh_ipVolume(ip,el),ip,el)
dLp_dMp = math_99to3333(dLp_dMp99) ! ToDo: We revert here the last statement in plastic_xx_LpAndItsTanget
case (PLASTICITY_DISLOTWIN_ID) plasticityType case (PLASTICITY_DISLOTWIN_ID) plasticityType
of = phasememberAt(ipc,ip,el) of = phasememberAt(ipc,ip,el)
@ -529,7 +520,8 @@ end subroutine constitutive_LpAndItsTangents
!> @brief contains the constitutive equation for calculating the velocity gradient !> @brief contains the constitutive equation for calculating the velocity gradient
! ToDo: MD: S is Mi? ! ToDo: MD: S is Mi?
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine constitutive_LiAndItsTangents(Li, dLi_dS, dLi_dFi, S6, Fi, ipc, ip, el) subroutine constitutive_LiAndItsTangents(Li, dLi_dS, dLi_dFi, &
S, Fi, ipc, ip, el)
use prec, only: & use prec, only: &
pReal pReal
use math, only: & use math, only: &
@ -564,8 +556,8 @@ subroutine constitutive_LiAndItsTangents(Li, dLi_dS, dLi_dFi, S6, Fi, ipc, ip, e
ipc, & !< component-ID of integration point ipc, & !< component-ID of integration point
ip, & !< integration point ip, & !< integration point
el !< element el !< element
real(pReal), intent(in), dimension(6) :: & real(pReal), intent(in), dimension(3,3) :: &
S6 !< 2nd Piola-Kirchhoff stress (vector notation) S !< 2nd Piola-Kirchhoff stress
real(pReal), intent(in), dimension(3,3) :: & real(pReal), intent(in), dimension(3,3) :: &
Fi !< intermediate deformation gradient Fi !< intermediate deformation gradient
real(pReal), intent(out), dimension(3,3) :: & real(pReal), intent(out), dimension(3,3) :: &
@ -594,7 +586,7 @@ subroutine constitutive_LiAndItsTangents(Li, dLi_dS, dLi_dFi, S6, Fi, ipc, ip, e
case (PLASTICITY_isotropic_ID) plasticityType case (PLASTICITY_isotropic_ID) plasticityType
of = phasememberAt(ipc,ip,el) of = phasememberAt(ipc,ip,el)
instance = phase_plasticityInstance(material_phase(ipc,ip,el)) instance = phase_plasticityInstance(material_phase(ipc,ip,el))
call plastic_isotropic_LiAndItsTangent(my_Li, my_dLi_dS, math_6toSym33(S6),instance,of) call plastic_isotropic_LiAndItsTangent(my_Li, my_dLi_dS, S ,instance,of)
case default plasticityType case default plasticityType
my_Li = 0.0_pReal my_Li = 0.0_pReal
my_dLi_dS = 0.0_pReal my_dLi_dS = 0.0_pReal
@ -606,9 +598,9 @@ subroutine constitutive_LiAndItsTangents(Li, dLi_dS, dLi_dFi, S6, Fi, ipc, ip, e
KinematicsLoop: do k = 1_pInt, phase_Nkinematics(material_phase(ipc,ip,el)) KinematicsLoop: do k = 1_pInt, phase_Nkinematics(material_phase(ipc,ip,el))
kinematicsType: select case (phase_kinematics(k,material_phase(ipc,ip,el))) kinematicsType: select case (phase_kinematics(k,material_phase(ipc,ip,el)))
case (KINEMATICS_cleavage_opening_ID) kinematicsType case (KINEMATICS_cleavage_opening_ID) kinematicsType
call kinematics_cleavage_opening_LiAndItsTangent(my_Li, my_dLi_dS, math_6toSym33(S6), ipc, ip, el) call kinematics_cleavage_opening_LiAndItsTangent(my_Li, my_dLi_dS, S, ipc, ip, el)
case (KINEMATICS_slipplane_opening_ID) kinematicsType case (KINEMATICS_slipplane_opening_ID) kinematicsType
call kinematics_slipplane_opening_LiAndItsTangent(my_Li, my_dLi_dS, math_6toSym33(S6), ipc, ip, el) call kinematics_slipplane_opening_LiAndItsTangent(my_Li, my_dLi_dS, S, ipc, ip, el)
case (KINEMATICS_thermal_expansion_ID) kinematicsType case (KINEMATICS_thermal_expansion_ID) kinematicsType
call kinematics_thermal_expansion_LiAndItsTangent(my_Li, my_dLi_dS, ipc, ip, el) call kinematics_thermal_expansion_LiAndItsTangent(my_Li, my_dLi_dS, ipc, ip, el)
case default kinematicsType case default kinematicsType
@ -707,7 +699,8 @@ end subroutine constitutive_SandItsTangents
!> @brief returns the 2nd Piola-Kirchhoff stress tensor and its tangent with respect to !> @brief returns the 2nd Piola-Kirchhoff stress tensor and its tangent with respect to
!> the elastic and intermeidate deformation gradients using Hookes law !> the elastic and intermeidate deformation gradients using Hookes law
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine constitutive_hooke_SandItsTangents(S, dS_dFe, dS_dFi, Fe, Fi, ipc, ip, el) subroutine constitutive_hooke_SandItsTangents(S, dS_dFe, dS_dFi, &
Fe, Fi, ipc, ip, el)
use prec, only: & use prec, only: &
pReal pReal
use math, only : & use math, only : &
@ -771,7 +764,7 @@ 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
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine constitutive_collectDotState(S6, FeArray, Fi, FpArray, subdt, subfracArray,ipc, ip, el) subroutine constitutive_collectDotState(S, FeArray, Fi, FpArray, subdt, subfracArray,ipc, ip, el)
use prec, only: & use prec, only: &
pReal, & pReal, &
pLongInt pLongInt
@ -843,20 +836,20 @@ subroutine constitutive_collectDotState(S6, FeArray, Fi, FpArray, subdt, subfrac
FpArray !< plastic deformation gradient FpArray !< plastic deformation gradient
real(pReal), intent(in), dimension(3,3) :: & real(pReal), intent(in), dimension(3,3) :: &
Fi !< intermediate deformation gradient Fi !< intermediate deformation gradient
real(pReal), intent(in), dimension(6) :: & real(pReal), intent(in), dimension(3,3) :: &
S6 !< 2nd Piola Kirchhoff stress (vector notation) S !< 2nd Piola Kirchhoff stress (vector notation)
real(pReal), dimension(3,3) :: & real(pReal), dimension(3,3) :: &
Mp Mp
integer(pInt) :: & integer(pInt) :: &
ho, & !< homogenization ho, & !< homogenization
tme, & !< thermal member position tme, & !< thermal member position
s, & !< counter in source loop i, & !< counter in source loop
instance, of instance, of
ho = material_homogenizationAt(el) ho = material_homogenizationAt(el)
tme = thermalMapping(ho)%p(ip,el) tme = thermalMapping(ho)%p(ip,el)
Mp = math_mul33x33(math_mul33x33(transpose(Fi),Fi),math_6toSym33(S6)) Mp = math_mul33x33(math_mul33x33(transpose(Fi),Fi),S)
plasticityType: select case (phase_plasticity(material_phase(ipc,ip,el))) plasticityType: select case (phase_plasticity(material_phase(ipc,ip,el)))
@ -886,16 +879,16 @@ subroutine constitutive_collectDotState(S6, FeArray, Fi, FpArray, subdt, subfrac
call plastic_disloucla_dotState (Mp,temperature(ho)%p(tme),instance,of) call plastic_disloucla_dotState (Mp,temperature(ho)%p(tme),instance,of)
case (PLASTICITY_NONLOCAL_ID) plasticityType case (PLASTICITY_NONLOCAL_ID) plasticityType
call plastic_nonlocal_dotState (math_sym33to6(Mp),FeArray,FpArray,temperature(ho)%p(tme), & call plastic_nonlocal_dotState (Mp,FeArray,FpArray,temperature(ho)%p(tme), &
subdt,subfracArray,ip,el) subdt,ip,el)
end select plasticityType end select plasticityType
SourceLoop: do s = 1_pInt, phase_Nsources(material_phase(ipc,ip,el)) SourceLoop: do i = 1_pInt, phase_Nsources(material_phase(ipc,ip,el))
sourceType: select case (phase_source(s,material_phase(ipc,ip,el))) sourceType: select case (phase_source(i,material_phase(ipc,ip,el)))
case (SOURCE_damage_anisoBrittle_ID) sourceType case (SOURCE_damage_anisoBrittle_ID) sourceType
call source_damage_anisoBrittle_dotState (math_6toSym33(S6), ipc, ip, el) !< correct stress? call source_damage_anisoBrittle_dotState (S, ipc, ip, el) !< correct stress?
case (SOURCE_damage_isoDuctile_ID) sourceType case (SOURCE_damage_isoDuctile_ID) sourceType
call source_damage_isoDuctile_dotState ( ipc, ip, el) call source_damage_isoDuctile_dotState ( ipc, ip, el)
@ -969,7 +962,7 @@ subroutine constitutive_collectDeltaState(S, Fe, Fi, ipc, ip, el)
call plastic_kinehardening_deltaState(Mp,instance,of) call plastic_kinehardening_deltaState(Mp,instance,of)
case (PLASTICITY_NONLOCAL_ID) plasticityType case (PLASTICITY_NONLOCAL_ID) plasticityType
call plastic_nonlocal_deltaState(math_sym33to6(Mp),ip,el) call plastic_nonlocal_deltaState(Mp,ip,el)
end select plasticityType end select plasticityType
@ -991,7 +984,7 @@ end subroutine constitutive_collectDeltaState
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief returns array of constitutive results !> @brief returns array of constitutive results
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function constitutive_postResults(S6, Fi, FeArray, ipc, ip, el) function constitutive_postResults(S, Fi, FeArray, ipc, ip, el)
use prec, only: & use prec, only: &
pReal pReal
use math, only: & use math, only: &
@ -1056,8 +1049,8 @@ function constitutive_postResults(S6, Fi, FeArray, ipc, ip, el)
Fi !< intermediate deformation gradient Fi !< intermediate deformation gradient
real(pReal), intent(in), dimension(3,3,homogenization_maxNgrains,theMesh%elem%nIPs,theMesh%Nelems) :: & real(pReal), intent(in), dimension(3,3,homogenization_maxNgrains,theMesh%elem%nIPs,theMesh%Nelems) :: &
FeArray !< elastic deformation gradient FeArray !< elastic deformation gradient
real(pReal), intent(in), dimension(6) :: & real(pReal), intent(in), dimension(3,3) :: &
S6 !< 2nd Piola Kirchhoff stress (vector notation) S !< 2nd Piola Kirchhoff stress
real(pReal), dimension(3,3) :: & real(pReal), dimension(3,3) :: &
Mp !< Mandel stress Mp !< Mandel stress
integer(pInt) :: & integer(pInt) :: &
@ -1065,11 +1058,11 @@ function constitutive_postResults(S6, Fi, FeArray, ipc, ip, el)
integer(pInt) :: & integer(pInt) :: &
ho, & !< homogenization ho, & !< homogenization
tme, & !< thermal member position tme, & !< thermal member position
s, of, instance !< counter in source loop i, of, instance !< counter in source loop
constitutive_postResults = 0.0_pReal constitutive_postResults = 0.0_pReal
Mp = math_mul33x33(math_mul33x33(transpose(Fi),Fi),math_6toSym33(S6)) Mp = math_mul33x33(math_mul33x33(transpose(Fi),Fi),S)
ho = material_homogenizationAt(el) ho = material_homogenizationAt(el)
tme = thermalMapping(ho)%p(ip,el) tme = thermalMapping(ho)%p(ip,el)
@ -1110,14 +1103,14 @@ function constitutive_postResults(S6, Fi, FeArray, ipc, ip, el)
case (PLASTICITY_NONLOCAL_ID) plasticityType case (PLASTICITY_NONLOCAL_ID) plasticityType
constitutive_postResults(startPos:endPos) = & constitutive_postResults(startPos:endPos) = &
plastic_nonlocal_postResults (S6,FeArray,ip,el) plastic_nonlocal_postResults (Mp,ip,el)
end select plasticityType end select plasticityType
SourceLoop: do s = 1_pInt, phase_Nsources(material_phase(ipc,ip,el)) SourceLoop: do i = 1_pInt, phase_Nsources(material_phase(ipc,ip,el))
startPos = endPos + 1_pInt startPos = endPos + 1_pInt
endPos = endPos + sourceState(material_phase(ipc,ip,el))%p(s)%sizePostResults endPos = endPos + sourceState(material_phase(ipc,ip,el))%p(i)%sizePostResults
of = phasememberAt(ipc,ip,el) of = phasememberAt(ipc,ip,el)
sourceType: select case (phase_source(s,material_phase(ipc,ip,el))) sourceType: select case (phase_source(i,material_phase(ipc,ip,el)))
case (SOURCE_damage_isoBrittle_ID) sourceType case (SOURCE_damage_isoBrittle_ID) sourceType
constitutive_postResults(startPos:endPos) = source_damage_isoBrittle_postResults(material_phase(ipc,ip,el),of) constitutive_postResults(startPos:endPos) = source_damage_isoBrittle_postResults(material_phase(ipc,ip,el),of)
case (SOURCE_damage_isoDuctile_ID) sourceType case (SOURCE_damage_isoDuctile_ID) sourceType

View File

@ -20,7 +20,6 @@ module crystallite
use material, only: & use material, only: &
homogenization_Ngrains homogenization_Ngrains
implicit none implicit none
private private
@ -284,7 +283,7 @@ subroutine crystallite_init
crystallite_outputID(o,c) = orientation_ID crystallite_outputID(o,c) = orientation_ID
case ('grainrotation') outputName case ('grainrotation') outputName
crystallite_outputID(o,c) = grainrotation_ID crystallite_outputID(o,c) = grainrotation_ID
case ('defgrad','f') outputName case ('defgrad','f') outputName ! ToDo: no alias (f only)
crystallite_outputID(o,c) = defgrad_ID crystallite_outputID(o,c) = defgrad_ID
case ('fe') outputName case ('fe') outputName
crystallite_outputID(o,c) = fe_ID crystallite_outputID(o,c) = fe_ID
@ -298,13 +297,13 @@ subroutine crystallite_init
crystallite_outputID(o,c) = li_ID crystallite_outputID(o,c) = li_ID
case ('p','firstpiola','1stpiola') outputName case ('p','firstpiola','1stpiola') outputName
crystallite_outputID(o,c) = p_ID crystallite_outputID(o,c) = p_ID
case ('s','tstar','secondpiola','2ndpiola') outputName case ('s','tstar','secondpiola','2ndpiola') outputName ! ToDo: no alias (s only)
crystallite_outputID(o,c) = s_ID crystallite_outputID(o,c) = s_ID
case ('elasmatrix') outputName case ('elasmatrix') outputName
crystallite_outputID(o,c) = elasmatrix_ID crystallite_outputID(o,c) = elasmatrix_ID
case ('neighboringip') outputName case ('neighboringip') outputName ! ToDo: this is not a result, it is static. Should be written out by mesh
crystallite_outputID(o,c) = neighboringip_ID crystallite_outputID(o,c) = neighboringip_ID
case ('neighboringelement') outputName case ('neighboringelement') outputName ! ToDo: this is not a result, it is static. Should be written out by mesh
crystallite_outputID(o,c) = neighboringelement_ID crystallite_outputID(o,c) = neighboringelement_ID
case default outputName case default outputName
call IO_error(105_pInt,ext_msg=trim(str(o))//' (Crystallite)') call IO_error(105_pInt,ext_msg=trim(str(o))//' (Crystallite)')
@ -421,7 +420,7 @@ end subroutine crystallite_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculate stress (P) !> @brief calculate stress (P)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function crystallite_stress(a) function crystallite_stress(dummyArgumentToPreventInternalCompilerErrorWithGCC)
use prec, only: & use prec, only: &
tol_math_check, & tol_math_check, &
dNeq0 dNeq0
@ -457,14 +456,11 @@ function crystallite_stress(a)
sourceState, & sourceState, &
phase_Nsources, & phase_Nsources, &
phaseAt, phasememberAt phaseAt, phasememberAt
use constitutive, only: &
constitutive_SandItsTangents, &
constitutive_LpAndItsTangents, &
constitutive_LiAndItsTangents
implicit none implicit none
logical, dimension(theMesh%elem%nIPs,theMesh%Nelems) :: crystallite_stress logical, dimension(theMesh%elem%nIPs,theMesh%Nelems) :: crystallite_stress
real(pReal), intent(in), optional :: a !ToDo: for some reason this prevents an internal compiler error in GNU. Very strange real(pReal), intent(in), optional :: &
dummyArgumentToPreventInternalCompilerErrorWithGCC
real(pReal) :: & real(pReal) :: &
formerSubStep formerSubStep
integer(pInt) :: & integer(pInt) :: &
@ -759,7 +755,7 @@ subroutine crystallite_stressTangent()
crystallite_Fe(1:3,1:3,c,i,e), & crystallite_Fe(1:3,1:3,c,i,e), &
crystallite_Fi(1:3,1:3,c,i,e),c,i,e) ! call constitutive law to calculate elastic stress tangent crystallite_Fi(1:3,1:3,c,i,e),c,i,e) ! call constitutive law to calculate elastic stress tangent
call constitutive_LiAndItsTangents(devNull,dLidS,dLidFi, & call constitutive_LiAndItsTangents(devNull,dLidS,dLidFi, &
crystallite_Tstar_v(1:6,c,i,e), & math_6toSym33(crystallite_Tstar_v(1:6,c,i,e)), &
crystallite_Fi(1:3,1:3,c,i,e), & crystallite_Fi(1:3,1:3,c,i,e), &
c,i,e) ! call constitutive law to calculate Li tangent in lattice configuration c,i,e) ! call constitutive law to calculate Li tangent in lattice configuration
@ -788,7 +784,7 @@ subroutine crystallite_stressTangent()
endif endif
call constitutive_LpAndItsTangents(devNull,dLpdS,dLpdFi, & call constitutive_LpAndItsTangents(devNull,dLpdS,dLpdFi, &
crystallite_Tstar_v(1:6,c,i,e), & math_6toSym33(crystallite_Tstar_v(1:6,c,i,e)), &
crystallite_Fi(1:3,1:3,c,i,e),c,i,e) ! call constitutive law to calculate Lp tangent in lattice configuration crystallite_Fi(1:3,1:3,c,i,e),c,i,e) ! call constitutive law to calculate Lp tangent in lattice configuration
dLpdS = math_mul3333xx3333(dLpdFi,dFidS) + dLpdS dLpdS = math_mul3333xx3333(dLpdFi,dFidS) + dLpdS
@ -1071,7 +1067,7 @@ function crystallite_postResults(ipc, ip, el)
c = c + 1_pInt c = c + 1_pInt
if (size(crystallite_postResults)-c > 0_pInt) & if (size(crystallite_postResults)-c > 0_pInt) &
crystallite_postResults(c+1:size(crystallite_postResults)) = & crystallite_postResults(c+1:size(crystallite_postResults)) = &
constitutive_postResults(crystallite_Tstar_v(1:6,ipc,ip,el), crystallite_Fi(1:3,1:3,ipc,ip,el), & constitutive_postResults(math_6toSym33(crystallite_Tstar_v(1:6,ipc,ip,el)), crystallite_Fi(1:3,1:3,ipc,ip,el), &
crystallite_Fe, ipc, ip, el) crystallite_Fe, ipc, ip, el)
end function crystallite_postResults end function crystallite_postResults
@ -1383,7 +1379,7 @@ logical function integrateStress(&
!* calculate intermediate velocity gradient and its tangent from constitutive law !* calculate intermediate velocity gradient and its tangent from constitutive law
call constitutive_LiAndItsTangents(Li_constitutive, dLi_dS, dLi_dFi, & call constitutive_LiAndItsTangents(Li_constitutive, dLi_dS, dLi_dFi, &
math_sym33to6(S), Fi_new, ipc, ip, el) S, Fi_new, ipc, ip, el)
#ifdef DEBUG #ifdef DEBUG
if (iand(debug_level(debug_crystallite), debug_levelExtensive) /= 0_pInt & if (iand(debug_level(debug_crystallite), debug_levelExtensive) /= 0_pInt &
@ -2263,6 +2259,8 @@ end subroutine update_state
subroutine update_dotState(timeFraction) subroutine update_dotState(timeFraction)
use, intrinsic :: & use, intrinsic :: &
IEEE_arithmetic IEEE_arithmetic
use math, only: &
math_6toSym33 !ToDo: Temporarly needed until T_star_v is called S and stored as matrix
use material, only: & use material, only: &
plasticState, & plasticState, &
sourceState, & sourceState, &
@ -2295,7 +2293,7 @@ subroutine update_dotState(timeFraction)
do g = 1,homogenization_Ngrains(mesh_element(3,e)) do g = 1,homogenization_Ngrains(mesh_element(3,e))
!$OMP FLUSH(nonlocalStop) !$OMP FLUSH(nonlocalStop)
if ((crystallite_todo(g,i,e) .and. .not. crystallite_converged(g,i,e)) .and. .not. nonlocalStop) then if ((crystallite_todo(g,i,e) .and. .not. crystallite_converged(g,i,e)) .and. .not. nonlocalStop) then
call constitutive_collectDotState(crystallite_Tstar_v(1:6,g,i,e), & call constitutive_collectDotState(math_6toSym33(crystallite_Tstar_v(1:6,g,i,e)), &
crystallite_Fe, & crystallite_Fe, &
crystallite_Fi(1:3,1:3,g,i,e), & crystallite_Fi(1:3,1:3,g,i,e), &
crystallite_Fp, & crystallite_Fp, &

File diff suppressed because it is too large Load Diff

View File

@ -70,6 +70,10 @@ module math
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! Provide deprecated names for compatibility ! Provide deprecated names for compatibility
interface math_cross
module procedure math_crossproduct
end interface math_cross
! ToDo MD: Our naming scheme was a little bit odd: We use essentially the re-ordering according to Nye ! ToDo MD: Our naming scheme was a little bit odd: We use essentially the re-ordering according to Nye
! (convenient because Abaqus and Marc want to have 12 on position 4) ! (convenient because Abaqus and Marc want to have 12 on position 4)
! but weight the shear components according to Mandel (convenient for matrix multiplications) ! but weight the shear components according to Mandel (convenient for matrix multiplications)
@ -98,23 +102,13 @@ module math
module procedure math_99to3333 module procedure math_99to3333
end interface math_Plain99to3333 end interface math_Plain99to3333
interface math_Mandel3333to66
module procedure math_sym3333to66
end interface math_Mandel3333to66
interface math_Mandel66to3333
module procedure math_66toSym3333
end interface math_Mandel66to3333
public :: & public :: &
math_Plain33to9, & math_Plain33to9, &
math_Plain9to33, & math_Plain9to33, &
math_Mandel33to6, & math_Mandel33to6, &
math_Mandel6to33, & math_Mandel6to33, &
math_Plain3333to99, & math_Plain3333to99, &
math_Plain99to3333, & math_Plain99to3333
math_Mandel3333to66, &
math_Mandel66to3333
!--------------------------------------------------------------------------------------------------- !---------------------------------------------------------------------------------------------------
public :: & public :: &
@ -129,6 +123,7 @@ module math
math_identity4th, & math_identity4th, &
math_civita, & math_civita, &
math_delta, & math_delta, &
math_cross, &
math_crossproduct, & math_crossproduct, &
math_tensorproduct33, & math_tensorproduct33, &
math_mul3x3, & math_mul3x3, &

File diff suppressed because it is too large Load Diff