all constitutive modules now contain a new function "deltaState", which in the future allows to have an instantaneous and incremental change of the state (additional to the rate based evolution with dotState).
This commit is contained in:
parent
1a96a9fbad
commit
84d4652a07
|
@ -39,6 +39,7 @@ type(p_vec), dimension(:,:,:), allocatable :: &
|
|||
constitutive_state, & ! pointer array to current microstructure (end of converged time step)
|
||||
constitutive_state_backup, & ! pointer array to backed up microstructure (end of converged time step)
|
||||
constitutive_dotState, & ! pointer array to evolution of current microstructure
|
||||
constitutive_deltaState, & ! pointer array to incremental change of current microstructure
|
||||
constitutive_previousDotState,& ! pointer array to previous evolution of current microstructure
|
||||
constitutive_previousDotState2,& ! pointer array to 2nd previous evolution of current microstructure
|
||||
constitutive_dotState_backup, & ! pointer array to backed up evolution of current microstructure
|
||||
|
@ -70,6 +71,7 @@ contains
|
|||
!* - constitutive_TandItsTangent
|
||||
!* - constitutive_hooke_TandItsTangent
|
||||
!* - constitutive_collectDotState
|
||||
!* - constitutive_collectDeltaState
|
||||
!* - constitutive_collectDotTemperature
|
||||
!* - constitutive_postResults
|
||||
!****************************************
|
||||
|
@ -187,6 +189,7 @@ allocate(constitutive_subState0(gMax,iMax,eMax))
|
|||
allocate(constitutive_state(gMax,iMax,eMax))
|
||||
allocate(constitutive_state_backup(gMax,iMax,eMax))
|
||||
allocate(constitutive_dotState(gMax,iMax,eMax))
|
||||
allocate(constitutive_deltaState(gMax,iMax,eMax))
|
||||
allocate(constitutive_dotState_backup(gMax,iMax,eMax))
|
||||
allocate(constitutive_aTolState(gMax,iMax,eMax))
|
||||
allocate(constitutive_sizeDotState(gMax,iMax,eMax)) ; constitutive_sizeDotState = 0_pInt
|
||||
|
@ -219,6 +222,7 @@ endif
|
|||
allocate(constitutive_state_backup(g,i,e)%p(constitutive_j2_sizeState(myInstance)))
|
||||
allocate(constitutive_aTolState(g,i,e)%p(constitutive_j2_sizeState(myInstance)))
|
||||
allocate(constitutive_dotState(g,i,e)%p(constitutive_j2_sizeDotState(myInstance)))
|
||||
allocate(constitutive_deltaState(g,i,e)%p(constitutive_j2_sizeDotState(myInstance)))
|
||||
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_j2_sizeDotState(myInstance)))
|
||||
if (any(numerics_integrator == 1_pInt)) then
|
||||
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_j2_sizeDotState(myInstance)))
|
||||
|
@ -246,6 +250,7 @@ endif
|
|||
allocate(constitutive_state_backup(g,i,e)%p(constitutive_phenopowerlaw_sizeState(myInstance)))
|
||||
allocate(constitutive_aTolState(g,i,e)%p(constitutive_phenopowerlaw_sizeState(myInstance)))
|
||||
allocate(constitutive_dotState(g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(myInstance)))
|
||||
allocate(constitutive_deltaState(g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(myInstance)))
|
||||
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(myInstance)))
|
||||
if (any(numerics_integrator == 1_pInt)) then
|
||||
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(myInstance)))
|
||||
|
@ -273,6 +278,7 @@ endif
|
|||
allocate(constitutive_state_backup(g,i,e)%p(constitutive_titanmod_sizeState(myInstance)))
|
||||
allocate(constitutive_aTolState(g,i,e)%p(constitutive_titanmod_sizeState(myInstance)))
|
||||
allocate(constitutive_dotState(g,i,e)%p(constitutive_titanmod_sizeDotState(myInstance)))
|
||||
allocate(constitutive_deltaState(g,i,e)%p(constitutive_titanmod_sizeDotState(myInstance)))
|
||||
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_titanmod_sizeDotState(myInstance)))
|
||||
if (any(numerics_integrator == 1_pInt)) then
|
||||
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_titanmod_sizeDotState(myInstance)))
|
||||
|
@ -300,6 +306,7 @@ endif
|
|||
allocate(constitutive_state_backup(g,i,e)%p(constitutive_dislotwin_sizeState(myInstance)))
|
||||
allocate(constitutive_aTolState(g,i,e)%p(constitutive_dislotwin_sizeState(myInstance)))
|
||||
allocate(constitutive_dotState(g,i,e)%p(constitutive_dislotwin_sizeDotState(myInstance)))
|
||||
allocate(constitutive_deltaState(g,i,e)%p(constitutive_dislotwin_sizeDotState(myInstance)))
|
||||
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_dislotwin_sizeDotState(myInstance)))
|
||||
if (any(numerics_integrator == 1_pInt)) then
|
||||
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_dislotwin_sizeDotState(myInstance)))
|
||||
|
@ -327,6 +334,7 @@ endif
|
|||
allocate(constitutive_state_backup(g,i,e)%p(constitutive_nonlocal_sizeState(myInstance)))
|
||||
allocate(constitutive_aTolState(g,i,e)%p(constitutive_nonlocal_sizeState(myInstance)))
|
||||
allocate(constitutive_dotState(g,i,e)%p(constitutive_nonlocal_sizeDotState(myInstance)))
|
||||
allocate(constitutive_deltaState(g,i,e)%p(constitutive_nonlocal_sizeDotState(myInstance)))
|
||||
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_nonlocal_sizeDotState(myInstance)))
|
||||
if (any(numerics_integrator == 1_pInt)) then
|
||||
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_nonlocal_sizeDotState(myInstance)))
|
||||
|
@ -380,6 +388,7 @@ constitutive_maxSizePostResults = maxval(constitutive_sizePostResults)
|
|||
write(6,'(a32,1x,7(i8,1x))') 'constitutive_state: ', shape(constitutive_state)
|
||||
write(6,'(a32,1x,7(i8,1x))') 'constitutive_aTolState: ', shape(constitutive_aTolState)
|
||||
write(6,'(a32,1x,7(i8,1x))') 'constitutive_dotState: ', shape(constitutive_dotState)
|
||||
write(6,'(a32,1x,7(i8,1x))') 'constitutive_deltaState: ', shape(constitutive_deltaState)
|
||||
write(6,'(a32,1x,7(i8,1x))') 'constitutive_sizeState: ', shape(constitutive_sizeState)
|
||||
write(6,'(a32,1x,7(i8,1x))') 'constitutive_sizeDotState: ', shape(constitutive_sizeDotState)
|
||||
write(6,'(a32,1x,7(i8,1x))') 'constitutive_sizePostResults: ', shape(constitutive_sizePostResults)
|
||||
|
@ -755,6 +764,87 @@ endif
|
|||
endsubroutine
|
||||
|
||||
|
||||
!*********************************************************************
|
||||
!* This subroutine contains the constitutive equation for *
|
||||
!* calculating the incremental change of microstructure based on the *
|
||||
!* state at the beginning of the timestep *
|
||||
!*********************************************************************
|
||||
subroutine constitutive_collectDeltaState(Tstar_v, Fe, Fp, Temperature, ipc, ip, el)
|
||||
|
||||
use prec, only: pReal, pLongInt
|
||||
use debug, only: debug_cumDeltaStateCalls, &
|
||||
debug_cumDeltaStateTicks, &
|
||||
debug_what, &
|
||||
debug_constitutive, &
|
||||
debug_levelBasic
|
||||
use mesh, only: mesh_NcpElems, &
|
||||
mesh_maxNips
|
||||
use material, only: phase_plasticity, &
|
||||
material_phase, &
|
||||
homogenization_maxNgrains
|
||||
use constitutive_j2, only: constitutive_j2_deltaState, &
|
||||
constitutive_j2_label
|
||||
use constitutive_phenopowerlaw, only: constitutive_phenopowerlaw_deltaState, &
|
||||
constitutive_phenopowerlaw_label
|
||||
use constitutive_titanmod, only: constitutive_titanmod_deltaState, &
|
||||
constitutive_titanmod_label
|
||||
use constitutive_dislotwin, only: constitutive_dislotwin_deltaState, &
|
||||
constitutive_dislotwin_label
|
||||
use constitutive_nonlocal, only: constitutive_nonlocal_deltaState, &
|
||||
constitutive_nonlocal_label
|
||||
|
||||
implicit none
|
||||
!*** input variables
|
||||
integer(pInt), intent(in) :: ipc, & ! component-ID of current integration point
|
||||
ip, & ! current integration point
|
||||
el ! current element
|
||||
real(pReal), intent(in) :: Temperature
|
||||
real(pReal), dimension(3,3,homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
||||
Fe, & ! elastic deformation gradient
|
||||
Fp ! plastic deformation gradient
|
||||
real(pReal), dimension(6), intent(in) :: &
|
||||
Tstar_v ! 2nd Piola Kirchhoff stress tensor (Mandel)
|
||||
!*** local variables
|
||||
integer(pLongInt) tick, tock, &
|
||||
tickrate, &
|
||||
maxticks
|
||||
|
||||
if (iand(debug_what(debug_constitutive), debug_levelBasic) /= 0_pInt) then
|
||||
call system_clock(count=tick,count_rate=tickrate,count_max=maxticks)
|
||||
endif
|
||||
|
||||
select case (phase_plasticity(material_phase(ipc,ip,el)))
|
||||
|
||||
case (constitutive_j2_label)
|
||||
constitutive_deltaState(ipc,ip,el)%p = constitutive_j2_deltaState(Tstar_v,Temperature,constitutive_subState0,ipc,ip,el)
|
||||
|
||||
case (constitutive_phenopowerlaw_label)
|
||||
constitutive_deltaState(ipc,ip,el)%p = constitutive_phenopowerlaw_deltaState(Tstar_v,Temperature,constitutive_subState0,ipc,ip,el)
|
||||
|
||||
case (constitutive_titanmod_label)
|
||||
constitutive_deltaState(ipc,ip,el)%p = constitutive_titanmod_deltaState(Tstar_v,Temperature,constitutive_subState0,ipc,ip,el)
|
||||
|
||||
case (constitutive_dislotwin_label)
|
||||
constitutive_deltaState(ipc,ip,el)%p = constitutive_dislotwin_deltaState(Tstar_v,Temperature,constitutive_subState0,ipc,ip,el)
|
||||
|
||||
case (constitutive_nonlocal_label)
|
||||
constitutive_deltaState(ipc,ip,el)%p = constitutive_nonlocal_deltaState(Tstar_v, Fe, Fp, Temperature, constitutive_subState0, ipc, ip, el)
|
||||
|
||||
end select
|
||||
|
||||
if (iand(debug_what(debug_constitutive), debug_levelBasic) /= 0_pInt) then
|
||||
call system_clock(count=tock,count_rate=tickrate,count_max=maxticks)
|
||||
!$OMP CRITICAL (debugTimingDeltaState)
|
||||
debug_cumDeltaStateCalls = debug_cumDeltaStateCalls + 1_pInt
|
||||
debug_cumDeltaStateTicks = debug_cumDeltaStateTicks + tock-tick
|
||||
!$OMP FLUSH (debug_cumDeltaStateTicks)
|
||||
if (tock < tick) debug_cumDeltaStateTicks = debug_cumDeltaStateTicks + maxticks
|
||||
!$OMP END CRITICAL (debugTimingDeltaState)
|
||||
endif
|
||||
|
||||
endsubroutine
|
||||
|
||||
|
||||
|
||||
!*********************************************************************
|
||||
!* This subroutine contains the constitutive equation for *
|
||||
|
|
|
@ -124,9 +124,10 @@ CONTAINS
|
|||
!* - constitutive_dislotwin_homogenizedC
|
||||
!* - constitutive_dislotwin_microstructure
|
||||
!* - constitutive_dislotwin_LpAndItsTangent
|
||||
!* - consistutive_dislotwin_dotState
|
||||
!* - constitutive_dislotwin_dotState
|
||||
!* - constitutive_dislotwin_deltaState
|
||||
!* - constitutive_dislotwin_dotTemperature
|
||||
!* - consistutive_dislotwin_postResults
|
||||
!* - constitutive_dislotwin_postResults
|
||||
!****************************************
|
||||
|
||||
subroutine constitutive_dislotwin_init(file)
|
||||
|
@ -1319,6 +1320,43 @@ return
|
|||
end function
|
||||
|
||||
|
||||
!*********************************************************************
|
||||
!* (instantaneous) incremental change of microstructure *
|
||||
!*********************************************************************
|
||||
function constitutive_dislotwin_deltaState(Tstar_v, Temperature, state, g,ip,el)
|
||||
|
||||
use prec, only: pReal, &
|
||||
pInt, &
|
||||
p_vec
|
||||
use mesh, only: mesh_NcpElems, &
|
||||
mesh_maxNips
|
||||
use material, only: homogenization_maxNgrains, &
|
||||
material_phase, &
|
||||
phase_plasticityInstance
|
||||
|
||||
implicit none
|
||||
|
||||
!*** input variables
|
||||
integer(pInt), intent(in) :: g, & ! current grain number
|
||||
ip, & ! current integration point
|
||||
el ! current element number
|
||||
real(pReal), intent(in) :: Temperature ! temperature
|
||||
real(pReal), dimension(6), intent(in) :: Tstar_v ! current 2nd Piola-Kirchhoff stress in Mandel notation
|
||||
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
||||
state ! current microstructural state
|
||||
|
||||
!*** output variables
|
||||
real(pReal), dimension(constitutive_dislotwin_sizeDotState(phase_plasticityInstance(material_phase(g,ip,el)))) :: &
|
||||
constitutive_dislotwin_deltaState ! change of state variables / microstructure
|
||||
|
||||
!*** local variables
|
||||
|
||||
|
||||
constitutive_dislotwin_deltaState = 0.0_pReal
|
||||
|
||||
endfunction
|
||||
|
||||
|
||||
pure function constitutive_dislotwin_dotTemperature(Tstar_v,Temperature,state,g,ip,el)
|
||||
!*********************************************************************
|
||||
!* rate of change of microstructure *
|
||||
|
|
|
@ -93,6 +93,7 @@ module constitutive_j2
|
|||
constitutive_j2_microstructure, &
|
||||
constitutive_j2_LpAndItsTangent, &
|
||||
constitutive_j2_dotState, &
|
||||
constitutive_j2_deltaState, &
|
||||
constitutive_j2_dotTemperature, &
|
||||
constitutive_j2_postResults
|
||||
|
||||
|
@ -534,6 +535,44 @@ pure function constitutive_j2_dotState(Tstar_v, Temperature, state, g, ip, el)
|
|||
end function constitutive_j2_dotState
|
||||
|
||||
|
||||
|
||||
!*********************************************************************
|
||||
!* (instantaneous) incremental change of microstructure *
|
||||
!*********************************************************************
|
||||
function constitutive_j2_deltaState(Tstar_v, Temperature, state, g,ip,el)
|
||||
|
||||
use prec, only: pReal, &
|
||||
pInt, &
|
||||
p_vec
|
||||
use mesh, only: mesh_NcpElems, &
|
||||
mesh_maxNips
|
||||
use material, only: homogenization_maxNgrains, &
|
||||
material_phase, &
|
||||
phase_plasticityInstance
|
||||
|
||||
implicit none
|
||||
|
||||
!*** input variables
|
||||
integer(pInt), intent(in) :: g, & ! current grain number
|
||||
ip, & ! current integration point
|
||||
el ! current element number
|
||||
real(pReal), intent(in) :: Temperature ! temperature
|
||||
real(pReal), dimension(6), intent(in) :: Tstar_v ! current 2nd Piola-Kirchhoff stress in Mandel notation
|
||||
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
||||
state ! current microstructural state
|
||||
|
||||
!*** output variables
|
||||
real(pReal), dimension(constitutive_j2_sizeDotState(phase_plasticityInstance(material_phase(g,ip,el)))) :: &
|
||||
constitutive_j2_deltaState ! change of state variables / microstructure
|
||||
|
||||
!*** local variables
|
||||
|
||||
|
||||
constitutive_j2_deltaState = 0.0_pReal
|
||||
|
||||
endfunction
|
||||
|
||||
|
||||
!****************************************************************
|
||||
!* calculates the rate of change of temperature *
|
||||
!****************************************************************
|
||||
|
|
|
@ -31,111 +31,160 @@ MODULE constitutive_nonlocal
|
|||
|
||||
!* Include other modules
|
||||
use prec, only: pReal,pInt
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
||||
|
||||
!* Definition of parameters
|
||||
character (len=*), parameter :: constitutive_nonlocal_label = 'nonlocal'
|
||||
character(len=22), dimension(10), parameter :: constitutive_nonlocal_listBasicStates = (/'rhoSglEdgePosMobile ', &
|
||||
'rhoSglEdgeNegMobile ', &
|
||||
'rhoSglScrewPosMobile ', &
|
||||
'rhoSglScrewNegMobile ', &
|
||||
'rhoSglEdgePosImmobile ', &
|
||||
'rhoSglEdgeNegImmobile ', &
|
||||
'rhoSglScrewPosImmobile', &
|
||||
'rhoSglScrewNegImmobile', &
|
||||
'rhoDipEdge ', &
|
||||
'rhoDipScrew ' /) ! list of "basic" microstructural state variables that are independent from other state variables
|
||||
character(len=16), dimension(3), parameter :: constitutive_nonlocal_listDependentStates = (/'rhoForest ', &
|
||||
'tauThreshold ', &
|
||||
'tauBack ' /) ! list of microstructural state variables that depend on other state variables
|
||||
character(len=16), dimension(4), parameter :: constitutive_nonlocal_listOtherStates = (/'velocityEdgePos ', &
|
||||
'velocityEdgeNeg ', &
|
||||
'velocityScrewPos', &
|
||||
'velocityScrewNeg' /) ! list of other dependent state variables that are not updated by microstructure
|
||||
real(pReal), parameter :: kB = 1.38e-23_pReal ! Physical parameter, Boltzmann constant in J/Kelvin
|
||||
|
||||
character (len=*), parameter, public :: &
|
||||
constitutive_nonlocal_label = 'nonlocal'
|
||||
|
||||
character(len=22), dimension(10), parameter, private :: &
|
||||
constitutive_nonlocal_listBasicStates = (/'rhoSglEdgePosMobile ', &
|
||||
'rhoSglEdgeNegMobile ', &
|
||||
'rhoSglScrewPosMobile ', &
|
||||
'rhoSglScrewNegMobile ', &
|
||||
'rhoSglEdgePosImmobile ', &
|
||||
'rhoSglEdgeNegImmobile ', &
|
||||
'rhoSglScrewPosImmobile', &
|
||||
'rhoSglScrewNegImmobile', &
|
||||
'rhoDipEdge ', &
|
||||
'rhoDipScrew ' /)! list of "basic" microstructural state variables that are independent from other state variables
|
||||
|
||||
character(len=16), dimension(3), parameter, private :: &
|
||||
constitutive_nonlocal_listDependentStates = (/'rhoForest ', &
|
||||
'tauThreshold ', &
|
||||
'tauBack ' /) ! list of microstructural state variables that depend on other state variables
|
||||
|
||||
character(len=16), dimension(4), parameter, private :: &
|
||||
constitutive_nonlocal_listOtherStates = (/'velocityEdgePos ', &
|
||||
'velocityEdgeNeg ', &
|
||||
'velocityScrewPos', &
|
||||
'velocityScrewNeg' /) ! list of other dependent state variables that are not updated by microstructure
|
||||
|
||||
real(pReal), parameter, private :: &
|
||||
kB = 1.38e-23_pReal ! Physical parameter, Boltzmann constant in J/Kelvin
|
||||
|
||||
|
||||
!* Definition of global variables
|
||||
integer(pInt), dimension(:), allocatable :: constitutive_nonlocal_sizeDotState, & ! number of dotStates = number of basic state variables
|
||||
constitutive_nonlocal_sizeDependentState, & ! number of dependent state variables
|
||||
constitutive_nonlocal_sizeState, & ! total number of state variables
|
||||
constitutive_nonlocal_sizePostResults ! cumulative size of post results
|
||||
integer(pInt), dimension(:,:), allocatable, target :: constitutive_nonlocal_sizePostResult ! size of each post result output
|
||||
character(len=64), dimension(:,:), allocatable, target :: constitutive_nonlocal_output ! name of each post result output
|
||||
integer(pInt), dimension(:), allocatable :: constitutive_nonlocal_Noutput ! number of outputs per instance of this plasticity
|
||||
|
||||
character(len=32), dimension(:), allocatable :: constitutive_nonlocal_structureName ! name of the lattice structure
|
||||
integer(pInt), dimension(:), allocatable :: constitutive_nonlocal_structure, & ! number representing the kind of lattice structure
|
||||
constitutive_nonlocal_totalNslip ! total number of active slip systems for each instance
|
||||
integer(pInt), dimension(:,:), allocatable :: constitutive_nonlocal_Nslip, & ! number of active slip systems for each family and instance
|
||||
constitutive_nonlocal_slipFamily, & ! lookup table relating active slip system to slip family for each instance
|
||||
constitutive_nonlocal_slipSystemLattice ! lookup table relating active slip system index to lattice slip system index for each instance
|
||||
integer(pInt), dimension(:), allocatable, public :: &
|
||||
constitutive_nonlocal_sizeDotState, & ! number of dotStates = number of basic state variables
|
||||
constitutive_nonlocal_sizeDependentState, & ! number of dependent state variables
|
||||
constitutive_nonlocal_sizeState, & ! total number of state variables
|
||||
constitutive_nonlocal_sizePostResults ! cumulative size of post results
|
||||
|
||||
real(pReal), dimension(:), allocatable :: constitutive_nonlocal_CoverA, & ! c/a ratio for hex type lattice
|
||||
constitutive_nonlocal_C11, & ! C11 element in elasticity matrix
|
||||
constitutive_nonlocal_C12, & ! C12 element in elasticity matrix
|
||||
constitutive_nonlocal_C13, & ! C13 element in elasticity matrix
|
||||
constitutive_nonlocal_C33, & ! C33 element in elasticity matrix
|
||||
constitutive_nonlocal_C44, & ! C44 element in elasticity matrix
|
||||
constitutive_nonlocal_Gmod, & ! shear modulus
|
||||
constitutive_nonlocal_nu, & ! poisson's ratio
|
||||
constitutive_nonlocal_atomicVolume, & ! atomic volume
|
||||
constitutive_nonlocal_Dsd0, & ! prefactor for self-diffusion coefficient
|
||||
constitutive_nonlocal_Qsd, & ! activation enthalpy for diffusion
|
||||
constitutive_nonlocal_aTolRho, & ! absolute tolerance for dislocation density in state integration
|
||||
constitutive_nonlocal_R, & ! cutoff radius for dislocation stress
|
||||
constitutive_nonlocal_doublekinkwidth, & ! width of a doubkle kink in multiples of the burgers vector length b
|
||||
constitutive_nonlocal_solidSolutionEnergy, & ! activation energy for solid solution in J
|
||||
constitutive_nonlocal_solidSolutionSize, & ! solid solution obstacle size in multiples of the burgers vector length
|
||||
constitutive_nonlocal_solidSolutionConcentration, & ! concentration of solid solution in atomic parts
|
||||
constitutive_nonlocal_p, & ! parameter for kinetic law (Kocks,Argon,Ashby)
|
||||
constitutive_nonlocal_q, & ! parameter for kinetic law (Kocks,Argon,Ashby)
|
||||
constitutive_nonlocal_viscosity, & ! viscosity for dislocation glide in Pa s
|
||||
constitutive_nonlocal_fattack, & ! attack frequency in Hz
|
||||
constitutive_nonlocal_rhoSglScatter, & ! standard deviation of scatter in initial dislocation density
|
||||
constitutive_nonlocal_surfaceTransmissivity ! transmissivity at free surface
|
||||
real(pReal), dimension(:,:,:), allocatable :: constitutive_nonlocal_Cslip_66 ! elasticity matrix in Mandel notation for each instance
|
||||
real(pReal), dimension(:,:,:,:,:), allocatable :: constitutive_nonlocal_Cslip_3333 ! elasticity matrix for each instance
|
||||
real(pReal), dimension(:,:), allocatable :: constitutive_nonlocal_rhoSglEdgePos0, & ! initial edge_pos dislocation density per slip system for each family and instance
|
||||
constitutive_nonlocal_rhoSglEdgeNeg0, & ! initial edge_neg dislocation density per slip system for each family and instance
|
||||
constitutive_nonlocal_rhoSglScrewPos0, & ! initial screw_pos dislocation density per slip system for each family and instance
|
||||
constitutive_nonlocal_rhoSglScrewNeg0, & ! initial screw_neg dislocation density per slip system for each family and instance
|
||||
constitutive_nonlocal_rhoDipEdge0, & ! initial edge dipole dislocation density per slip system for each family and instance
|
||||
constitutive_nonlocal_rhoDipScrew0, & ! initial screw dipole dislocation density per slip system for each family and instance
|
||||
constitutive_nonlocal_lambda0PerSlipFamily, & ! mean free path prefactor for each family and instance
|
||||
constitutive_nonlocal_lambda0, & ! mean free path prefactor for each slip system and instance
|
||||
constitutive_nonlocal_burgersPerSlipFamily, & ! absolute length of burgers vector [m] for each family and instance
|
||||
constitutive_nonlocal_burgers, & ! absolute length of burgers vector [m] for each slip system and instance
|
||||
constitutive_nonlocal_interactionSlipSlip ! coefficients for slip-slip interaction for each interaction type and instance
|
||||
real(pReal), dimension(:,:,:), allocatable :: constitutive_nonlocal_minimumDipoleHeightPerSlipFamily, & ! minimum stable edge/screw dipole height for each family and instance
|
||||
constitutive_nonlocal_minimumDipoleHeight, & ! minimum stable edge/screw dipole height for each slip system and instance
|
||||
constitutive_nonlocal_peierlsStressPerSlipFamily, & ! Peierls stress (edge and screw)
|
||||
constitutive_nonlocal_peierlsStress ! Peierls stress (edge and screw)
|
||||
real(pReal), dimension(:,:,:,:,:), allocatable :: constitutive_nonlocal_rhoDotFlux ! dislocation convection term
|
||||
real(pReal), dimension(:,:,:,:,:,:), allocatable :: constitutive_nonlocal_compatibility ! slip system compatibility between me and my neighbors
|
||||
real(pReal), dimension(:,:,:), allocatable :: constitutive_nonlocal_forestProjectionEdge, & ! matrix of forest projections of edge dislocations for each instance
|
||||
constitutive_nonlocal_forestProjectionScrew, & ! matrix of forest projections of screw dislocations for each instance
|
||||
constitutive_nonlocal_interactionMatrixSlipSlip ! interaction matrix of the different slip systems for each instance
|
||||
real(pReal), dimension(:,:,:,:), allocatable :: constitutive_nonlocal_lattice2slip, & ! orthogonal transformation matrix from lattice coordinate system to slip coordinate system (passive rotation !!!)
|
||||
constitutive_nonlocal_accumulatedShear ! accumulated shear per slip system up to the start of the FE increment
|
||||
logical, dimension(:), allocatable :: constitutive_nonlocal_shortRangeStressCorrection ! flag indicating the use of the short range stress correction by a excess density gradient term
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
constitutive_nonlocal_sizePostResult ! size of each post result output
|
||||
|
||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
constitutive_nonlocal_output ! name of each post result output
|
||||
|
||||
integer(pInt), dimension(:), allocatable, private :: &
|
||||
constitutive_nonlocal_Noutput ! number of outputs per instance of this plasticity
|
||||
|
||||
character(len=32), dimension(:), allocatable, private :: &
|
||||
constitutive_nonlocal_structureName ! name of the lattice structure
|
||||
|
||||
integer(pInt), dimension(:), allocatable, public :: &
|
||||
constitutive_nonlocal_structure ! number representing the kind of lattice structure
|
||||
|
||||
integer(pInt), dimension(:), allocatable, private :: &
|
||||
constitutive_nonlocal_totalNslip ! total number of active slip systems for each instance
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, private :: &
|
||||
constitutive_nonlocal_Nslip, & ! number of active slip systems for each family and instance
|
||||
constitutive_nonlocal_slipFamily, & ! lookup table relating active slip system to slip family for each instance
|
||||
constitutive_nonlocal_slipSystemLattice ! lookup table relating active slip system index to lattice slip system index for each instance
|
||||
|
||||
real(pReal), dimension(:), allocatable, private :: &
|
||||
constitutive_nonlocal_CoverA, & ! c/a ratio for hex type lattice
|
||||
constitutive_nonlocal_C11, & ! C11 element in elasticity matrix
|
||||
constitutive_nonlocal_C12, & ! C12 element in elasticity matrix
|
||||
constitutive_nonlocal_C13, & ! C13 element in elasticity matrix
|
||||
constitutive_nonlocal_C33, & ! C33 element in elasticity matrix
|
||||
constitutive_nonlocal_C44, & ! C44 element in elasticity matrix
|
||||
constitutive_nonlocal_Gmod, & ! shear modulus
|
||||
constitutive_nonlocal_nu, & ! poisson's ratio
|
||||
constitutive_nonlocal_atomicVolume, & ! atomic volume
|
||||
constitutive_nonlocal_Dsd0, & ! prefactor for self-diffusion coefficient
|
||||
constitutive_nonlocal_Qsd, & ! activation enthalpy for diffusion
|
||||
constitutive_nonlocal_aTolRho, & ! absolute tolerance for dislocation density in state integration
|
||||
constitutive_nonlocal_R, & ! cutoff radius for dislocation stress
|
||||
constitutive_nonlocal_doublekinkwidth, & ! width of a doubkle kink in multiples of the burgers vector length b
|
||||
constitutive_nonlocal_solidSolutionEnergy, & ! activation energy for solid solution in J
|
||||
constitutive_nonlocal_solidSolutionSize, & ! solid solution obstacle size in multiples of the burgers vector length
|
||||
constitutive_nonlocal_solidSolutionConcentration, & ! concentration of solid solution in atomic parts
|
||||
constitutive_nonlocal_p, & ! parameter for kinetic law (Kocks,Argon,Ashby)
|
||||
constitutive_nonlocal_q, & ! parameter for kinetic law (Kocks,Argon,Ashby)
|
||||
constitutive_nonlocal_viscosity, & ! viscosity for dislocation glide in Pa s
|
||||
constitutive_nonlocal_fattack, & ! attack frequency in Hz
|
||||
constitutive_nonlocal_rhoSglScatter, & ! standard deviation of scatter in initial dislocation density
|
||||
constitutive_nonlocal_surfaceTransmissivity ! transmissivity at free surface
|
||||
|
||||
real(pReal), dimension(:,:,:), allocatable, private :: &
|
||||
constitutive_nonlocal_Cslip_66 ! elasticity matrix in Mandel notation for each instance
|
||||
|
||||
real(pReal), dimension(:,:,:,:,:), allocatable, private :: &
|
||||
constitutive_nonlocal_Cslip_3333 ! elasticity matrix for each instance
|
||||
|
||||
real(pReal), dimension(:,:), allocatable, private :: &
|
||||
constitutive_nonlocal_rhoSglEdgePos0, & ! initial edge_pos dislocation density per slip system for each family and instance
|
||||
constitutive_nonlocal_rhoSglEdgeNeg0, & ! initial edge_neg dislocation density per slip system for each family and instance
|
||||
constitutive_nonlocal_rhoSglScrewPos0, & ! initial screw_pos dislocation density per slip system for each family and instance
|
||||
constitutive_nonlocal_rhoSglScrewNeg0, & ! initial screw_neg dislocation density per slip system for each family and instance
|
||||
constitutive_nonlocal_rhoDipEdge0, & ! initial edge dipole dislocation density per slip system for each family and instance
|
||||
constitutive_nonlocal_rhoDipScrew0, & ! initial screw dipole dislocation density per slip system for each family and instance
|
||||
constitutive_nonlocal_lambda0PerSlipFamily, & ! mean free path prefactor for each family and instance
|
||||
constitutive_nonlocal_lambda0, & ! mean free path prefactor for each slip system and instance
|
||||
constitutive_nonlocal_burgersPerSlipFamily, & ! absolute length of burgers vector [m] for each family and instance
|
||||
constitutive_nonlocal_burgers, & ! absolute length of burgers vector [m] for each slip system and instance
|
||||
constitutive_nonlocal_interactionSlipSlip ! coefficients for slip-slip interaction for each interaction type and instance
|
||||
|
||||
real(pReal), dimension(:,:,:), allocatable, private :: &
|
||||
constitutive_nonlocal_minimumDipoleHeightPerSlipFamily, & ! minimum stable edge/screw dipole height for each family and instance
|
||||
constitutive_nonlocal_minimumDipoleHeight, & ! minimum stable edge/screw dipole height for each slip system and instance
|
||||
constitutive_nonlocal_peierlsStressPerSlipFamily, & ! Peierls stress (edge and screw)
|
||||
constitutive_nonlocal_peierlsStress ! Peierls stress (edge and screw)
|
||||
|
||||
real(pReal), dimension(:,:,:,:,:), allocatable, private :: &
|
||||
constitutive_nonlocal_rhoDotFlux ! dislocation convection term
|
||||
|
||||
real(pReal), dimension(:,:,:,:,:,:), allocatable, private :: &
|
||||
constitutive_nonlocal_compatibility ! slip system compatibility between me and my neighbors
|
||||
|
||||
real(pReal), dimension(:,:,:), allocatable, private :: &
|
||||
constitutive_nonlocal_forestProjectionEdge, & ! matrix of forest projections of edge dislocations for each instance
|
||||
constitutive_nonlocal_forestProjectionScrew, & ! matrix of forest projections of screw dislocations for each instance
|
||||
constitutive_nonlocal_interactionMatrixSlipSlip ! interaction matrix of the different slip systems for each instance
|
||||
|
||||
real(pReal), dimension(:,:,:,:), allocatable, private :: &
|
||||
constitutive_nonlocal_lattice2slip, & ! orthogonal transformation matrix from lattice coordinate system to slip coordinate system (passive rotation !!!)
|
||||
constitutive_nonlocal_accumulatedShear ! accumulated shear per slip system up to the start of the FE increment
|
||||
|
||||
logical, dimension(:), allocatable, private :: &
|
||||
constitutive_nonlocal_shortRangeStressCorrection ! flag indicating the use of the short range stress correction by a excess density gradient term
|
||||
|
||||
public :: &
|
||||
constitutive_nonlocal_init, &
|
||||
constitutive_nonlocal_stateInit, &
|
||||
constitutive_nonlocal_aTolState, &
|
||||
constitutive_nonlocal_homogenizedC, &
|
||||
constitutive_nonlocal_microstructure, &
|
||||
constitutive_nonlocal_LpAndItsTangent, &
|
||||
constitutive_nonlocal_dotState, &
|
||||
constitutive_nonlocal_deltaState, &
|
||||
constitutive_nonlocal_dotTemperature, &
|
||||
constitutive_nonlocal_updateCompatibility, &
|
||||
constitutive_nonlocal_postResults
|
||||
|
||||
private :: &
|
||||
constitutive_nonlocal_kinetics
|
||||
|
||||
|
||||
CONTAINS
|
||||
!****************************************
|
||||
!* - constitutive_nonlocal_init
|
||||
!* - constitutive_nonlocal_stateInit
|
||||
!* - constitutive_nonlocal_aTolState
|
||||
!* - constitutive_nonlocal_homogenizedC
|
||||
!* - constitutive_nonlocal_microstructure
|
||||
!* - constitutive_nonlocal_kinetics
|
||||
!* - constitutive_nonlocal_LpAndItsTangent
|
||||
!* - constitutive_nonlocal_dotState
|
||||
!* - constitutive_nonlocal_dotTemperature
|
||||
!* - constitutive_nonlocal_updateCompatibility
|
||||
!* - constitutive_nonlocal_postResults
|
||||
!****************************************
|
||||
|
||||
|
||||
!**************************************
|
||||
!* Module initialization *
|
||||
|
@ -1472,6 +1521,46 @@ endsubroutine
|
|||
|
||||
|
||||
|
||||
!*********************************************************************
|
||||
!* incremental change of microstructure *
|
||||
!*********************************************************************
|
||||
function constitutive_nonlocal_deltaState(Tstar_v, Fe, Fp, Temperature, state, g,ip,el)
|
||||
|
||||
use prec, only: pReal, &
|
||||
pInt, &
|
||||
p_vec
|
||||
use mesh, only: mesh_NcpElems, &
|
||||
mesh_maxNips
|
||||
use material, only: homogenization_maxNgrains, &
|
||||
material_phase, &
|
||||
phase_plasticityInstance
|
||||
|
||||
implicit none
|
||||
|
||||
!*** input variables
|
||||
integer(pInt), intent(in) :: g, & ! current grain number
|
||||
ip, & ! current integration point
|
||||
el ! current element number
|
||||
real(pReal), intent(in) :: Temperature ! temperature
|
||||
real(pReal), dimension(6), intent(in) :: Tstar_v ! current 2nd Piola-Kirchhoff stress in Mandel notation
|
||||
real(pReal), dimension(3,3,homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
||||
Fe, & ! elastic deformation gradient
|
||||
Fp ! plastic deformation gradient
|
||||
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
||||
state ! current microstructural state
|
||||
|
||||
!*** output variables
|
||||
real(pReal), dimension(constitutive_nonlocal_sizeDotState(phase_plasticityInstance(material_phase(g,ip,el)))) :: &
|
||||
constitutive_nonlocal_deltaState ! change of state variables / microstructure
|
||||
|
||||
!*** local variables
|
||||
|
||||
constitutive_nonlocal_deltaState = 0.0_pReal
|
||||
|
||||
endfunction
|
||||
|
||||
|
||||
|
||||
!*********************************************************************
|
||||
!* rate of change of microstructure *
|
||||
!*********************************************************************
|
||||
|
|
|
@ -151,6 +151,7 @@ module constitutive_phenopowerlaw
|
|||
constitutive_phenopowerlaw_homogenizedC, &
|
||||
constitutive_phenopowerlaw_aTolState, &
|
||||
constitutive_phenopowerlaw_dotState, &
|
||||
constitutive_phenopowerlaw_deltaState, &
|
||||
constitutive_phenopowerlaw_dotTemperature, &
|
||||
constitutive_phenopowerlaw_microstructure, &
|
||||
constitutive_phenopowerlaw_LpAndItsTangent, &
|
||||
|
@ -890,6 +891,43 @@ function constitutive_phenopowerlaw_dotState(Tstar_v,Temperature,state,ipc,ip,el
|
|||
end function constitutive_phenopowerlaw_dotState
|
||||
|
||||
|
||||
!*********************************************************************
|
||||
!* (instantaneous) incremental change of microstructure *
|
||||
!*********************************************************************
|
||||
function constitutive_phenopowerlaw_deltaState(Tstar_v, Temperature, state, g,ip,el)
|
||||
|
||||
use prec, only: pReal, &
|
||||
pInt, &
|
||||
p_vec
|
||||
use mesh, only: mesh_NcpElems, &
|
||||
mesh_maxNips
|
||||
use material, only: homogenization_maxNgrains, &
|
||||
material_phase, &
|
||||
phase_plasticityInstance
|
||||
|
||||
implicit none
|
||||
|
||||
!*** input variables
|
||||
integer(pInt), intent(in) :: g, & ! current grain number
|
||||
ip, & ! current integration point
|
||||
el ! current element number
|
||||
real(pReal), intent(in) :: Temperature ! temperature
|
||||
real(pReal), dimension(6), intent(in) :: Tstar_v ! current 2nd Piola-Kirchhoff stress in Mandel notation
|
||||
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
||||
state ! current microstructural state
|
||||
|
||||
!*** output variables
|
||||
real(pReal), dimension(constitutive_phenopowerlaw_sizeDotState(phase_plasticityInstance(material_phase(g,ip,el)))) :: &
|
||||
constitutive_phenopowerlaw_deltaState ! change of state variables / microstructure
|
||||
|
||||
!*** local variables
|
||||
|
||||
|
||||
constitutive_phenopowerlaw_deltaState = 0.0_pReal
|
||||
|
||||
endfunction
|
||||
|
||||
|
||||
!****************************************************************
|
||||
!* calculates the rate of change of temperature *
|
||||
!****************************************************************
|
||||
|
|
|
@ -225,9 +225,10 @@ CONTAINS
|
|||
!* - constitutive_titanmod_homogenizedC
|
||||
!* - constitutive_titanmod_microstructure
|
||||
!* - constitutive_titanmod_LpAndItsTangent
|
||||
!* - consistutive_titanmod_dotState
|
||||
!* - constitutive_titanmod_dotState
|
||||
!* - constitutive_titanmod_deltaState
|
||||
!* - constitutive_titanmod_dotTemperature
|
||||
!* - consistutive_titanmod_postResults
|
||||
!* - constitutive_titanmod_postResults
|
||||
!****************************************
|
||||
|
||||
|
||||
|
@ -1724,6 +1725,45 @@ enddo
|
|||
end function
|
||||
|
||||
|
||||
|
||||
!*********************************************************************
|
||||
!* (instantaneous) incremental change of microstructure *
|
||||
!*********************************************************************
|
||||
function constitutive_titanmod_deltaState(Tstar_v, Temperature, state, g,ip,el)
|
||||
|
||||
use prec, only: pReal, &
|
||||
pInt, &
|
||||
p_vec
|
||||
use mesh, only: mesh_NcpElems, &
|
||||
mesh_maxNips
|
||||
use material, only: homogenization_maxNgrains, &
|
||||
material_phase, &
|
||||
phase_plasticityInstance
|
||||
|
||||
implicit none
|
||||
|
||||
!*** input variables
|
||||
integer(pInt), intent(in) :: g, & ! current grain number
|
||||
ip, & ! current integration point
|
||||
el ! current element number
|
||||
real(pReal), intent(in) :: Temperature ! temperature
|
||||
real(pReal), dimension(6), intent(in) :: Tstar_v ! current 2nd Piola-Kirchhoff stress in Mandel notation
|
||||
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
||||
state ! current microstructural state
|
||||
|
||||
!*** output variables
|
||||
real(pReal), dimension(constitutive_titanmod_sizeDotState(phase_plasticityInstance(material_phase(g,ip,el)))) :: &
|
||||
constitutive_titanmod_deltaState ! change of state variables / microstructure
|
||||
|
||||
!*** local variables
|
||||
|
||||
|
||||
constitutive_titanmod_deltaState = 0.0_pReal
|
||||
|
||||
endfunction
|
||||
|
||||
|
||||
|
||||
pure function constitutive_titanmod_dotTemperature(Tstar_v,Temperature,state,g,ip,el)
|
||||
!*********************************************************************
|
||||
!* rate of change of microstructure *
|
||||
|
|
|
@ -61,6 +61,7 @@ module debug
|
|||
|
||||
integer(pInt), public :: &
|
||||
debug_cumLpCalls = 0_pInt, &
|
||||
debug_cumDeltaStateCalls = 0_pInt, &
|
||||
debug_cumDotStateCalls = 0_pInt, &
|
||||
debug_cumDotTemperatureCalls = 0_pInt, &
|
||||
debug_e = 1_pInt, &
|
||||
|
@ -69,6 +70,7 @@ module debug
|
|||
|
||||
integer(pLongInt), public :: &
|
||||
debug_cumLpTicks = 0_pLongInt, &
|
||||
debug_cumDeltaStateTicks = 0_pLongInt, &
|
||||
debug_cumDotStateTicks = 0_pLongInt, &
|
||||
debug_cumDotTemperatureTicks = 0_pLongInt
|
||||
|
||||
|
@ -296,9 +298,11 @@ subroutine debug_reset
|
|||
debug_MaterialpointStateLoopDistribution = 0_pInt
|
||||
debug_MaterialpointLoopDistribution = 0_pInt
|
||||
debug_cumLpTicks = 0_pLongInt
|
||||
debug_cumDeltaStateTicks = 0_pLongInt
|
||||
debug_cumDotStateTicks = 0_pLongInt
|
||||
debug_cumDotTemperatureTicks = 0_pLongInt
|
||||
debug_cumLpCalls = 0_pInt
|
||||
debug_cumDeltaStateCalls = 0_pInt
|
||||
debug_cumDotStateCalls = 0_pInt
|
||||
debug_cumDotTemperatureCalls = 0_pInt
|
||||
debug_stressMaxLocation = 0_pInt
|
||||
|
@ -351,6 +355,15 @@ subroutine debug_info
|
|||
/real(debug_cumDotStateCalls,pReal)
|
||||
endif
|
||||
write(6,*)
|
||||
write(6,'(a33,1x,i12)') 'total calls to collectDeltaState:',debug_cumDeltaStateCalls
|
||||
if (debug_cumDeltaStateCalls > 0_pInt) then
|
||||
write(6,'(a33,1x,f12.3)') 'total CPU time/s :',real(debug_cumDeltaStateTicks,pReal)&
|
||||
/real(tickrate,pReal)
|
||||
write(6,'(a33,1x,f12.6)') 'avg CPU time/microsecs per call :',&
|
||||
real(debug_cumDeltaStateTicks,pReal)*1.0e6_pReal/real(tickrate,pReal)&
|
||||
/real(debug_cumDeltaStateCalls,pReal)
|
||||
endif
|
||||
write(6,*)
|
||||
write(6,'(a33,1x,i12)') 'total calls to dotTemperature :',debug_cumDotTemperatureCalls
|
||||
if (debug_cumdotTemperatureCalls > 0_pInt) then
|
||||
write(6,'(a33,1x,f12.3)') 'total CPU time/s :',real(debug_cumDotTemperatureTicks,pReal)&
|
||||
|
|
Loading…
Reference in New Issue