2015-04-21 20:46:13 +05:30
!--------------------------------------------------------------------------------------------------
2014-11-06 00:41:09 +05:30
! $Id$
!--------------------------------------------------------------------------------------------------
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @author David Cereceda, Lawrence Livermore National Laboratory
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @brief material subroutine incoprorating dislocation and twinning physics
!> @details to be done
!--------------------------------------------------------------------------------------------------
2015-01-21 20:44:00 +05:30
module plastic_disloUCLA
2014-11-06 00:41:09 +05:30
use prec , only : &
pReal , &
pInt
implicit none
private
integer ( pInt ) , dimension ( : ) , allocatable , public , protected :: &
2016-01-16 12:36:34 +05:30
plastic_disloUCLA_sizePostResults !< cumulative size of post results
2014-11-06 00:41:09 +05:30
integer ( pInt ) , dimension ( : , : ) , allocatable , target , public :: &
2016-01-16 12:36:34 +05:30
plastic_disloUCLA_sizePostResult !< size of each post result output
2014-11-06 00:41:09 +05:30
character ( len = 64 ) , dimension ( : , : ) , allocatable , target , public :: &
2016-01-16 12:36:34 +05:30
plastic_disloUCLA_output !< name of each post result output
2014-11-06 00:41:09 +05:30
real ( pReal ) , parameter , private :: &
2016-01-16 12:36:34 +05:30
kB = 1.38e-23_pReal !< Boltzmann constant in J/Kelvin
2014-11-06 00:41:09 +05:30
integer ( pInt ) , dimension ( : ) , allocatable , target , public :: &
2016-01-16 12:36:34 +05:30
plastic_disloUCLA_Noutput !< number of outputs per instance of this plasticity
2014-11-06 00:41:09 +05:30
2016-01-16 12:36:34 +05:30
integer ( pInt ) , dimension ( : ) , allocatable , private :: &
plastic_disloUCLA_totalNslip , & !< total number of active slip systems for each instance
plastic_disloUCLA_totalNtwin !< total number of active twin systems for each instance
2014-11-06 00:41:09 +05:30
integer ( pInt ) , dimension ( : , : ) , allocatable , private :: &
2016-01-16 12:36:34 +05:30
plastic_disloUCLA_Nslip , & !< number of active slip systems for each family and instance
plastic_disloUCLA_Ntwin !< number of active twin systems for each family and instance
2014-11-06 00:41:09 +05:30
real ( pReal ) , dimension ( : ) , allocatable , private :: &
2016-01-16 12:36:34 +05:30
plastic_disloUCLA_CAtomicVolume , & !< atomic volume in Bugers vector unit
plastic_disloUCLA_D0 , & !< prefactor for self-diffusion coefficient
plastic_disloUCLA_Qsd , & !< activation energy for dislocation climb
plastic_disloUCLA_GrainSize , & !< grain size
plastic_disloUCLA_MaxTwinFraction , & !< maximum allowed total twin volume fraction
plastic_disloUCLA_CEdgeDipMinDistance , & !<
plastic_disloUCLA_Cmfptwin , & !<
plastic_disloUCLA_Cthresholdtwin , & !<
plastic_disloUCLA_SolidSolutionStrength , & !< Strength due to elements in solid solution
plastic_disloUCLA_L0 , & !< Length of twin nuclei in Burgers vectors
plastic_disloUCLA_xc , & !< critical distance for formation of twin nucleus
plastic_disloUCLA_VcrossSlip , & !< cross slip volume
plastic_disloUCLA_SFE_0K , & !< stacking fault energy at zero K
plastic_disloUCLA_dSFE_dT , & !< temperature dependance of stacking fault energy
plastic_disloUCLA_dipoleFormationFactor , & !< scaling factor for dipole formation: 0: off, 1: on. other values not useful
plastic_disloUCLA_aTolRho , & !< absolute tolerance for integration of dislocation density
plastic_disloUCLA_aTolTwinFrac !< absolute tolerance for integration of twin volume fraction
2014-11-06 00:41:09 +05:30
real ( pReal ) , dimension ( : , : , : , : ) , allocatable , private :: &
2016-01-16 12:36:34 +05:30
plastic_disloUCLA_Ctwin66 !< twin elasticity matrix in Mandel notation for each instance
2014-11-06 00:41:09 +05:30
real ( pReal ) , dimension ( : , : , : , : , : , : ) , allocatable , private :: &
2016-01-16 12:36:34 +05:30
plastic_disloUCLA_Ctwin3333 !< twin elasticity matrix for each instance
2014-11-06 00:41:09 +05:30
real ( pReal ) , dimension ( : , : ) , allocatable , private :: &
2016-01-16 12:36:34 +05:30
plastic_disloUCLA_rhoEdge0 , & !< initial edge dislocation density per slip system for each family and instance
plastic_disloUCLA_rhoEdgeDip0 , & !< initial edge dipole density per slip system for each family and instance
plastic_disloUCLA_burgersPerSlipFamily , & !< absolute length of burgers vector [m] for each slip family and instance
plastic_disloUCLA_burgersPerSlipSystem , & !< absolute length of burgers vector [m] for each slip system and instance
plastic_disloUCLA_burgersPerTwinFamily , & !< absolute length of burgers vector [m] for each twin family and instance
plastic_disloUCLA_burgersPerTwinSystem , & !< absolute length of burgers vector [m] for each twin system and instance
plastic_disloUCLA_QedgePerSlipFamily , & !< activation energy for glide [J] for each slip family and instance
plastic_disloUCLA_QedgePerSlipSystem , & !< activation energy for glide [J] for each slip system and instance
plastic_disloUCLA_v0PerSlipFamily , & !< dislocation velocity prefactor [m/s] for each family and instance
plastic_disloUCLA_v0PerSlipSystem , & !< dislocation velocity prefactor [m/s] for each slip system and instance
plastic_disloUCLA_tau_peierlsPerSlipFamily , & !< Peierls stress [Pa] for each family and instance
plastic_disloUCLA_Ndot0PerTwinFamily , & !< twin nucleation rate [1/m³s] for each twin family and instance
plastic_disloUCLA_Ndot0PerTwinSystem , & !< twin nucleation rate [1/m³s] for each twin system and instance
plastic_disloUCLA_tau_r , & !< stress to bring partial close together for each twin system and instance
plastic_disloUCLA_twinsizePerTwinFamily , & !< twin thickness [m] for each twin family and instance
plastic_disloUCLA_twinsizePerTwinSystem , & !< twin thickness [m] for each twin system and instance
plastic_disloUCLA_CLambdaSlipPerSlipFamily , & !< Adj. parameter for distance between 2 forest dislocations for each slip family and instance
plastic_disloUCLA_CLambdaSlipPerSlipSystem , & !< Adj. parameter for distance between 2 forest dislocations for each slip system and instance
plastic_disloUCLA_interaction_SlipSlip , & !< coefficients for slip-slip interaction for each interaction type and instance
plastic_disloUCLA_interaction_SlipTwin , & !< coefficients for slip-twin interaction for each interaction type and instance
plastic_disloUCLA_interaction_TwinSlip , & !< coefficients for twin-slip interaction for each interaction type and instance
plastic_disloUCLA_interaction_TwinTwin , & !< coefficients for twin-twin interaction for each interaction type and instance
plastic_disloUCLA_pPerSlipFamily , & !< p-exponent in glide velocity
plastic_disloUCLA_qPerSlipFamily , & !< q-exponent in glide velocity
2015-01-15 16:26:15 +05:30
!* mobility law parameters
2016-01-16 12:36:34 +05:30
plastic_disloUCLA_kinkheight , & !< height of the kink pair
plastic_disloUCLA_omega , & !< attempt frequency for kink pair nucleation
plastic_disloUCLA_kinkwidth , & !< width of the kink pair
plastic_disloUCLA_dislolength , & !< dislocation length (lamda)
plastic_disloUCLA_friction , & !< friction coeff. B (kMC)
2015-01-15 16:26:15 +05:30
!*
2016-01-16 12:36:34 +05:30
plastic_disloUCLA_rPerTwinFamily , & !< r-exponent in twin nucleation rate
plastic_disloUCLA_nonSchmidCoeff !< non-Schmid coefficients (bcc)
2014-11-06 00:41:09 +05:30
real ( pReal ) , dimension ( : , : , : ) , allocatable , private :: &
2016-01-16 12:36:34 +05:30
plastic_disloUCLA_interactionMatrix_SlipSlip , & !< interaction matrix of the different slip systems for each instance
plastic_disloUCLA_interactionMatrix_SlipTwin , & !< interaction matrix of slip systems with twin systems for each instance
plastic_disloUCLA_interactionMatrix_TwinSlip , & !< interaction matrix of twin systems with slip systems for each instance
plastic_disloUCLA_interactionMatrix_TwinTwin , & !< interaction matrix of the different twin systems for each instance
plastic_disloUCLA_forestProjectionEdge !< matrix of forest projections of edge dislocations for each instance
2014-11-06 00:41:09 +05:30
enum , bind ( c )
enumerator :: undefined_ID , &
edge_density_ID , &
dipole_density_ID , &
shear_rate_slip_ID , &
accumulated_shear_slip_ID , &
mfp_slip_ID , &
resolved_stress_slip_ID , &
threshold_stress_slip_ID , &
edge_dipole_distance_ID , &
stress_exponent_ID , &
twin_fraction_ID , &
shear_rate_twin_ID , &
accumulated_shear_twin_ID , &
mfp_twin_ID , &
resolved_stress_twin_ID , &
threshold_stress_twin_ID
end enum
integer ( kind ( undefined_ID ) ) , dimension ( : , : ) , allocatable , private :: &
2016-01-16 12:36:34 +05:30
plastic_disloUCLA_outputID !< ID of each post result output
2016-01-15 20:56:24 +05:30
type , private :: tDisloUCLAState
real ( pReal ) , pointer , dimension ( : , : ) :: &
rhoEdge , &
rhoEdgeDip , &
accshear_slip , &
twinFraction , &
accshear_twin , &
invLambdaSlip , &
invLambdaSlipTwin , &
invLambdaTwin , &
mfp_slip , &
mfp_twin , &
threshold_stress_slip , &
threshold_stress_twin , &
twinVolume
end type
type ( tDisloUCLAState ) , allocatable , dimension ( : ) , private :: &
state , &
state0 , &
dotState
2014-11-06 00:41:09 +05:30
public :: &
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_init , &
plastic_disloUCLA_homogenizedC , &
plastic_disloUCLA_microstructure , &
plastic_disloUCLA_LpAndItsTangent , &
plastic_disloUCLA_dotState , &
plastic_disloUCLA_postResults
2014-11-06 00:41:09 +05:30
private :: &
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_stateInit , &
plastic_disloUCLA_aTolState
2014-11-06 00:41:09 +05:30
contains
!--------------------------------------------------------------------------------------------------
!> @brief module initialization
!> @details reads in material parameters, allocates arrays, and does sanity checks
!--------------------------------------------------------------------------------------------------
2015-01-21 20:44:00 +05:30
subroutine plastic_disloUCLA_init ( fileUnit )
2014-11-06 00:41:09 +05:30
use , intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
use debug , only : &
debug_level , &
debug_constitutive , &
debug_levelBasic
use math , only : &
math_Mandel3333to66 , &
math_Voigt66to3333 , &
math_mul3x3
use IO , only : &
IO_read , &
IO_lc , &
IO_getTag , &
IO_isBlank , &
IO_stringPos , &
IO_stringValue , &
IO_floatValue , &
IO_intValue , &
IO_warning , &
IO_error , &
IO_timeStamp , &
IO_EOF
use material , only : &
phase_plasticity , &
phase_plasticityInstance , &
phase_Noutput , &
2015-01-15 16:26:15 +05:30
PLASTICITY_DISLOUCLA_label , &
PLASTICITY_DISLOUCLA_ID , &
2014-11-06 00:41:09 +05:30
material_phase , &
plasticState , &
MATERIAL_partPhase
use lattice
use numerics , only : &
2015-08-28 16:25:38 +05:30
analyticJaco , &
2014-11-06 00:41:09 +05:30
worldrank , &
numerics_integrator
implicit none
integer ( pInt ) , intent ( in ) :: fileUnit
2015-08-28 13:08:48 +05:30
integer ( pInt ) , allocatable , dimension ( : ) :: chunkPos
2014-11-06 00:41:09 +05:30
integer ( pInt ) :: maxNinstance , mySize = 0_pInt , phase , maxTotalNslip , maxTotalNtwin , &
f , instance , j , k , l , m , n , o , p , q , r , s , ns , nt , &
2015-04-21 20:46:13 +05:30
Nchunks_SlipSlip = 0_pInt , Nchunks_SlipTwin = 0_pInt , &
Nchunks_TwinSlip = 0_pInt , Nchunks_TwinTwin = 0_pInt , &
Nchunks_SlipFamilies = 0_pInt , Nchunks_TwinFamilies = 0_pInt , Nchunks_nonSchmid = 0_pInt , &
2016-01-15 20:56:24 +05:30
offset_slip , index_myFamily , index_otherFamily , &
startIndex , endIndex
2015-06-01 21:32:27 +05:30
integer ( pInt ) :: sizeState , sizeDotState , sizeDeltaState
2014-11-06 00:41:09 +05:30
integer ( pInt ) :: NofMyPhase
character ( len = 65536 ) :: &
tag = '' , &
line = ''
real ( pReal ) , dimension ( : ) , allocatable :: tempPerSlip , tempPerTwin
mainProcess : if ( worldrank == 0 ) then
2015-01-15 16:26:15 +05:30
write ( 6 , '(/,a)' ) ' <<<+- constitutive_' / / PLASTICITY_DISLOUCLA_label / / ' init -+>>>'
2014-11-06 00:41:09 +05:30
write ( 6 , '(a)' ) ' $Id$'
write ( 6 , '(a15,a)' ) ' Current time: ' , IO_timeStamp ( )
#include "compilation_info.f90"
endif mainProcess
2015-01-15 16:26:15 +05:30
maxNinstance = int ( count ( phase_plasticity == PLASTICITY_DISLOUCLA_ID ) , pInt )
2014-11-06 00:41:09 +05:30
if ( maxNinstance == 0_pInt ) return
if ( iand ( debug_level ( debug_constitutive ) , debug_levelBasic ) / = 0_pInt ) &
write ( 6 , '(a16,1x,i5,/)' ) '# instances:' , maxNinstance
2015-01-21 20:44:00 +05:30
allocate ( plastic_disloUCLA_sizePostResults ( maxNinstance ) , source = 0_pInt )
allocate ( plastic_disloUCLA_sizePostResult ( maxval ( phase_Noutput ) , maxNinstance ) , source = 0_pInt )
allocate ( plastic_disloUCLA_output ( maxval ( phase_Noutput ) , maxNinstance ) )
plastic_disloUCLA_output = ''
allocate ( plastic_disloUCLA_outputID ( maxval ( phase_Noutput ) , maxNinstance ) , source = undefined_ID )
allocate ( plastic_disloUCLA_Noutput ( maxNinstance ) , source = 0_pInt )
allocate ( plastic_disloUCLA_Nslip ( lattice_maxNslipFamily , maxNinstance ) , source = 0_pInt )
allocate ( plastic_disloUCLA_Ntwin ( lattice_maxNtwinFamily , maxNinstance ) , source = 0_pInt )
allocate ( plastic_disloUCLA_totalNslip ( maxNinstance ) , source = 0_pInt )
allocate ( plastic_disloUCLA_totalNtwin ( maxNinstance ) , source = 0_pInt )
allocate ( plastic_disloUCLA_CAtomicVolume ( maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_D0 ( maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_Qsd ( maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_GrainSize ( maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_MaxTwinFraction ( maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_CEdgeDipMinDistance ( maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_Cmfptwin ( maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_Cthresholdtwin ( maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_SolidSolutionStrength ( maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_L0 ( maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_xc ( maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_VcrossSlip ( maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_aTolRho ( maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_aTolTwinFrac ( maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_SFE_0K ( maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_dSFE_dT ( maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_dipoleFormationFactor ( maxNinstance ) , source = 1.0_pReal ) !should be on by default
allocate ( plastic_disloUCLA_rhoEdge0 ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_rhoEdgeDip0 ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_burgersPerSlipFamily ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
2015-01-23 18:38:25 +05:30
allocate ( plastic_disloUCLA_kinkheight ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_omega ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_kinkwidth ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_dislolength ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_friction ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
2015-01-21 20:44:00 +05:30
allocate ( plastic_disloUCLA_burgersPerTwinFamily ( lattice_maxNtwinFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_QedgePerSlipFamily ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_v0PerSlipFamily ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_tau_peierlsPerSlipFamily ( lattice_maxNslipFamily , maxNinstance ) , &
2014-12-11 20:34:16 +05:30
source = 0.0_pReal )
2015-01-21 20:44:00 +05:30
allocate ( plastic_disloUCLA_pPerSlipFamily ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_qPerSlipFamily ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_Ndot0PerTwinFamily ( lattice_maxNtwinFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_twinsizePerTwinFamily ( lattice_maxNtwinFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_CLambdaSlipPerSlipFamily ( lattice_maxNslipFamily , maxNinstance ) , &
2014-12-11 20:34:16 +05:30
source = 0.0_pReal )
2015-01-21 20:44:00 +05:30
allocate ( plastic_disloUCLA_rPerTwinFamily ( lattice_maxNtwinFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_interaction_SlipSlip ( lattice_maxNinteraction , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_interaction_SlipTwin ( lattice_maxNinteraction , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_interaction_TwinSlip ( lattice_maxNinteraction , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_interaction_TwinTwin ( lattice_maxNinteraction , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_nonSchmidCoeff ( lattice_maxNnonSchmid , maxNinstance ) , source = 0.0_pReal )
2014-11-06 00:41:09 +05:30
rewind ( fileUnit )
phase = 0_pInt
do while ( trim ( line ) / = IO_EOF . and . IO_lc ( IO_getTag ( line , '<' , '>' ) ) / = MATERIAL_partPhase ) ! wind forward to <phase>
line = IO_read ( fileUnit )
enddo
parsingFile : do while ( trim ( line ) / = IO_EOF ) ! read through sections of phase part
line = IO_read ( fileUnit )
if ( IO_isBlank ( line ) ) cycle ! skip empty lines
if ( IO_getTag ( line , '<' , '>' ) / = '' ) then ! stop at next part
line = IO_read ( fileUnit , . true . ) ! reset IO_read
exit
endif
if ( IO_getTag ( line , '[' , ']' ) / = '' ) then ! next phase section
phase = phase + 1_pInt ! advance phase section counter
2015-01-15 16:26:15 +05:30
if ( phase_plasticity ( phase ) == PLASTICITY_DISLOUCLA_ID ) then
2014-11-06 00:41:09 +05:30
Nchunks_SlipFamilies = count ( lattice_NslipSystem ( : , phase ) > 0_pInt )
Nchunks_TwinFamilies = count ( lattice_NtwinSystem ( : , phase ) > 0_pInt )
Nchunks_SlipSlip = maxval ( lattice_interactionSlipSlip ( : , : , phase ) )
Nchunks_SlipTwin = maxval ( lattice_interactionSlipTwin ( : , : , phase ) )
Nchunks_TwinSlip = maxval ( lattice_interactionTwinSlip ( : , : , phase ) )
Nchunks_TwinTwin = maxval ( lattice_interactionTwinTwin ( : , : , phase ) )
Nchunks_nonSchmid = lattice_NnonSchmid ( phase )
if ( allocated ( tempPerSlip ) ) deallocate ( tempPerSlip )
if ( allocated ( tempPerTwin ) ) deallocate ( tempPerTwin )
allocate ( tempPerSlip ( Nchunks_SlipFamilies ) )
allocate ( tempPerTwin ( Nchunks_TwinFamilies ) )
endif
cycle ! skip to next line
endif
2015-01-15 16:26:15 +05:30
if ( phase > 0_pInt ) then ; if ( phase_plasticity ( phase ) == PLASTICITY_DISLOUCLA_ID ) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
2014-11-06 00:41:09 +05:30
instance = phase_plasticityInstance ( phase ) ! which instance of my plasticity is present phase
2015-08-28 13:08:48 +05:30
chunkPos = IO_stringPos ( line )
tag = IO_lc ( IO_stringValue ( line , chunkPos , 1_pInt ) ) ! extract key
2014-11-06 00:41:09 +05:30
select case ( tag )
case ( '(output)' )
2015-08-28 13:08:48 +05:30
select case ( IO_lc ( IO_stringValue ( line , chunkPos , 2_pInt ) ) )
2014-11-06 00:41:09 +05:30
case ( 'edge_density' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Noutput ( instance ) = plastic_disloUCLA_Noutput ( instance ) + 1_pInt
plastic_disloUCLA_outputID ( plastic_disloUCLA_Noutput ( instance ) , instance ) = edge_density_ID
plastic_disloUCLA_output ( plastic_disloUCLA_Noutput ( instance ) , instance ) = &
2015-08-28 13:08:48 +05:30
IO_lc ( IO_stringValue ( line , chunkPos , 2_pInt ) )
2014-11-06 00:41:09 +05:30
case ( 'dipole_density' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Noutput ( instance ) = plastic_disloUCLA_Noutput ( instance ) + 1_pInt
plastic_disloUCLA_outputID ( plastic_disloUCLA_Noutput ( instance ) , instance ) = dipole_density_ID
plastic_disloUCLA_output ( plastic_disloUCLA_Noutput ( instance ) , instance ) = &
2015-08-28 13:08:48 +05:30
IO_lc ( IO_stringValue ( line , chunkPos , 2_pInt ) )
2015-03-09 16:59:44 +05:30
case ( 'shear_rate_slip' , 'shearrate_slip' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Noutput ( instance ) = plastic_disloUCLA_Noutput ( instance ) + 1_pInt
plastic_disloUCLA_outputID ( plastic_disloUCLA_Noutput ( instance ) , instance ) = shear_rate_slip_ID
plastic_disloUCLA_output ( plastic_disloUCLA_Noutput ( instance ) , instance ) = &
2015-08-28 13:08:48 +05:30
IO_lc ( IO_stringValue ( line , chunkPos , 2_pInt ) )
2014-11-06 00:41:09 +05:30
case ( 'accumulated_shear_slip' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Noutput ( instance ) = plastic_disloUCLA_Noutput ( instance ) + 1_pInt
plastic_disloUCLA_outputID ( plastic_disloUCLA_Noutput ( instance ) , instance ) = accumulated_shear_slip_ID
plastic_disloUCLA_output ( plastic_disloUCLA_Noutput ( instance ) , instance ) = &
2015-08-28 13:08:48 +05:30
IO_lc ( IO_stringValue ( line , chunkPos , 2_pInt ) )
2014-11-06 00:41:09 +05:30
case ( 'mfp_slip' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Noutput ( instance ) = plastic_disloUCLA_Noutput ( instance ) + 1_pInt
plastic_disloUCLA_outputID ( plastic_disloUCLA_Noutput ( instance ) , instance ) = mfp_slip_ID
plastic_disloUCLA_output ( plastic_disloUCLA_Noutput ( instance ) , instance ) = &
2015-08-28 13:08:48 +05:30
IO_lc ( IO_stringValue ( line , chunkPos , 2_pInt ) )
2014-11-06 00:41:09 +05:30
case ( 'resolved_stress_slip' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Noutput ( instance ) = plastic_disloUCLA_Noutput ( instance ) + 1_pInt
plastic_disloUCLA_outputID ( plastic_disloUCLA_Noutput ( instance ) , instance ) = resolved_stress_slip_ID
plastic_disloUCLA_output ( plastic_disloUCLA_Noutput ( instance ) , instance ) = &
2015-08-28 13:08:48 +05:30
IO_lc ( IO_stringValue ( line , chunkPos , 2_pInt ) )
2015-01-22 15:04:11 +05:30
case ( 'threshold_stress_slip' )
plastic_disloUCLA_Noutput ( instance ) = plastic_disloUCLA_Noutput ( instance ) + 1_pInt
plastic_disloUCLA_outputID ( plastic_disloUCLA_Noutput ( instance ) , instance ) = threshold_stress_slip_ID
plastic_disloUCLA_output ( plastic_disloUCLA_Noutput ( instance ) , instance ) = &
2015-08-28 13:08:48 +05:30
IO_lc ( IO_stringValue ( line , chunkPos , 2_pInt ) )
2014-11-06 00:41:09 +05:30
case ( 'edge_dipole_distance' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Noutput ( instance ) = plastic_disloUCLA_Noutput ( instance ) + 1_pInt
plastic_disloUCLA_outputID ( plastic_disloUCLA_Noutput ( instance ) , instance ) = edge_dipole_distance_ID
plastic_disloUCLA_output ( plastic_disloUCLA_Noutput ( instance ) , instance ) = &
2015-08-28 13:08:48 +05:30
IO_lc ( IO_stringValue ( line , chunkPos , 2_pInt ) )
2014-11-06 00:41:09 +05:30
case ( 'stress_exponent' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Noutput ( instance ) = plastic_disloUCLA_Noutput ( instance ) + 1_pInt
plastic_disloUCLA_outputID ( plastic_disloUCLA_Noutput ( instance ) , instance ) = stress_exponent_ID
plastic_disloUCLA_output ( plastic_disloUCLA_Noutput ( instance ) , instance ) = &
2015-08-28 13:08:48 +05:30
IO_lc ( IO_stringValue ( line , chunkPos , 2_pInt ) )
2014-11-06 00:41:09 +05:30
case ( 'twin_fraction' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Noutput ( instance ) = plastic_disloUCLA_Noutput ( instance ) + 1_pInt
plastic_disloUCLA_outputID ( plastic_disloUCLA_Noutput ( instance ) , instance ) = twin_fraction_ID
plastic_disloUCLA_output ( plastic_disloUCLA_Noutput ( instance ) , instance ) = &
2015-08-28 13:08:48 +05:30
IO_lc ( IO_stringValue ( line , chunkPos , 2_pInt ) )
2015-03-09 16:59:44 +05:30
case ( 'shear_rate_twin' , 'shearrate_twin' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Noutput ( instance ) = plastic_disloUCLA_Noutput ( instance ) + 1_pInt
plastic_disloUCLA_outputID ( plastic_disloUCLA_Noutput ( instance ) , instance ) = shear_rate_twin_ID
plastic_disloUCLA_output ( plastic_disloUCLA_Noutput ( instance ) , instance ) = &
2015-08-28 13:08:48 +05:30
IO_lc ( IO_stringValue ( line , chunkPos , 2_pInt ) )
2014-11-06 00:41:09 +05:30
case ( 'accumulated_shear_twin' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Noutput ( instance ) = plastic_disloUCLA_Noutput ( instance ) + 1_pInt
plastic_disloUCLA_outputID ( plastic_disloUCLA_Noutput ( instance ) , instance ) = accumulated_shear_twin_ID
plastic_disloUCLA_output ( plastic_disloUCLA_Noutput ( instance ) , instance ) = &
2015-08-28 13:08:48 +05:30
IO_lc ( IO_stringValue ( line , chunkPos , 2_pInt ) )
2014-11-06 00:41:09 +05:30
case ( 'mfp_twin' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Noutput ( instance ) = plastic_disloUCLA_Noutput ( instance ) + 1_pInt
plastic_disloUCLA_outputID ( plastic_disloUCLA_Noutput ( instance ) , instance ) = mfp_twin_ID
plastic_disloUCLA_output ( plastic_disloUCLA_Noutput ( instance ) , instance ) = &
2015-08-28 13:08:48 +05:30
IO_lc ( IO_stringValue ( line , chunkPos , 2_pInt ) )
2014-11-06 00:41:09 +05:30
case ( 'resolved_stress_twin' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Noutput ( instance ) = plastic_disloUCLA_Noutput ( instance ) + 1_pInt
plastic_disloUCLA_outputID ( plastic_disloUCLA_Noutput ( instance ) , instance ) = resolved_stress_twin_ID
plastic_disloUCLA_output ( plastic_disloUCLA_Noutput ( instance ) , instance ) = &
2015-08-28 13:08:48 +05:30
IO_lc ( IO_stringValue ( line , chunkPos , 2_pInt ) )
2014-11-06 00:41:09 +05:30
case ( 'threshold_stress_twin' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Noutput ( instance ) = plastic_disloUCLA_Noutput ( instance ) + 1_pInt
plastic_disloUCLA_outputID ( plastic_disloUCLA_Noutput ( instance ) , instance ) = threshold_stress_twin_ID
plastic_disloUCLA_output ( plastic_disloUCLA_Noutput ( instance ) , instance ) = &
2015-08-28 13:08:48 +05:30
IO_lc ( IO_stringValue ( line , chunkPos , 2_pInt ) )
2014-11-06 00:41:09 +05:30
end select
!--------------------------------------------------------------------------------------------------
! parameters depending on number of slip system families
case ( 'nslip' )
2015-08-28 13:08:48 +05:30
if ( chunkPos ( 1 ) < Nchunks_SlipFamilies + 1_pInt ) &
2015-01-15 16:26:15 +05:30
call IO_warning ( 50_pInt , ext_msg = trim ( tag ) / / ' (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-08-28 13:08:48 +05:30
if ( chunkPos ( 1 ) > Nchunks_SlipFamilies + 1_pInt ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 150_pInt , ext_msg = trim ( tag ) / / ' (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-08-28 13:08:48 +05:30
Nchunks_SlipFamilies = chunkPos ( 1 ) - 1_pInt
2014-11-06 00:41:09 +05:30
do j = 1_pInt , Nchunks_SlipFamilies
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_Nslip ( j , instance ) = IO_intValue ( line , chunkPos , 1_pInt + j )
2014-11-06 00:41:09 +05:30
enddo
case ( 'rhoedge0' , 'rhoedgedip0' , 'slipburgers' , 'qedge' , 'v0' , 'clambdaslip' , 'tau_peierls' , 'p_slip' , 'q_slip' , &
2015-01-21 20:44:00 +05:30
'kink_height' , 'omega' , 'kink_width' , 'dislolength' , 'friction_coeff' )
2014-11-06 00:41:09 +05:30
do j = 1_pInt , Nchunks_SlipFamilies
2015-08-28 13:08:48 +05:30
tempPerSlip ( j ) = IO_floatValue ( line , chunkPos , 1_pInt + j )
2014-11-06 00:41:09 +05:30
enddo
select case ( tag )
case ( 'rhoedge0' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_rhoEdge0 ( 1 : Nchunks_SlipFamilies , instance ) = tempPerSlip ( 1 : Nchunks_SlipFamilies )
2014-11-06 00:41:09 +05:30
case ( 'rhoedgedip0' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_rhoEdgeDip0 ( 1 : Nchunks_SlipFamilies , instance ) = tempPerSlip ( 1 : Nchunks_SlipFamilies )
2014-11-06 00:41:09 +05:30
case ( 'slipburgers' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_burgersPerSlipFamily ( 1 : Nchunks_SlipFamilies , instance ) = tempPerSlip ( 1 : Nchunks_SlipFamilies )
2014-11-06 00:41:09 +05:30
case ( 'qedge' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_QedgePerSlipFamily ( 1 : Nchunks_SlipFamilies , instance ) = tempPerSlip ( 1 : Nchunks_SlipFamilies )
2014-11-06 00:41:09 +05:30
case ( 'v0' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_v0PerSlipFamily ( 1 : Nchunks_SlipFamilies , instance ) = tempPerSlip ( 1 : Nchunks_SlipFamilies )
2014-11-06 00:41:09 +05:30
case ( 'clambdaslip' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_CLambdaSlipPerSlipFamily ( 1 : Nchunks_SlipFamilies , instance ) = tempPerSlip ( 1 : Nchunks_SlipFamilies )
2014-11-06 00:41:09 +05:30
case ( 'tau_peierls' )
if ( lattice_structure ( phase ) / = LATTICE_bcc_ID ) &
2015-01-15 16:26:15 +05:30
call IO_warning ( 42_pInt , ext_msg = trim ( tag ) / / ' for non-bcc (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_tau_peierlsPerSlipFamily ( 1 : Nchunks_SlipFamilies , instance ) = tempPerSlip ( 1 : Nchunks_SlipFamilies )
2014-11-06 00:41:09 +05:30
case ( 'p_slip' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_pPerSlipFamily ( 1 : Nchunks_SlipFamilies , instance ) = tempPerSlip ( 1 : Nchunks_SlipFamilies )
2014-11-06 00:41:09 +05:30
case ( 'q_slip' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_qPerSlipFamily ( 1 : Nchunks_SlipFamilies , instance ) = tempPerSlip ( 1 : Nchunks_SlipFamilies )
2015-01-15 16:26:15 +05:30
case ( 'kink_height' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_kinkheight ( 1 : Nchunks_SlipFamilies , instance ) = &
2015-01-16 04:10:17 +05:30
tempPerSlip ( 1 : Nchunks_SlipFamilies )
2015-01-15 16:26:15 +05:30
case ( 'omega' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_omega ( 1 : Nchunks_SlipFamilies , instance ) = &
2015-01-16 04:10:17 +05:30
tempPerSlip ( 1 : Nchunks_SlipFamilies )
2015-01-15 16:26:15 +05:30
case ( 'kink_width' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_kinkwidth ( 1 : Nchunks_SlipFamilies , instance ) = &
2015-01-16 04:10:17 +05:30
tempPerSlip ( 1 : Nchunks_SlipFamilies )
2015-01-15 16:26:15 +05:30
case ( 'dislolength' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_dislolength ( 1 : Nchunks_SlipFamilies , instance ) = &
2015-01-16 04:10:17 +05:30
tempPerSlip ( 1 : Nchunks_SlipFamilies )
case ( 'friction_coeff' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_friction ( 1 : Nchunks_SlipFamilies , instance ) = &
2015-01-16 04:10:17 +05:30
tempPerSlip ( 1 : Nchunks_SlipFamilies )
2014-11-06 00:41:09 +05:30
end select
!--------------------------------------------------------------------------------------------------
! parameters depending on slip number of twin families
case ( 'ntwin' )
2015-08-28 13:08:48 +05:30
if ( chunkPos ( 1 ) < Nchunks_TwinFamilies + 1_pInt ) &
2015-01-15 16:26:15 +05:30
call IO_warning ( 51_pInt , ext_msg = trim ( tag ) / / ' (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-08-28 13:08:48 +05:30
if ( chunkPos ( 1 ) > Nchunks_TwinFamilies + 1_pInt ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 150_pInt , ext_msg = trim ( tag ) / / ' (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-08-28 13:08:48 +05:30
Nchunks_TwinFamilies = chunkPos ( 1 ) - 1_pInt
2014-11-06 00:41:09 +05:30
do j = 1_pInt , Nchunks_TwinFamilies
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_Ntwin ( j , instance ) = IO_intValue ( line , chunkPos , 1_pInt + j )
2014-11-06 00:41:09 +05:30
enddo
case ( 'ndot0' , 'twinsize' , 'twinburgers' , 'r_twin' )
do j = 1_pInt , Nchunks_TwinFamilies
2015-08-28 13:08:48 +05:30
tempPerTwin ( j ) = IO_floatValue ( line , chunkPos , 1_pInt + j )
2014-11-06 00:41:09 +05:30
enddo
select case ( tag )
case ( 'ndot0' )
if ( lattice_structure ( phase ) == LATTICE_fcc_ID ) &
2015-01-15 16:26:15 +05:30
call IO_warning ( 42_pInt , ext_msg = trim ( tag ) / / ' for fcc (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Ndot0PerTwinFamily ( 1 : Nchunks_TwinFamilies , instance ) = tempPerTwin ( 1 : Nchunks_TwinFamilies )
2014-11-06 00:41:09 +05:30
case ( 'twinsize' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_twinsizePerTwinFamily ( 1 : Nchunks_TwinFamilies , instance ) = tempPerTwin ( 1 : Nchunks_TwinFamilies )
2014-11-06 00:41:09 +05:30
case ( 'twinburgers' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_burgersPerTwinFamily ( 1 : Nchunks_TwinFamilies , instance ) = tempPerTwin ( 1 : Nchunks_TwinFamilies )
2014-11-06 00:41:09 +05:30
case ( 'r_twin' )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_rPerTwinFamily ( 1 : Nchunks_TwinFamilies , instance ) = tempPerTwin ( 1 : Nchunks_TwinFamilies )
2014-11-06 00:41:09 +05:30
end select
!--------------------------------------------------------------------------------------------------
! parameters depending on number of interactions
case ( 'interaction_slipslip' , 'interactionslipslip' )
2015-08-28 13:08:48 +05:30
if ( chunkPos ( 1 ) < 1_pInt + Nchunks_SlipSlip ) &
2015-01-15 16:26:15 +05:30
call IO_warning ( 52_pInt , ext_msg = trim ( tag ) / / ' (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2014-11-06 00:41:09 +05:30
do j = 1_pInt , Nchunks_SlipSlip
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_interaction_SlipSlip ( j , instance ) = IO_floatValue ( line , chunkPos , 1_pInt + j )
2014-11-06 00:41:09 +05:30
enddo
case ( 'interaction_sliptwin' , 'interactionsliptwin' )
2015-08-28 13:08:48 +05:30
if ( chunkPos ( 1 ) < 1_pInt + Nchunks_SlipTwin ) &
2015-01-15 16:26:15 +05:30
call IO_warning ( 52_pInt , ext_msg = trim ( tag ) / / ' (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2014-11-06 00:41:09 +05:30
do j = 1_pInt , Nchunks_SlipTwin
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_interaction_SlipTwin ( j , instance ) = IO_floatValue ( line , chunkPos , 1_pInt + j )
2014-11-06 00:41:09 +05:30
enddo
case ( 'interaction_twinslip' , 'interactiontwinslip' )
2015-08-28 13:08:48 +05:30
if ( chunkPos ( 1 ) < 1_pInt + Nchunks_TwinSlip ) &
2015-01-15 16:26:15 +05:30
call IO_warning ( 52_pInt , ext_msg = trim ( tag ) / / ' (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2014-11-06 00:41:09 +05:30
do j = 1_pInt , Nchunks_TwinSlip
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_interaction_TwinSlip ( j , instance ) = IO_floatValue ( line , chunkPos , 1_pInt + j )
2014-11-06 00:41:09 +05:30
enddo
case ( 'interaction_twintwin' , 'interactiontwintwin' )
2015-08-28 13:08:48 +05:30
if ( chunkPos ( 1 ) < 1_pInt + Nchunks_TwinTwin ) &
2015-01-15 16:26:15 +05:30
call IO_warning ( 52_pInt , ext_msg = trim ( tag ) / / ' (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2014-11-06 00:41:09 +05:30
do j = 1_pInt , Nchunks_TwinTwin
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_interaction_TwinTwin ( j , instance ) = IO_floatValue ( line , chunkPos , 1_pInt + j )
2014-11-06 00:41:09 +05:30
enddo
case ( 'nonschmid_coefficients' )
2015-08-28 13:08:48 +05:30
if ( chunkPos ( 1 ) < 1_pInt + Nchunks_nonSchmid ) &
2015-01-15 16:26:15 +05:30
call IO_warning ( 52_pInt , ext_msg = trim ( tag ) / / ' (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2014-11-06 00:41:09 +05:30
do j = 1_pInt , Nchunks_nonSchmid
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_nonSchmidCoeff ( j , instance ) = IO_floatValue ( line , chunkPos , 1_pInt + j )
2014-11-06 00:41:09 +05:30
enddo
!--------------------------------------------------------------------------------------------------
! parameters independent of number of slip/twin systems
case ( 'grainsize' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_GrainSize ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
case ( 'maxtwinfraction' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_MaxTwinFraction ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
case ( 'd0' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_D0 ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
case ( 'qsd' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_Qsd ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
case ( 'atol_rho' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_aTolRho ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
case ( 'atol_twinfrac' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_aTolTwinFrac ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
case ( 'cmfptwin' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_Cmfptwin ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
case ( 'cthresholdtwin' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_Cthresholdtwin ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
case ( 'solidsolutionstrength' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_SolidSolutionStrength ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
case ( 'l0' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_L0 ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
case ( 'xc' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_xc ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
case ( 'vcrossslip' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_VcrossSlip ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
case ( 'cedgedipmindistance' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_CEdgeDipMinDistance ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
case ( 'catomicvolume' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_CAtomicVolume ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
case ( 'sfe_0k' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_SFE_0K ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
case ( 'dsfe_dt' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_dSFE_dT ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
case ( 'dipoleformationfactor' )
2015-08-28 13:08:48 +05:30
plastic_disloUCLA_dipoleFormationFactor ( instance ) = IO_floatValue ( line , chunkPos , 2_pInt )
2014-11-06 00:41:09 +05:30
end select
endif ; endif
enddo parsingFile
sanityChecks : do phase = 1_pInt , size ( phase_plasticity )
2015-01-21 20:44:00 +05:30
myPhase : if ( phase_plasticity ( phase ) == PLASTICITY_disloUCLA_ID ) then
2014-11-06 00:41:09 +05:30
instance = phase_plasticityInstance ( phase )
2015-01-21 20:44:00 +05:30
if ( sum ( plastic_disloUCLA_Nslip ( : , instance ) ) < 0_pInt ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'Nslip (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-01-21 20:44:00 +05:30
if ( sum ( plastic_disloUCLA_Ntwin ( : , instance ) ) < 0_pInt ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'Ntwin (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2014-11-06 00:41:09 +05:30
do f = 1_pInt , lattice_maxNslipFamily
2015-01-21 20:44:00 +05:30
if ( plastic_disloUCLA_Nslip ( f , instance ) > 0_pInt ) then
if ( plastic_disloUCLA_rhoEdge0 ( f , instance ) < 0.0_pReal ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'rhoEdge0 (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-01-21 20:44:00 +05:30
if ( plastic_disloUCLA_rhoEdgeDip0 ( f , instance ) < 0.0_pReal ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'rhoEdgeDip0 (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-01-21 20:44:00 +05:30
if ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) < = 0.0_pReal ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'slipBurgers (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-01-21 20:44:00 +05:30
if ( plastic_disloUCLA_v0PerSlipFamily ( f , instance ) < = 0.0_pReal ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'v0 (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-01-21 20:44:00 +05:30
if ( plastic_disloUCLA_tau_peierlsPerSlipFamily ( f , instance ) < 0.0_pReal ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'tau_peierls (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2014-11-06 00:41:09 +05:30
endif
enddo
do f = 1_pInt , lattice_maxNtwinFamily
2015-01-21 20:44:00 +05:30
if ( plastic_disloUCLA_Ntwin ( f , instance ) > 0_pInt ) then
if ( plastic_disloUCLA_burgersPerTwinFamily ( f , instance ) < = 0.0_pReal ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'twinburgers (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-01-21 20:44:00 +05:30
if ( plastic_disloUCLA_Ndot0PerTwinFamily ( f , instance ) < 0.0_pReal ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'ndot0 (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2014-11-06 00:41:09 +05:30
endif
enddo
2015-01-21 20:44:00 +05:30
if ( plastic_disloUCLA_CAtomicVolume ( instance ) < = 0.0_pReal ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'cAtomicVolume (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-01-21 20:44:00 +05:30
if ( plastic_disloUCLA_D0 ( instance ) < = 0.0_pReal ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'D0 (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-01-21 20:44:00 +05:30
if ( plastic_disloUCLA_Qsd ( instance ) < = 0.0_pReal ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'Qsd (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-01-21 20:44:00 +05:30
if ( sum ( plastic_disloUCLA_Ntwin ( : , instance ) ) > 0_pInt ) then
2015-04-11 17:17:33 +05:30
if ( abs ( plastic_disloUCLA_SFE_0K ( instance ) ) < = tiny ( 0.0_pReal ) . and . &
abs ( plastic_disloUCLA_dSFE_dT ( instance ) ) < = tiny ( 0.0_pReal ) . and . &
lattice_structure ( phase ) == LATTICE_fcc_ID ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'SFE0K (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-01-21 20:44:00 +05:30
if ( plastic_disloUCLA_aTolRho ( instance ) < = 0.0_pReal ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'aTolRho (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2015-01-21 20:44:00 +05:30
if ( plastic_disloUCLA_aTolTwinFrac ( instance ) < = 0.0_pReal ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'aTolTwinFrac (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2014-11-06 00:41:09 +05:30
endif
2015-04-11 17:17:33 +05:30
if ( abs ( plastic_disloUCLA_dipoleFormationFactor ( instance ) ) > tiny ( 0.0_pReal ) . and . &
plastic_disloUCLA_dipoleFormationFactor ( instance ) / = 1.0_pReal ) &
2015-01-15 16:26:15 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'dipoleFormationFactor (' / / PLASTICITY_DISLOUCLA_label / / ')' )
2014-11-06 00:41:09 +05:30
!--------------------------------------------------------------------------------------------------
! Determine total number of active slip or twin systems
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Nslip ( : , instance ) = min ( lattice_NslipSystem ( : , phase ) , plastic_disloUCLA_Nslip ( : , instance ) )
plastic_disloUCLA_Ntwin ( : , instance ) = min ( lattice_NtwinSystem ( : , phase ) , plastic_disloUCLA_Ntwin ( : , instance ) )
plastic_disloUCLA_totalNslip ( instance ) = sum ( plastic_disloUCLA_Nslip ( : , instance ) )
plastic_disloUCLA_totalNtwin ( instance ) = sum ( plastic_disloUCLA_Ntwin ( : , instance ) )
2014-11-06 00:41:09 +05:30
endif myPhase
enddo sanityChecks
!--------------------------------------------------------------------------------------------------
! allocation of variables whose size depends on the total number of active slip systems
2015-01-21 20:44:00 +05:30
maxTotalNslip = maxval ( plastic_disloUCLA_totalNslip )
maxTotalNtwin = maxval ( plastic_disloUCLA_totalNtwin )
allocate ( plastic_disloUCLA_burgersPerSlipSystem ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_burgersPerTwinSystem ( maxTotalNtwin , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_QedgePerSlipSystem ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_v0PerSlipSystem ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_Ndot0PerTwinSystem ( maxTotalNtwin , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_tau_r ( maxTotalNtwin , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_twinsizePerTwinSystem ( maxTotalNtwin , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_CLambdaSlipPerSlipSystem ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_interactionMatrix_SlipSlip ( maxval ( plastic_disloUCLA_totalNslip ) , & ! slip resistance from slip activity
maxval ( plastic_disloUCLA_totalNslip ) , &
2014-11-06 00:41:09 +05:30
maxNinstance ) , source = 0.0_pReal )
2015-01-21 20:44:00 +05:30
allocate ( plastic_disloUCLA_interactionMatrix_SlipTwin ( maxval ( plastic_disloUCLA_totalNslip ) , & ! slip resistance from twin activity
maxval ( plastic_disloUCLA_totalNtwin ) , &
2014-11-06 00:41:09 +05:30
maxNinstance ) , source = 0.0_pReal )
2015-01-21 20:44:00 +05:30
allocate ( plastic_disloUCLA_interactionMatrix_TwinSlip ( maxval ( plastic_disloUCLA_totalNtwin ) , & ! twin resistance from slip activity
maxval ( plastic_disloUCLA_totalNslip ) , &
2014-11-06 00:41:09 +05:30
maxNinstance ) , source = 0.0_pReal )
2015-01-21 20:44:00 +05:30
allocate ( plastic_disloUCLA_interactionMatrix_TwinTwin ( maxval ( plastic_disloUCLA_totalNtwin ) , & ! twin resistance from twin activity
maxval ( plastic_disloUCLA_totalNtwin ) , &
2014-11-06 00:41:09 +05:30
maxNinstance ) , source = 0.0_pReal )
2015-01-21 20:44:00 +05:30
allocate ( plastic_disloUCLA_forestProjectionEdge ( maxTotalNslip , maxTotalNslip , maxNinstance ) , &
2014-11-06 00:41:09 +05:30
source = 0.0_pReal )
2015-01-21 20:44:00 +05:30
allocate ( plastic_disloUCLA_Ctwin66 ( 6 , 6 , maxTotalNtwin , maxNinstance ) , source = 0.0_pReal )
allocate ( plastic_disloUCLA_Ctwin3333 ( 3 , 3 , 3 , 3 , maxTotalNtwin , maxNinstance ) , source = 0.0_pReal )
2016-01-15 20:56:24 +05:30
allocate ( state ( maxNinstance ) )
allocate ( state0 ( maxNinstance ) )
allocate ( dotState ( maxNinstance ) )
2014-11-06 00:41:09 +05:30
initializeInstances : do phase = 1_pInt , size ( phase_plasticity )
2015-01-21 20:44:00 +05:30
myPhase2 : if ( phase_plasticity ( phase ) == PLASTICITY_disloUCLA_ID ) then
2014-11-06 00:41:09 +05:30
NofMyPhase = count ( material_phase == phase )
instance = phase_plasticityInstance ( phase )
2015-01-21 20:44:00 +05:30
ns = plastic_disloUCLA_totalNslip ( instance )
nt = plastic_disloUCLA_totalNtwin ( instance )
2014-11-06 00:41:09 +05:30
!--------------------------------------------------------------------------------------------------
! Determine size of postResults array
2015-01-21 20:44:00 +05:30
outputs : do o = 1_pInt , plastic_disloUCLA_Noutput ( instance )
select case ( plastic_disloUCLA_outputID ( o , instance ) )
2014-11-06 00:41:09 +05:30
case ( edge_density_ID , &
dipole_density_ID , &
shear_rate_slip_ID , &
accumulated_shear_slip_ID , &
mfp_slip_ID , &
resolved_stress_slip_ID , &
threshold_stress_slip_ID , &
edge_dipole_distance_ID , &
stress_exponent_ID &
)
mySize = ns
case ( twin_fraction_ID , &
shear_rate_twin_ID , &
accumulated_shear_twin_ID , &
mfp_twin_ID , &
resolved_stress_twin_ID , &
threshold_stress_twin_ID &
)
mySize = nt
end select
if ( mySize > 0_pInt ) then ! any meaningful output found
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_sizePostResult ( o , instance ) = mySize
plastic_disloUCLA_sizePostResults ( instance ) = plastic_disloUCLA_sizePostResults ( instance ) + mySize
2014-11-06 00:41:09 +05:30
endif
enddo outputs
2016-01-16 12:36:34 +05:30
2014-11-06 00:41:09 +05:30
!--------------------------------------------------------------------------------------------------
! allocate state arrays
2016-01-16 12:36:34 +05:30
sizeDotState = int ( size ( [ 'rhoEdge ' , 'rhoEdgeDip ' , 'accshearslip' ] ) , pInt ) * ns &
+ int ( size ( [ 'twinFraction' , 'accsheartwin' ] ) , pInt ) * nt
sizeDeltaState = 0_pInt
sizeState = sizeDotState &
+ int ( size ( [ 'invLambdaSlip ' , 'invLambdaSlipTwin ' , &
'meanFreePathSlip ' , 'tauSlipThreshold ' ] ) , pInt ) * ns &
+ int ( size ( [ 'invLambdaTwin ' , 'meanFreePathTwin' , 'tauTwinThreshold' , &
'twinVolume ' ] ) , pInt ) * nt
2014-11-06 00:41:09 +05:30
plasticState ( phase ) % sizeState = sizeState
plasticState ( phase ) % sizeDotState = sizeDotState
2015-06-01 21:32:27 +05:30
plasticState ( phase ) % sizeDeltaState = sizeDeltaState
2015-01-23 18:38:25 +05:30
plasticState ( phase ) % sizePostResults = plastic_disloUCLA_sizePostResults ( instance )
plasticState ( phase ) % nSlip = plastic_disloucla_totalNslip ( instance )
plasticState ( phase ) % nTwin = plastic_disloucla_totalNtwin ( instance )
plasticState ( phase ) % nTrans = 0_pInt
2014-11-06 00:41:09 +05:30
allocate ( plasticState ( phase ) % aTolState ( sizeState ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % state0 ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % partionedState0 ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % subState0 ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % state ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % dotState ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
2015-06-01 21:32:27 +05:30
allocate ( plasticState ( phase ) % deltaState ( sizeDeltaState , NofMyPhase ) , source = 0.0_pReal )
2015-08-28 16:25:38 +05:30
if ( . not . analyticJaco ) then
allocate ( plasticState ( phase ) % state_backup ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % dotState_backup ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
endif
2014-11-06 00:41:09 +05:30
if ( any ( numerics_integrator == 1_pInt ) ) then
allocate ( plasticState ( phase ) % previousDotState ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % previousDotState2 ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
endif
if ( any ( numerics_integrator == 4_pInt ) ) &
allocate ( plasticState ( phase ) % RK4dotState ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
if ( any ( numerics_integrator == 5_pInt ) ) &
allocate ( plasticState ( phase ) % RKCK45dotState ( 6 , sizeDotState , NofMyPhase ) , source = 0.0_pReal )
2015-01-23 18:38:25 +05:30
offset_slip = 2_pInt * plasticState ( phase ) % nSlip
plasticState ( phase ) % slipRate = > &
plasticState ( phase ) % dotState ( offset_slip + 1 : offset_slip + plasticState ( phase ) % nSlip , 1 : NofMyPhase )
plasticState ( phase ) % accumulatedSlip = > &
plasticState ( phase ) % state ( offset_slip + 1 : offset_slip + plasticState ( phase ) % nSlip , 1 : NofMyPhase )
2014-11-06 00:41:09 +05:30
!* Process slip related parameters ------------------------------------------------
mySlipFamilies : do f = 1_pInt , lattice_maxNslipFamily
2015-01-21 20:44:00 +05:30
index_myFamily = sum ( plastic_disloUCLA_Nslip ( 1 : f - 1_pInt , instance ) ) ! index in truncated slip system list
mySlipSystems : do j = 1_pInt , plastic_disloUCLA_Nslip ( f , instance )
2014-11-06 00:41:09 +05:30
!* Burgers vector,
! dislocation velocity prefactor,
! mean free path prefactor,
! and minimum dipole distance
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_burgersPerSlipSystem ( index_myFamily + j , instance ) = &
plastic_disloUCLA_burgersPerSlipFamily ( f , instance )
2014-11-06 00:41:09 +05:30
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_QedgePerSlipSystem ( index_myFamily + j , instance ) = &
plastic_disloUCLA_QedgePerSlipFamily ( f , instance )
2014-11-06 00:41:09 +05:30
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_v0PerSlipSystem ( index_myFamily + j , instance ) = &
plastic_disloUCLA_v0PerSlipFamily ( f , instance )
2014-11-06 00:41:09 +05:30
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_CLambdaSlipPerSlipSystem ( index_myFamily + j , instance ) = &
plastic_disloUCLA_CLambdaSlipPerSlipFamily ( f , instance )
2014-11-06 00:41:09 +05:30
!* Calculation of forest projections for edge dislocations
!* Interaction matrices
otherSlipFamilies : do o = 1_pInt , lattice_maxNslipFamily
2015-01-21 20:44:00 +05:30
index_otherFamily = sum ( plastic_disloUCLA_Nslip ( 1 : o - 1_pInt , instance ) )
otherSlipSystems : do k = 1_pInt , plastic_disloUCLA_Nslip ( o , instance )
plastic_disloUCLA_forestProjectionEdge ( index_myFamily + j , index_otherFamily + k , instance ) = &
2014-11-06 00:41:09 +05:30
abs ( math_mul3x3 ( lattice_sn ( : , sum ( lattice_NslipSystem ( 1 : f - 1 , phase ) ) + j , phase ) , &
lattice_st ( : , sum ( lattice_NslipSystem ( 1 : o - 1 , phase ) ) + k , phase ) ) )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_interactionMatrix_SlipSlip ( index_myFamily + j , index_otherFamily + k , instance ) = &
plastic_disloUCLA_interaction_SlipSlip ( lattice_interactionSlipSlip ( &
2014-11-06 00:41:09 +05:30
sum ( lattice_NslipSystem ( 1 : f - 1 , phase ) ) + j , &
sum ( lattice_NslipSystem ( 1 : o - 1 , phase ) ) + k , &
phase ) , instance )
enddo otherSlipSystems ; enddo otherSlipFamilies
otherTwinFamilies : do o = 1_pInt , lattice_maxNtwinFamily
2015-01-21 20:44:00 +05:30
index_otherFamily = sum ( plastic_disloUCLA_Ntwin ( 1 : o - 1_pInt , instance ) )
otherTwinSystems : do k = 1_pInt , plastic_disloUCLA_Ntwin ( o , instance )
plastic_disloUCLA_interactionMatrix_SlipTwin ( index_myFamily + j , index_otherFamily + k , instance ) = &
plastic_disloUCLA_interaction_SlipTwin ( lattice_interactionSlipTwin ( &
2014-11-06 00:41:09 +05:30
sum ( lattice_NslipSystem ( 1 : f - 1_pInt , phase ) ) + j , &
sum ( lattice_NtwinSystem ( 1 : o - 1_pInt , phase ) ) + k , &
phase ) , instance )
enddo otherTwinSystems ; enddo otherTwinFamilies
enddo mySlipSystems
enddo mySlipFamilies
!* Process twin related parameters ------------------------------------------------
myTwinFamilies : do f = 1_pInt , lattice_maxNtwinFamily
2015-01-21 20:44:00 +05:30
index_myFamily = sum ( plastic_disloUCLA_Ntwin ( 1 : f - 1_pInt , instance ) ) ! index in truncated twin system list
myTwinSystems : do j = 1_pInt , plastic_disloUCLA_Ntwin ( f , instance )
2014-11-06 00:41:09 +05:30
!* Burgers vector,
! nucleation rate prefactor,
! and twin size
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_burgersPerTwinSystem ( index_myFamily + j , instance ) = &
plastic_disloUCLA_burgersPerTwinFamily ( f , instance )
2014-11-06 00:41:09 +05:30
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Ndot0PerTwinSystem ( index_myFamily + j , instance ) = &
plastic_disloUCLA_Ndot0PerTwinFamily ( f , instance )
2014-11-06 00:41:09 +05:30
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_twinsizePerTwinSystem ( index_myFamily + j , instance ) = &
plastic_disloUCLA_twinsizePerTwinFamily ( f , instance )
2014-11-06 00:41:09 +05:30
!* Rotate twin elasticity matrices
index_otherFamily = sum ( lattice_NtwinSystem ( 1 : f - 1_pInt , phase ) ) ! index in full lattice twin list
do l = 1_pInt , 3_pInt ; do m = 1_pInt , 3_pInt ; do n = 1_pInt , 3_pInt ; do o = 1_pInt , 3_pInt
do p = 1_pInt , 3_pInt ; do q = 1_pInt , 3_pInt ; do r = 1_pInt , 3_pInt ; do s = 1_pInt , 3_pInt
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Ctwin3333 ( l , m , n , o , index_myFamily + j , instance ) = &
plastic_disloUCLA_Ctwin3333 ( l , m , n , o , index_myFamily + j , instance ) + &
2014-11-06 00:41:09 +05:30
lattice_C3333 ( p , q , r , s , instance ) * &
lattice_Qtwin ( l , p , index_otherFamily + j , phase ) * &
lattice_Qtwin ( m , q , index_otherFamily + j , phase ) * &
lattice_Qtwin ( n , r , index_otherFamily + j , phase ) * &
lattice_Qtwin ( o , s , index_otherFamily + j , phase )
enddo ; enddo ; enddo ; enddo
enddo ; enddo ; enddo ; enddo
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Ctwin66 ( 1 : 6 , 1 : 6 , index_myFamily + j , instance ) = &
math_Mandel3333to66 ( plastic_disloUCLA_Ctwin3333 ( 1 : 3 , 1 : 3 , 1 : 3 , 1 : 3 , index_myFamily + j , instance ) )
2014-11-06 00:41:09 +05:30
!* Interaction matrices
otherSlipFamilies2 : do o = 1_pInt , lattice_maxNslipFamily
2015-01-21 20:44:00 +05:30
index_otherFamily = sum ( plastic_disloUCLA_Nslip ( 1 : o - 1_pInt , instance ) )
otherSlipSystems2 : do k = 1_pInt , plastic_disloUCLA_Nslip ( o , instance )
plastic_disloUCLA_interactionMatrix_TwinSlip ( index_myFamily + j , index_otherFamily + k , instance ) = &
plastic_disloUCLA_interaction_TwinSlip ( lattice_interactionTwinSlip ( &
2014-11-06 00:41:09 +05:30
sum ( lattice_NtwinSystem ( 1 : f - 1_pInt , phase ) ) + j , &
sum ( lattice_NslipSystem ( 1 : o - 1_pInt , phase ) ) + k , &
phase ) , instance )
enddo otherSlipSystems2 ; enddo otherSlipFamilies2
otherTwinFamilies2 : do o = 1_pInt , lattice_maxNtwinFamily
2015-01-21 20:44:00 +05:30
index_otherFamily = sum ( plastic_disloUCLA_Ntwin ( 1 : o - 1_pInt , instance ) )
otherTwinSystems2 : do k = 1_pInt , plastic_disloUCLA_Ntwin ( o , instance )
plastic_disloUCLA_interactionMatrix_TwinTwin ( index_myFamily + j , index_otherFamily + k , instance ) = &
plastic_disloUCLA_interaction_TwinTwin ( lattice_interactionTwinTwin ( &
2014-11-06 00:41:09 +05:30
sum ( lattice_NtwinSystem ( 1 : f - 1_pInt , phase ) ) + j , &
sum ( lattice_NtwinSystem ( 1 : o - 1_pInt , phase ) ) + k , &
phase ) , instance )
enddo otherTwinSystems2 ; enddo otherTwinFamilies2
enddo myTwinSystems
2016-01-16 12:36:34 +05:30
enddo myTwinFamilies
startIndex = 1_pInt
endIndex = ns
state ( instance ) % rhoEdge = > plasticState ( phase ) % state ( startIndex : endIndex , : )
state0 ( instance ) % rhoEdge = > plasticState ( phase ) % state0 ( startIndex : endIndex , : )
dotState ( instance ) % rhoEdge = > plasticState ( phase ) % dotState ( startIndex : endIndex , : )
startIndex = endIndex + 1_pInt
endIndex = endIndex + ns
state ( instance ) % rhoEdgeDip = > plasticState ( phase ) % state ( startIndex : endIndex , : )
state0 ( instance ) % rhoEdgeDip = > plasticState ( phase ) % state0 ( startIndex : endIndex , : )
dotState ( instance ) % rhoEdgeDip = > plasticState ( phase ) % dotState ( startIndex : endIndex , : )
startIndex = endIndex + 1_pInt
endIndex = endIndex + ns
state ( instance ) % accshear_slip = > plasticState ( phase ) % state ( startIndex : endIndex , : )
state0 ( instance ) % accshear_slip = > plasticState ( phase ) % state0 ( startIndex : endIndex , : )
dotState ( instance ) % accshear_slip = > plasticState ( phase ) % dotState ( startIndex : endIndex , : )
startIndex = endIndex + 1_pInt
endIndex = endIndex + nt
state ( instance ) % twinFraction = > plasticState ( phase ) % state ( startIndex : endIndex , : )
state0 ( instance ) % twinFraction = > plasticState ( phase ) % state0 ( startIndex : endIndex , : )
dotState ( instance ) % twinFraction = > plasticState ( phase ) % dotState ( startIndex : endIndex , : )
startIndex = endIndex + 1_pInt
endIndex = endIndex + nt
state ( instance ) % accshear_twin = > plasticState ( phase ) % state ( startIndex : endIndex , : )
state0 ( instance ) % accshear_twin = > plasticState ( phase ) % state0 ( startIndex : endIndex , : )
dotState ( instance ) % accshear_twin = > plasticState ( phase ) % dotState ( startIndex : endIndex , : )
startIndex = endIndex + 1_pInt
endIndex = endIndex + ns
state ( instance ) % invLambdaSlip = > plasticState ( phase ) % state ( startIndex : endIndex , : )
state0 ( instance ) % invLambdaSlip = > plasticState ( phase ) % state0 ( startIndex : endIndex , : )
startIndex = endIndex + 1
endIndex = endIndex + ns
state ( instance ) % invLambdaSlipTwin = > plasticState ( phase ) % state ( startIndex : endIndex , : )
state0 ( instance ) % invLambdaSlipTwin = > plasticState ( phase ) % state0 ( startIndex : endIndex , : )
startIndex = endIndex + 1
endIndex = endIndex + nt
state ( instance ) % invLambdaTwin = > plasticState ( phase ) % state ( startIndex : endIndex , : )
state0 ( instance ) % invLambdaTwin = > plasticState ( phase ) % state0 ( startIndex : endIndex , : )
startIndex = endIndex + 1
endIndex = endIndex + ns
state ( instance ) % mfp_slip = > plasticState ( phase ) % state ( startIndex : endIndex , : )
state0 ( instance ) % mfp_slip = > plasticState ( phase ) % state0 ( startIndex : endIndex , : )
startIndex = endIndex + 1
endIndex = endIndex + nt
state ( instance ) % mfp_twin = > plasticState ( phase ) % state ( startIndex : endIndex , : )
state0 ( instance ) % mfp_twin = > plasticState ( phase ) % state0 ( startIndex : endIndex , : )
startIndex = endIndex + 1
endIndex = endIndex + ns
state ( instance ) % threshold_stress_slip = > plasticState ( phase ) % state ( startIndex : endIndex , : )
state0 ( instance ) % threshold_stress_slip = > plasticState ( phase ) % state0 ( startIndex : endIndex , : )
2016-01-15 20:56:24 +05:30
2016-01-16 12:36:34 +05:30
startIndex = endIndex + 1
endIndex = endIndex + nt
state ( instance ) % threshold_stress_twin = > plasticState ( phase ) % state ( startIndex : endIndex , : )
state0 ( instance ) % threshold_stress_twin = > plasticState ( phase ) % state0 ( startIndex : endIndex , : )
startIndex = endIndex + 1
endIndex = endIndex + nt
state ( instance ) % twinVolume = > plasticState ( phase ) % state ( startIndex : endIndex , : )
state0 ( instance ) % twinVolume = > plasticState ( phase ) % state0 ( startIndex : endIndex , : )
2015-01-21 20:44:00 +05:30
call plastic_disloUCLA_stateInit ( phase , instance )
call plastic_disloUCLA_aTolState ( phase , instance )
2014-11-06 00:41:09 +05:30
endif myPhase2
enddo initializeInstances
2015-01-21 20:44:00 +05:30
end subroutine plastic_disloUCLA_init
2014-11-06 00:41:09 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief sets the relevant state values for a given instance of this plasticity
!--------------------------------------------------------------------------------------------------
2015-01-21 20:44:00 +05:30
subroutine plastic_disloUCLA_stateInit ( ph , instance )
2014-11-06 00:41:09 +05:30
use math , only : &
pi
use lattice , only : &
lattice_maxNslipFamily , &
2014-11-06 02:23:25 +05:30
lattice_mu
2014-11-06 00:41:09 +05:30
use material , only : &
plasticState
implicit none
integer ( pInt ) , intent ( in ) :: &
instance , & !< number specifying the instance of the plasticity
ph
real ( pReal ) , dimension ( plasticState ( ph ) % sizeState ) :: tempState
integer ( pInt ) :: i , j , f , ns , nt , index_myFamily
2015-01-21 20:44:00 +05:30
real ( pReal ) , dimension ( plastic_disloUCLA_totalNslip ( instance ) ) :: &
2014-11-06 00:41:09 +05:30
rhoEdge0 , &
rhoEdgeDip0 , &
invLambdaSlip0 , &
MeanFreePathSlip0 , &
tauSlipThreshold0
2015-01-21 20:44:00 +05:30
real ( pReal ) , dimension ( plastic_disloUCLA_totalNtwin ( instance ) ) :: &
2014-11-06 00:41:09 +05:30
MeanFreePathTwin0 , TwinVolume0
tempState = 0.0_pReal
2015-01-21 20:44:00 +05:30
ns = plastic_disloUCLA_totalNslip ( instance )
nt = plastic_disloUCLA_totalNtwin ( instance )
2014-11-06 00:41:09 +05:30
!--------------------------------------------------------------------------------------------------
! initialize basic slip state variables
do f = 1_pInt , lattice_maxNslipFamily
2015-01-21 20:44:00 +05:30
index_myFamily = sum ( plastic_disloUCLA_Nslip ( 1 : f - 1_pInt , instance ) ) ! index in truncated slip system list
2014-11-06 00:41:09 +05:30
rhoEdge0 ( index_myFamily + 1_pInt : &
2015-01-21 20:44:00 +05:30
index_myFamily + plastic_disloUCLA_Nslip ( f , instance ) ) = &
plastic_disloUCLA_rhoEdge0 ( f , instance )
2014-11-06 00:41:09 +05:30
rhoEdgeDip0 ( index_myFamily + 1_pInt : &
2015-01-21 20:44:00 +05:30
index_myFamily + plastic_disloUCLA_Nslip ( f , instance ) ) = &
plastic_disloUCLA_rhoEdgeDip0 ( f , instance )
2014-11-06 00:41:09 +05:30
enddo
tempState ( 1_pInt : ns ) = rhoEdge0
tempState ( ns + 1_pInt : 2_pInt * ns ) = rhoEdgeDip0
!--------------------------------------------------------------------------------------------------
! initialize dependent slip microstructural variables
forall ( i = 1_pInt : ns ) &
2015-01-21 20:44:00 +05:30
invLambdaSlip0 ( i ) = sqrt ( dot_product ( ( rhoEdge0 + rhoEdgeDip0 ) , plastic_disloUCLA_forestProjectionEdge ( 1 : ns , i , instance ) ) ) / &
plastic_disloUCLA_CLambdaSlipPerSlipSystem ( i , instance )
2014-11-06 00:41:09 +05:30
tempState ( 3_pInt * ns + 2_pInt * nt + 1 : 4_pInt * ns + 2_pInt * nt ) = invLambdaSlip0
forall ( i = 1_pInt : ns ) &
MeanFreePathSlip0 ( i ) = &
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_GrainSize ( instance ) / ( 1.0_pReal + invLambdaSlip0 ( i ) * plastic_disloUCLA_GrainSize ( instance ) )
2014-11-06 00:41:09 +05:30
tempState ( 5_pInt * ns + 3_pInt * nt + 1 : 6_pInt * ns + 3_pInt * nt ) = MeanFreePathSlip0
forall ( i = 1_pInt : ns ) &
tauSlipThreshold0 ( i ) = &
2015-01-21 20:44:00 +05:30
lattice_mu ( ph ) * plastic_disloUCLA_burgersPerSlipSystem ( i , instance ) * &
sqrt ( dot_product ( ( rhoEdge0 + rhoEdgeDip0 ) , plastic_disloUCLA_interactionMatrix_SlipSlip ( i , 1 : ns , instance ) ) )
2014-11-06 00:41:09 +05:30
tempState ( 6_pInt * ns + 4_pInt * nt + 1 : 7_pInt * ns + 4_pInt * nt ) = tauSlipThreshold0
!--------------------------------------------------------------------------------------------------
! initialize dependent twin microstructural variables
forall ( j = 1_pInt : nt ) &
2015-01-21 20:44:00 +05:30
MeanFreePathTwin0 ( j ) = plastic_disloUCLA_GrainSize ( instance )
2014-11-06 00:41:09 +05:30
tempState ( 6_pInt * ns + 3_pInt * nt + 1_pInt : 6_pInt * ns + 4_pInt * nt ) = MeanFreePathTwin0
forall ( j = 1_pInt : nt ) &
TwinVolume0 ( j ) = &
2015-01-21 20:44:00 +05:30
( pi / 4.0_pReal ) * plastic_disloUCLA_twinsizePerTwinSystem ( j , instance ) * MeanFreePathTwin0 ( j ) ** ( 2.0_pReal )
2014-11-06 00:41:09 +05:30
tempState ( 7_pInt * ns + 5_pInt * nt + 1_pInt : 7_pInt * ns + 6_pInt * nt ) = TwinVolume0
plasticState ( ph ) % state0 = spread ( tempState , 2 , size ( plasticState ( ph ) % state ( 1 , : ) ) )
2015-01-21 20:44:00 +05:30
end subroutine plastic_disloUCLA_stateInit
2014-11-06 00:41:09 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief sets the relevant state values for a given instance of this plasticity
!--------------------------------------------------------------------------------------------------
2015-01-21 20:44:00 +05:30
subroutine plastic_disloUCLA_aTolState ( ph , instance )
2014-11-06 00:41:09 +05:30
use material , only : &
plasticState
implicit none
integer ( pInt ) , intent ( in ) :: &
ph , &
instance ! number specifying the current instance of the plasticity
! Tolerance state for dislocation densities
2015-01-21 20:44:00 +05:30
plasticState ( ph ) % aTolState ( 1_pInt : 2_pInt * plastic_disloUCLA_totalNslip ( instance ) ) = &
plastic_disloUCLA_aTolRho ( instance )
2014-11-06 00:41:09 +05:30
! Tolerance state for accumulated shear due to slip
2015-01-21 20:44:00 +05:30
plasticState ( ph ) % aTolState ( 2_pInt * plastic_disloUCLA_totalNslip ( instance ) + 1_pInt : &
3_pInt * plastic_disloUCLA_totalNslip ( instance ) ) = 1e6_pReal
2014-11-06 00:41:09 +05:30
! Tolerance state for twin volume fraction
2015-01-21 20:44:00 +05:30
plasticState ( ph ) % aTolState ( 3_pInt * plastic_disloUCLA_totalNslip ( instance ) + 1_pInt : &
3_pInt * plastic_disloUCLA_totalNslip ( instance ) + &
plastic_disloUCLA_totalNtwin ( instance ) ) = &
plastic_disloUCLA_aTolTwinFrac ( instance )
2014-11-06 00:41:09 +05:30
! Tolerance state for accumulated shear due to twin
2015-01-21 20:44:00 +05:30
plasticState ( ph ) % aTolState ( 3_pInt * plastic_disloUCLA_totalNslip ( instance ) + &
plastic_disloUCLA_totalNtwin ( instance ) + 1_pInt : &
3_pInt * plastic_disloUCLA_totalNslip ( instance ) + &
2_pInt * plastic_disloUCLA_totalNtwin ( instance ) ) = 1e6_pReal
2014-11-06 00:41:09 +05:30
2015-01-21 20:44:00 +05:30
end subroutine plastic_disloUCLA_aTolState
2014-11-06 00:41:09 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief returns the homogenized elasticity matrix
!--------------------------------------------------------------------------------------------------
2015-01-21 20:44:00 +05:30
function plastic_disloUCLA_homogenizedC ( ipc , ip , el )
2014-11-06 00:41:09 +05:30
use material , only : &
phase_plasticityInstance , &
plasticState , &
2016-01-15 05:49:44 +05:30
phaseAt , phasememberAt
2014-11-06 00:41:09 +05:30
use lattice , only : &
lattice_C66
implicit none
real ( pReal ) , dimension ( 6 , 6 ) :: &
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_homogenizedC
2014-11-06 00:41:09 +05:30
integer ( pInt ) , intent ( in ) :: &
ipc , & !< component-ID of integration point
ip , & !< integration point
el !< element
integer ( pInt ) :: instance , ns , nt , i , &
ph , &
of
real ( pReal ) :: sumf
!* Shortened notation
2016-01-15 05:49:44 +05:30
of = phasememberAt ( ipc , ip , el )
ph = phaseAt ( ipc , ip , el )
2014-11-06 00:41:09 +05:30
instance = phase_plasticityInstance ( ph )
2015-01-21 20:44:00 +05:30
ns = plastic_disloUCLA_totalNslip ( instance )
nt = plastic_disloUCLA_totalNtwin ( instance )
2014-11-06 00:41:09 +05:30
!* Total twin volume fraction
2016-01-15 20:56:24 +05:30
sumf = sum ( state ( instance ) % twinFraction ( 1_pInt : nt , of ) ) ! safe for nt == 0
2014-11-06 00:41:09 +05:30
!* Homogenized elasticity matrix
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_homogenizedC = ( 1.0_pReal - sumf ) * lattice_C66 ( 1 : 6 , 1 : 6 , ph )
2014-11-06 00:41:09 +05:30
do i = 1_pInt , nt
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_homogenizedC = plastic_disloUCLA_homogenizedC &
2016-01-15 20:56:24 +05:30
+ state ( instance ) % twinFraction ( i , of ) * plastic_disloUCLA_Ctwin66 ( 1 : 6 , 1 : 6 , i , instance )
2014-11-06 00:41:09 +05:30
enddo
2014-12-11 20:34:16 +05:30
2015-01-21 20:44:00 +05:30
end function plastic_disloUCLA_homogenizedC
2014-11-06 00:41:09 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief calculates derived quantities from state
!--------------------------------------------------------------------------------------------------
2015-01-21 20:44:00 +05:30
subroutine plastic_disloUCLA_microstructure ( temperature , ipc , ip , el )
2014-11-06 00:41:09 +05:30
use math , only : &
pi
use material , only : &
material_phase , &
phase_plasticityInstance , &
2016-01-15 05:49:44 +05:30
phaseAt , phasememberAt
2014-11-06 00:41:09 +05:30
use lattice , only : &
lattice_mu , &
2014-11-06 02:23:25 +05:30
lattice_nu
2014-11-06 00:41:09 +05:30
implicit none
integer ( pInt ) , intent ( in ) :: &
ipc , & !< component-ID of integration point
ip , & !< integration point
el !< element
real ( pReal ) , intent ( in ) :: &
temperature !< temperature at IP
integer ( pInt ) :: &
instance , &
ns , nt , s , t , &
ph , &
of
real ( pReal ) :: &
sumf , sfe , x0
2015-01-21 20:44:00 +05:30
real ( pReal ) , dimension ( plastic_disloUCLA_totalNtwin ( phase_plasticityInstance ( material_phase ( ipc , ip , el ) ) ) ) :: fOverStacksize
2014-11-06 00:41:09 +05:30
!* Shortened notation
2016-01-15 05:49:44 +05:30
of = phasememberAt ( ipc , ip , el )
ph = phaseAt ( ipc , ip , el )
2014-11-06 00:41:09 +05:30
instance = phase_plasticityInstance ( ph )
2015-01-21 20:44:00 +05:30
ns = plastic_disloUCLA_totalNslip ( instance )
nt = plastic_disloUCLA_totalNtwin ( instance )
2014-11-06 00:41:09 +05:30
!* Total twin volume fraction
2016-01-15 20:56:24 +05:30
sumf = sum ( state ( instance ) % twinFraction ( 1_pInt : nt , of ) ) ! safe for nt == 0
2014-11-06 00:41:09 +05:30
!* Stacking fault energy
2015-01-21 20:44:00 +05:30
sfe = plastic_disloUCLA_SFE_0K ( instance ) + &
plastic_disloUCLA_dSFE_dT ( instance ) * Temperature
2014-11-06 00:41:09 +05:30
!* rescaled twin volume fraction for topology
forall ( t = 1_pInt : nt ) &
fOverStacksize ( t ) = &
2016-01-15 20:56:24 +05:30
state ( instance ) % twinFraction ( t , of ) / plastic_disloUCLA_twinsizePerTwinSystem ( t , instance )
2014-11-06 00:41:09 +05:30
!* 1/mean free distance between 2 forest dislocations seen by a moving dislocation
forall ( s = 1_pInt : ns ) &
2016-01-15 20:56:24 +05:30
state ( instance ) % invLambdaSlip ( s , of ) = &
sqrt ( dot_product ( ( state ( instance ) % rhoEdge ( 1_pInt : ns , of ) + state ( instance ) % rhoEdgeDip ( 1_pInt : ns , of ) ) , &
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_forestProjectionEdge ( 1 : ns , s , instance ) ) ) / &
plastic_disloUCLA_CLambdaSlipPerSlipSystem ( s , instance )
2014-11-06 00:41:09 +05:30
!* 1/mean free distance between 2 twin stacks from different systems seen by a moving dislocation
!$OMP CRITICAL (evilmatmul)
2016-01-15 20:56:24 +05:30
state ( instance ) % invLambdaSlipTwin ( 1_pInt : ns , of ) = 0.0_pReal
2014-11-06 00:41:09 +05:30
if ( nt > 0_pInt . and . ns > 0_pInt ) &
2016-01-15 20:56:24 +05:30
state ( instance ) % invLambdaSlipTwin ( 1_pInt : ns , of ) = &
2015-01-21 20:44:00 +05:30
matmul ( plastic_disloUCLA_interactionMatrix_SlipTwin ( 1 : ns , 1 : nt , instance ) , fOverStacksize ( 1 : nt ) ) / ( 1.0_pReal - sumf )
2014-11-06 00:41:09 +05:30
!$OMP END CRITICAL (evilmatmul)
!* 1/mean free distance between 2 twin stacks from different systems seen by a growing twin
!$OMP CRITICAL (evilmatmul)
if ( nt > 0_pInt ) &
2016-01-15 20:56:24 +05:30
state ( instance ) % invLambdaTwin ( 1_pInt : nt , of ) = &
2015-01-21 20:44:00 +05:30
matmul ( plastic_disloUCLA_interactionMatrix_TwinTwin ( 1 : nt , 1 : nt , instance ) , fOverStacksize ( 1 : nt ) ) / ( 1.0_pReal - sumf )
2014-11-06 00:41:09 +05:30
!$OMP END CRITICAL (evilmatmul)
!* mean free path between 2 obstacles seen by a moving dislocation
do s = 1_pInt , ns
if ( nt > 0_pInt ) then
2016-01-15 20:56:24 +05:30
state ( instance ) % mfp_slip ( s , of ) = &
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_GrainSize ( instance ) / ( 1.0_pReal + plastic_disloUCLA_GrainSize ( instance ) * &
2016-01-15 20:56:24 +05:30
( state ( instance ) % invLambdaSlip ( s , of ) + state ( instance ) % invLambdaSlipTwin ( s , of ) ) )
2014-11-06 00:41:09 +05:30
else
2016-01-15 20:56:24 +05:30
state ( instance ) % mfp_slip ( s , of ) = &
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_GrainSize ( instance ) / &
2016-01-15 20:56:24 +05:30
( 1.0_pReal + plastic_disloUCLA_GrainSize ( instance ) * ( state ( instance ) % invLambdaSlip ( s , of ) ) )
2014-11-06 00:41:09 +05:30
endif
enddo
!* mean free path between 2 obstacles seen by a growing twin
forall ( t = 1_pInt : nt ) &
2016-01-15 20:56:24 +05:30
state ( instance ) % mfp_twin ( t , of ) = &
2015-01-21 20:44:00 +05:30
( plastic_disloUCLA_Cmfptwin ( instance ) * plastic_disloUCLA_GrainSize ( instance ) ) / &
2016-01-15 20:56:24 +05:30
( 1.0_pReal + plastic_disloUCLA_GrainSize ( instance ) * state ( instance ) % invLambdaTwin ( t , of ) )
2014-11-06 00:41:09 +05:30
!* threshold stress for dislocation motion
forall ( s = 1_pInt : ns ) &
2016-01-15 20:56:24 +05:30
state ( instance ) % threshold_stress_slip ( s , of ) = &
2015-01-21 20:44:00 +05:30
lattice_mu ( ph ) * plastic_disloUCLA_burgersPerSlipSystem ( s , instance ) * &
2016-01-15 20:56:24 +05:30
sqrt ( dot_product ( ( state ( instance ) % rhoEdge ( 1_pInt : ns , of ) + state ( instance ) % rhoEdgeDip ( 1_pInt : ns , of ) ) , &
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_interactionMatrix_SlipSlip ( s , 1 : ns , instance ) ) )
2014-11-06 00:41:09 +05:30
!* threshold stress for growing twin
forall ( t = 1_pInt : nt ) &
2016-01-15 20:56:24 +05:30
state ( instance ) % threshold_stress_twin ( t , of ) = &
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_Cthresholdtwin ( instance ) * &
( sfe / ( 3.0_pReal * plastic_disloUCLA_burgersPerTwinSystem ( t , instance ) ) + &
3.0_pReal * plastic_disloUCLA_burgersPerTwinSystem ( t , instance ) * lattice_mu ( ph ) / &
( plastic_disloUCLA_L0 ( instance ) * plastic_disloUCLA_burgersPerSlipSystem ( t , instance ) ) )
2014-11-06 00:41:09 +05:30
!* final twin volume after growth
forall ( t = 1_pInt : nt ) &
2016-01-15 20:56:24 +05:30
state ( instance ) % twinVolume ( t , of ) = &
( pi / 4.0_pReal ) * plastic_disloUCLA_twinsizePerTwinSystem ( t , instance ) * state ( instance ) % mfp_twin ( t , of ) ** ( 2.0_pReal )
2014-11-06 00:41:09 +05:30
!* equilibrium seperation of partial dislocations
do t = 1_pInt , nt
2015-01-21 20:44:00 +05:30
x0 = lattice_mu ( ph ) * plastic_disloUCLA_burgersPerTwinSystem ( t , instance ) ** ( 2.0_pReal ) / &
2014-11-06 00:41:09 +05:30
( sfe * 8.0_pReal * pi ) * ( 2.0_pReal + lattice_nu ( ph ) ) / ( 1.0_pReal - lattice_nu ( ph ) )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_tau_r ( t , instance ) = &
lattice_mu ( ph ) * plastic_disloUCLA_burgersPerTwinSystem ( t , instance ) / ( 2.0_pReal * pi ) * &
( 1 / ( x0 + plastic_disloUCLA_xc ( instance ) ) + cos ( pi / 3.0_pReal ) / x0 ) !!! used where??
2014-11-06 00:41:09 +05:30
enddo
2015-01-21 20:44:00 +05:30
end subroutine plastic_disloUCLA_microstructure
2014-11-06 00:41:09 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief calculates plastic velocity gradient and its tangent
!--------------------------------------------------------------------------------------------------
2015-01-29 19:26:09 +05:30
subroutine plastic_disloUCLA_LpAndItsTangent ( Lp , dLp_dTstar99 , Tstar_v , Temperature , ipc , ip , el )
2014-11-06 00:41:09 +05:30
use prec , only : &
tol_math_check
use math , only : &
math_Plain3333to99 , &
math_Mandel6to33 , &
math_Mandel33to6 , &
math_spectralDecompositionSym33 , &
math_symmetric33 , &
math_mul33x3
use material , only : &
material_phase , &
phase_plasticityInstance , &
2016-01-15 20:56:24 +05:30
!plasticState, &
2016-01-15 05:49:44 +05:30
phaseAt , phasememberAt
2014-11-06 00:41:09 +05:30
use lattice , only : &
lattice_Sslip , &
lattice_Sslip_v , &
lattice_Stwin , &
lattice_Stwin_v , &
lattice_maxNslipFamily , &
lattice_maxNtwinFamily , &
lattice_NslipSystem , &
lattice_NtwinSystem , &
lattice_NnonSchmid , &
lattice_shearTwin , &
lattice_structure , &
lattice_fcc_twinNucleationSlipPair , &
LATTICE_fcc_ID
implicit none
2015-01-29 19:26:09 +05:30
integer ( pInt ) , intent ( in ) :: ipc , ip , el
2014-11-06 00:41:09 +05:30
real ( pReal ) , intent ( in ) :: Temperature
real ( pReal ) , dimension ( 6 ) , intent ( in ) :: Tstar_v
real ( pReal ) , dimension ( 3 , 3 ) , intent ( out ) :: Lp
2014-11-07 16:53:34 +05:30
real ( pReal ) , dimension ( 9 , 9 ) , intent ( out ) :: dLp_dTstar99
2014-11-06 00:41:09 +05:30
integer ( pInt ) :: instance , ph , of , ns , nt , f , i , j , k , l , m , n , index_myFamily , s1 , s2
real ( pReal ) :: sumf , StressRatio_p , StressRatio_pminus1 , StressRatio_r , BoltzmannRatio , DotGamma0 , Ndot0 , &
2015-01-21 20:44:00 +05:30
tau_slip_pos , tau_slip_neg , vel_slip , dvel_slip , &
2014-11-06 00:41:09 +05:30
dgdot_dtauslip_pos , dgdot_dtauslip_neg , dgdot_dtautwin , tau_twin , gdot_twin , stressRatio
real ( pReal ) , dimension ( 3 , 3 , 2 ) :: &
nonSchmid_tensor
real ( pReal ) , dimension ( 3 , 3 , 3 , 3 ) :: &
dLp_dTstar3333
2015-01-21 20:44:00 +05:30
real ( pReal ) , dimension ( plastic_disloUCLA_totalNslip ( phase_plasticityInstance ( material_phase ( ipc , ip , el ) ) ) ) :: &
2014-11-06 00:41:09 +05:30
gdot_slip_pos , gdot_slip_neg
!* Shortened notation
2016-01-15 05:49:44 +05:30
of = phasememberAt ( ipc , ip , el )
ph = phaseAt ( ipc , ip , el )
2014-11-06 00:41:09 +05:30
instance = phase_plasticityInstance ( ph )
2015-01-21 20:44:00 +05:30
ns = plastic_disloUCLA_totalNslip ( instance )
nt = plastic_disloUCLA_totalNtwin ( instance )
2014-11-06 00:41:09 +05:30
Lp = 0.0_pReal
dLp_dTstar3333 = 0.0_pReal
!--------------------------------------------------------------------------------------------------
! Dislocation glide part
gdot_slip_pos = 0.0_pReal
gdot_slip_neg = 0.0_pReal
dgdot_dtauslip_pos = 0.0_pReal
dgdot_dtauslip_neg = 0.0_pReal
j = 0_pInt
slipFamilies : do f = 1_pInt , lattice_maxNslipFamily
index_myFamily = sum ( lattice_NslipSystem ( 1 : f - 1_pInt , ph ) ) ! at which index starts my family
2015-01-21 20:44:00 +05:30
slipSystems : do i = 1_pInt , plastic_disloUCLA_Nslip ( f , instance )
2014-11-06 00:41:09 +05:30
j = j + 1_pInt
2014-11-07 16:53:34 +05:30
!* Boltzmann ratio
2015-01-21 20:44:00 +05:30
BoltzmannRatio = plastic_disloUCLA_QedgePerSlipSystem ( j , instance ) / ( kB * Temperature )
2014-11-07 16:53:34 +05:30
!* Initial shear rates
DotGamma0 = &
2016-01-15 20:56:24 +05:30
state ( instance ) % rhoEdge ( j , of ) * plastic_disloUCLA_burgersPerSlipSystem ( j , instance ) * &
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_v0PerSlipSystem ( j , instance )
2014-11-07 16:53:34 +05:30
!* Resolved shear stress on slip system
2014-11-06 00:41:09 +05:30
tau_slip_pos = dot_product ( Tstar_v , lattice_Sslip_v ( 1 : 6 , 1 , index_myFamily + i , ph ) )
tau_slip_neg = tau_slip_pos
nonSchmid_tensor ( 1 : 3 , 1 : 3 , 1 ) = lattice_Sslip ( 1 : 3 , 1 : 3 , 1 , index_myFamily + i , ph )
nonSchmid_tensor ( 1 : 3 , 1 : 3 , 2 ) = nonSchmid_tensor ( 1 : 3 , 1 : 3 , 1 )
nonSchmidSystems : do k = 1 , lattice_NnonSchmid ( ph )
2015-01-21 20:44:00 +05:30
tau_slip_pos = tau_slip_pos + plastic_disloUCLA_nonSchmidCoeff ( k , instance ) * &
2015-12-22 14:52:57 +05:30
dot_product ( Tstar_v , lattice_Sslip_v ( 1 : 6 , 2 * k , index_myFamily + i , ph ) )
2015-01-21 20:44:00 +05:30
tau_slip_neg = tau_slip_neg + plastic_disloUCLA_nonSchmidCoeff ( k , instance ) * &
2014-11-06 00:41:09 +05:30
dot_product ( Tstar_v , lattice_Sslip_v ( 1 : 6 , 2 * k + 1 , index_myFamily + i , ph ) )
2015-01-21 20:44:00 +05:30
nonSchmid_tensor ( 1 : 3 , 1 : 3 , 1 ) = nonSchmid_tensor ( 1 : 3 , 1 : 3 , 1 ) + plastic_disloUCLA_nonSchmidCoeff ( k , instance ) * &
2015-12-22 14:52:57 +05:30
lattice_Sslip ( 1 : 3 , 1 : 3 , 2 * k , index_myFamily + i , ph )
2015-01-21 20:44:00 +05:30
nonSchmid_tensor ( 1 : 3 , 1 : 3 , 2 ) = nonSchmid_tensor ( 1 : 3 , 1 : 3 , 2 ) + plastic_disloUCLA_nonSchmidCoeff ( k , instance ) * &
2014-11-06 00:41:09 +05:30
lattice_Sslip ( 1 : 3 , 1 : 3 , 2 * k + 1 , index_myFamily + i , ph )
enddo nonSchmidSystems
2014-11-07 16:53:34 +05:30
2016-01-15 20:56:24 +05:30
significantPostitiveStress : if ( ( abs ( tau_slip_pos ) - state ( instance ) % threshold_stress_slip ( j , of ) ) > tol_math_check ) then
2015-01-21 20:44:00 +05:30
!* Stress ratio
2016-01-15 20:56:24 +05:30
stressRatio = ( ( abs ( tau_slip_pos ) - state ( instance ) % threshold_stress_slip ( j , of ) ) / &
2015-01-21 20:44:00 +05:30
( plastic_disloUCLA_SolidSolutionStrength ( instance ) + &
plastic_disloUCLA_tau_peierlsPerSlipFamily ( f , instance ) ) )
stressRatio_p = stressRatio ** plastic_disloUCLA_pPerSlipFamily ( f , instance )
stressRatio_pminus1 = stressRatio ** ( plastic_disloUCLA_pPerSlipFamily ( f , instance ) - 1.0_pReal )
2014-11-06 00:41:09 +05:30
!* Shear rates due to slip
2015-01-21 20:44:00 +05:30
vel_slip = 2.0_pReal * plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_kinkheight ( f , instance ) * plastic_disloUCLA_omega ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
* ( tau_slip_pos &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) &
2015-01-16 04:10:17 +05:30
/ ( &
2015-01-21 20:44:00 +05:30
2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) * tau_slip_pos &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
)
2014-11-06 00:41:09 +05:30
gdot_slip_pos ( j ) = DotGamma0 &
2015-01-15 16:26:15 +05:30
* vel_slip &
2014-11-06 00:41:09 +05:30
* sign ( 1.0_pReal , tau_slip_pos )
!* Derivatives of shear rates
dvel_slip = &
2015-01-21 20:44:00 +05:30
2.0_pReal * plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_kinkheight ( f , instance ) * plastic_disloUCLA_omega ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
* ( &
2015-01-21 20:44:00 +05:30
( exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
+ tau_slip_pos &
2015-01-21 20:44:00 +05:30
* ( abs ( exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) & !deltaf(i)
* BoltzmannRatio * plastic_disloUCLA_pPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_qPerSlipFamily ( f , instance ) / &
( plastic_disloUCLA_SolidSolutionStrength ( instance ) + plastic_disloUCLA_tau_peierlsPerSlipFamily ( f , instance ) ) * &
StressRatio_pminus1 * ( 1 - StressRatio_p ) ** ( plastic_disloUCLA_qPerSlipFamily ( f , instance ) - 1.0_pReal ) ) & !deltaf(f)
2015-01-16 04:10:17 +05:30
) &
2015-01-21 20:44:00 +05:30
* ( 2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) * tau_slip_pos &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
) &
- ( tau_slip_pos &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) &
* ( 2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* ( abs ( exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) & !deltaf(i)
* BoltzmannRatio * plastic_disloUCLA_pPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_qPerSlipFamily ( f , instance ) / &
( plastic_disloUCLA_SolidSolutionStrength ( instance ) + plastic_disloUCLA_tau_peierlsPerSlipFamily ( f , instance ) ) * &
StressRatio_pminus1 * ( 1 - StressRatio_p ) ** ( plastic_disloUCLA_qPerSlipFamily ( f , instance ) - 1.0_pReal ) ) & !deltaf(f)
2015-01-16 04:10:17 +05:30
) &
) &
/ ( &
( &
2015-01-21 20:44:00 +05:30
2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) * tau_slip_pos &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
) ** 2.0_pReal &
)
2015-01-15 16:26:15 +05:30
dgdot_dtauslip_pos = DotGamma0 * dvel_slip
2014-11-06 02:23:25 +05:30
endif significantPostitiveStress
2016-01-15 20:56:24 +05:30
significantNegativeStress : if ( ( abs ( tau_slip_neg ) - state ( instance ) % threshold_stress_slip ( j , of ) ) > tol_math_check ) then
2015-01-21 20:44:00 +05:30
!* Stress ratio
2016-01-15 20:56:24 +05:30
stressRatio = ( ( abs ( tau_slip_neg ) - state ( instance ) % threshold_stress_slip ( j , of ) ) / &
2015-01-21 20:44:00 +05:30
( plastic_disloUCLA_SolidSolutionStrength ( instance ) + &
plastic_disloUCLA_tau_peierlsPerSlipFamily ( f , instance ) ) )
stressRatio_p = stressRatio ** plastic_disloUCLA_pPerSlipFamily ( f , instance )
stressRatio_pminus1 = stressRatio ** ( plastic_disloUCLA_pPerSlipFamily ( f , instance ) - 1.0_pReal )
2014-11-06 02:23:25 +05:30
!* Shear rates due to slip
2015-01-21 20:44:00 +05:30
vel_slip = 2.0_pReal * plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_kinkheight ( f , instance ) * plastic_disloUCLA_omega ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
* ( tau_slip_neg &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) &
2015-01-16 04:10:17 +05:30
/ ( &
2015-01-21 20:44:00 +05:30
2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) * tau_slip_neg &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
)
2015-01-15 16:26:15 +05:30
2014-11-06 02:23:25 +05:30
gdot_slip_neg ( j ) = DotGamma0 &
2015-01-15 16:26:15 +05:30
* vel_slip &
2014-11-06 02:23:25 +05:30
* sign ( 1.0_pReal , tau_slip_neg )
!* Derivatives of shear rates
dvel_slip = &
2015-01-21 20:44:00 +05:30
2.0_pReal * plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_kinkheight ( f , instance ) * plastic_disloUCLA_omega ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
* ( &
2015-01-21 20:44:00 +05:30
( exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
+ tau_slip_neg &
2015-01-21 20:44:00 +05:30
* ( abs ( exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) & !deltaf(i)
* BoltzmannRatio * plastic_disloUCLA_pPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_qPerSlipFamily ( f , instance ) / &
( plastic_disloUCLA_SolidSolutionStrength ( instance ) + plastic_disloUCLA_tau_peierlsPerSlipFamily ( f , instance ) ) * &
StressRatio_pminus1 * ( 1 - StressRatio_p ) ** ( plastic_disloUCLA_qPerSlipFamily ( f , instance ) - 1.0_pReal ) ) & !deltaf(f)
2015-01-16 04:10:17 +05:30
) &
2015-01-21 20:44:00 +05:30
* ( 2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) * tau_slip_neg &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
) &
- ( tau_slip_neg &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) &
* ( 2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* ( abs ( exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) & !deltaf(i)
* BoltzmannRatio * plastic_disloUCLA_pPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_qPerSlipFamily ( f , instance ) / &
( plastic_disloUCLA_SolidSolutionStrength ( instance ) + plastic_disloUCLA_tau_peierlsPerSlipFamily ( f , instance ) ) * &
StressRatio_pminus1 * ( 1 - StressRatio_p ) ** ( plastic_disloUCLA_qPerSlipFamily ( f , instance ) - 1.0_pReal ) ) & !deltaf(f)
2015-01-16 04:10:17 +05:30
) &
) &
/ ( &
( &
2015-01-21 20:44:00 +05:30
2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) * tau_slip_neg &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
) ** 2.0_pReal &
)
2015-01-15 16:26:15 +05:30
dgdot_dtauslip_neg = DotGamma0 * dvel_slip
2015-01-16 04:10:17 +05:30
2014-11-06 02:23:25 +05:30
endif significantNegativeStress
2014-11-07 16:53:34 +05:30
!* Plastic velocity gradient for dislocation glide
Lp = Lp + ( gdot_slip_pos ( j ) + gdot_slip_neg ( j ) ) * 0.5_pReal * lattice_Sslip ( 1 : 3 , 1 : 3 , 1 , index_myFamily + i , ph )
!* Calculation of the tangent of Lp
forall ( k = 1_pInt : 3_pInt , l = 1_pInt : 3_pInt , m = 1_pInt : 3_pInt , n = 1_pInt : 3_pInt ) &
2014-11-06 00:41:09 +05:30
dLp_dTstar3333 ( k , l , m , n ) = &
2014-11-07 16:53:34 +05:30
dLp_dTstar3333 ( k , l , m , n ) + ( dgdot_dtauslip_pos * nonSchmid_tensor ( m , n , 1 ) + &
dgdot_dtauslip_neg * nonSchmid_tensor ( m , n , 2 ) ) * 0.5_pReal * &
lattice_Sslip ( k , l , 1 , index_myFamily + i , ph )
2014-11-06 00:41:09 +05:30
enddo slipSystems
enddo slipFamilies
!--------------------------------------------------------------------------------------------------
! correct Lp and dLp_dTstar3333 for twinned fraction
!* Total twin volume fraction
2016-01-15 20:56:24 +05:30
sumf = sum ( state ( instance ) % twinFraction ( 1_pInt : nt , of ) ) ! safe for nt == 0
2014-11-06 00:41:09 +05:30
Lp = Lp * ( 1.0_pReal - sumf )
dLp_dTstar3333 = dLp_dTstar3333 * ( 1.0_pReal - sumf )
!--------------------------------------------------------------------------------------------------
! Mechanical twinning part
gdot_twin = 0.0_pReal
dgdot_dtautwin = 0.0_pReal
j = 0_pInt
twinFamilies : do f = 1_pInt , lattice_maxNtwinFamily
index_myFamily = sum ( lattice_NtwinSystem ( 1 : f - 1_pInt , ph ) ) ! at which index starts my family
2015-01-21 20:44:00 +05:30
twinSystems : do i = 1_pInt , plastic_disloUCLA_Ntwin ( f , instance )
2014-11-06 00:41:09 +05:30
j = j + 1_pInt
!* Resolved shear stress on twin system
tau_twin = dot_product ( Tstar_v , lattice_Stwin_v ( : , index_myFamily + i , ph ) )
!* Stress ratios
if ( tau_twin > tol_math_check ) then
2016-01-15 20:56:24 +05:30
StressRatio_r = ( state ( instance ) % threshold_stress_twin ( j , of ) / tau_twin ) ** plastic_disloUCLA_rPerTwinFamily ( f , instance )
2014-11-06 00:41:09 +05:30
!* Shear rates and their derivatives due to twin
select case ( lattice_structure ( ph ) )
case ( LATTICE_fcc_ID )
s1 = lattice_fcc_twinNucleationSlipPair ( 1 , index_myFamily + i )
s2 = lattice_fcc_twinNucleationSlipPair ( 2 , index_myFamily + i )
2015-01-21 20:44:00 +05:30
if ( tau_twin < plastic_disloUCLA_tau_r ( j , instance ) ) then
2016-01-15 20:56:24 +05:30
Ndot0 = ( abs ( gdot_slip_pos ( s1 ) ) * ( state ( instance ) % rhoEdge ( s2 , of ) + state ( instance ) % rhoEdgeDip ( s2 , of ) ) + & !no non-Schmid behavior for fcc, just take the not influenced positive gdot_slip_pos (= gdot_slip_neg)
abs ( gdot_slip_pos ( s2 ) ) * ( state ( instance ) % rhoEdge ( s1 , of ) + state ( instance ) % rhoEdgeDip ( s1 , of ) ) ) / &
2015-01-21 20:44:00 +05:30
( plastic_disloUCLA_L0 ( instance ) * plastic_disloUCLA_burgersPerSlipSystem ( j , instance ) ) * &
( 1.0_pReal - exp ( - plastic_disloUCLA_VcrossSlip ( instance ) / ( kB * Temperature ) * &
( plastic_disloUCLA_tau_r ( j , instance ) - tau_twin ) ) )
2014-11-06 00:41:09 +05:30
else
Ndot0 = 0.0_pReal
end if
case default
2015-01-21 20:44:00 +05:30
Ndot0 = plastic_disloUCLA_Ndot0PerTwinSystem ( j , instance )
2014-11-06 00:41:09 +05:30
end select
gdot_twin = &
2015-01-21 20:44:00 +05:30
( plastic_disloUCLA_MaxTwinFraction ( instance ) - sumf ) * lattice_shearTwin ( index_myFamily + i , ph ) * &
2016-01-15 20:56:24 +05:30
state ( instance ) % twinVolume ( j , of ) * Ndot0 * exp ( - StressRatio_r )
2015-01-21 20:44:00 +05:30
dgdot_dtautwin = ( ( gdot_twin * plastic_disloUCLA_rPerTwinFamily ( f , instance ) ) / tau_twin ) * StressRatio_r
2014-11-06 00:41:09 +05:30
endif
!* Plastic velocity gradient for mechanical twinning
Lp = Lp + gdot_twin * lattice_Stwin ( 1 : 3 , 1 : 3 , index_myFamily + i , ph )
!* Calculation of the tangent of Lp
forall ( k = 1_pInt : 3_pInt , l = 1_pInt : 3_pInt , m = 1_pInt : 3_pInt , n = 1_pInt : 3_pInt ) &
dLp_dTstar3333 ( k , l , m , n ) = &
dLp_dTstar3333 ( k , l , m , n ) + dgdot_dtautwin * &
lattice_Stwin ( k , l , index_myFamily + i , ph ) * &
lattice_Stwin ( m , n , index_myFamily + i , ph )
enddo twinSystems
enddo twinFamilies
2014-11-07 16:53:34 +05:30
dLp_dTstar99 = math_Plain3333to99 ( dLp_dTstar3333 )
2014-11-06 00:41:09 +05:30
2015-01-21 20:44:00 +05:30
end subroutine plastic_disloUCLA_LpAndItsTangent
2014-11-06 00:41:09 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief calculates the rate of change of microstructure
!--------------------------------------------------------------------------------------------------
2015-01-29 19:26:09 +05:30
subroutine plastic_disloUCLA_dotState ( Tstar_v , Temperature , ipc , ip , el )
2014-11-06 00:41:09 +05:30
use prec , only : &
tol_math_check
use math , only : &
pi
use material , only : &
material_phase , &
phase_plasticityInstance , &
plasticState , &
2016-01-15 05:49:44 +05:30
phaseAt , phasememberAt
2014-11-06 00:41:09 +05:30
use lattice , only : &
lattice_Sslip_v , &
lattice_Stwin_v , &
lattice_maxNslipFamily , &
lattice_maxNtwinFamily , &
lattice_NslipSystem , &
lattice_NtwinSystem , &
lattice_NnonSchmid , &
lattice_sheartwin , &
lattice_mu , &
lattice_structure , &
lattice_fcc_twinNucleationSlipPair , &
2014-11-06 02:23:25 +05:30
LATTICE_fcc_ID
2014-11-06 00:41:09 +05:30
implicit none
real ( pReal ) , dimension ( 6 ) , intent ( in ) :: &
Tstar_v !< 2nd Piola Kirchhoff stress tensor in Mandel notation
real ( pReal ) , intent ( in ) :: &
temperature !< temperature at integration point
integer ( pInt ) , intent ( in ) :: &
ipc , & !< component-ID of integration point
ip , & !< integration point
el !< element
integer ( pInt ) :: instance , ns , nt , f , i , j , k , index_myFamily , s1 , s2 , &
ph , &
of
real ( pReal ) :: &
sumf , &
stressRatio_p , &
BoltzmannRatio , &
DotGamma0 , &
stressRatio , &
EdgeDipMinDistance , &
AtomicVolume , &
VacancyDiffusion , &
StressRatio_r , &
Ndot0 , &
tau_slip_pos , &
2014-11-06 02:23:25 +05:30
tau_slip_neg , &
2014-11-06 00:41:09 +05:30
DotRhoMultiplication , &
EdgeDipDistance , &
DotRhoEdgeDipAnnihilation , &
DotRhoEdgeEdgeAnnihilation , &
ClimbVelocity , &
DotRhoEdgeDipClimb , &
DotRhoDipFormation , &
tau_twin , &
2014-11-07 16:53:34 +05:30
vel_slip , &
gdot_slip
2015-01-21 20:44:00 +05:30
real ( pReal ) , dimension ( plastic_disloUCLA_totalNslip ( phase_plasticityInstance ( material_phase ( ipc , ip , el ) ) ) ) :: &
2014-11-06 02:23:25 +05:30
gdot_slip_pos , gdot_slip_neg
2014-11-06 00:41:09 +05:30
!* Shortened notation
2016-01-15 05:49:44 +05:30
of = phasememberAt ( ipc , ip , el )
ph = phaseAt ( ipc , ip , el )
2014-11-06 00:41:09 +05:30
instance = phase_plasticityInstance ( ph )
2015-01-21 20:44:00 +05:30
ns = plastic_disloUCLA_totalNslip ( instance )
nt = plastic_disloUCLA_totalNtwin ( instance )
2014-11-06 00:41:09 +05:30
!* Total twin volume fraction
2016-01-15 20:56:24 +05:30
sumf = sum ( state ( instance ) % twinFraction ( 1_pInt : nt , of ) ) ! safe for nt == 0
2014-11-06 00:41:09 +05:30
plasticState ( ph ) % dotState ( : , of ) = 0.0_pReal
!* Dislocation density evolution
gdot_slip_pos = 0.0_pReal
2014-12-11 20:34:16 +05:30
gdot_slip_neg = 0.0_pReal
2014-11-06 00:41:09 +05:30
j = 0_pInt
slipFamilies : do f = 1_pInt , lattice_maxNslipFamily
index_myFamily = sum ( lattice_NslipSystem ( 1 : f - 1_pInt , ph ) ) ! at which index starts my family
2015-01-21 20:44:00 +05:30
slipSystems : do i = 1_pInt , plastic_disloUCLA_Nslip ( f , instance )
2014-11-06 00:41:09 +05:30
j = j + 1_pInt
2014-11-07 16:53:34 +05:30
!* Boltzmann ratio
2015-01-21 20:44:00 +05:30
BoltzmannRatio = plastic_disloUCLA_QedgePerSlipSystem ( j , instance ) / ( kB * Temperature )
2014-11-07 16:53:34 +05:30
!* Initial shear rates
DotGamma0 = &
2016-01-15 20:56:24 +05:30
state ( instance ) % rhoEdge ( j , of ) * plastic_disloUCLA_burgersPerSlipSystem ( j , instance ) * &
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_v0PerSlipSystem ( j , instance )
2014-11-07 16:53:34 +05:30
!* Resolved shear stress on slip system
2014-11-06 00:41:09 +05:30
tau_slip_pos = dot_product ( Tstar_v , lattice_Sslip_v ( 1 : 6 , 1 , index_myFamily + i , ph ) )
tau_slip_neg = tau_slip_pos
nonSchmidSystems : do k = 1 , lattice_NnonSchmid ( ph )
2015-01-21 20:44:00 +05:30
tau_slip_pos = tau_slip_pos + plastic_disloUCLA_nonSchmidCoeff ( k , instance ) * &
2014-11-07 16:53:34 +05:30
dot_product ( Tstar_v , lattice_Sslip_v ( 1 : 6 , 2 * k , index_myFamily + i , ph ) )
2015-01-21 20:44:00 +05:30
tau_slip_neg = tau_slip_neg + plastic_disloUCLA_nonSchmidCoeff ( k , instance ) * &
2014-11-06 00:41:09 +05:30
dot_product ( Tstar_v , lattice_Sslip_v ( 1 : 6 , 2 * k + 1 , index_myFamily + i , ph ) )
enddo nonSchmidSystems
2016-01-15 20:56:24 +05:30
significantPositiveStress : if ( ( abs ( tau_slip_pos ) - state ( instance ) % threshold_stress_slip ( j , of ) ) > tol_math_check ) then
2014-11-06 00:41:09 +05:30
!* Stress ratios
2016-01-15 20:56:24 +05:30
stressRatio = ( ( abs ( tau_slip_pos ) - state ( instance ) % threshold_stress_slip ( j , of ) ) / &
2015-01-21 20:44:00 +05:30
( plastic_disloUCLA_SolidSolutionStrength ( instance ) + &
plastic_disloUCLA_tau_peierlsPerSlipFamily ( f , instance ) ) )
stressRatio_p = stressRatio ** plastic_disloUCLA_pPerSlipFamily ( f , instance )
2014-11-06 00:41:09 +05:30
!* Shear rates due to slip
2015-01-21 20:44:00 +05:30
vel_slip = 2.0_pReal * plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_kinkheight ( f , instance ) * plastic_disloUCLA_omega ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
* ( tau_slip_pos &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) &
2015-01-16 04:10:17 +05:30
/ ( &
2015-01-21 20:44:00 +05:30
2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) * tau_slip_pos &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
)
2014-11-06 00:41:09 +05:30
gdot_slip_pos ( j ) = DotGamma0 &
2015-01-15 16:26:15 +05:30
* vel_slip &
2014-11-06 00:41:09 +05:30
* sign ( 1.0_pReal , tau_slip_pos )
2014-11-06 02:23:25 +05:30
endif significantPositiveStress
2016-01-15 20:56:24 +05:30
significantNegativeStress : if ( ( abs ( tau_slip_neg ) - state ( instance ) % threshold_stress_slip ( j , of ) ) > tol_math_check ) then
2014-11-06 02:23:25 +05:30
!* Stress ratios
2016-01-15 20:56:24 +05:30
stressRatio = ( ( abs ( tau_slip_neg ) - state ( instance ) % threshold_stress_slip ( j , of ) ) / &
2015-01-21 20:44:00 +05:30
( plastic_disloUCLA_SolidSolutionStrength ( instance ) + &
plastic_disloUCLA_tau_peierlsPerSlipFamily ( f , instance ) ) )
stressRatio_p = stressRatio ** plastic_disloUCLA_pPerSlipFamily ( f , instance )
2015-01-16 04:10:17 +05:30
2015-01-21 20:44:00 +05:30
vel_slip = 2.0_pReal * plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_kinkheight ( f , instance ) * plastic_disloUCLA_omega ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
* ( tau_slip_neg &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) &
2015-01-16 04:10:17 +05:30
/ ( &
2015-01-21 20:44:00 +05:30
2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) * tau_slip_neg &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
)
2014-11-06 02:23:25 +05:30
gdot_slip_neg ( j ) = DotGamma0 &
2015-01-15 16:26:15 +05:30
* vel_slip &
2014-11-06 02:23:25 +05:30
* sign ( 1.0_pReal , tau_slip_neg )
endif significantNegativeStress
2014-11-07 16:53:34 +05:30
gdot_slip = ( gdot_slip_pos ( j ) + gdot_slip_neg ( j ) ) * 0.5_pReal
2014-11-06 00:41:09 +05:30
!* Multiplication
2014-11-07 16:53:34 +05:30
DotRhoMultiplication = abs ( gdot_slip ) / &
2015-01-21 20:44:00 +05:30
( plastic_disloUCLA_burgersPerSlipSystem ( j , instance ) * &
2016-01-15 20:56:24 +05:30
state ( instance ) % mfp_slip ( j , of ) )
2014-11-06 00:41:09 +05:30
!* Dipole formation
EdgeDipMinDistance = &
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_CEdgeDipMinDistance ( instance ) * plastic_disloUCLA_burgersPerSlipSystem ( j , instance )
2015-04-11 17:17:33 +05:30
if ( abs ( tau_slip_pos ) < = tiny ( 0.0_pReal ) ) then
2014-11-06 00:41:09 +05:30
DotRhoDipFormation = 0.0_pReal
else
EdgeDipDistance = &
2015-01-21 20:44:00 +05:30
( 3.0_pReal * lattice_mu ( ph ) * plastic_disloUCLA_burgersPerSlipSystem ( j , instance ) ) / &
2014-11-06 00:41:09 +05:30
( 1 6.0_pReal * pi * abs ( tau_slip_pos ) )
2016-01-15 20:56:24 +05:30
if ( EdgeDipDistance > state ( instance ) % mfp_slip ( j , of ) ) EdgeDipDistance = state ( instance ) % mfp_slip ( j , of )
2014-11-06 00:41:09 +05:30
if ( EdgeDipDistance < EdgeDipMinDistance ) EdgeDipDistance = EdgeDipMinDistance
DotRhoDipFormation = &
2015-01-21 20:44:00 +05:30
( ( 2.0_pReal * EdgeDipDistance ) / plastic_disloUCLA_burgersPerSlipSystem ( j , instance ) ) * &
2016-01-15 20:56:24 +05:30
state ( instance ) % rhoEdge ( j , of ) * abs ( gdot_slip ) * plastic_disloUCLA_dipoleFormationFactor ( instance )
2014-11-06 00:41:09 +05:30
endif
!* Spontaneous annihilation of 2 single edge dislocations
DotRhoEdgeEdgeAnnihilation = &
2015-01-21 20:44:00 +05:30
( ( 2.0_pReal * EdgeDipMinDistance ) / plastic_disloUCLA_burgersPerSlipSystem ( j , instance ) ) * &
2016-01-15 20:56:24 +05:30
state ( instance ) % rhoEdge ( j , of ) * abs ( gdot_slip )
2014-11-06 00:41:09 +05:30
!* Spontaneous annihilation of a single edge dislocation with a dipole constituent
DotRhoEdgeDipAnnihilation = &
2015-01-21 20:44:00 +05:30
( ( 2.0_pReal * EdgeDipMinDistance ) / plastic_disloUCLA_burgersPerSlipSystem ( j , instance ) ) * &
2016-01-15 20:56:24 +05:30
state ( instance ) % rhoEdgeDip ( j , of ) * abs ( gdot_slip )
2014-11-06 00:41:09 +05:30
!* Dislocation dipole climb
AtomicVolume = &
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_CAtomicVolume ( instance ) * plastic_disloUCLA_burgersPerSlipSystem ( j , instance ) ** ( 3.0_pReal )
2014-11-06 00:41:09 +05:30
VacancyDiffusion = &
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_D0 ( instance ) * exp ( - plastic_disloUCLA_Qsd ( instance ) / ( kB * Temperature ) )
2015-04-11 17:17:33 +05:30
if ( abs ( tau_slip_pos ) < = tiny ( 0.0_pReal ) ) then
2014-11-06 00:41:09 +05:30
DotRhoEdgeDipClimb = 0.0_pReal
else
ClimbVelocity = &
( ( 3.0_pReal * lattice_mu ( ph ) * VacancyDiffusion * AtomicVolume ) / ( 2.0_pReal * pi * kB * Temperature ) ) * &
( 1 / ( EdgeDipDistance + EdgeDipMinDistance ) )
DotRhoEdgeDipClimb = &
2016-01-15 20:56:24 +05:30
( 4.0_pReal * ClimbVelocity * state ( instance ) % rhoEdgeDip ( j , of ) ) / ( EdgeDipDistance - EdgeDipMinDistance )
2014-11-06 00:41:09 +05:30
endif
!* Edge dislocation density rate of change
2016-01-15 20:56:24 +05:30
dotState ( instance ) % rhoEdge ( j , of ) = &
2014-11-06 00:41:09 +05:30
DotRhoMultiplication - DotRhoDipFormation - DotRhoEdgeEdgeAnnihilation
!* Edge dislocation dipole density rate of change
2016-01-15 20:56:24 +05:30
dotState ( instance ) % rhoEdgeDip ( j , of ) = &
2014-11-06 00:41:09 +05:30
DotRhoDipFormation - DotRhoEdgeDipAnnihilation - DotRhoEdgeDipClimb
!* Dotstate for accumulated shear due to slip
2016-01-15 20:56:24 +05:30
dotState ( instance ) % accshear_slip ( j , of ) = gdot_slip
2014-11-06 00:41:09 +05:30
enddo slipSystems
enddo slipFamilies
!* Twin volume fraction evolution
j = 0_pInt
twinFamilies : do f = 1_pInt , lattice_maxNtwinFamily
index_myFamily = sum ( lattice_NtwinSystem ( 1 : f - 1_pInt , ph ) ) ! at which index starts my family
2015-01-21 20:44:00 +05:30
twinSystems : do i = 1_pInt , plastic_disloUCLA_Ntwin ( f , instance )
2014-11-06 00:41:09 +05:30
j = j + 1_pInt
!* Resolved shear stress on twin system
tau_twin = dot_product ( Tstar_v , lattice_Stwin_v ( : , index_myFamily + i , ph ) )
!* Stress ratios
if ( tau_twin > tol_math_check ) then
2016-01-15 20:56:24 +05:30
StressRatio_r = ( state ( instance ) % threshold_stress_twin ( j , of ) / tau_twin ) ** plastic_disloUCLA_rPerTwinFamily ( f , instance )
2014-11-06 00:41:09 +05:30
!* Shear rates and their derivatives due to twin
select case ( lattice_structure ( ph ) )
case ( LATTICE_fcc_ID )
s1 = lattice_fcc_twinNucleationSlipPair ( 1 , index_myFamily + i )
s2 = lattice_fcc_twinNucleationSlipPair ( 2 , index_myFamily + i )
2015-01-21 20:44:00 +05:30
if ( tau_twin < plastic_disloUCLA_tau_r ( j , instance ) ) then
2016-01-15 20:56:24 +05:30
Ndot0 = ( abs ( gdot_slip_pos ( s1 ) ) * ( state ( instance ) % rhoEdge ( s2 , of ) + state ( instance ) % rhoEdgeDip ( s2 , of ) ) + & !no non-Schmid behavior for fcc, just take the not influenced positive slip (gdot_slip_pos = gdot_slip_neg)
abs ( gdot_slip_pos ( s2 ) ) * ( state ( instance ) % rhoEdge ( s1 , of ) + state ( instance ) % rhoEdgeDip ( s1 , of ) ) ) / &
2015-01-21 20:44:00 +05:30
( plastic_disloUCLA_L0 ( instance ) * plastic_disloUCLA_burgersPerSlipSystem ( j , instance ) ) * &
( 1.0_pReal - exp ( - plastic_disloUCLA_VcrossSlip ( instance ) / ( kB * Temperature ) * &
( plastic_disloUCLA_tau_r ( j , instance ) - tau_twin ) ) )
2014-11-06 00:41:09 +05:30
else
Ndot0 = 0.0_pReal
end if
case default
2015-01-21 20:44:00 +05:30
Ndot0 = plastic_disloUCLA_Ndot0PerTwinSystem ( j , instance )
2014-11-06 00:41:09 +05:30
end select
2014-11-07 16:53:34 +05:30
2016-01-15 20:56:24 +05:30
dotState ( instance ) % twinFraction ( j , of ) = &
2015-01-21 20:44:00 +05:30
( plastic_disloUCLA_MaxTwinFraction ( instance ) - sumf ) * &
2016-01-15 20:56:24 +05:30
state ( instance ) % twinVolume ( j , of ) * Ndot0 * exp ( - StressRatio_r )
2014-11-06 00:41:09 +05:30
!* Dotstate for accumulated shear due to twin
2016-01-15 20:56:24 +05:30
dotState ( instance ) % accshear_twin ( j , of ) = dotState ( ph ) % twinFraction ( j , of ) * &
2014-11-06 00:41:09 +05:30
lattice_sheartwin ( index_myfamily + i , ph )
endif
enddo twinSystems
enddo twinFamilies
2015-01-21 20:44:00 +05:30
end subroutine plastic_disloUCLA_dotState
2014-11-06 00:41:09 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief return array of constitutive results
!--------------------------------------------------------------------------------------------------
2015-01-21 20:44:00 +05:30
function plastic_disloUCLA_postResults ( Tstar_v , Temperature , ipc , ip , el )
2014-11-06 00:41:09 +05:30
use prec , only : &
tol_math_check
use math , only : &
pi
use material , only : &
material_phase , &
phase_plasticityInstance , &
2016-01-15 20:56:24 +05:30
!plasticState, &
2016-01-15 05:49:44 +05:30
phaseAt , phasememberAt
2014-11-06 00:41:09 +05:30
use lattice , only : &
lattice_Sslip_v , &
lattice_Stwin_v , &
lattice_maxNslipFamily , &
lattice_maxNtwinFamily , &
lattice_NslipSystem , &
lattice_NtwinSystem , &
lattice_NnonSchmid , &
lattice_shearTwin , &
lattice_mu , &
lattice_structure , &
lattice_fcc_twinNucleationSlipPair , &
LATTICE_fcc_ID
implicit none
real ( pReal ) , dimension ( 6 ) , intent ( in ) :: &
Tstar_v !< 2nd Piola Kirchhoff stress tensor in Mandel notation
real ( pReal ) , intent ( in ) :: &
temperature !< temperature at integration point
integer ( pInt ) , intent ( in ) :: &
ipc , & !< component-ID of integration point
ip , & !< integration point
el !< element
2015-01-21 20:44:00 +05:30
real ( pReal ) , dimension ( plastic_disloUCLA_sizePostResults ( phase_plasticityInstance ( material_phase ( ipc , ip , el ) ) ) ) :: &
plastic_disloUCLA_postResults
2014-11-06 00:41:09 +05:30
integer ( pInt ) :: &
instance , &
ns , nt , &
f , o , i , c , j , k , index_myFamily , &
s1 , s2 , &
ph , &
of
2014-11-06 02:23:25 +05:30
real ( pReal ) :: sumf , tau_twin , StressRatio_p , StressRatio_pminus1 , &
BoltzmannRatio , DotGamma0 , StressRatio_r , Ndot0 , stressRatio
2014-11-06 01:09:23 +05:30
real ( pReal ) :: dvel_slip , vel_slip
2015-01-21 20:44:00 +05:30
real ( pReal ) , dimension ( plastic_disloUCLA_totalNslip ( phase_plasticityInstance ( material_phase ( ipc , ip , el ) ) ) ) :: &
2014-11-06 02:23:25 +05:30
gdot_slip_pos , dgdot_dtauslip_pos , tau_slip_pos , gdot_slip_neg , dgdot_dtauslip_neg , tau_slip_neg
2014-11-06 00:41:09 +05:30
!* Shortened notation
2016-01-15 05:49:44 +05:30
of = phasememberAt ( ipc , ip , el )
ph = phaseAt ( ipc , ip , el )
2014-11-06 00:41:09 +05:30
instance = phase_plasticityInstance ( ph )
2015-01-21 20:44:00 +05:30
ns = plastic_disloUCLA_totalNslip ( instance )
nt = plastic_disloUCLA_totalNtwin ( instance )
2014-11-06 00:41:09 +05:30
!* Total twin volume fraction
2016-01-15 20:56:24 +05:30
sumf = sum ( state ( ph ) % twinFraction ( 1_pInt : nt , of ) ) ! safe for nt == 0
2014-11-06 00:41:09 +05:30
!* Required output
c = 0_pInt
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_postResults = 0.0_pReal
2014-11-06 00:41:09 +05:30
2015-01-21 20:44:00 +05:30
do o = 1_pInt , plastic_disloUCLA_Noutput ( instance )
select case ( plastic_disloUCLA_outputID ( o , instance ) )
2014-11-06 00:41:09 +05:30
case ( edge_density_ID )
2016-01-15 20:56:24 +05:30
plastic_disloUCLA_postResults ( c + 1_pInt : c + ns ) = state ( instance ) % rhoEdge ( 1_pInt : ns , of )
2014-11-06 00:41:09 +05:30
c = c + ns
case ( dipole_density_ID )
2016-01-15 20:56:24 +05:30
plastic_disloUCLA_postResults ( c + 1_pInt : c + ns ) = state ( instance ) % rhoEdgeDip ( 1_pInt : ns , of )
2014-11-06 00:41:09 +05:30
c = c + ns
2014-11-06 02:23:25 +05:30
case ( shear_rate_slip_ID , shear_rate_twin_ID , stress_exponent_ID )
2014-11-06 00:41:09 +05:30
gdot_slip_pos = 0.0_pReal
2014-11-06 02:23:25 +05:30
gdot_slip_neg = 0.0_pReal
dgdot_dtauslip_pos = 0.0_pReal
dgdot_dtauslip_neg = 0.0_pReal
2014-11-06 00:41:09 +05:30
j = 0_pInt
2014-11-06 02:23:25 +05:30
slipFamilies : do f = 1_pInt , lattice_maxNslipFamily
2014-11-06 01:09:23 +05:30
index_myFamily = sum ( lattice_NslipSystem ( 1 : f - 1_pInt , ph ) ) ! at which index starts my family
2015-01-21 20:44:00 +05:30
slipSystems : do i = 1_pInt , plastic_disloUCLA_Nslip ( f , instance )
2014-11-06 01:09:23 +05:30
j = j + 1_pInt
2014-11-07 16:53:34 +05:30
!* Boltzmann ratio
2015-01-21 20:44:00 +05:30
BoltzmannRatio = plastic_disloUCLA_QedgePerSlipSystem ( j , instance ) / ( kB * Temperature )
2014-11-07 16:53:34 +05:30
!* Initial shear rates
DotGamma0 = &
2016-01-15 20:56:24 +05:30
state ( instance ) % rhoEdge ( j , of ) * plastic_disloUCLA_burgersPerSlipSystem ( j , instance ) * &
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_v0PerSlipSystem ( j , instance )
2014-11-06 01:09:23 +05:30
!* Resolved shear stress on slip system
2014-11-06 02:23:25 +05:30
tau_slip_pos ( j ) = dot_product ( Tstar_v , lattice_Sslip_v ( : , 1 , index_myFamily + i , ph ) )
tau_slip_neg ( j ) = tau_slip_pos ( j )
nonSchmidSystems : do k = 1 , lattice_NnonSchmid ( ph )
2015-01-21 20:44:00 +05:30
tau_slip_pos = tau_slip_pos + plastic_disloUCLA_nonSchmidCoeff ( k , instance ) * &
2014-11-06 02:23:25 +05:30
dot_product ( Tstar_v , lattice_Sslip_v ( 1 : 6 , 2 * k , index_myFamily + i , ph ) )
2015-01-21 20:44:00 +05:30
tau_slip_neg = tau_slip_neg + plastic_disloUCLA_nonSchmidCoeff ( k , instance ) * &
2014-11-06 02:23:25 +05:30
dot_product ( Tstar_v , lattice_Sslip_v ( 1 : 6 , 2 * k + 1 , index_myFamily + i , ph ) )
enddo nonSchmidSystems
2014-11-07 16:53:34 +05:30
2016-01-15 20:56:24 +05:30
significantPositiveTau : if ( ( abs ( tau_slip_pos ( j ) ) - state ( instance ) % threshold_stress_slip ( j , of ) ) > tol_math_check ) then
2015-01-21 20:44:00 +05:30
!* Stress ratio
2016-01-15 20:56:24 +05:30
stressRatio = ( ( abs ( tau_slip_pos ( j ) ) - state ( instance ) % threshold_stress_slip ( j , of ) ) / &
2015-01-21 20:44:00 +05:30
( plastic_disloUCLA_SolidSolutionStrength ( instance ) + &
plastic_disloUCLA_tau_peierlsPerSlipFamily ( f , instance ) ) )
stressRatio_p = stressRatio ** plastic_disloUCLA_pPerSlipFamily ( f , instance )
stressRatio_pminus1 = stressRatio ** ( plastic_disloUCLA_pPerSlipFamily ( f , instance ) - 1.0_pReal )
!* Shear rates due to slip
vel_slip = 2.0_pReal * plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_kinkheight ( f , instance ) * plastic_disloUCLA_omega ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
* ( tau_slip_pos ( j ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) &
2015-01-16 04:10:17 +05:30
/ ( &
2015-01-21 20:44:00 +05:30
2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) * tau_slip_pos ( j ) &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
)
2014-11-06 00:41:09 +05:30
2014-11-06 01:09:23 +05:30
gdot_slip_pos ( j ) = DotGamma0 &
2015-01-15 16:26:15 +05:30
* vel_slip &
2014-11-06 02:23:25 +05:30
* sign ( 1.0_pReal , tau_slip_pos ( j ) )
!* Derivatives of shear rates
2015-01-21 20:44:00 +05:30
2014-11-06 02:23:25 +05:30
dvel_slip = &
2015-01-21 20:44:00 +05:30
2.0_pReal * plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_kinkheight ( f , instance ) * plastic_disloUCLA_omega ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
* ( &
2015-01-21 20:44:00 +05:30
( exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
+ tau_slip_pos ( j ) &
2015-01-21 20:44:00 +05:30
* ( abs ( exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) & !deltaf(i)
* BoltzmannRatio * plastic_disloUCLA_pPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_qPerSlipFamily ( f , instance ) / &
( plastic_disloUCLA_SolidSolutionStrength ( instance ) + plastic_disloUCLA_tau_peierlsPerSlipFamily ( f , instance ) ) * &
StressRatio_pminus1 * ( 1 - StressRatio_p ) ** ( plastic_disloUCLA_qPerSlipFamily ( f , instance ) - 1.0_pReal ) ) & !deltaf(f)
2015-01-16 04:10:17 +05:30
) &
2015-01-21 20:44:00 +05:30
* ( 2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) * tau_slip_pos ( j ) &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
) &
- ( tau_slip_pos ( j ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) &
* ( 2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* ( abs ( exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) & !deltaf(i)
* BoltzmannRatio * plastic_disloUCLA_pPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_qPerSlipFamily ( f , instance ) / &
( plastic_disloUCLA_SolidSolutionStrength ( instance ) + plastic_disloUCLA_tau_peierlsPerSlipFamily ( f , instance ) ) * &
StressRatio_pminus1 * ( 1 - StressRatio_p ) ** ( plastic_disloUCLA_qPerSlipFamily ( f , instance ) - 1.0_pReal ) ) & !deltaf(f)
2015-01-16 04:10:17 +05:30
) &
) &
/ ( &
( &
2015-01-21 20:44:00 +05:30
2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) * tau_slip_pos ( j ) &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
) ** 2.0_pReal &
)
2015-01-15 16:26:15 +05:30
dgdot_dtauslip_pos ( j ) = DotGamma0 * dvel_slip
2016-01-15 20:56:24 +05:30
endif significantPositiveTau
significantNegativeTau : if ( ( abs ( tau_slip_neg ( j ) ) - state ( instance ) % threshold_stress_slip ( j , of ) ) > tol_math_check ) then
2014-11-06 02:23:25 +05:30
!* Stress ratios
2016-01-15 20:56:24 +05:30
stressRatio = ( ( abs ( tau_slip_neg ( j ) ) - state ( instance ) % threshold_stress_slip ( j , of ) ) / &
2015-01-21 20:44:00 +05:30
( plastic_disloUCLA_SolidSolutionStrength ( instance ) + &
plastic_disloUCLA_tau_peierlsPerSlipFamily ( f , instance ) ) )
stressRatio_p = stressRatio ** plastic_disloUCLA_pPerSlipFamily ( f , instance )
stressRatio_pminus1 = stressRatio ** ( plastic_disloUCLA_pPerSlipFamily ( f , instance ) - 1.0_pReal )
2014-11-06 02:23:25 +05:30
!* Shear rates due to slip
2015-01-21 20:44:00 +05:30
vel_slip = 2.0_pReal * plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_kinkheight ( f , instance ) * plastic_disloUCLA_omega ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
* ( tau_slip_neg ( j ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) &
2015-01-16 04:10:17 +05:30
/ ( &
2015-01-21 20:44:00 +05:30
2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) * tau_slip_neg ( j ) &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
)
2015-01-15 16:26:15 +05:30
2014-11-06 02:23:25 +05:30
gdot_slip_neg ( j ) = DotGamma0 &
2015-01-15 16:26:15 +05:30
* vel_slip &
2014-11-06 02:23:25 +05:30
* sign ( 1.0_pReal , tau_slip_neg ( j ) )
2014-11-06 01:09:23 +05:30
!* Derivatives of shear rates
dvel_slip = &
2015-01-21 20:44:00 +05:30
2.0_pReal * plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_kinkheight ( f , instance ) * plastic_disloUCLA_omega ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
* ( &
2015-01-21 20:44:00 +05:30
( exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
+ tau_slip_neg ( j ) &
2015-01-21 20:44:00 +05:30
* ( abs ( exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) & !deltaf(i)
* BoltzmannRatio * plastic_disloUCLA_pPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_qPerSlipFamily ( f , instance ) / &
( plastic_disloUCLA_SolidSolutionStrength ( instance ) + plastic_disloUCLA_tau_peierlsPerSlipFamily ( f , instance ) ) * &
StressRatio_pminus1 * ( 1 - StressRatio_p ) ** ( plastic_disloUCLA_qPerSlipFamily ( f , instance ) - 1.0_pReal ) ) & !deltaf(f)
2015-01-16 04:10:17 +05:30
) &
2015-01-21 20:44:00 +05:30
* ( 2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) * tau_slip_neg ( j ) &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
) &
- ( tau_slip_neg ( j ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) &
* ( 2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* ( abs ( exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) ) & !deltaf(i)
* BoltzmannRatio * plastic_disloUCLA_pPerSlipFamily ( f , instance ) &
* plastic_disloUCLA_qPerSlipFamily ( f , instance ) / &
( plastic_disloUCLA_SolidSolutionStrength ( instance ) + plastic_disloUCLA_tau_peierlsPerSlipFamily ( f , instance ) ) * &
StressRatio_pminus1 * ( 1 - StressRatio_p ) ** ( plastic_disloUCLA_qPerSlipFamily ( f , instance ) - 1.0_pReal ) ) & !deltaf(f)
2015-01-16 04:10:17 +05:30
) &
) &
/ ( &
( &
2015-01-21 20:44:00 +05:30
2.0_pReal * ( plastic_disloUCLA_burgersPerSlipFamily ( f , instance ) ** 2.0_pReal ) * tau_slip_neg ( j ) &
+ plastic_disloUCLA_omega ( f , instance ) * plastic_disloUCLA_friction ( f , instance ) &
2016-01-15 20:56:24 +05:30
* ( ( state ( instance ) % mfp_slip ( j , of ) - plastic_disloUCLA_kinkwidth ( f , instance ) ) ** 2.0_pReal ) &
2015-01-21 20:44:00 +05:30
* exp ( - BoltzmannRatio * ( 1 - StressRatio_p ) ** plastic_disloUCLA_qPerSlipFamily ( f , instance ) ) &
2015-01-16 04:10:17 +05:30
) ** 2.0_pReal &
)
2015-01-15 16:26:15 +05:30
dgdot_dtauslip_neg ( j ) = DotGamma0 * dvel_slip
2016-01-15 20:56:24 +05:30
endif significantNegativeTau
2014-11-06 02:23:25 +05:30
enddo slipSystems
enddo slipFamilies
2015-01-21 20:44:00 +05:30
if ( plastic_disloUCLA_outputID ( o , instance ) == shear_rate_slip_ID ) then
plastic_disloUCLA_postResults ( c + 1 : c + ns ) = ( gdot_slip_pos + gdot_slip_neg ) * 0.5_pReal
2014-11-06 02:23:25 +05:30
c = c + ns
2015-01-21 20:44:00 +05:30
elseif ( plastic_disloUCLA_outputID ( o , instance ) == shear_rate_twin_ID ) then
2014-11-06 02:23:25 +05:30
if ( nt > 0_pInt ) then
j = 0_pInt
twinFamilies1 : do f = 1_pInt , lattice_maxNtwinFamily
index_myFamily = sum ( lattice_NtwinSystem ( 1 : f - 1_pInt , ph ) ) ! at which index starts my family
2015-01-21 20:44:00 +05:30
twinSystems1 : do i = 1 , plastic_disloUCLA_Ntwin ( f , instance )
2014-11-06 02:23:25 +05:30
j = j + 1_pInt
!* Resolved shear stress on twin system
tau_twin = dot_product ( Tstar_v , lattice_Stwin_v ( : , index_myFamily + i , ph ) )
!* Stress ratios
2016-01-15 20:56:24 +05:30
StressRatio_r = ( state ( instance ) % threshold_stress_twin ( j , of ) / &
2015-01-21 20:44:00 +05:30
tau_twin ) ** plastic_disloUCLA_rPerTwinFamily ( f , instance )
2014-11-06 02:23:25 +05:30
!* Shear rates due to twin
if ( tau_twin > 0.0_pReal ) then
select case ( lattice_structure ( ph ) )
case ( LATTICE_fcc_ID )
s1 = lattice_fcc_twinNucleationSlipPair ( 1 , index_myFamily + i )
s2 = lattice_fcc_twinNucleationSlipPair ( 2 , index_myFamily + i )
2015-01-21 20:44:00 +05:30
if ( tau_twin < plastic_disloUCLA_tau_r ( j , instance ) ) then
2016-01-15 20:56:24 +05:30
Ndot0 = ( abs ( gdot_slip_pos ( s1 ) ) * ( state ( instance ) % rhoEdge ( s2 , of ) + state ( instance ) % rhoEdgeDip ( s2 , of ) ) + & !no non-Schmid behavior for fcc, just take the not influenced positive slip (gdot_slip_pos = gdot_slip_neg)
abs ( gdot_slip_pos ( s2 ) ) * ( state ( instance ) % rhoEdge ( s1 , of ) + state ( instance ) % rhoEdgeDip ( s1 , of ) ) ) / &
2015-01-21 20:44:00 +05:30
( plastic_disloUCLA_L0 ( instance ) * &
plastic_disloUCLA_burgersPerSlipSystem ( j , instance ) ) * &
( 1.0_pReal - exp ( - plastic_disloUCLA_VcrossSlip ( instance ) / ( kB * Temperature ) * &
( plastic_disloUCLA_tau_r ( j , instance ) - tau_twin ) ) )
2014-11-06 02:23:25 +05:30
else
Ndot0 = 0.0_pReal
end if
case default
2015-01-21 20:44:00 +05:30
Ndot0 = plastic_disloUCLA_Ndot0PerTwinSystem ( j , instance )
2014-11-06 02:23:25 +05:30
end select
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_postResults ( c + j ) = &
( plastic_disloUCLA_MaxTwinFraction ( instance ) - sumf ) * lattice_shearTwin ( index_myFamily + i , ph ) * &
2016-01-15 20:56:24 +05:30
state ( instance ) % twinVolume ( j , of ) * Ndot0 * exp ( - StressRatio_r )
2014-11-06 02:23:25 +05:30
endif
enddo twinSystems1
enddo twinFamilies1
endif
c = c + nt
2015-01-21 20:44:00 +05:30
elseif ( plastic_disloUCLA_outputID ( o , instance ) == stress_exponent_ID ) then
2014-11-06 02:23:25 +05:30
do j = 1_pInt , ns
2015-04-11 17:17:33 +05:30
if ( abs ( gdot_slip_pos ( j ) + gdot_slip_neg ( j ) ) < = tiny ( 0.0_pReal ) ) then
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_postResults ( c + j ) = 0.0_pReal
2014-11-06 02:23:25 +05:30
else
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_postResults ( c + j ) = ( tau_slip_pos ( j ) + tau_slip_neg ( j ) ) / &
2014-11-07 16:53:34 +05:30
( gdot_slip_pos ( j ) + gdot_slip_neg ( j ) ) * &
( dgdot_dtauslip_pos ( j ) + dgdot_dtauslip_neg ( j ) ) * 0.5_pReal
2014-11-06 01:09:23 +05:30
endif
2014-11-06 02:23:25 +05:30
enddo
c = c + ns
endif
2014-11-06 00:41:09 +05:30
case ( accumulated_shear_slip_ID )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_postResults ( c + 1_pInt : c + ns ) = &
2016-01-15 20:56:24 +05:30
state ( instance ) % accshear_slip ( 1_pInt : ns , of )
2014-11-06 00:41:09 +05:30
c = c + ns
case ( mfp_slip_ID )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_postResults ( c + 1_pInt : c + ns ) = &
2016-01-15 20:56:24 +05:30
state ( instance ) % mfp_slip ( 1_pInt : ns , of )
2014-11-06 00:41:09 +05:30
c = c + ns
case ( resolved_stress_slip_ID )
j = 0_pInt
2014-11-07 16:53:34 +05:30
slipFamilies1 : do f = 1_pInt , lattice_maxNslipFamily
2014-11-06 00:41:09 +05:30
index_myFamily = sum ( lattice_NslipSystem ( 1 : f - 1_pInt , ph ) ) ! at which index starts my family
2015-01-21 20:44:00 +05:30
slipSystems1 : do i = 1_pInt , plastic_disloUCLA_Nslip ( f , instance )
2014-11-06 00:41:09 +05:30
j = j + 1_pInt
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_postResults ( c + j ) = &
2014-11-06 00:41:09 +05:30
dot_product ( Tstar_v , lattice_Sslip_v ( : , 1 , index_myFamily + i , ph ) )
2014-11-07 16:53:34 +05:30
enddo slipSystems1 ; enddo slipFamilies1
2014-11-06 00:41:09 +05:30
c = c + ns
case ( threshold_stress_slip_ID )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_postResults ( c + 1_pInt : c + ns ) = &
2016-01-15 20:56:24 +05:30
state ( instance ) % threshold_stress_slip ( 1_pInt : ns , of )
2014-11-06 00:41:09 +05:30
c = c + ns
case ( edge_dipole_distance_ID )
j = 0_pInt
2014-11-07 16:53:34 +05:30
slipFamilies2 : do f = 1_pInt , lattice_maxNslipFamily
2014-11-06 00:41:09 +05:30
index_myFamily = sum ( lattice_NslipSystem ( 1 : f - 1_pInt , ph ) ) ! at which index starts my family
2015-01-21 20:44:00 +05:30
slipSystems2 : do i = 1_pInt , plastic_disloUCLA_Nslip ( f , instance )
2014-11-06 00:41:09 +05:30
j = j + 1_pInt
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_postResults ( c + j ) = &
( 3.0_pReal * lattice_mu ( ph ) * plastic_disloUCLA_burgersPerSlipSystem ( j , instance ) ) / &
2014-11-06 00:41:09 +05:30
( 1 6.0_pReal * pi * abs ( dot_product ( Tstar_v , lattice_Sslip_v ( : , 1 , index_myFamily + i , ph ) ) ) )
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_postResults ( c + j ) = min ( plastic_disloUCLA_postResults ( c + j ) , &
2016-01-15 20:56:24 +05:30
state ( instance ) % mfp_slip ( j , of ) )
2014-11-07 16:53:34 +05:30
enddo slipSystems2 ; enddo slipFamilies2
2014-11-06 00:41:09 +05:30
c = c + ns
case ( twin_fraction_ID )
2016-01-15 20:56:24 +05:30
plastic_disloUCLA_postResults ( c + 1_pInt : c + nt ) = state ( instance ) % twinFraction ( 1_pInt : nt , of )
2014-11-06 00:41:09 +05:30
c = c + nt
case ( accumulated_shear_twin_ID )
2016-01-15 20:56:24 +05:30
plastic_disloUCLA_postResults ( c + 1_pInt : c + nt ) = state ( instance ) % accshear_twin ( 1_pInt : nt , of )
2014-11-06 00:41:09 +05:30
c = c + nt
2016-01-15 20:56:24 +05:30
2014-11-06 00:41:09 +05:30
case ( mfp_twin_ID )
2016-01-15 20:56:24 +05:30
plastic_disloUCLA_postResults ( c + 1_pInt : c + nt ) = state ( instance ) % mfp_twin ( 1_pInt : nt , of )
2014-11-06 00:41:09 +05:30
c = c + nt
2016-01-15 20:56:24 +05:30
2014-11-06 00:41:09 +05:30
case ( resolved_stress_twin_ID )
if ( nt > 0_pInt ) then
j = 0_pInt
2014-11-06 01:09:23 +05:30
twinFamilies2 : do f = 1_pInt , lattice_maxNtwinFamily
2014-11-06 00:41:09 +05:30
index_myFamily = sum ( lattice_NtwinSystem ( 1 : f - 1_pInt , ph ) ) ! at which index starts my family
2015-01-21 20:44:00 +05:30
twinSystems2 : do i = 1_pInt , plastic_disloUCLA_Ntwin ( f , instance )
2014-11-06 00:41:09 +05:30
j = j + 1_pInt
2015-01-21 20:44:00 +05:30
plastic_disloUCLA_postResults ( c + j ) = dot_product ( Tstar_v , lattice_Stwin_v ( : , index_myFamily + i , ph ) )
2014-11-06 01:09:23 +05:30
enddo twinSystems2 ; enddo twinFamilies2
2014-11-06 00:41:09 +05:30
endif
c = c + nt
case ( threshold_stress_twin_ID )
2016-01-15 20:56:24 +05:30
plastic_disloUCLA_postResults ( c + 1_pInt : c + nt ) = state ( instance ) % threshold_stress_twin ( 1_pInt : nt , of )
2014-11-06 00:41:09 +05:30
c = c + nt
end select
enddo
2015-01-21 20:44:00 +05:30
end function plastic_disloUCLA_postResults
2014-11-06 00:41:09 +05:30
2015-01-21 20:44:00 +05:30
end module plastic_disloUCLA