2009-08-31 20:39:15 +05:30
!* $Id$
2009-08-11 22:01:57 +05:30
!************************************
!* Module: CONSTITUTIVE_NONLOCAL *
!************************************
!* contains: *
!* - constitutive equations *
!* - parameters definition *
!************************************
MODULE constitutive_nonlocal
!* Include other modules
use prec , only : pReal , pInt
implicit none
!* Definition of parameters
character ( len = * ) , parameter :: constitutive_nonlocal_label = 'nonlocal'
2010-02-17 18:51:36 +05:30
character ( len = 22 ) , dimension ( 10 ) , parameter :: constitutive_nonlocal_listBasicStates = ( / 'rhoSglEdgePosMobile ' , &
'rhoSglEdgeNegMobile ' , &
'rhoSglScrewPosMobile ' , &
'rhoSglScrewNegMobile ' , &
'rhoSglEdgePosImmobile ' , &
'rhoSglEdgeNegImmobile ' , &
'rhoSglScrewPosImmobile' , &
'rhoSglScrewNegImmobile' , &
'rhoDipEdge ' , &
'rhoDipScrew ' / ) ! list of "basic" microstructural state variables that are independent from other state variables
character ( len = 15 ) , dimension ( 3 ) , parameter :: constitutive_nonlocal_listDependentStates = ( / 'rhoForest ' , &
'tauThreshold ' , &
'Tdislocation_v ' / ) ! list of microstructural state variables that depend on other state variables
2009-09-18 21:07:14 +05:30
real ( pReal ) , parameter :: kB = 1.38e-23_pReal ! Physical parameter, Boltzmann constant in J/Kelvin
2009-08-11 22:01:57 +05:30
!* Definition of global variables
integer ( pInt ) , dimension ( : ) , allocatable :: constitutive_nonlocal_sizeDotState , & ! number of dotStates
constitutive_nonlocal_sizeState , & ! total number of microstructural state variables
constitutive_nonlocal_sizePostResults ! cumulative size of post results
integer ( pInt ) , dimension ( : , : ) , allocatable , target :: constitutive_nonlocal_sizePostResult ! size of each post result output
character ( len = 64 ) , dimension ( : , : ) , allocatable , target :: constitutive_nonlocal_output ! name of each post result output
character ( len = 32 ) , dimension ( : ) , allocatable :: constitutive_nonlocal_structureName ! name of the lattice structure
integer ( pInt ) , dimension ( : ) , allocatable :: constitutive_nonlocal_structure , & ! number representing the kind of lattice structure
constitutive_nonlocal_totalNslip ! total number of active slip systems for each instance
integer ( pInt ) , dimension ( : , : ) , allocatable :: constitutive_nonlocal_Nslip , & ! number of active slip systems for each family and instance
constitutive_nonlocal_slipFamily , & ! lookup table relating active slip system to slip family for each instance
constitutive_nonlocal_slipSystemLattice ! lookup table relating active slip system index to lattice slip system index for each instance
real ( pReal ) , dimension ( : ) , allocatable :: constitutive_nonlocal_CoverA , & ! c/a ratio for hex type lattice
constitutive_nonlocal_C11 , & ! C11 element in elasticity matrix
constitutive_nonlocal_C12 , & ! C12 element in elasticity matrix
constitutive_nonlocal_C13 , & ! C13 element in elasticity matrix
constitutive_nonlocal_C33 , & ! C33 element in elasticity matrix
constitutive_nonlocal_C44 , & ! C44 element in elasticity matrix
constitutive_nonlocal_Gmod , & ! shear modulus
2009-08-28 19:20:47 +05:30
constitutive_nonlocal_nu , & ! poisson's ratio
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
constitutive_nonlocal_Q0 , & ! activation energy for dislocation glide
2009-08-28 19:20:47 +05:30
constitutive_nonlocal_atomicVolume , & ! atomic volume
2009-09-18 21:07:14 +05:30
constitutive_nonlocal_D0 , & ! prefactor for self-diffusion coefficient
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
constitutive_nonlocal_Qsd , & ! activation enthalpy for diffusion
2010-06-07 20:02:23 +05:30
constitutive_nonlocal_relevantRho , & ! dislocation density considered relevant
constitutive_nonlocal_a , & ! a0 * burgers vector gives the spreading of the dislocation core for non-singular solution of dislocation stress in the core
constitutive_nonlocal_R ! cutoff radius for dislocation stress
2009-08-11 22:01:57 +05:30
real ( pReal ) , dimension ( : , : , : ) , allocatable :: constitutive_nonlocal_Cslip_66 ! elasticity matrix in Mandel notation for each instance
real ( pReal ) , dimension ( : , : , : , : , : ) , allocatable :: constitutive_nonlocal_Cslip_3333 ! elasticity matrix for each instance
2010-01-05 21:37:24 +05:30
real ( pReal ) , dimension ( : , : ) , allocatable :: constitutive_nonlocal_rhoSglEdgePos0 , & ! initial edge_pos dislocation density per slip system for each family and instance
constitutive_nonlocal_rhoSglEdgeNeg0 , & ! initial edge_neg dislocation density per slip system for each family and instance
constitutive_nonlocal_rhoSglScrewPos0 , & ! initial screw_pos dislocation density per slip system for each family and instance
constitutive_nonlocal_rhoSglScrewNeg0 , & ! initial screw_neg dislocation density per slip system for each family and instance
constitutive_nonlocal_rhoDipEdge0 , & ! initial edge dipole dislocation density per slip system for each family and instance
constitutive_nonlocal_rhoDipScrew0 , & ! initial screw dipole dislocation density per slip system for each family and instance
2009-08-28 19:20:47 +05:30
constitutive_nonlocal_v0PerSlipFamily , & ! dislocation velocity prefactor [m/s] for each family and instance
constitutive_nonlocal_v0PerSlipSystem , & ! dislocation velocity prefactor [m/s] for each slip system and instance
constitutive_nonlocal_lambda0PerSlipFamily , & ! mean free path prefactor for each family and instance
constitutive_nonlocal_lambda0PerSlipSystem , & ! mean free path prefactor for each slip system and instance
constitutive_nonlocal_burgersPerSlipFamily , & ! absolute length of burgers vector [m] for each family and instance
constitutive_nonlocal_burgersPerSlipSystem , & ! absolute length of burgers vector [m] for each slip system and instance
2010-03-24 21:53:21 +05:30
constitutive_nonlocal_dLowerEdgePerSlipFamily , & ! minimum stable edge dipole height for each family and instance
constitutive_nonlocal_dLowerEdgePerSlipSystem , & ! minimum stable edge dipole height for each slip system and instance
constitutive_nonlocal_dLowerScrewPerSlipFamily , & ! minimum stable screw dipole height for each family and instance
constitutive_nonlocal_dLowerScrewPerSlipSystem , & ! minimum stable screw dipole height for each slip system and instance
2009-08-11 22:01:57 +05:30
constitutive_nonlocal_interactionSlipSlip ! coefficients for slip-slip interaction for each interaction type and instance
2010-03-10 15:19:40 +05:30
real ( pReal ) , dimension ( : , : , : , : , : ) , allocatable :: constitutive_nonlocal_v , & ! dislocation velocity
constitutive_nonlocal_rhoDotFlux ! dislocation convection term
2009-08-11 22:01:57 +05:30
real ( pReal ) , dimension ( : , : , : ) , allocatable :: constitutive_nonlocal_forestProjectionEdge , & ! matrix of forest projections of edge dislocations for each instance
constitutive_nonlocal_forestProjectionScrew , & ! matrix of forest projections of screw dislocations for each instance
2010-05-21 14:21:15 +05:30
constitutive_nonlocal_interactionMatrixSlipSlip ! interaction matrix of the different slip systems for each instance
2009-08-11 22:01:57 +05:30
CONTAINS
!****************************************
!* - constitutive_init
!* - constitutive_stateInit
!* - constitutive_homogenizedC
!* - constitutive_microstructure
!* - constitutive_LpAndItsTangent
!* - constitutive_dotState
!* - constitutive_dotTemperature
!* - constitutive_postResults
!****************************************
!**************************************
!* Module initialization *
!**************************************
subroutine constitutive_nonlocal_init ( file )
use prec , only : pInt , pReal
use math , only : math_Mandel3333to66 , &
math_Voigt66to3333 , &
math_mul3x3
use IO , only : IO_lc , &
IO_getTag , &
IO_isBlank , &
IO_stringPos , &
IO_stringValue , &
IO_floatValue , &
IO_intValue , &
IO_error
2010-02-17 18:51:36 +05:30
use mesh , only : mesh_NcpElems , &
mesh_maxNips
use material , only : homogenization_maxNgrains , &
phase_constitution , &
2009-08-11 22:01:57 +05:30
phase_constitutionInstance , &
phase_Noutput
use lattice , only : lattice_maxNslipFamily , &
lattice_maxNtwinFamily , &
lattice_maxNslip , &
lattice_maxNtwin , &
lattice_maxNinteraction , &
lattice_NslipSystem , &
lattice_NtwinSystem , &
lattice_initializeStructure , &
lattice_Qtwin , &
lattice_sd , &
lattice_sn , &
lattice_st , &
lattice_interactionSlipSlip
!*** output variables
!*** input variables
integer ( pInt ) , intent ( in ) :: file
!*** local variables
integer ( pInt ) , parameter :: maxNchunks = 21
integer ( pInt ) , dimension ( 1 + 2 * maxNchunks ) :: positions
integer ( pInt ) section , &
maxNinstance , &
maxTotalNslip , &
myStructure , &
f , & ! index of my slip family
i , & ! index of my instance of this constitution
j , &
k , &
l , &
2009-09-18 21:07:14 +05:30
ns , & ! short notation for total number of active slip systems for the current instance
2009-08-11 22:01:57 +05:30
o , & ! index of my output
s , & ! index of my slip system
s1 , & ! index of my slip system
s2 , & ! index of my slip system
2009-08-24 13:46:01 +05:30
it , & ! index of my interaction type
2009-08-11 22:01:57 +05:30
output , &
mySize
character ( len = 64 ) tag
character ( len = 1024 ) line
write ( 6 , * )
write ( 6 , '(a20,a20,a12)' ) '<<<+- constitutive_' , constitutive_nonlocal_label , ' init -+>>>'
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
write ( 6 , * ) '$Id$'
2009-08-11 22:01:57 +05:30
write ( 6 , * )
maxNinstance = count ( phase_constitution == constitutive_nonlocal_label )
if ( maxNinstance == 0 ) return ! we don't have to do anything if there's no instance for this constitutive law
!*** space allocation for global variables
2009-08-28 19:20:47 +05:30
allocate ( constitutive_nonlocal_sizeDotState ( maxNinstance ) )
allocate ( constitutive_nonlocal_sizeState ( maxNinstance ) )
allocate ( constitutive_nonlocal_sizePostResults ( maxNinstance ) )
allocate ( constitutive_nonlocal_sizePostResult ( maxval ( phase_Noutput ) , maxNinstance ) )
allocate ( constitutive_nonlocal_output ( maxval ( phase_Noutput ) , maxNinstance ) )
constitutive_nonlocal_sizeDotState = 0_pInt
constitutive_nonlocal_sizeState = 0_pInt
constitutive_nonlocal_sizePostResults = 0_pInt
constitutive_nonlocal_sizePostResult = 0_pInt
constitutive_nonlocal_output = ''
allocate ( constitutive_nonlocal_structureName ( maxNinstance ) )
allocate ( constitutive_nonlocal_structure ( maxNinstance ) )
allocate ( constitutive_nonlocal_Nslip ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( constitutive_nonlocal_slipFamily ( lattice_maxNslip , maxNinstance ) )
allocate ( constitutive_nonlocal_slipSystemLattice ( lattice_maxNslip , maxNinstance ) )
allocate ( constitutive_nonlocal_totalNslip ( maxNinstance ) )
constitutive_nonlocal_structureName = ''
constitutive_nonlocal_structure = 0_pInt
constitutive_nonlocal_Nslip = 0_pInt
constitutive_nonlocal_slipFamily = 0_pInt
constitutive_nonlocal_slipSystemLattice = 0_pInt
constitutive_nonlocal_totalNslip = 0_pInt
allocate ( constitutive_nonlocal_CoverA ( maxNinstance ) )
allocate ( constitutive_nonlocal_C11 ( maxNinstance ) )
allocate ( constitutive_nonlocal_C12 ( maxNinstance ) )
allocate ( constitutive_nonlocal_C13 ( maxNinstance ) )
allocate ( constitutive_nonlocal_C33 ( maxNinstance ) )
allocate ( constitutive_nonlocal_C44 ( maxNinstance ) )
allocate ( constitutive_nonlocal_Gmod ( maxNinstance ) )
allocate ( constitutive_nonlocal_nu ( maxNinstance ) )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
allocate ( constitutive_nonlocal_Q0 ( maxNinstance ) )
2009-08-28 19:20:47 +05:30
allocate ( constitutive_nonlocal_atomicVolume ( maxNinstance ) )
allocate ( constitutive_nonlocal_D0 ( maxNinstance ) )
allocate ( constitutive_nonlocal_Qsd ( maxNinstance ) )
2009-09-18 21:07:14 +05:30
allocate ( constitutive_nonlocal_relevantRho ( maxNinstance ) )
2009-08-28 19:20:47 +05:30
allocate ( constitutive_nonlocal_Cslip_66 ( 6 , 6 , maxNinstance ) )
allocate ( constitutive_nonlocal_Cslip_3333 ( 3 , 3 , 3 , 3 , maxNinstance ) )
2010-06-07 20:02:23 +05:30
allocate ( constitutive_nonlocal_a ( maxNinstance ) )
allocate ( constitutive_nonlocal_R ( maxNinstance ) )
2009-08-28 19:20:47 +05:30
constitutive_nonlocal_CoverA = 0.0_pReal
constitutive_nonlocal_C11 = 0.0_pReal
constitutive_nonlocal_C12 = 0.0_pReal
constitutive_nonlocal_C13 = 0.0_pReal
constitutive_nonlocal_C33 = 0.0_pReal
constitutive_nonlocal_C44 = 0.0_pReal
constitutive_nonlocal_Gmod = 0.0_pReal
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
constitutive_nonlocal_Q0 = 0.0_pReal
2009-08-28 19:20:47 +05:30
constitutive_nonlocal_atomicVolume = 0.0_pReal
constitutive_nonlocal_D0 = 0.0_pReal
constitutive_nonlocal_Qsd = 0.0_pReal
2009-09-18 21:07:14 +05:30
constitutive_nonlocal_relevantRho = 0.0_pReal
2009-08-28 19:20:47 +05:30
constitutive_nonlocal_nu = 0.0_pReal
constitutive_nonlocal_Cslip_66 = 0.0_pReal
constitutive_nonlocal_Cslip_3333 = 0.0_pReal
2010-06-07 20:02:23 +05:30
constitutive_nonlocal_a = - 1.0_pReal
constitutive_nonlocal_R = 0.0_pReal
2009-08-28 19:20:47 +05:30
2010-01-05 21:37:24 +05:30
allocate ( constitutive_nonlocal_rhoSglEdgePos0 ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( constitutive_nonlocal_rhoSglEdgeNeg0 ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( constitutive_nonlocal_rhoSglScrewPos0 ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( constitutive_nonlocal_rhoSglScrewNeg0 ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( constitutive_nonlocal_rhoDipEdge0 ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( constitutive_nonlocal_rhoDipScrew0 ( lattice_maxNslipFamily , maxNinstance ) )
2009-08-28 19:20:47 +05:30
allocate ( constitutive_nonlocal_v0PerSlipFamily ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( constitutive_nonlocal_burgersPerSlipFamily ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( constitutive_nonlocal_Lambda0PerSlipFamily ( lattice_maxNslipFamily , maxNinstance ) )
2009-08-11 22:01:57 +05:30
allocate ( constitutive_nonlocal_interactionSlipSlip ( lattice_maxNinteraction , maxNinstance ) )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
allocate ( constitutive_nonlocal_dLowerEdgePerSlipFamily ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( constitutive_nonlocal_dLowerScrewPerSlipFamily ( lattice_maxNslipFamily , maxNinstance ) )
2010-06-07 20:02:23 +05:30
constitutive_nonlocal_rhoSglEdgePos0 = - 1.0_pReal
constitutive_nonlocal_rhoSglEdgeNeg0 = - 1.0_pReal
constitutive_nonlocal_rhoSglScrewPos0 = - 1.0_pReal
constitutive_nonlocal_rhoSglScrewNeg0 = - 1.0_pReal
constitutive_nonlocal_rhoDipEdge0 = - 1.0_pReal
constitutive_nonlocal_rhoDipScrew0 = - 1.0_pReal
2009-08-28 19:20:47 +05:30
constitutive_nonlocal_v0PerSlipFamily = 0.0_pReal
constitutive_nonlocal_burgersPerSlipFamily = 0.0_pReal
constitutive_nonlocal_lambda0PerSlipFamily = 0.0_pReal
constitutive_nonlocal_interactionSlipSlip = 0.0_pReal
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
constitutive_nonlocal_dLowerEdgePerSlipFamily = 0.0_pReal
constitutive_nonlocal_dLowerScrewPerSlipFamily = 0.0_pReal
2009-08-11 22:01:57 +05:30
!*** readout data from material.config file
rewind ( file )
line = ''
section = 0
do while ( IO_lc ( IO_getTag ( line , '<' , '>' ) ) / = 'phase' ) ! wind forward to <phase>
read ( file , '(a1024)' , END = 100 ) line
enddo
do ! read thru sections of phase part
read ( file , '(a1024)' , END = 100 ) line
if ( IO_isBlank ( line ) ) cycle ! skip empty lines
if ( IO_getTag ( line , '<' , '>' ) / = '' ) exit ! stop at next part
if ( IO_getTag ( line , '[' , ']' ) / = '' ) then ! next section
section = section + 1
output = 0 ! reset output counter
endif
if ( section > 0 . and . phase_constitution ( section ) == constitutive_nonlocal_label ) then ! one of my sections
i = phase_constitutionInstance ( section ) ! which instance of my constitution is present phase
positions = IO_stringPos ( line , maxNchunks )
tag = IO_lc ( IO_stringValue ( line , positions , 1 ) ) ! extract key
select case ( tag )
case ( '(output)' )
output = output + 1
constitutive_nonlocal_output ( output , i ) = IO_lc ( IO_stringValue ( line , positions , 2 ) )
case ( 'lattice_structure' )
constitutive_nonlocal_structureName ( i ) = IO_lc ( IO_stringValue ( line , positions , 2 ) )
case ( 'covera_ratio' )
constitutive_nonlocal_CoverA ( i ) = IO_floatValue ( line , positions , 2 )
case ( 'c11' )
constitutive_nonlocal_C11 ( i ) = IO_floatValue ( line , positions , 2 )
case ( 'c12' )
constitutive_nonlocal_C12 ( i ) = IO_floatValue ( line , positions , 2 )
case ( 'c13' )
constitutive_nonlocal_C13 ( i ) = IO_floatValue ( line , positions , 2 )
case ( 'c33' )
constitutive_nonlocal_C33 ( i ) = IO_floatValue ( line , positions , 2 )
case ( 'c44' )
constitutive_nonlocal_C44 ( i ) = IO_floatValue ( line , positions , 2 )
case ( 'nslip' )
forall ( f = 1 : lattice_maxNslipFamily ) constitutive_nonlocal_Nslip ( f , i ) = IO_intValue ( line , positions , 1 + f )
2010-01-05 21:37:24 +05:30
case ( 'rhosgledgepos0' )
forall ( f = 1 : lattice_maxNslipFamily ) constitutive_nonlocal_rhoSglEdgePos0 ( f , i ) = IO_floatValue ( line , positions , 1 + f )
case ( 'rhosgledgeneg0' )
forall ( f = 1 : lattice_maxNslipFamily ) constitutive_nonlocal_rhoSglEdgeNeg0 ( f , i ) = IO_floatValue ( line , positions , 1 + f )
case ( 'rhosglscrewpos0' )
forall ( f = 1 : lattice_maxNslipFamily ) constitutive_nonlocal_rhoSglScrewPos0 ( f , i ) = IO_floatValue ( line , positions , 1 + f )
case ( 'rhosglscrewneg0' )
forall ( f = 1 : lattice_maxNslipFamily ) constitutive_nonlocal_rhoSglScrewNeg0 ( f , i ) = IO_floatValue ( line , positions , 1 + f )
case ( 'rhodipedge0' )
forall ( f = 1 : lattice_maxNslipFamily ) constitutive_nonlocal_rhoDipEdge0 ( f , i ) = IO_floatValue ( line , positions , 1 + f )
case ( 'rhodipscrew0' )
forall ( f = 1 : lattice_maxNslipFamily ) constitutive_nonlocal_rhoDipScrew0 ( f , i ) = IO_floatValue ( line , positions , 1 + f )
2009-08-11 22:01:57 +05:30
case ( 'v0' )
2009-08-28 19:20:47 +05:30
forall ( f = 1 : lattice_maxNslipFamily ) constitutive_nonlocal_v0PerSlipFamily ( f , i ) = IO_floatValue ( line , positions , 1 + f )
2009-08-12 16:52:02 +05:30
case ( 'lambda0' )
2009-08-28 19:20:47 +05:30
forall ( f = 1 : lattice_maxNslipFamily ) constitutive_nonlocal_lambda0PerSlipFamily ( f , i ) = IO_floatValue ( line , positions , 1 + f )
2009-08-11 22:01:57 +05:30
case ( 'burgers' )
2009-08-28 19:20:47 +05:30
forall ( f = 1 : lattice_maxNslipFamily ) constitutive_nonlocal_burgersPerSlipFamily ( f , i ) = IO_floatValue ( line , positions , 1 + f )
2010-06-07 20:02:23 +05:30
case ( 'a' )
constitutive_nonlocal_a ( i ) = IO_floatValue ( line , positions , 2 )
case ( 'r' )
constitutive_nonlocal_R ( i ) = IO_floatValue ( line , positions , 2 )
2009-08-28 19:20:47 +05:30
case ( 'ddipminedge' )
forall ( f = 1 : lattice_maxNslipFamily ) &
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
constitutive_nonlocal_dLowerEdgePerSlipFamily ( f , i ) = IO_floatValue ( line , positions , 1 + f )
2009-08-28 19:20:47 +05:30
case ( 'ddipminscrew' )
forall ( f = 1 : lattice_maxNslipFamily ) &
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
constitutive_nonlocal_dLowerScrewPerSlipFamily ( f , i ) = IO_floatValue ( line , positions , 1 + f )
case ( 'q0' )
constitutive_nonlocal_Q0 ( i ) = IO_floatValue ( line , positions , 2 )
2009-08-28 19:20:47 +05:30
case ( 'atomicvolume' )
constitutive_nonlocal_atomicVolume ( i ) = IO_floatValue ( line , positions , 2 )
case ( 'd0' )
constitutive_nonlocal_D0 ( i ) = IO_floatValue ( line , positions , 2 )
case ( 'qsd' )
constitutive_nonlocal_Qsd ( i ) = IO_floatValue ( line , positions , 2 )
2009-09-18 21:07:14 +05:30
case ( 'relevantrho' )
constitutive_nonlocal_relevantRho ( i ) = IO_floatValue ( line , positions , 2 )
2009-08-11 22:01:57 +05:30
case ( 'interaction_slipslip' )
2009-08-24 13:46:01 +05:30
forall ( it = 1 : lattice_maxNinteraction ) constitutive_nonlocal_interactionSlipSlip ( it , i ) = IO_floatValue ( line , positions , 1 + it )
2009-08-11 22:01:57 +05:30
end select
endif
enddo
100 do i = 1 , maxNinstance
constitutive_nonlocal_structure ( i ) = &
lattice_initializeStructure ( constitutive_nonlocal_structureName ( i ) , constitutive_nonlocal_CoverA ( i ) ) ! our lattice structure is defined in the material.config file by the structureName (and the c/a ratio)
2009-09-18 21:07:14 +05:30
myStructure = constitutive_nonlocal_structure ( i )
2009-08-11 22:01:57 +05:30
2009-09-18 21:07:14 +05:30
!*** sanity checks
2009-08-11 22:01:57 +05:30
2009-09-18 21:07:14 +05:30
if ( myStructure < 1 . or . myStructure > 3 ) call IO_error ( 205 )
if ( sum ( constitutive_nonlocal_Nslip ( : , i ) ) < = 0_pInt ) call IO_error ( 225 )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
do o = 1 , maxval ( phase_Noutput )
if ( len ( constitutive_nonlocal_output ( o , i ) ) > 64 ) call IO_error ( 666 )
enddo
2009-08-12 16:52:02 +05:30
do f = 1 , lattice_maxNslipFamily
2009-09-18 21:07:14 +05:30
if ( constitutive_nonlocal_Nslip ( f , i ) > 0_pInt ) then
2010-05-21 14:21:15 +05:30
if ( constitutive_nonlocal_rhoSglEdgePos0 ( f , i ) < 0.0_pReal ) call IO_error ( 220 )
if ( constitutive_nonlocal_rhoSglEdgeNeg0 ( f , i ) < 0.0_pReal ) call IO_error ( 220 )
if ( constitutive_nonlocal_rhoSglScrewPos0 ( f , i ) < 0.0_pReal ) call IO_error ( 220 )
if ( constitutive_nonlocal_rhoSglScrewNeg0 ( f , i ) < 0.0_pReal ) call IO_error ( 220 )
2010-01-05 21:37:24 +05:30
if ( constitutive_nonlocal_rhoDipEdge0 ( f , i ) < 0.0_pReal ) call IO_error ( 220 )
if ( constitutive_nonlocal_rhoDipScrew0 ( f , i ) < 0.0_pReal ) call IO_error ( 220 )
2009-08-28 19:20:47 +05:30
if ( constitutive_nonlocal_burgersPerSlipFamily ( f , i ) < = 0.0_pReal ) call IO_error ( 221 )
2009-09-18 21:07:14 +05:30
if ( constitutive_nonlocal_v0PerSlipFamily ( f , i ) < = 0.0_pReal ) call IO_error ( 226 )
if ( constitutive_nonlocal_lambda0PerSlipFamily ( f , i ) < = 0.0_pReal ) call IO_error ( 227 )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
if ( constitutive_nonlocal_dLowerEdgePerSlipFamily ( f , i ) < = 0.0_pReal ) call IO_error ( 228 )
if ( constitutive_nonlocal_dLowerScrewPerSlipFamily ( f , i ) < = 0.0_pReal ) call IO_error ( 228 )
2009-08-12 16:52:02 +05:30
endif
enddo
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
if ( any ( constitutive_nonlocal_interactionSlipSlip ( 1 : maxval ( lattice_interactionSlipSlip ( : , : , myStructure ) ) , i ) < 0.0_pReal ) ) &
2009-09-18 21:07:14 +05:30
call IO_error ( 229 )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
if ( constitutive_nonlocal_Q0 ( i ) < = 0.0_pReal ) call IO_error ( - 1 )
2010-06-07 20:02:23 +05:30
if ( constitutive_nonlocal_a ( i ) < 0.0_pReal ) call IO_error ( - 1 )
if ( constitutive_nonlocal_R ( i ) < = 0.0_pReal ) call IO_error ( - 1 )
2009-09-18 21:07:14 +05:30
if ( constitutive_nonlocal_atomicVolume ( i ) < = 0.0_pReal ) call IO_error ( 230 )
if ( constitutive_nonlocal_D0 ( i ) < = 0.0_pReal ) call IO_error ( 231 )
if ( constitutive_nonlocal_Qsd ( i ) < = 0.0_pReal ) call IO_error ( 232 )
if ( constitutive_nonlocal_relevantRho ( i ) < = 0.0_pReal ) call IO_error ( 233 )
2009-08-24 13:46:01 +05:30
2009-08-11 22:01:57 +05:30
!*** determine total number of active slip systems
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
constitutive_nonlocal_Nslip ( : , i ) = min ( lattice_NslipSystem ( : , myStructure ) , constitutive_nonlocal_Nslip ( : , i ) ) ! we can't use more slip systems per family than specified in lattice
2009-08-11 22:01:57 +05:30
constitutive_nonlocal_totalNslip ( i ) = sum ( constitutive_nonlocal_Nslip ( : , i ) )
enddo
!*** allocation of variables whose size depends on the total number of active slip systems
maxTotalNslip = maxval ( constitutive_nonlocal_totalNslip )
2009-08-28 19:20:47 +05:30
allocate ( constitutive_nonlocal_burgersPerSlipSystem ( maxTotalNslip , maxNinstance ) )
constitutive_nonlocal_burgersPerSlipSystem = 0.0_pReal
allocate ( constitutive_nonlocal_v0PerSlipSystem ( maxTotalNslip , maxNinstance ) )
constitutive_nonlocal_v0PerSlipSystem = 0.0_pReal
allocate ( constitutive_nonlocal_lambda0PerSlipSystem ( maxTotalNslip , maxNinstance ) )
constitutive_nonlocal_lambda0PerSlipSystem = 0.0_pReal
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
allocate ( constitutive_nonlocal_dLowerEdgePerSlipSystem ( maxTotalNslip , maxNinstance ) )
constitutive_nonlocal_dLowerEdgePerSlipSystem = 0.0_pReal
2009-08-28 19:20:47 +05:30
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
allocate ( constitutive_nonlocal_dLowerScrewPerSlipSystem ( maxTotalNslip , maxNinstance ) )
constitutive_nonlocal_dLowerScrewPerSlipSystem = 0.0_pReal
2009-08-28 19:20:47 +05:30
2009-08-11 22:01:57 +05:30
allocate ( constitutive_nonlocal_forestProjectionEdge ( maxTotalNslip , maxTotalNslip , maxNinstance ) )
2009-08-28 19:20:47 +05:30
constitutive_nonlocal_forestProjectionEdge = 0.0_pReal
2009-08-11 22:01:57 +05:30
allocate ( constitutive_nonlocal_forestProjectionScrew ( maxTotalNslip , maxTotalNslip , maxNinstance ) )
2009-08-28 19:20:47 +05:30
constitutive_nonlocal_forestProjectionScrew = 0.0_pReal
2009-08-11 22:01:57 +05:30
allocate ( constitutive_nonlocal_interactionMatrixSlipSlip ( maxTotalNslip , maxTotalNslip , maxNinstance ) )
2009-08-28 19:20:47 +05:30
constitutive_nonlocal_interactionMatrixSlipSlip = 0.0_pReal
2010-02-17 18:51:36 +05:30
allocate ( constitutive_nonlocal_v ( maxTotalNslip , 4 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
constitutive_nonlocal_v = 0.0_pReal
2009-08-11 22:01:57 +05:30
2010-03-10 15:19:40 +05:30
allocate ( constitutive_nonlocal_rhoDotFlux ( maxTotalNslip , 8 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
constitutive_nonlocal_rhoDotFlux = 0.0_pReal
2009-08-11 22:01:57 +05:30
do i = 1 , maxNinstance
myStructure = constitutive_nonlocal_structure ( i ) ! lattice structure of this instance
!*** Inverse lookup of my slip system family and the slip system in lattice
l = 0_pInt
do f = 1 , lattice_maxNslipFamily
do s = 1 , constitutive_nonlocal_Nslip ( f , i )
l = l + 1
constitutive_nonlocal_slipFamily ( l , i ) = f
constitutive_nonlocal_slipSystemLattice ( l , i ) = sum ( lattice_NslipSystem ( 1 : f - 1 , myStructure ) ) + s
enddo ; enddo
!*** determine size of state array
2009-09-18 21:07:14 +05:30
ns = constitutive_nonlocal_totalNslip ( i )
constitutive_nonlocal_sizeState ( i ) = size ( constitutive_nonlocal_listBasicStates ) * ns &
+ ( size ( constitutive_nonlocal_listDependentStates ) - 1_pInt ) * ns + 6_pInt
constitutive_nonlocal_sizeDotState ( i ) = size ( constitutive_nonlocal_listBasicStates ) * ns
2009-08-11 22:01:57 +05:30
!*** determine size of postResults array
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
do o = 1 , maxval ( phase_Noutput )
2009-08-11 22:01:57 +05:30
select case ( constitutive_nonlocal_output ( o , i ) )
2009-08-24 13:46:01 +05:30
case ( 'rho' , &
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
'delta' , &
2009-08-24 13:46:01 +05:30
'rho_edge' , &
'rho_screw' , &
2010-01-05 21:37:24 +05:30
'rho_sgl' , &
'delta_sgl' , &
'rho_sgl_edge' , &
'rho_sgl_edge_pos' , &
'rho_sgl_edge_neg' , &
'rho_sgl_screw' , &
'rho_sgl_screw_pos' , &
'rho_sgl_screw_neg' , &
'rho_sgl_mobile' , &
'rho_sgl_edge_mobile' , &
'rho_sgl_edge_pos_mobile' , &
'rho_sgl_edge_neg_mobile' , &
'rho_sgl_screw_mobile' , &
'rho_sgl_screw_pos_mobile' , &
'rho_sgl_screw_neg_mobile' , &
'rho_sgl_immobile' , &
'rho_sgl_edge_immobile' , &
'rho_sgl_edge_pos_immobile' , &
'rho_sgl_edge_neg_immobile' , &
'rho_sgl_screw_immobile' , &
'rho_sgl_screw_pos_immobile' , &
'rho_sgl_screw_neg_immobile' , &
'rho_dip' , &
'delta_dip' , &
'rho_dip_edge' , &
'rho_dip_screw' , &
2009-08-28 19:20:47 +05:30
'excess_rho' , &
2009-08-24 13:46:01 +05:30
'excess_rho_edge' , &
'excess_rho_screw' , &
'rho_forest' , &
'shearrate' , &
'resolvedstress' , &
2010-02-17 18:51:36 +05:30
'resolvedstress_internal' , &
'resolvedstress_external' , &
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
'resistance' , &
'rho_dot' , &
2010-01-05 21:37:24 +05:30
'rho_dot_sgl' , &
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
'rho_dot_dip' , &
'rho_dot_gen' , &
2010-01-05 21:37:24 +05:30
'rho_dot_gen_edge' , &
'rho_dot_gen_screw' , &
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
'rho_dot_sgl2dip' , &
'rho_dot_dip2sgl' , &
'rho_dot_ann_ath' , &
'rho_dot_ann_the' , &
2010-03-10 15:19:40 +05:30
'rho_dot_flux' , &
2010-05-21 14:21:15 +05:30
'rho_dot_flux_edge' , &
'rho_dot_flux_screw' , &
2010-02-23 22:53:07 +05:30
'dislocationvelocity' , &
2010-02-17 18:51:36 +05:30
'fluxdensity_edge_pos_x' , &
'fluxdensity_edge_pos_y' , &
'fluxdensity_edge_pos_z' , &
'fluxdensity_edge_neg_x' , &
'fluxdensity_edge_neg_y' , &
'fluxdensity_edge_neg_z' , &
'fluxdensity_screw_pos_x' , &
'fluxdensity_screw_pos_y' , &
'fluxdensity_screw_pos_z' , &
'fluxdensity_screw_neg_x' , &
'fluxdensity_screw_neg_y' , &
'fluxdensity_screw_neg_z' , &
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
'd_upper_edge' , &
'd_upper_screw' , &
'd_upper_dot_edge' , &
'd_upper_dot_screw' )
2009-08-11 22:01:57 +05:30
mySize = constitutive_nonlocal_totalNslip ( i )
case default
mySize = 0_pInt
end select
if ( mySize > 0_pInt ) then ! any meaningful output found
constitutive_nonlocal_sizePostResult ( o , i ) = mySize
constitutive_nonlocal_sizePostResults ( i ) = constitutive_nonlocal_sizePostResults ( i ) + mySize
endif
enddo
!*** elasticity matrix and shear modulus according to material.config
select case ( myStructure )
case ( 1 : 2 ) ! cubic(s)
forall ( k = 1 : 3 )
forall ( j = 1 : 3 ) constitutive_nonlocal_Cslip_66 ( k , j , i ) = constitutive_nonlocal_C12 ( i )
constitutive_nonlocal_Cslip_66 ( k , k , i ) = constitutive_nonlocal_C11 ( i )
constitutive_nonlocal_Cslip_66 ( k + 3 , k + 3 , i ) = constitutive_nonlocal_C44 ( i )
end forall
case ( 3 : ) ! all hex
constitutive_nonlocal_Cslip_66 ( 1 , 1 , i ) = constitutive_nonlocal_C11 ( i )
constitutive_nonlocal_Cslip_66 ( 2 , 2 , i ) = constitutive_nonlocal_C11 ( i )
constitutive_nonlocal_Cslip_66 ( 3 , 3 , i ) = constitutive_nonlocal_C33 ( i )
constitutive_nonlocal_Cslip_66 ( 1 , 2 , i ) = constitutive_nonlocal_C12 ( i )
constitutive_nonlocal_Cslip_66 ( 2 , 1 , i ) = constitutive_nonlocal_C12 ( i )
constitutive_nonlocal_Cslip_66 ( 1 , 3 , i ) = constitutive_nonlocal_C13 ( i )
constitutive_nonlocal_Cslip_66 ( 3 , 1 , i ) = constitutive_nonlocal_C13 ( i )
constitutive_nonlocal_Cslip_66 ( 2 , 3 , i ) = constitutive_nonlocal_C13 ( i )
constitutive_nonlocal_Cslip_66 ( 3 , 2 , i ) = constitutive_nonlocal_C13 ( i )
constitutive_nonlocal_Cslip_66 ( 4 , 4 , i ) = constitutive_nonlocal_C44 ( i )
constitutive_nonlocal_Cslip_66 ( 5 , 5 , i ) = constitutive_nonlocal_C44 ( i )
constitutive_nonlocal_Cslip_66 ( 6 , 6 , i ) = 0.5_pReal * ( constitutive_nonlocal_C11 ( i ) - constitutive_nonlocal_C12 ( i ) )
end select
constitutive_nonlocal_Cslip_66 ( : , : , i ) = math_Mandel3333to66 ( math_Voigt66to3333 ( constitutive_nonlocal_Cslip_66 ( : , : , i ) ) )
constitutive_nonlocal_Cslip_3333 ( : , : , : , : , i ) = math_Voigt66to3333 ( constitutive_nonlocal_Cslip_66 ( : , : , i ) )
2010-06-07 20:02:23 +05:30
constitutive_nonlocal_Gmod ( i ) = 0.2_pReal * ( constitutive_nonlocal_C11 ( i ) - constitutive_nonlocal_C12 ( i ) &
+ 3.0_pReal * constitutive_nonlocal_C44 ( i ) ) ! (C11iso-C12iso)/2 with C11iso=(3*C11+2*C12+4*C44)/5 and C12iso=(C11+4*C12-2*C44)/5
constitutive_nonlocal_nu ( i ) = ( constitutive_nonlocal_C11 ( i ) + 4.0_pReal * constitutive_nonlocal_C12 ( i ) &
- 2.0_pReal * constitutive_nonlocal_C44 ( i ) ) &
/ ( 4.0_pReal * constitutive_nonlocal_C11 ( i ) + 6.0_pReal * constitutive_nonlocal_C12 ( i ) &
+ 2.0_pReal * constitutive_nonlocal_C44 ( i ) ) ! C12iso/(C11iso+C12iso) with C11iso=(3*C11+2*C12+4*C44)/5 and C12iso=(C11+4*C12-2*C44)/5
2009-08-11 22:01:57 +05:30
2009-10-07 21:01:52 +05:30
do s1 = 1 , ns
2009-08-12 16:52:02 +05:30
2009-10-07 21:01:52 +05:30
f = constitutive_nonlocal_slipFamily ( s1 , i )
2009-08-12 16:52:02 +05:30
2009-10-07 21:01:52 +05:30
!*** burgers vector, dislocation velocity prefactor, mean free path prefactor and minimum dipole distance for each slip system
2009-08-11 22:01:57 +05:30
2009-10-07 21:01:52 +05:30
constitutive_nonlocal_burgersPerSlipSystem ( s1 , i ) = constitutive_nonlocal_burgersPerSlipFamily ( f , i )
constitutive_nonlocal_v0PerSlipSystem ( s1 , i ) = constitutive_nonlocal_v0PerSlipFamily ( f , i )
constitutive_nonlocal_lambda0PerSlipSystem ( s1 , i ) = constitutive_nonlocal_lambda0PerSlipFamily ( f , i )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
constitutive_nonlocal_dLowerEdgePerSlipSystem ( s1 , i ) = constitutive_nonlocal_dLowerEdgePerSlipFamily ( f , i )
constitutive_nonlocal_dLowerScrewPerSlipSystem ( s1 , i ) = constitutive_nonlocal_dLowerScrewPerSlipFamily ( f , i )
2009-10-07 21:01:52 +05:30
do s2 = 1 , ns
2009-08-11 22:01:57 +05:30
2009-10-07 21:01:52 +05:30
!*** calculation of forest projections for edge and screw dislocations. s2 acts as forest to s1
2009-08-11 22:01:57 +05:30
constitutive_nonlocal_forestProjectionEdge ( s1 , s2 , i ) &
= abs ( math_mul3x3 ( lattice_sn ( : , constitutive_nonlocal_slipSystemLattice ( s1 , i ) , myStructure ) , &
2009-10-07 21:01:52 +05:30
lattice_st ( : , constitutive_nonlocal_slipSystemLattice ( s2 , i ) , myStructure ) ) ) ! forest projection of edge dislocations is the projection of (t = b x n) onto the slip normal of the respective slip plane
2009-08-11 22:01:57 +05:30
constitutive_nonlocal_forestProjectionScrew ( s1 , s2 , i ) &
= abs ( math_mul3x3 ( lattice_sn ( : , constitutive_nonlocal_slipSystemLattice ( s1 , i ) , myStructure ) , &
lattice_sd ( : , constitutive_nonlocal_slipSystemLattice ( s2 , i ) , myStructure ) ) ) ! forest projection of screw dislocations is the projection of b onto the slip normal of the respective splip plane
!*** calculation of interaction matrices
2009-10-07 21:01:52 +05:30
2009-08-11 22:01:57 +05:30
constitutive_nonlocal_interactionMatrixSlipSlip ( s1 , s2 , i ) &
= constitutive_nonlocal_interactionSlipSlip ( lattice_interactionSlipSlip ( constitutive_nonlocal_slipSystemLattice ( s1 , i ) , &
constitutive_nonlocal_slipSystemLattice ( s2 , i ) , &
myStructure ) , &
i )
2009-10-07 21:01:52 +05:30
enddo ; enddo
2009-08-11 22:01:57 +05:30
enddo
endsubroutine
!*********************************************************************
!* initial microstructural state (just the "basic" states) *
!*********************************************************************
pure function constitutive_nonlocal_stateInit ( myInstance )
use prec , only : pReal , &
pInt
use lattice , only : lattice_maxNslipFamily
implicit none
!*** input variables
integer ( pInt ) , intent ( in ) :: myInstance ! number specifying the current instance of the constitution
!*** output variables
real ( pReal ) , dimension ( constitutive_nonlocal_sizeState ( myInstance ) ) :: &
constitutive_nonlocal_stateInit
!*** local variables
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( myInstance ) ) :: &
2010-01-05 21:37:24 +05:30
rhoSglEdgePos , & ! positive edge dislocation density
rhoSglEdgeNeg , & ! negative edge dislocation density
rhoSglScrewPos , & ! positive screw dislocation density
rhoSglScrewNeg , & ! negative screw dislocation density
rhoSglEdgePosUsed , & ! used positive edge dislocation density
rhoSglEdgeNegUsed , & ! used negative edge dislocation density
rhoSglScrewPosUsed , & ! used positive screw dislocation density
rhoSglScrewNegUsed , & ! used negative screw dislocation density
rhoDipEdge , & ! edge dipole dislocation density
rhoDipScrew , & ! screw dipole dislocation density
2009-08-11 22:01:57 +05:30
rhoForest , & ! forest dislocation density
tauSlipThreshold ! threshold shear stress for slip
integer ( pInt ) ns , & ! short notation for total number of active slip systems
f , & ! index of lattice family
2009-10-07 21:01:52 +05:30
from , &
upto , &
2009-08-11 22:01:57 +05:30
s ! index of slip system
constitutive_nonlocal_stateInit = 0.0_pReal
ns = constitutive_nonlocal_totalNslip ( myInstance )
!*** set the basic state variables
do f = 1 , lattice_maxNslipFamily
2009-10-07 21:01:52 +05:30
from = 1 + sum ( constitutive_nonlocal_Nslip ( 1 : f - 1 , myInstance ) )
upto = sum ( constitutive_nonlocal_Nslip ( 1 : f , myInstance ) )
2010-01-05 21:37:24 +05:30
rhoSglEdgePos ( from : upto ) = constitutive_nonlocal_rhoSglEdgePos0 ( f , myInstance )
rhoSglEdgeNeg ( from : upto ) = constitutive_nonlocal_rhoSglEdgeNeg0 ( f , myInstance )
rhoSglScrewPos ( from : upto ) = constitutive_nonlocal_rhoSglScrewPos0 ( f , myInstance )
rhoSglScrewNeg ( from : upto ) = constitutive_nonlocal_rhoSglScrewNeg0 ( f , myInstance )
rhoSglEdgePosUsed ( from : upto ) = 0.0_pReal
rhoSglEdgeNegUsed ( from : upto ) = 0.0_pReal
rhoSglScrewPosUsed ( from : upto ) = 0.0_pReal
rhoSglScrewNegUsed ( from : upto ) = 0.0_pReal
rhoDipEdge ( from : upto ) = constitutive_nonlocal_rhoDipEdge0 ( f , myInstance )
rhoDipScrew ( from : upto ) = constitutive_nonlocal_rhoDipScrew0 ( f , myInstance )
2009-08-28 19:20:47 +05:30
enddo
2009-08-11 22:01:57 +05:30
!*** put everything together and in right order
2010-01-05 21:37:24 +05:30
constitutive_nonlocal_stateInit ( 1 : ns ) = rhoSglEdgePos
constitutive_nonlocal_stateInit ( ns + 1 : 2 * ns ) = rhoSglEdgeNeg
constitutive_nonlocal_stateInit ( 2 * ns + 1 : 3 * ns ) = rhoSglScrewPos
constitutive_nonlocal_stateInit ( 3 * ns + 1 : 4 * ns ) = rhoSglScrewNeg
constitutive_nonlocal_stateInit ( 4 * ns + 1 : 5 * ns ) = rhoSglEdgePosUsed
constitutive_nonlocal_stateInit ( 5 * ns + 1 : 6 * ns ) = rhoSglEdgeNegUsed
constitutive_nonlocal_stateInit ( 6 * ns + 1 : 7 * ns ) = rhoSglScrewPosUsed
constitutive_nonlocal_stateInit ( 7 * ns + 1 : 8 * ns ) = rhoSglScrewNegUsed
constitutive_nonlocal_stateInit ( 8 * ns + 1 : 9 * ns ) = rhoDipEdge
constitutive_nonlocal_stateInit ( 9 * ns + 1 : 10 * ns ) = rhoDipScrew
2009-08-11 22:01:57 +05:30
endfunction
2009-09-18 21:07:14 +05:30
!*********************************************************************
!* relevant microstructural state *
!*********************************************************************
pure function constitutive_nonlocal_relevantState ( myInstance )
use prec , only : pReal , &
pInt
implicit none
!*** input variables
integer ( pInt ) , intent ( in ) :: myInstance ! number specifying the current instance of the constitution
!*** output variables
real ( pReal ) , dimension ( constitutive_nonlocal_sizeState ( myInstance ) ) :: &
constitutive_nonlocal_relevantState ! relevant state values for the current instance of this constitution
!*** local variables
constitutive_nonlocal_relevantState = constitutive_nonlocal_relevantRho ( myInstance )
endfunction
2009-08-11 22:01:57 +05:30
!*********************************************************************
!* calculates homogenized elacticity matrix *
!*********************************************************************
pure function constitutive_nonlocal_homogenizedC ( state , g , ip , el )
use prec , only : pReal , &
pInt , &
p_vec
use mesh , only : mesh_NcpElems , &
mesh_maxNips
use material , only : homogenization_maxNgrains , &
material_phase , &
phase_constitutionInstance
implicit none
!*** input variables
integer ( pInt ) , intent ( in ) :: g , & ! current grain ID
ip , & ! current integration point
el ! current element
type ( p_vec ) , dimension ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: state ! microstructural state
!*** output variables
real ( pReal ) , dimension ( 6 , 6 ) :: constitutive_nonlocal_homogenizedC ! homogenized elasticity matrix
!*** local variables
integer ( pInt ) myInstance ! current instance of this constitution
myInstance = phase_constitutionInstance ( material_phase ( g , ip , el ) )
constitutive_nonlocal_homogenizedC = constitutive_nonlocal_Cslip_66 ( : , : , myInstance )
endfunction
!*********************************************************************
!* calculates quantities characterizing the microstructure *
!*********************************************************************
2010-06-07 21:31:37 +05:30
subroutine constitutive_nonlocal_microstructure ( state , Temperature , Tstar_v , Fe , Fp , disorientation , g , ip , el )
2009-08-11 22:01:57 +05:30
use prec , only : pReal , &
pInt , &
p_vec
use math , only : math_Plain3333to99 , &
math_Mandel33to6 , &
math_Mandel6to33 , &
math_mul33x33 , &
math_mul3x3 , &
math_mul33x3 , &
2009-10-07 21:01:52 +05:30
math_inv3x3 , &
math_det3x3 , &
2009-08-11 22:01:57 +05:30
pi
2010-02-17 18:51:36 +05:30
use debug , only : debugger , &
2010-05-21 14:21:15 +05:30
verboseDebugger , &
2010-02-17 18:51:36 +05:30
selectiveDebugger
2009-08-11 22:01:57 +05:30
use mesh , only : mesh_NcpElems , &
mesh_maxNips , &
2010-06-07 21:31:37 +05:30
mesh_maxNipNeighbors , &
2009-08-11 22:01:57 +05:30
mesh_element , &
FE_NipNeighbors , &
mesh_ipNeighborhood , &
mesh_ipVolume , &
mesh_ipCenterOfGravity
use material , only : homogenization_maxNgrains , &
material_phase , &
phase_constitutionInstance
use lattice , only : lattice_Sslip , &
lattice_Sslip_v , &
lattice_maxNslipFamily , &
lattice_NslipSystem , &
lattice_maxNslip , &
lattice_sd , &
lattice_sn , &
lattice_st
implicit none
!*** input variables
integer ( pInt ) , intent ( in ) :: g , & ! current grain ID
ip , & ! current integration point
el ! current element
real ( pReal ) , intent ( in ) :: Temperature ! temperature
real ( pReal ) , dimension ( 3 , 3 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
2009-10-07 21:01:52 +05:30
Fe , & ! elastic deformation gradient
2009-08-11 22:01:57 +05:30
Fp ! plastic deformation gradient
2010-02-17 18:51:36 +05:30
real ( pReal ) , dimension ( 6 ) , intent ( in ) :: &
Tstar_v ! 2nd Piola-Kirchhoff stress in Mandel notation
2010-06-07 21:31:37 +05:30
real ( pReal ) , dimension ( 4 , mesh_maxNipNeighbors ) , intent ( in ) :: &
disorientation ! crystal disorientation between me and my neighbor as quaternion
2010-02-17 18:51:36 +05:30
2009-08-11 22:01:57 +05:30
!*** input/output variables
type ( p_vec ) , dimension ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( inout ) :: &
state ! microstructural state
!*** output variables
!*** local variables
integer ( pInt ) myInstance , & ! current instance of this constitution
myStructure , & ! current lattice structure
ns , & ! short notation for the total number of active slip systems
neighboring_el , & ! element number of my neighbor
neighboring_ip , & ! integration point of my neighbor
2010-01-05 21:37:24 +05:30
c , & ! index of dilsocation character (edge, screw)
2009-08-11 22:01:57 +05:30
n , & ! index of my current neighbor
2010-05-21 14:21:15 +05:30
opposite_n , & ! index of my opposite neighbor
opposite_ip , & ! ip of my opposite neighbor
opposite_el , & ! element index of my opposite neighbor
2009-08-11 22:01:57 +05:30
s , & ! index of my current slip system
2010-01-05 21:37:24 +05:30
t , & ! index of dilsocation type (e+, e-, s+, s-, used e+, used e-, used s+, used s-)
2010-06-07 20:02:23 +05:30
sLattice , & ! index of my current slip system according to lattice order
i , &
j
2009-08-11 22:01:57 +05:30
real ( pReal ) gb , & ! short notation for G*b/2/pi
x , & ! coordinate in direction of lvec
y , & ! coordinate in direction of bvec
2009-10-07 21:01:52 +05:30
z , & ! coordinate in direction of nvec
2010-06-07 20:02:23 +05:30
a , & ! coordinate offset from dislocation core
2009-10-07 21:01:52 +05:30
detFe , & ! determinant of elastic deformation gradient
2010-06-07 20:02:23 +05:30
neighboring_detFe , & ! determinant of my neighboring elastic deformation gradient
L , & ! dislocation segment length
r1_2 , &
r2_2
2010-06-07 21:31:37 +05:30
real ( pReal ) , dimension ( 6 ) :: transmissivity ! transmissivity factor for each interface
2010-06-07 20:02:23 +05:30
real ( pReal ) , dimension ( 2 ) :: lambda ! distance of (x y z) from the segment end projected onto the dislocation segment
2010-05-21 14:21:15 +05:30
real ( pReal ) , dimension ( 3 , 6 ) :: connectingVector ! vector connecting the centers of gravity of me and my neigbor (for each neighbor)
2009-08-28 19:20:47 +05:30
real ( pReal ) , dimension ( 6 ) :: Tdislocation_v ! dislocation stress (resulting from the neighboring excess dislocation densities) as 2nd Piola-Kirchhoff stress in Mandel notation
2010-06-07 20:02:23 +05:30
real ( pReal ) , dimension ( 3 , 3 , 2 ) :: sigma ! dislocation stress for both ends of a single dislocation segment
real ( pReal ) , dimension ( 3 , 3 ) :: lattice2slip , & ! orthogonal transformation matrix from lattice coordinate system to slip coordinate system with e1=bxn, e2=b, e3=n (passive rotation!!!)
2009-10-07 21:01:52 +05:30
neighboringSlip2myLattice , & ! mapping from my neighbors slip coordinate system to my lattice coordinate system
2010-06-07 20:02:23 +05:30
deltaSigma , & ! Tdislocation resulting from the excess dislocation density on one slip system of one neighbor calculated in the coordinate system of the slip system
2009-10-07 21:01:52 +05:30
F , & ! total deformation gradient
neighboring_F , & ! total deformation gradient of my neighbor
Favg , & ! average total deformation gradient of me and my neighbor
invFe , & ! inverse of elastic deformation gradient
neighboring_invFe ! inverse of my neighboring elastic deformation gradient
2010-01-05 21:37:24 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 8 ) :: &
rhoSgl , & ! single dislocation density (edge+, edge-, screw+, screw-, used edge+, used edge-, used screw+, used screw-)
neighboring_rhoSgl ! single dislocation density of my neighbor (edge+, edge-, screw+, screw-, used edge+, used edge-, used screw+, used screw-)
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 2 ) :: &
rhoDip ! dipole dislocation density (edge, screw)
2009-08-11 22:01:57 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) ) :: &
rhoForest , & ! forest dislocation density
2010-02-17 18:51:36 +05:30
tauThreshold , & ! threshold shear stress
tau , & ! resolved shear stress
2009-08-11 22:01:57 +05:30
neighboring_rhoEdgeExcess , & ! edge excess dislocation density of my neighbor
neighboring_rhoScrewExcess , & ! screw excess dislocation density of my neighbor
neighboring_Nedge , & ! total number of edge excess dislocations in my neighbor
2010-01-05 21:37:24 +05:30
neighboring_Nscrew ! total number of screw excess dislocations in my neighbor
2009-08-11 22:01:57 +05:30
myInstance = phase_constitutionInstance ( material_phase ( g , ip , el ) )
myStructure = constitutive_nonlocal_structure ( myInstance )
ns = constitutive_nonlocal_totalNslip ( myInstance )
!**********************************************************************
!*** get basic states
2010-01-05 21:37:24 +05:30
forall ( t = 1 : 8 ) rhoSgl ( : , t ) = state ( g , ip , el ) % p ( ( t - 1 ) * ns + 1 : t * ns )
forall ( c = 1 : 2 ) rhoDip ( : , c ) = state ( g , ip , el ) % p ( ( c + 7 ) * ns + 1 : ( c + 8 ) * ns )
2009-08-11 22:01:57 +05:30
!**********************************************************************
!*** calculate dependent states
!*** calculate the forest dislocation density
forall ( s = 1 : ns ) &
2010-01-05 21:37:24 +05:30
rhoForest ( s ) = dot_product ( ( sum ( abs ( rhoSgl ( : , ( / 1 , 2 , 5 , 6 / ) ) ) , 2 ) + rhoDip ( : , 1 ) ) , &
constitutive_nonlocal_forestProjectionEdge ( s , 1 : ns , myInstance ) ) &
+ dot_product ( ( sum ( abs ( rhoSgl ( : , ( / 3 , 4 , 7 , 8 / ) ) ) , 2 ) + rhoDip ( : , 2 ) ) , &
constitutive_nonlocal_forestProjectionScrew ( s , 1 : ns , myInstance ) ) ! calculation of forest dislocation density as projection of screw and edge dislocations
2009-12-15 13:50:31 +05:30
! if (debugger) write(6,'(a30,3(i3,x),/,12(e10.3,x),/)') 'forest dislocation density at ',g,ip,el, rhoForest
2009-08-11 22:01:57 +05:30
2009-10-07 21:01:52 +05:30
2009-08-11 22:01:57 +05:30
!*** calculate the threshold shear stress for dislocation slip
forall ( s = 1 : ns ) &
2010-02-17 18:51:36 +05:30
tauThreshold ( s ) = constitutive_nonlocal_Gmod ( myInstance ) &
* constitutive_nonlocal_burgersPerSlipSystem ( s , myInstance ) &
* sqrt ( dot_product ( ( sum ( abs ( rhoSgl ) , 2 ) + sum ( abs ( rhoDip ) , 2 ) ) , &
constitutive_nonlocal_interactionMatrixSlipSlip ( s , 1 : ns , myInstance ) ) )
2010-06-07 20:02:23 +05:30
! if (debugger) write(6,'(a22,3(i3,x),/,12(f10.5,x),/)') 'tauThreshold / MPa at ',g,ip,el, tauThreshold/1e6
2009-08-28 19:20:47 +05:30
2009-08-11 22:01:57 +05:30
2009-08-28 19:20:47 +05:30
!*** calculate the dislocation stress of the neighboring excess dislocation densities
2009-08-11 22:01:57 +05:30
2009-08-28 19:20:47 +05:30
Tdislocation_v = 0.0_pReal
2010-05-21 14:21:15 +05:30
connectingVector = 0.0_pReal
2009-10-07 21:01:52 +05:30
F = math_mul33x33 ( Fe ( : , : , g , ip , el ) , Fp ( : , : , g , ip , el ) )
detFe = math_det3x3 ( Fe )
invFe = math_inv3x3 ( Fe )
2009-08-11 22:01:57 +05:30
do n = 1 , FE_NipNeighbors ( mesh_element ( 2 , el ) )
2010-05-21 14:21:15 +05:30
2010-06-07 21:31:37 +05:30
transmissivity ( n ) = constitutive_nonlocal_transmissivity ( disorientation ( : , n ) )
2009-08-11 22:01:57 +05:30
neighboring_el = mesh_ipNeighborhood ( 1 , n , ip , el )
2010-05-21 14:21:15 +05:30
neighboring_ip = mesh_ipNeighborhood ( 2 , n , ip , el )
2010-06-07 21:31:37 +05:30
if ( neighboring_ip == 0 . or . transmissivity ( n ) < 1.0_pReal ) & ! if no neighbor present or at grain boundary, don't calculate anything, since we use mirrored connecting vector of opposite neighbor
2010-05-21 14:21:15 +05:30
cycle
2009-08-11 22:01:57 +05:30
2009-10-07 21:01:52 +05:30
neighboring_F = math_mul33x33 ( Fe ( : , : , g , neighboring_ip , neighboring_el ) , Fp ( : , : , g , neighboring_ip , neighboring_el ) )
Favg = 0.5_pReal * ( F + neighboring_F )
neighboring_detFe = math_det3x3 ( Fe ( : , : , g , neighboring_ip , neighboring_el ) )
neighboring_invFe = math_inv3x3 ( Fe ( : , : , g , neighboring_ip , neighboring_el ) )
2009-08-11 22:01:57 +05:30
2010-05-21 14:21:15 +05:30
connectingVector ( : , n ) = math_mul33x3 ( neighboring_invFe , math_mul33x3 ( Favg , &
2010-01-05 21:37:24 +05:30
( mesh_ipCenterOfGravity ( : , neighboring_ip , neighboring_el ) - mesh_ipCenterOfGravity ( : , ip , el ) ) ) ) ! calculate connection vector between me and my neighbor in its lattice configuration
2009-08-11 22:01:57 +05:30
2010-05-21 14:21:15 +05:30
opposite_n = n - 1_pInt + 2_pInt * mod ( n , 2_pInt )
opposite_el = mesh_ipNeighborhood ( 1 , opposite_n , ip , el )
opposite_ip = mesh_ipNeighborhood ( 2 , opposite_n , ip , el )
2010-06-07 21:31:37 +05:30
if ( opposite_ip == 0 . or . transmissivity ( opposite_n ) < 1.0_pReal ) & ! if no opposite neighbor present or at grain boundary ...
connectingVector ( : , opposite_n ) = - connectingVector ( : , n ) ! ... use mirrored connecting vector of opposite neighbor
2010-05-21 14:21:15 +05:30
enddo
do n = 1 , FE_NipNeighbors ( mesh_element ( 2 , el ) ) ! loop through my neighbors
neighboring_el = mesh_ipNeighborhood ( 1 , n , ip , el )
neighboring_ip = mesh_ipNeighborhood ( 2 , n , ip , el )
2010-06-07 21:31:37 +05:30
if ( neighboring_ip == 0 . or . transmissivity ( n ) < 1.0_pReal ) then ! if no neighbor present or at grain boundary ...
2010-05-21 14:21:15 +05:30
opposite_n = n - 1_pInt + 2_pInt * mod ( n , 2_pInt )
opposite_el = mesh_ipNeighborhood ( 1 , opposite_n , ip , el )
opposite_ip = mesh_ipNeighborhood ( 2 , opposite_n , ip , el )
2010-06-07 21:31:37 +05:30
if ( opposite_ip == 0 . or . transmissivity ( opposite_n ) < 1.0_pReal ) & ! (special case if no valid neighbor on both sides)
2010-06-07 20:02:23 +05:30
cycle
neighboring_el = opposite_el
2010-05-21 14:21:15 +05:30
neighboring_ip = opposite_ip
2010-05-28 18:42:36 +05:30
forall ( t = 1 : 8 , s = 1 : ns ) &
neighboring_rhoSgl ( s , t ) = max ( 0.0_pReal , &
2010-06-07 21:31:37 +05:30
2.0_pReal * state ( g , ip , el ) % p ( ( t - 1 ) * ns + s ) - state ( g , opposite_ip , opposite_el ) % p ( ( t - 1 ) * ns + s ) ) ! ... extrapolate density from opposite neighbor (but assure positive value for density)
2010-05-21 14:21:15 +05:30
else
forall ( t = 1 : 8 ) neighboring_rhoSgl ( : , t ) = state ( g , neighboring_ip , neighboring_el ) % p ( ( t - 1 ) * ns + 1 : t * ns )
endif
2010-01-05 21:37:24 +05:30
neighboring_rhoEdgeExcess = sum ( abs ( neighboring_rhoSgl ( : , ( / 1 , 5 / ) ) ) , 2 ) - sum ( abs ( neighboring_rhoSgl ( : , ( / 2 , 6 / ) ) ) , 2 )
neighboring_rhoScrewExcess = sum ( abs ( neighboring_rhoSgl ( : , ( / 3 , 7 / ) ) ) , 2 ) - sum ( abs ( neighboring_rhoSgl ( : , ( / 4 , 8 / ) ) ) , 2 )
2009-08-11 22:01:57 +05:30
2010-06-07 20:02:23 +05:30
L = mesh_ipVolume ( neighboring_ip , neighboring_el ) ** ( 1.0_pReal / 3.0_pReal )
neighboring_Nedge = neighboring_rhoEdgeExcess * mesh_ipVolume ( neighboring_ip , neighboring_el ) / L
neighboring_Nscrew = neighboring_rhoScrewExcess * mesh_ipVolume ( neighboring_ip , neighboring_el ) / L
2010-05-28 18:42:36 +05:30
2009-08-11 22:01:57 +05:30
do s = 1 , ns
2010-06-07 20:02:23 +05:30
deltaSigma = 0.0_pReal
2010-05-28 18:42:36 +05:30
lattice2slip = transpose ( reshape ( ( / lattice_st ( : , constitutive_nonlocal_slipSystemLattice ( s , myInstance ) , myStructure ) , &
lattice_sd ( : , constitutive_nonlocal_slipSystemLattice ( s , myInstance ) , myStructure ) , &
lattice_sn ( : , constitutive_nonlocal_slipSystemLattice ( s , myInstance ) , myStructure ) / ) , &
( / 3 , 3 / ) ) )
2009-08-11 22:01:57 +05:30
2010-05-21 14:21:15 +05:30
x = math_mul3x3 ( lattice2slip ( 1 , : ) , - connectingVector ( : , n ) ) ! coordinate transformation of connecting vector from the lattice coordinate system to the slip coordinate system
y = math_mul3x3 ( lattice2slip ( 2 , : ) , - connectingVector ( : , n ) )
z = math_mul3x3 ( lattice2slip ( 3 , : ) , - connectingVector ( : , n ) )
2010-06-07 20:02:23 +05:30
a = constitutive_nonlocal_a ( myInstance ) * constitutive_nonlocal_burgersPerSlipSystem ( s , myInstance )
gb = constitutive_nonlocal_Gmod ( myInstance ) * constitutive_nonlocal_burgersPerSlipSystem ( s , myInstance ) &
/ ( 4.0_pReal * pi * ( 1.0_pReal - constitutive_nonlocal_nu ( myInstance ) ) )
! EDGE CONTRIBUTION
2009-08-11 22:01:57 +05:30
2010-06-07 20:02:23 +05:30
lambda = ( / 0.5_pReal * L - x , - 0.5_pReal * L - x / )
r1_2 = y ** 2.0_pReal + z ** 2.0_pReal + a ** 2.0_pReal
2009-08-11 22:01:57 +05:30
2010-06-07 20:02:23 +05:30
sigma = 0.0_pReal
do i = 1 , 2
r2_2 = lambda ( i ) ** 2.0_pReal + r1_2
sigma ( 1 , 1 , i ) = z * lambda ( i ) / dsqrt ( r2_2 ) * ( - 2.0_pReal * constitutive_nonlocal_nu ( myInstance ) / r1_2 &
* ( 1.0_pReal + a ** 2.0_pReal / r1_2 + 0.5_pReal * a ** 2.0_pReal / r2_2 ) &
+ 1.0_pReal / r2_2 )
sigma ( 2 , 2 , i ) = z * lambda ( i ) / ( r1_2 * dsqrt ( r2_2 ) ) &
* ( 1.0_pReal + 2.0_pReal * ( y ** 2.0_pReal + a ** 2.0_pReal ) / r1_2 + ( y ** 2.0_pReal + a ** 2.0_pReal ) / r2_2 )
sigma ( 3 , 3 , i ) = z * lambda ( i ) / ( r1_2 * dsqrt ( r2_2 ) ) &
* ( 1.0_pReal - 2.0_pReal * ( z ** 2.0_pReal + a ** 2.0_pReal ) / r1_2 - ( z ** 2.0_pReal + a ** 2.0_pReal ) / r2_2 )
sigma ( 1 , 2 , i ) = y * z / ( r2_2 * dsqrt ( r2_2 ) )
sigma ( 2 , 3 , i ) = y * lambda ( i ) / ( r1_2 * dsqrt ( r2_2 ) ) * ( 1.0_pReal - 2.0_pReal * z ** 2.0_pReal / r1_2 - z ** 2.0_pReal / r2_2 )
sigma ( 1 , 3 , i ) = 1.0_pReal / dsqrt ( r2_2 ) * ( constitutive_nonlocal_nu ( myInstance ) - z ** 2.0_pReal / r2_2 &
- 0.5_pReal * ( 1.0_pReal - constitutive_nonlocal_nu ( myInstance ) ) * a ** 2.0_pReal / r2_2 )
enddo
forall ( i = 1 : 3 , j = 1 : 3 , i < = j ) &
deltaSigma ( i , j ) = ( sigma ( i , j , 1 ) - sigma ( i , j , 2 ) ) * gb * neighboring_Nedge ( s )
! SCREW CONTRIBUTION
2009-08-11 22:01:57 +05:30
2010-06-07 20:02:23 +05:30
lambda = ( / 0.5_pReal * L - y , - 0.5_pReal * L - y / )
r1_2 = x ** 2.0_pReal + z ** 2.0_pReal + a ** 2.0_pReal
2009-08-11 22:01:57 +05:30
2010-06-07 20:02:23 +05:30
sigma = 0.0_pReal
do i = 1 , 2
r2_2 = lambda ( i ) ** 2.0_pReal + r1_2
sigma ( 1 , 2 , i ) = z * ( 1.0_pReal - constitutive_nonlocal_nu ( myInstance ) ) * lambda ( i ) / ( r1_2 * dsqrt ( r2_2 ) ) &
* ( 1.0_pReal + a ** 2.0_pReal / r1_2 + 0.5_pReal * a ** 2.0_pReal / r2_2 )
sigma ( 2 , 3 , i ) = - x * ( 1.0_pReal - constitutive_nonlocal_nu ( myInstance ) ) * lambda ( i ) / ( r1_2 * dsqrt ( r2_2 ) ) &
* ( 1.0_pReal + a ** 2.0_pReal / r1_2 + 0.5_pReal * a ** 2.0_pReal / r2_2 )
enddo
2009-08-11 22:01:57 +05:30
2010-06-07 20:02:23 +05:30
forall ( i = 1 : 2 , j = 2 : 3 , i < j ) &
deltaSigma ( i , j ) = deltaSigma ( i , j ) + ( sigma ( i , j , 1 ) - sigma ( i , j , 2 ) ) * gb * neighboring_Nscrew ( s )
2009-08-11 22:01:57 +05:30
2010-06-07 20:02:23 +05:30
deltaSigma ( 2 , 1 ) = deltaSigma ( 1 , 2 )
deltaSigma ( 3 , 2 ) = deltaSigma ( 2 , 3 )
deltaSigma ( 3 , 1 ) = deltaSigma ( 1 , 3 )
2009-08-11 22:01:57 +05:30
2010-06-07 20:02:23 +05:30
deltaSigma = deltaSigma * &
( constitutive_nonlocal_R ( myInstance ) / mesh_ipVolume ( neighboring_ip , neighboring_el ) ** ( 1.0_pReal / 3.0_pReal ) ) ** 2.0_pReal ! scale stress with (R/meshsize)^2
2010-01-05 21:37:24 +05:30
neighboringSlip2myLattice = math_mul33x33 ( invFe , math_mul33x33 ( Fe ( : , : , g , neighboring_ip , neighboring_el ) , transpose ( lattice2slip ) ) ) ! coordinate transformation from the slip coordinate system to the lattice coordinate system
2010-05-21 14:21:15 +05:30
Tdislocation_v = Tdislocation_v + math_Mandel33to6 ( detFe / math_det3x3 ( Fe ( : , : , g , neighboring_ip , neighboring_el ) ) &
2010-06-07 20:02:23 +05:30
* math_mul33x33 ( neighboringSlip2myLattice , math_mul33x33 ( deltaSigma , transpose ( neighboringSlip2myLattice ) ) ) )
if ( selectiveDebugger . and . verboseDebugger ) then
write ( 6 , * )
2010-06-07 21:31:37 +05:30
write ( 6 , '(a20,i1,x,i2,x,i5)' ) '::: microstructure ' , g , ip , el
2010-06-07 20:02:23 +05:30
write ( 6 , '(i2)' ) n
write ( 6 , '(2(a20,x,e12.3,5x))' ) 'delta_rho_edge:' , neighboring_rhoEdgeExcess ( s ) , 'delta_rho_screw:' , neighboring_rhoScrewExcess ( s )
write ( 6 , '(2(a20,x,f12.3,5x))' ) 'Nedge:' , neighboring_Nedge ( s ) , 'Nscrew:' , neighboring_Nscrew ( s )
write ( 6 , * )
if ( mesh_ipNeighborhood ( 2 , n , ip , el ) > 0 ) then
write ( 6 , '(a20,x,3(f10.3,x))' ) 'delta_g0 / mu:' , &
( mesh_ipCenterOfGravity ( : , mesh_ipNeighborhood ( 2 , n , ip , el ) , mesh_ipNeighborhood ( 1 , n , ip , el ) ) &
- mesh_ipCenterOfGravity ( : , ip , el ) ) * 1e6
else
write ( 6 , '(a20,x,3(f10.3,x))' ) 'delta_g0 / mu:' , 0.0_pReal , 0.0_pReal , 0.0_pReal
endif
write ( 6 , '(a20,x,3(f10.3,x))' ) 'delta_g / mu:' , connectingVector ( : , n ) * 1e6
write ( 6 , '(a20,x,3(f10.3,x))' ) '(x,y,z) / mu:' , x * 1e6 , y * 1e6 , z * 1e6
write ( 6 , * )
write ( 6 , '(a20,/,3(21x,3(f10.4,x)/))' ) 'sigma / MPa:' , transpose ( deltaSigma ) * 1e-6
write ( 6 , '(a20,/,3(21x,3(f10.4,x)/))' ) '2ndPK / MPa:' , transpose ( detFe / math_det3x3 ( Fe ( : , : , g , neighboring_ip , neighboring_el ) ) &
* math_mul33x33 ( neighboringSlip2myLattice , math_mul33x33 ( deltaSigma , transpose ( neighboringSlip2myLattice ) ) ) ) * 1e-6
write ( 6 , * )
endif
2009-08-11 22:01:57 +05:30
enddo
enddo
!**********************************************************************
!*** set dependent states
2010-01-05 21:37:24 +05:30
state ( g , ip , el ) % p ( 10 * ns + 1 : 11 * ns ) = rhoForest
2010-02-17 18:51:36 +05:30
state ( g , ip , el ) % p ( 11 * ns + 1 : 12 * ns ) = tauThreshold
2010-01-05 21:37:24 +05:30
state ( g , ip , el ) % p ( 12 * ns + 1 : 12 * ns + 6 ) = Tdislocation_v
2009-08-11 22:01:57 +05:30
2010-02-17 18:51:36 +05:30
!**********************************************************************
!*** calculate the dislocation velocity
call constitutive_nonlocal_kinetics ( Tstar_v , Temperature , state , g , ip , el )
endsubroutine
!*********************************************************************
!* calculates kinetics *
!*********************************************************************
subroutine constitutive_nonlocal_kinetics ( Tstar_v , Temperature , state , g , ip , el )
use prec , only : pReal , &
pInt , &
p_vec
use math , only : math_mul6x6 , &
math_Mandel6to33
use debug , only : debugger , &
2010-03-19 19:44:08 +05:30
selectiveDebugger , &
verboseDebugger
2010-02-17 18:51:36 +05:30
use mesh , only : mesh_NcpElems , &
mesh_maxNips
use material , only : homogenization_maxNgrains , &
material_phase , &
phase_constitutionInstance
use lattice , only : lattice_Sslip , &
lattice_Sslip_v
implicit none
!*** input variables
integer ( pInt ) , intent ( in ) :: g , & ! current grain number
ip , & ! current integration point
el ! current element number
real ( pReal ) , intent ( in ) :: Temperature ! temperature
type ( p_vec ) , dimension ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
state ! microstructural state
real ( pReal ) , dimension ( 6 ) , intent ( in ) :: Tstar_v ! 2nd Piola-Kirchhoff stress in Mandel notation
!*** output variables
!*** local variables
integer ( pInt ) myInstance , & ! current instance of this constitution
myStructure , & ! current lattice structure
ns , & ! short notation for the total number of active slip systems
t , & ! dislocation type
s ! index of my current slip system
real ( pReal ) , dimension ( 6 ) :: Tdislocation_v ! dislocation stress (resulting from the neighboring excess dislocation densities) as 2nd Piola-Kirchhoff stress
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) ) :: &
tauThreshold , & ! threshold shear stress
tau ! resolved shear stress
myInstance = phase_constitutionInstance ( material_phase ( g , ip , el ) )
myStructure = constitutive_nonlocal_structure ( myInstance )
ns = constitutive_nonlocal_totalNslip ( myInstance )
tauThreshold = state ( g , ip , el ) % p ( 11 * ns + 1 : 12 * ns )
Tdislocation_v = state ( g , ip , el ) % p ( 12 * ns + 1 : 12 * ns + 6 )
tau = 0.0_pReal
constitutive_nonlocal_v ( : , : , g , ip , el ) = 0.0_pReal
do s = 1 , ns
if ( ( tauThreshold ( s ) > 0.0_pReal ) . and . ( Temperature > 0.0_pReal ) ) then
tau ( s ) = math_mul6x6 ( Tstar_v + Tdislocation_v , &
lattice_Sslip_v ( : , constitutive_nonlocal_slipSystemLattice ( s , myInstance ) , myStructure ) )
constitutive_nonlocal_v ( s , : , g , ip , el ) = constitutive_nonlocal_v0PerSlipSystem ( s , myInstance ) &
* exp ( - constitutive_nonlocal_Q0 ( myInstance ) / ( kB * Temperature ) * ( 1.0_pReal - ( abs ( tau ( s ) ) / tauThreshold ( s ) ) ) ) &
* sign ( 1.0_pReal , tau ( s ) )
endif
enddo
2010-03-19 19:44:08 +05:30
if ( verboseDebugger . and . selectiveDebugger ) then
2010-02-17 18:51:36 +05:30
!$OMP CRITICAL (write2out)
write ( 6 , * ) '::: kinetics' , g , ip , el
write ( 6 , * )
2010-05-21 14:21:15 +05:30
! write(6,'(a,/,3(3(f12.3,x)/))') 'Tdislocation / MPa', math_Mandel6to33(Tdislocation_v/1e6)
! write(6,'(a,/,3(3(f12.3,x)/))') 'Tstar / MPa', math_Mandel6to33(Tstar_v/1e6)
2010-02-17 18:51:36 +05:30
write ( 6 , '(a,/,12(f12.5,x),/)' ) 'tau / MPa' , tau / 1e6_pReal
write ( 6 , '(a,/,12(f12.5,x),/)' ) 'tauThreshold / MPa' , tauThreshold / 1e6_pReal
2010-03-04 22:44:47 +05:30
write ( 6 , '(a,/,4(12(f12.5,x),/))' ) 'v / 1e-3m/s' , constitutive_nonlocal_v ( : , : , g , ip , el ) * 1e3
2010-02-17 18:51:36 +05:30
!$OMPEND CRITICAL (write2out)
endif
2009-08-11 22:01:57 +05:30
endsubroutine
!*********************************************************************
!* calculates plastic velocity gradient and its tangent *
!*********************************************************************
subroutine constitutive_nonlocal_LpAndItsTangent ( Lp , dLp_dTstar99 , Tstar_v , Temperature , state , g , ip , el )
use prec , only : pReal , &
pInt , &
p_vec
use math , only : math_Plain3333to99 , &
math_mul6x6 , &
math_Mandel6to33
2010-02-17 18:51:36 +05:30
use debug , only : debugger , &
2010-03-19 19:44:08 +05:30
selectiveDebugger , &
verboseDebugger
2009-08-11 22:01:57 +05:30
use mesh , only : mesh_NcpElems , &
mesh_maxNips
use material , only : homogenization_maxNgrains , &
material_phase , &
phase_constitutionInstance
use lattice , only : lattice_Sslip , &
lattice_Sslip_v
implicit none
!*** input variables
integer ( pInt ) , intent ( in ) :: g , & ! current grain number
ip , & ! current integration point
el ! current element number
real ( pReal ) , intent ( in ) :: Temperature ! temperature
type ( p_vec ) , dimension ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
state ! microstructural state
real ( pReal ) , dimension ( 6 ) , intent ( in ) :: Tstar_v ! 2nd Piola-Kirchhoff stress in Mandel notation
!*** output variables
real ( pReal ) , dimension ( 3 , 3 ) , intent ( out ) :: Lp ! plastic velocity gradient
real ( pReal ) , dimension ( 9 , 9 ) , intent ( out ) :: dLp_dTstar99 ! derivative of Lp with respect to Tstar (9x9 matrix)
!*** local variables
integer ( pInt ) myInstance , & ! current instance of this constitution
myStructure , & ! current lattice structure
ns , & ! short notation for the total number of active slip systems
i , &
j , &
k , &
l , &
t , & ! dislocation type
s , & ! index of my current slip system
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
sLattice ! index of my current slip system according to lattice order
2009-08-11 22:01:57 +05:30
real ( pReal ) , dimension ( 3 , 3 , 3 , 3 ) :: dLp_dTstar3333 ! derivative of Lp with respect to Tstar (3x3x3x3 matrix)
2010-01-05 21:37:24 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 8 ) :: &
rhoSgl ! single dislocation densities (including used)
2010-02-17 18:51:36 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 4 ) :: &
gdot ! shear rate per dislocation type
2009-08-11 22:01:57 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) ) :: &
2010-02-17 18:51:36 +05:30
tauThreshold , & ! threshold shear stress
gdotTotal , & ! shear rate
dgdotTotal_dtau ! derivative of the shear rate with respect to the shear stress
2009-08-11 22:01:57 +05:30
!*** initialize local variables
2010-02-17 18:51:36 +05:30
gdot = 0.0_pReal
2009-08-11 22:01:57 +05:30
Lp = 0.0_pReal
dLp_dTstar3333 = 0.0_pReal
myInstance = phase_constitutionInstance ( material_phase ( g , ip , el ) )
myStructure = constitutive_nonlocal_structure ( myInstance )
ns = constitutive_nonlocal_totalNslip ( myInstance )
!*** shortcut to state variables
2010-02-17 18:51:36 +05:30
forall ( t = 1 : 8 ) &
rhoSgl ( : , t ) = state ( g , ip , el ) % p ( ( t - 1 ) * ns + 1 : t * ns )
forall ( s = 1 : ns , t = 5 : 8 , rhoSgl ( s , t ) * constitutive_nonlocal_v ( s , t - 4 , g , ip , el ) < 0.0_pReal ) & ! contribution of used rho for changing sign of v
rhoSgl ( s , t - 4 ) = rhoSgl ( s , t - 4 ) + abs ( rhoSgl ( s , t ) )
2009-08-28 19:20:47 +05:30
2010-02-17 18:51:36 +05:30
tauThreshold = state ( g , ip , el ) % p ( 11 * ns + 1 : 12 * ns )
2009-08-28 19:20:47 +05:30
2010-02-17 18:51:36 +05:30
call constitutive_nonlocal_kinetics ( Tstar_v , Temperature , state , g , ip , el ) ! update dislocation velocity
2009-08-28 19:20:47 +05:30
!*** Calculation of gdot and its tangent
2010-02-17 18:51:36 +05:30
forall ( t = 1 : 4 ) &
gdot ( : , t ) = rhoSgl ( : , t ) * constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance ) * constitutive_nonlocal_v ( : , t , g , ip , el )
gdotTotal = sum ( gdot , 2 )
2009-08-28 19:20:47 +05:30
2010-02-17 18:51:36 +05:30
dgdotTotal_dtau = abs ( gdotTotal ) * constitutive_nonlocal_Q0 ( myInstance ) / ( kB * Temperature * tauThreshold )
2009-08-28 19:20:47 +05:30
!*** Calculation of Lp and its tangent
2009-08-24 13:46:01 +05:30
do s = 1 , ns
2009-08-11 22:01:57 +05:30
sLattice = constitutive_nonlocal_slipSystemLattice ( s , myInstance )
2010-02-17 18:51:36 +05:30
Lp = Lp + gdotTotal ( s ) * lattice_Sslip ( : , : , sLattice , myStructure )
2009-08-11 22:01:57 +05:30
forall ( i = 1 : 3 , j = 1 : 3 , k = 1 : 3 , l = 1 : 3 ) &
2010-02-17 18:51:36 +05:30
dLp_dTstar3333 ( i , j , k , l ) = dLp_dTstar3333 ( i , j , k , l ) + dgdotTotal_dtau ( s ) * lattice_Sslip ( i , j , sLattice , myStructure ) &
* lattice_Sslip ( k , l , sLattice , myStructure )
2009-08-11 22:01:57 +05:30
enddo
2009-08-12 16:52:02 +05:30
dLp_dTstar99 = math_Plain3333to99 ( dLp_dTstar3333 )
2010-05-21 14:21:15 +05:30
!if (verboseDebugger .and. selectiveDebugger) then
! !$OMP CRITICAL (write2out)
! write(6,*) '::: LpandItsTangent',g,ip,el
! write(6,*)
! ! write(6,'(a,/,12(f12.5,x),/)') 'v', constitutive_nonlocal_v(:,t,g,ip,el)
! write(6,'(a,/,12(f12.5,x),/)') 'gdot /1e-3',gdot*1e3_pReal
! write(6,'(a,/,12(f12.5,x),/)') 'gdot total /1e-3',gdotTotal*1e3_pReal
! write(6,'(a,/,3(3(f12.7,x)/))') 'Lp',Lp
! ! call flush(6)
! !$OMPEND CRITICAL (write2out)
!endif
2009-08-11 22:01:57 +05:30
endsubroutine
!*********************************************************************
!* rate of change of microstructure *
!*********************************************************************
2010-05-21 14:21:15 +05:30
subroutine constitutive_nonlocal_dotState ( dotState , Tstar_v , previousTstar_v , Fe , Fp , Temperature , disorientation , dt_previous , &
state , previousState , relevantState , timestep , g , ip , el )
2009-08-11 22:01:57 +05:30
use prec , only : pReal , &
pInt , &
p_vec
2010-03-04 22:44:47 +05:30
use IO , only : IO_error
2010-02-17 18:51:36 +05:30
use debug , only : debugger , &
2010-03-19 19:44:08 +05:30
selectiveDebugger , &
verboseDebugger
2009-08-11 22:01:57 +05:30
use math , only : math_norm3 , &
math_mul6x6 , &
math_mul3x3 , &
math_mul33x3 , &
2009-10-07 21:01:52 +05:30
math_mul33x33 , &
math_inv3x3 , &
math_det3x3 , &
2009-12-15 13:50:31 +05:30
math_Mandel6to33 , &
2010-05-21 14:21:15 +05:30
pi , &
NaN
2009-08-11 22:01:57 +05:30
use mesh , only : mesh_NcpElems , &
mesh_maxNips , &
2009-12-18 21:16:33 +05:30
mesh_maxNipNeighbors , &
2009-08-11 22:01:57 +05:30
mesh_element , &
FE_NipNeighbors , &
mesh_ipNeighborhood , &
mesh_ipVolume , &
mesh_ipArea , &
2010-03-04 22:44:47 +05:30
mesh_ipAreaNormal , &
mesh_ipCenterOfGravity
2009-08-11 22:01:57 +05:30
use material , only : homogenization_maxNgrains , &
material_phase , &
2010-03-04 22:44:47 +05:30
phase_constitutionInstance , &
phase_localConstitution
2009-08-11 22:01:57 +05:30
use lattice , only : lattice_Sslip , &
lattice_Sslip_v , &
lattice_sd , &
lattice_sn , &
lattice_st , &
lattice_maxNslipFamily , &
lattice_NslipSystem
implicit none
!*** input variables
integer ( pInt ) , intent ( in ) :: g , & ! current grain number
ip , & ! current integration point
el ! current element number
2009-08-28 19:20:47 +05:30
real ( pReal ) , intent ( in ) :: Temperature , & ! temperature
2009-12-15 13:50:31 +05:30
timestep , & ! substepped crystallite time increment
dt_previous ! time increment between previous and current state
2009-08-28 19:20:47 +05:30
real ( pReal ) , dimension ( 6 ) , intent ( in ) :: Tstar_v , & ! current 2nd Piola-Kirchhoff stress in Mandel notation
2009-12-15 13:50:31 +05:30
previousTstar_v ! previous 2nd Piola-Kirchhoff stress in Mandel notation
2009-12-18 21:16:33 +05:30
real ( pReal ) , dimension ( 4 , mesh_maxNipNeighbors ) , intent ( in ) :: &
2010-06-07 21:31:37 +05:30
disorientation ! crystal disorientation between me and my neighbor as quaternion
2009-10-07 21:01:52 +05:30
real ( pReal ) , dimension ( 3 , 3 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
Fe , & ! elastic deformation gradient
Fp ! plastic deformation gradient
2009-08-11 22:01:57 +05:30
type ( p_vec ) , dimension ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
2009-08-28 19:20:47 +05:30
state , & ! current microstructural state
2010-05-21 14:21:15 +05:30
previousState , & ! previous microstructural state
relevantState ! relevant microstructural state
2009-08-11 22:01:57 +05:30
!*** input/output variables
type ( p_vec ) , dimension ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( inout ) :: &
dotState ! evolution of state variables / microstructure
!*** output variables
!*** local variables
integer ( pInt ) myInstance , & ! current instance of this constitution
myStructure , & ! current lattice structure
ns , & ! short notation for the total number of active slip systems
neighboring_el , & ! element number of my neighbor
neighboring_ip , & ! integration point of my neighbor
2009-08-28 19:20:47 +05:30
c , & ! character of dislocation
2009-08-11 22:01:57 +05:30
n , & ! index of my current neighbor
2010-03-24 21:53:21 +05:30
opposite_n , & ! index of my opposite neighbor
opposite_ip , & ! ip of my opposite neighbor
opposite_el , & ! element index of my opposite neighbor
2009-08-11 22:01:57 +05:30
t , & ! type of dislocation
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
s , & ! index of my current slip system
2010-05-21 14:21:15 +05:30
sLattice , & ! index of my current slip system according to lattice order
i
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 10 ) :: &
rhoDot , & ! density evolution
rhoDotRemobilization , & ! density evolution by remobilization
rhoDotMultiplication , & ! density evolution by multiplication
rhoDotFlux , & ! density evolution by flux
rhoDotSingle2DipoleGlide , & ! density evolution by dipole formation (by glide)
rhoDotAthermalAnnihilation , & ! density evolution by athermal annihilation
rhoDotThermalAnnihilation , & ! density evolution by thermal annihilation
rhoDotDipole2SingleStressChange , & ! density evolution by dipole dissociation (by stress increase)
rhoDotSingle2DipoleStressChange ! density evolution by dipole formation (by stress decrease)
2010-03-24 21:53:21 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 8 ) :: &
rhoSgl , & ! current single dislocation densities (positive/negative screw and edge without dipoles)
2010-05-21 14:21:15 +05:30
previousRhoSgl ! previous single dislocation densities (positive/negative screw and edge without dipoles)
2009-08-28 19:20:47 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 4 ) :: &
2010-03-04 22:44:47 +05:30
fluxdensity , & ! flux density at central material point
neighboring_fluxdensity , & ! flux density at neighbroing material point
2010-02-17 18:51:36 +05:30
gdot ! shear rates
2009-08-11 22:01:57 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) ) :: &
rhoForest , & ! forest dislocation density
2010-02-17 18:51:36 +05:30
tauThreshold , & ! threshold shear stress
tau , & ! current resolved shear stress
previousTau , & ! previous resolved shear stress
2009-08-28 19:20:47 +05:30
invLambda , & ! inverse of mean free path for dislocations
vClimb ! climb velocity of edge dipoles
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 2 ) :: &
2009-12-15 13:50:31 +05:30
rhoDip , & ! current dipole dislocation densities (screw and edge dipoles)
previousRhoDip , & ! previous dipole dislocation densities (screw and edge dipoles)
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
dLower , & ! minimum stable dipole distance for edges and screws
dUpper , & ! current maximum stable dipole distance for edges and screws
2009-12-15 13:50:31 +05:30
previousDUpper , & ! previous maximum stable dipole distance for edges and screws
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
dUpperDot ! rate of change of the maximum stable dipole distance for edges and screws
2009-08-28 19:20:47 +05:30
real ( pReal ) , dimension ( 3 , constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 4 ) :: &
2009-08-11 22:01:57 +05:30
m ! direction of dislocation motion
2009-10-07 21:01:52 +05:30
real ( pReal ) , dimension ( 3 , 3 ) :: F , & ! total deformation gradient
neighboring_F , & ! total deformation gradient of my neighbor
Favg ! average total deformation gradient of me and my neighbor
2009-08-28 19:20:47 +05:30
real ( pReal ) , dimension ( 6 ) :: Tdislocation_v , & ! current dislocation stress (resulting from the neighboring excess dislocation densities) as 2nd Piola-Kirchhoff stress
2009-12-15 13:50:31 +05:30
previousTdislocation_v ! previous dislocation stress (resulting from the neighboring excess dislocation densities) as 2nd Piola-Kirchhoff stress
real ( pReal ) , dimension ( 3 ) :: surfaceNormal , & ! surface normal in lattice configuration
surfaceNormal_currentconf ! surface normal in current configuration
real ( pReal ) area , & ! area of the current interface
2009-10-07 21:01:52 +05:30
detFe , & ! determinant of elastic defornmation gradient
2010-02-17 18:51:36 +05:30
transmissivity , & ! transmissivity of interfaces for dislocation flux
2010-03-04 22:44:47 +05:30
average_fluxdensity , & ! average flux density at interface
maximum_fluxdensity , & ! upper bound for flux density at interface
weight , & ! weight for interpolation of flux density
2010-02-17 18:51:36 +05:30
lineLength , & ! dislocation line length leaving the current interface
2009-08-28 19:20:47 +05:30
D ! self diffusion
2010-03-04 22:44:47 +05:30
logical highOrderScheme ! flag indicating whether we use a high order interpolation scheme or not
2010-03-19 19:44:08 +05:30
if ( verboseDebugger . and . selectiveDebugger ) then
2010-03-04 22:44:47 +05:30
!$OMP CRITICAL (write2out)
write ( 6 , * ) '::: constitutive_nonlocal_dotState at ' , g , ip , el
write ( 6 , * )
!$OMPEND CRITICAL (write2out)
endif
2009-12-15 13:50:31 +05:30
2010-05-18 13:43:23 +05:30
if ( . not . ( mesh_element ( 2 , el ) == 1_pInt &
. or . mesh_element ( 2 , el ) == 6_pInt &
. or . mesh_element ( 2 , el ) == 7_pInt &
. or . mesh_element ( 2 , el ) == 8_pInt ) ) &
2010-03-04 22:44:47 +05:30
call IO_error ( - 1 , el , ip , g , 'element type not supported for nonlocal constitution' )
2009-08-11 22:01:57 +05:30
myInstance = phase_constitutionInstance ( material_phase ( g , ip , el ) )
myStructure = constitutive_nonlocal_structure ( myInstance )
ns = constitutive_nonlocal_totalNslip ( myInstance )
2010-02-17 18:51:36 +05:30
tau = 0.0_pReal
previousTau = 0.0_pReal
2009-08-12 16:52:02 +05:30
gdot = 0.0_pReal
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
dLower = 0.0_pReal
dUpper = 0.0_pReal
2009-12-15 13:50:31 +05:30
previousDUpper = 0.0_pReal
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
dUpperDot = 0.0_pReal
2009-08-11 22:01:57 +05:30
!*** shortcut to state variables
2010-01-05 21:37:24 +05:30
forall ( t = 1 : 8 ) rhoSgl ( : , t ) = state ( g , ip , el ) % p ( ( t - 1 ) * ns + 1 : t * ns )
forall ( t = 1 : 8 ) previousRhoSgl ( : , t ) = previousState ( g , ip , el ) % p ( ( t - 1 ) * ns + 1 : t * ns )
forall ( c = 1 : 2 ) rhoDip ( : , c ) = state ( g , ip , el ) % p ( ( 7 + c ) * ns + 1 : ( 8 + c ) * ns )
forall ( c = 1 : 2 ) previousRhoDip ( : , c ) = previousState ( g , ip , el ) % p ( ( 7 + c ) * ns + 1 : ( 8 + c ) * ns )
rhoForest = state ( g , ip , el ) % p ( 10 * ns + 1 : 11 * ns )
2010-02-17 18:51:36 +05:30
tauThreshold = state ( g , ip , el ) % p ( 11 * ns + 1 : 12 * ns )
2010-01-05 21:37:24 +05:30
Tdislocation_v = state ( g , ip , el ) % p ( 12 * ns + 1 : 12 * ns + 6 )
previousTdislocation_v = previousState ( g , ip , el ) % p ( 12 * ns + 1 : 12 * ns + 6 )
2009-08-11 22:01:57 +05:30
2010-03-04 22:44:47 +05:30
!*** sanity check for timestep
if ( timestep < = 0.0_pReal ) then ! if illegal timestep...
dotState ( 1 , ip , el ) % p ( 1 : 10 * ns ) = 0.0_pReal ! ...return without doing anything (-> zero dotState)
return
endif
if ( any ( constitutive_nonlocal_v ( : , : , g , ip , el ) * timestep > mesh_ipVolume ( ip , el ) ** ( 1.0_pReal / 3.0_pReal ) ) ) then ! if timestep is too large,...
2010-05-21 14:21:15 +05:30
dotState ( 1 , ip , el ) % p ( 1 : 10 * ns ) = NaN ! ...assign NaN and enforce a cutback
if ( verboseDebugger ) then
!$OMP CRITICAL (write2out)
write ( 6 , * ) 'exceeded maximum allowed dislocation velocity at ' , g , ip , el
write ( 6 , * )
!$OMPEND CRITICAL (write2out)
endif
2010-03-04 22:44:47 +05:30
return
endif
2009-08-11 22:01:57 +05:30
2009-08-12 16:52:02 +05:30
!****************************************************************************
!*** Calculate shear rate
2009-08-28 19:20:47 +05:30
forall ( t = 1 : 4 ) &
2010-02-17 18:51:36 +05:30
gdot ( : , t ) = rhoSgl ( : , t ) * constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance ) * constitutive_nonlocal_v ( : , t , g , ip , el )
forall ( s = 1 : ns , t = 1 : 4 , rhoSgl ( s , t + 4 ) * constitutive_nonlocal_v ( s , t , g , ip , el ) < 0.0_pReal ) & ! contribution of used rho for changing sign of v
gdot ( s , t ) = gdot ( s , t ) + abs ( rhoSgl ( s , t + 4 ) ) * constitutive_nonlocal_burgersPerSlipSystem ( s , myInstance ) &
* constitutive_nonlocal_v ( s , t , g , ip , el )
2010-01-05 21:37:24 +05:30
2009-08-12 16:52:02 +05:30
!****************************************************************************
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
!*** calculate limits for stable dipole height and its rate of change
2010-02-17 18:51:36 +05:30
do s = 1 , ns ! loop over slip systems
sLattice = constitutive_nonlocal_slipSystemLattice ( s , myInstance )
tau ( s ) = math_mul6x6 ( Tstar_v + Tdislocation_v , lattice_Sslip_v ( : , sLattice , myStructure ) )
previousTau ( s ) = math_mul6x6 ( previousTstar_v + previousTdislocation_v , lattice_Sslip_v ( : , sLattice , myStructure ) )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
2010-02-17 18:51:36 +05:30
enddo
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
dLower ( : , 1 ) = constitutive_nonlocal_dLowerEdgePerSlipSystem ( : , myInstance )
dLower ( : , 2 ) = constitutive_nonlocal_dLowerScrewPerSlipSystem ( : , myInstance )
2010-02-17 18:51:36 +05:30
dUpper ( : , 2 ) = min ( 1.0_pReal / sqrt ( sum ( abs ( rhoSgl ) , 2 ) + sum ( rhoDip , 2 ) ) , &
constitutive_nonlocal_Gmod ( myInstance ) * constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance ) &
/ ( 8.0_pReal * pi * abs ( tau ) ) )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
dUpper ( : , 1 ) = dUpper ( : , 2 ) / ( 1.0_pReal - constitutive_nonlocal_nu ( myInstance ) )
2010-02-17 18:51:36 +05:30
previousDUpper ( : , 2 ) = min ( 1.0_pReal / sqrt ( sum ( abs ( previousRhoSgl ) , 2 ) + sum ( previousRhoDip , 2 ) ) , &
constitutive_nonlocal_Gmod ( myInstance ) * constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance ) &
/ ( 8.0_pReal * pi * abs ( previousTau ) ) )
2009-12-15 13:50:31 +05:30
previousDUpper ( : , 1 ) = previousDUpper ( : , 2 ) / ( 1.0_pReal - constitutive_nonlocal_nu ( myInstance ) )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
2009-12-15 13:50:31 +05:30
if ( dt_previous > 0.0_pReal ) dUpperDot = ( dUpper - previousDUpper ) / dt_previous
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
2010-01-05 21:37:24 +05:30
!****************************************************************************
2010-01-06 15:24:00 +05:30
!*** dislocation remobilization (bauschinger effect)
2010-01-05 21:37:24 +05:30
2010-05-21 14:21:15 +05:30
rhoDotRemobilization = 0.0_pReal
2010-01-05 21:37:24 +05:30
if ( timestep > 0.0_pReal ) then
do t = 1 , 4
do s = 1 , ns
2010-02-17 18:51:36 +05:30
if ( rhoSgl ( s , t + 4 ) * constitutive_nonlocal_v ( s , t , g , ip , el ) < 0.0_pReal ) then
2010-05-21 14:21:15 +05:30
rhoDotRemobilization ( s , t ) = abs ( rhoSgl ( s , t + 4 ) ) / timestep
2010-01-06 15:24:00 +05:30
rhoSgl ( s , t ) = rhoSgl ( s , t ) + abs ( rhoSgl ( s , t + 4 ) )
2010-05-21 14:21:15 +05:30
rhoDotRemobilization ( s , t + 4 ) = - rhoSgl ( s , t + 4 ) / timestep
2010-01-06 15:24:00 +05:30
rhoSgl ( s , t + 4 ) = 0.0_pReal
2010-01-05 21:37:24 +05:30
endif
enddo
enddo
endif
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
!****************************************************************************
!*** calculate dislocation multiplication
2009-10-07 21:01:52 +05:30
2010-05-21 14:21:15 +05:30
rhoDotMultiplication ( : , 1 : 2 ) = spread ( 0.5_pReal * sum ( abs ( gdot ( : , 3 : 4 ) ) , 2 ) * sqrt ( rhoForest ) &
/ constitutive_nonlocal_lambda0PerSlipSystem ( : , myInstance ) &
/ constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance ) , 2 , 2 )
rhoDotMultiplication ( : , 3 : 4 ) = spread ( 0.5_pReal * sum ( abs ( gdot ( : , 1 : 2 ) ) , 2 ) * sqrt ( rhoForest ) &
/ constitutive_nonlocal_lambda0PerSlipSystem ( : , myInstance ) &
/ constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance ) , 2 , 2 )
rhoDotMultiplication ( : , 5 : 10 ) = 0.0_pReal ! used dislocation densities and dipoles don't multiplicate
2009-08-11 22:01:57 +05:30
2009-08-12 16:52:02 +05:30
!****************************************************************************
!*** calculate dislocation fluxes
2010-05-21 14:21:15 +05:30
rhoDotFlux = 0.0_pReal
2009-10-07 21:01:52 +05:30
2009-08-28 19:20:47 +05:30
m ( : , : , 1 ) = lattice_sd ( : , constitutive_nonlocal_slipSystemLattice ( : , myInstance ) , myStructure )
m ( : , : , 2 ) = - lattice_sd ( : , constitutive_nonlocal_slipSystemLattice ( : , myInstance ) , myStructure )
m ( : , : , 3 ) = lattice_st ( : , constitutive_nonlocal_slipSystemLattice ( : , myInstance ) , myStructure )
m ( : , : , 4 ) = - lattice_st ( : , constitutive_nonlocal_slipSystemLattice ( : , myInstance ) , myStructure )
2009-08-12 16:52:02 +05:30
2009-10-07 21:01:52 +05:30
F = math_mul33x33 ( Fe ( : , : , g , ip , el ) , Fp ( : , : , g , ip , el ) )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
detFe = math_det3x3 ( Fe ( : , : , g , ip , el ) )
2009-10-07 21:01:52 +05:30
2010-03-10 15:19:40 +05:30
fluxdensity = rhoSgl ( : , 1 : 4 ) * constitutive_nonlocal_v ( : , : , g , ip , el )
2010-05-21 14:21:15 +05:30
do n = 1 , FE_NipNeighbors ( mesh_element ( 2 , el ) ) ! loop through my neighbors
2010-03-04 22:44:47 +05:30
opposite_n = n - 1_pInt + 2_pInt * mod ( n , 2_pInt )
2010-05-21 14:21:15 +05:30
2009-08-11 22:01:57 +05:30
neighboring_el = mesh_ipNeighborhood ( 1 , n , ip , el )
neighboring_ip = mesh_ipNeighborhood ( 2 , n , ip , el )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
2010-03-04 22:44:47 +05:30
opposite_el = mesh_ipNeighborhood ( 1 , opposite_n , ip , el )
opposite_ip = mesh_ipNeighborhood ( 2 , opposite_n , ip , el )
2010-05-21 14:21:15 +05:30
if ( neighboring_el > 0_pInt . and . neighboring_ip > 0_pInt ) then ! if neighbor exists, average deformation gradient
2009-10-07 21:01:52 +05:30
neighboring_F = math_mul33x33 ( Fe ( : , : , g , neighboring_ip , neighboring_el ) , Fp ( : , : , g , neighboring_ip , neighboring_el ) )
Favg = 0.5_pReal * ( F + neighboring_F )
2010-02-17 18:51:36 +05:30
else ! if no neighbor, take my value as average
2009-10-07 21:01:52 +05:30
Favg = F
2010-02-17 18:51:36 +05:30
endif
2009-08-11 22:01:57 +05:30
2010-02-17 18:51:36 +05:30
surfaceNormal_currentconf = math_det3x3 ( Favg ) * math_mul33x3 ( math_inv3x3 ( transpose ( Favg ) ) , mesh_ipAreaNormal ( : , n , ip , el ) ) ! calculate the normal of the interface in current ...
surfaceNormal = math_mul33x3 ( transpose ( Fe ( : , : , g , ip , el ) ) , surfaceNormal_currentconf ) / detFe ! ... and lattice configuration
2009-12-15 13:50:31 +05:30
area = mesh_ipArea ( n , ip , el ) * math_norm3 ( surfaceNormal )
2010-02-17 18:51:36 +05:30
surfaceNormal = surfaceNormal / math_norm3 ( surfaceNormal ) ! normalize the surface normal to unit length
2009-12-15 13:50:31 +05:30
2010-05-21 14:21:15 +05:30
transmissivity = constitutive_nonlocal_transmissivity ( disorientation ( : , n ) )
2010-03-04 22:44:47 +05:30
highOrderScheme = . false .
if ( neighboring_el > 0 . and . neighboring_ip > 0 ) then ! if neighbor exists...
if ( . not . phase_localConstitution ( material_phase ( 1 , neighboring_ip , neighboring_el ) ) ) then ! ... and is of nonlocal constitution...
forall ( t = 1 : 4 ) & ! ... then calculate neighboring flux density
neighboring_fluxdensity ( : , t ) = state ( g , neighboring_ip , neighboring_el ) % p ( ( t - 1 ) * ns + 1 : t * ns ) &
* constitutive_nonlocal_v ( : , t , g , neighboring_ip , neighboring_el )
if ( transmissivity == 1.0_pReal ) then ! ... if additionally interface's transmission is perfect...
highOrderScheme = . true . ! ... then use high order interpolation scheme
weight = 0.5_pReal * mesh_ipVolume ( ip , el ) / area &
/ math_norm3 ( math_mul33x3 ( Favg , ( mesh_ipCenterOfGravity ( : , neighboring_ip , neighboring_el ) &
- mesh_ipCenterOfGravity ( : , ip , el ) ) ) )
endif
else ! ... and is of local constitution...
neighboring_fluxdensity = fluxdensity ! ... then copy flux density to neighbor
endif
else ! if no neighbor existent...
neighboring_fluxdensity = 0.0_pReal ! ... assume zero density
endif
2010-02-17 18:51:36 +05:30
do s = 1 , ns
do t = 1 , 4
2010-03-04 22:44:47 +05:30
if ( fluxdensity ( s , t ) * math_mul3x3 ( m ( : , s , t ) , surfaceNormal ) > 0.0_pReal ) then ! outgoing flux
if ( highOrderScheme ) then
average_fluxdensity = fluxdensity ( s , t ) + weight * ( neighboring_fluxdensity ( s , t ) - fluxdensity ( s , t ) )
maximum_fluxdensity = rhoSgl ( s , t ) * mesh_ipVolume ( ip , el ) ** ( 1.0_pReal / 3.0_pReal ) / timestep
average_fluxdensity = min ( abs ( average_fluxdensity ) , maximum_fluxdensity ) * sign ( 1.0_pReal , average_fluxdensity )
else
average_fluxdensity = fluxdensity ( s , t )
2010-02-17 18:51:36 +05:30
endif
2010-03-04 22:44:47 +05:30
lineLength = average_fluxdensity * math_mul3x3 ( m ( : , s , t ) , surfaceNormal ) * area ! line length that wants to leave this interface
2010-05-21 14:21:15 +05:30
rhoDotFlux ( s , t ) = rhoDotFlux ( s , t ) - lineLength / mesh_ipVolume ( ip , el ) ! subtract positive dislocation flux that leaves the material point
rhoDotFlux ( s , t + 4 ) = rhoDotFlux ( s , t + 4 ) + lineLength / mesh_ipVolume ( ip , el ) * ( 1.0_pReal - transmissivity ) &
* sign ( 1.0_pReal , average_fluxdensity ) ! dislocation flux that is not able to leave through interface (because of low transmissivity) will remain as immobile single density at the material point
! if (selectiveDebugger .and. s==1) &
! write(6,'(a22,i2,a15,i2,a3,4(e20.10,x))') 'outgoing flux of type ',t,' to neighbor ',n,' : ', &
! -lineLength / mesh_ipVolume(ip,el), average_fluxdensity, maximum_fluxdensity, &
! average_fluxdensity / maximum_fluxdensity
2010-02-17 18:51:36 +05:30
else ! incoming flux
2010-03-04 22:44:47 +05:30
if ( highOrderScheme ) then
average_fluxdensity = fluxdensity ( s , t ) + weight * ( neighboring_fluxdensity ( s , t ) - fluxdensity ( s , t ) )
maximum_fluxdensity = state ( g , neighboring_ip , neighboring_el ) % p ( ( t - 1 ) * ns + s ) &
* mesh_ipVolume ( neighboring_ip , neighboring_el ) ** ( 1.0_pReal / 3.0_pReal ) / timestep
average_fluxdensity = min ( abs ( average_fluxdensity ) , maximum_fluxdensity ) * sign ( 1.0_pReal , average_fluxdensity )
else
average_fluxdensity = neighboring_fluxdensity ( s , t )
2009-08-11 22:01:57 +05:30
endif
2010-02-17 18:51:36 +05:30
2010-03-04 22:44:47 +05:30
lineLength = average_fluxdensity * math_mul3x3 ( m ( : , s , t ) , surfaceNormal ) * area ! line length that wants to leave this interface
2010-05-21 14:21:15 +05:30
rhoDotFlux ( s , t ) = rhoDotFlux ( s , t ) - lineLength / mesh_ipVolume ( ip , el ) * transmissivity ! subtract negative dislocation flux that enters the material point
! if (selectiveDebugger .and. s==1) &
! write(6,'(a22,i2,a15,i2,a3,4(e20.10,x))') 'incoming flux of type ',t,' from neighbor ',n,' : ', &
! -lineLength / mesh_ipVolume(ip,el) * transmissivity, average_fluxdensity, maximum_fluxdensity, &
! average_fluxdensity / maximum_fluxdensity
2009-08-11 22:01:57 +05:30
endif
2010-03-04 22:44:47 +05:30
2009-08-11 22:01:57 +05:30
enddo
enddo
2010-05-21 14:21:15 +05:30
2009-08-11 22:01:57 +05:30
enddo
2009-10-07 21:01:52 +05:30
2010-05-21 14:21:15 +05:30
constitutive_nonlocal_rhoDotFlux ( : , : , g , ip , el ) = rhoDotFlux
2009-08-28 19:20:47 +05:30
!****************************************************************************
!*** calculate dipole formation and annihilation
!*** formation by glide
2010-01-05 21:37:24 +05:30
do c = 1 , 2
2010-02-17 18:51:36 +05:30
2010-05-21 14:21:15 +05:30
rhoDotSingle2DipoleGlide ( : , 2 * c - 1 ) = - 2.0_pReal * dUpper ( : , c ) / constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance ) &
* ( rhoSgl ( : , 2 * c - 1 ) * abs ( gdot ( : , 2 * c ) ) + rhoSgl ( : , 2 * c ) * abs ( gdot ( : , 2 * c - 1 ) ) & ! negative mobile <-> positive mobile
+ abs ( rhoSgl ( : , 2 * c + 4 ) ) * abs ( gdot ( : , 2 * c - 1 ) ) ) ! negative immobile <-> positive mobile
2010-02-17 18:51:36 +05:30
2010-05-21 14:21:15 +05:30
rhoDotSingle2DipoleGlide ( : , 2 * c ) = - 2.0_pReal * dUpper ( : , c ) / constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance ) &
* ( rhoSgl ( : , 2 * c - 1 ) * abs ( gdot ( : , 2 * c ) ) + rhoSgl ( : , 2 * c ) * abs ( gdot ( : , 2 * c - 1 ) ) & ! negative mobile <-> positive mobile
+ abs ( rhoSgl ( : , 2 * c + 3 ) ) * abs ( gdot ( : , 2 * c ) ) ) ! negative mobile <-> positive immobile
2010-02-17 18:51:36 +05:30
2010-05-21 14:21:15 +05:30
rhoDotSingle2DipoleGlide ( : , 2 * c + 3 ) = - 2.0_pReal * dUpper ( : , c ) / constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance ) & ! negative mobile <-> positive immobile
* rhoSgl ( : , 2 * c + 3 ) * abs ( gdot ( : , 2 * c ) )
2010-02-17 18:51:36 +05:30
2010-05-21 14:21:15 +05:30
rhoDotSingle2DipoleGlide ( : , 2 * c + 4 ) = - 2.0_pReal * dUpper ( : , c ) / constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance ) &
* rhoSgl ( : , 2 * c + 4 ) * abs ( gdot ( : , 2 * c - 1 ) ) ! negative immobile <-> positive mobile
2010-02-17 18:51:36 +05:30
2010-05-21 14:21:15 +05:30
rhoDotSingle2DipoleGlide ( : , c + 8 ) = - rhoDotSingle2DipoleGlide ( : , 2 * c - 1 ) - rhoDotSingle2DipoleGlide ( : , 2 * c ) &
+ abs ( rhoDotSingle2DipoleGlide ( : , 2 * c + 3 ) ) + abs ( rhoDotSingle2DipoleGlide ( : , 2 * c + 4 ) )
2010-01-05 21:37:24 +05:30
enddo
2009-10-07 21:01:52 +05:30
2009-08-28 19:20:47 +05:30
!*** athermal annihilation
2010-05-21 14:21:15 +05:30
rhoDotAthermalAnnihilation = 0.0_pReal
2009-08-28 19:20:47 +05:30
forall ( c = 1 : 2 ) &
2010-05-21 14:21:15 +05:30
rhoDotAthermalAnnihilation ( : , c + 8 ) = - 2.0_pReal * dLower ( : , c ) / constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance ) &
2010-02-17 18:51:36 +05:30
* ( 2.0_pReal * ( rhoSgl ( : , 2 * c - 1 ) * abs ( gdot ( : , 2 * c ) ) + rhoSgl ( : , 2 * c ) * abs ( gdot ( : , 2 * c - 1 ) ) ) & ! was single hitting single
2010-03-04 22:44:47 +05:30
+ 2.0_pReal * ( abs ( rhoSgl ( : , 2 * c + 3 ) ) * abs ( gdot ( : , 2 * c ) ) + abs ( rhoSgl ( : , 2 * c + 4 ) ) * abs ( gdot ( : , 2 * c - 1 ) ) ) & ! was single hitting immobile single or was immobile single hit by single
2010-02-17 18:51:36 +05:30
+ rhoDip ( : , c ) * ( abs ( gdot ( : , 2 * c - 1 ) ) + abs ( gdot ( : , 2 * c ) ) ) ) ! single knocks dipole constituent
2009-08-28 19:20:47 +05:30
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
!*** thermally activated annihilation of dipoles
2009-10-07 21:01:52 +05:30
2010-05-21 14:21:15 +05:30
rhoDotThermalAnnihilation = 0.0_pReal
2009-08-28 19:20:47 +05:30
D = constitutive_nonlocal_D0 ( myInstance ) * exp ( - constitutive_nonlocal_Qsd ( myInstance ) / ( kB * Temperature ) )
vClimb = constitutive_nonlocal_atomicVolume ( myInstance ) * D / ( kB * Temperature ) &
* constitutive_nonlocal_Gmod ( myInstance ) / ( 2.0_pReal * pi * ( 1.0_pReal - constitutive_nonlocal_nu ( myInstance ) ) ) &
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
* 2.0_pReal / ( dUpper ( : , 1 ) + dLower ( : , 1 ) )
2009-08-28 19:20:47 +05:30
2010-05-21 14:21:15 +05:30
rhoDotThermalAnnihilation ( : , 9 ) = - 4.0_pReal * rhoDip ( : , 1 ) * vClimb / ( dUpper ( : , 1 ) - dLower ( : , 1 ) ) ! edge climb
rhoDotThermalAnnihilation ( : , 10 ) = 0.0_pReal !!! cross slipping still has to be implemented !!!
2009-08-28 19:20:47 +05:30
2009-12-15 13:50:31 +05:30
!*** formation/dissociation by stress change = alteration in dUpper
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
2010-05-21 14:21:15 +05:30
rhoDotDipole2SingleStressChange = 0.0_pReal
forall ( c = 1 : 2 , s = 1 : ns , dUpperDot ( s , c ) < 0.0_pReal ) & ! increased stress => dipole dissociation
rhoDotDipole2SingleStressChange ( s , 8 + c ) = rhoDip ( s , c ) * dUpperDot ( s , c ) / ( previousDUpper ( s , c ) - dLower ( s , c ) )
2010-03-10 15:19:40 +05:30
forall ( t = 1 : 4 ) &
2010-05-21 14:21:15 +05:30
rhoDotDipole2SingleStressChange ( : , t ) = - 0.5_pReal * rhoDotDipole2SingleStressChange ( : , ( t - 1 ) / 2 + 9 )
2010-03-10 15:19:40 +05:30
2010-05-21 14:21:15 +05:30
rhoDotSingle2DipoleStressChange = 0.0_pReal
do c = 1 , 2
do s = 1 , ns
if ( dUpperDot ( s , c ) > 0.0_pReal ) then ! stress decrease => dipole formation
rhoDotSingle2DipoleStressChange ( s , 2 * ( c - 1 ) + 1 ) = - 4.0_pReal * dUpperDot ( s , c ) * previousDUpper ( s , c ) * rhoSgl ( s , 2 * ( c - 1 ) + 1 ) &
* ( rhoSgl ( s , 2 * ( c - 1 ) + 2 ) + abs ( rhoSgl ( s , 2 * ( c - 1 ) + 6 ) ) )
rhoDotSingle2DipoleStressChange ( s , 2 * ( c - 1 ) + 2 ) = - 4.0_pReal * dUpperDot ( s , c ) * previousDUpper ( s , c ) * rhoSgl ( s , 2 * ( c - 1 ) + 2 ) &
* ( rhoSgl ( s , 2 * ( c - 1 ) + 1 ) + abs ( rhoSgl ( s , 2 * ( c - 1 ) + 5 ) ) )
rhoDotSingle2DipoleStressChange ( s , 2 * ( c - 1 ) + 5 ) = - 4.0_pReal * dUpperDot ( s , c ) * previousDUpper ( s , c ) * rhoSgl ( s , 2 * ( c - 1 ) + 5 ) &
* ( rhoSgl ( s , 2 * ( c - 1 ) + 2 ) + abs ( rhoSgl ( s , 2 * ( c - 1 ) + 6 ) ) )
rhoDotSingle2DipoleStressChange ( s , 2 * ( c - 1 ) + 6 ) = - 4.0_pReal * dUpperDot ( s , c ) * previousDUpper ( s , c ) * rhoSgl ( s , 2 * ( c - 1 ) + 6 ) &
* ( rhoSgl ( s , 2 * ( c - 1 ) + 1 ) + abs ( rhoSgl ( s , 2 * ( c - 1 ) + 5 ) ) )
endif
enddo
enddo
forall ( c = 1 : 2 ) &
rhoDotSingle2DipoleStressChange ( : , 8 + c ) = abs ( rhoDotSingle2DipoleStressChange ( : , 2 * ( c - 1 ) + 1 ) ) &
+ abs ( rhoDotSingle2DipoleStressChange ( : , 2 * ( c - 1 ) + 2 ) ) &
+ abs ( rhoDotSingle2DipoleStressChange ( : , 2 * ( c - 1 ) + 5 ) ) &
+ abs ( rhoDotSingle2DipoleStressChange ( : , 2 * ( c - 1 ) + 6 ) )
2009-08-28 19:20:47 +05:30
!****************************************************************************
!*** assign the rates of dislocation densities to my dotState
2010-05-21 14:21:15 +05:30
rhoDot = 0.0_pReal
forall ( t = 1 : 10 ) &
rhoDot ( : , t ) = rhoDotFlux ( : , t ) &
+ rhoDotSingle2DipoleGlide ( : , t ) &
+ rhoDotAthermalAnnihilation ( : , t ) &
+ rhoDotRemobilization ( : , t ) &
+ rhoDotMultiplication ( : , t ) &
+ rhoDotThermalAnnihilation ( : , t )
! + rhoDotDipole2SingleStressChange(:,t) &
! + rhoDotSingle2DipoleStressChange(:,t)
dotState ( g , ip , el ) % p ( 1 : 10 * ns ) = dotState ( g , ip , el ) % p ( 1 : 10 * ns ) + reshape ( rhoDot , ( / 10 * ns / ) )
do i = 1 , 4 * ns
if ( previousState ( g , ip , el ) % p ( i ) + dotState ( g , ip , el ) % p ( i ) * timestep < 0.0_pReal ) then ! if single mobile densities become negative...
if ( previousState ( g , ip , el ) % p ( i ) < relevantState ( g , ip , el ) % p ( i ) ) then ! ... and density is already below relevance...
dotState ( g , ip , el ) % p ( i ) = 0.0_pReal ! ... set dotState to zero
else ! ... otherwise...
if ( verboseDebugger ) then
!$OMP CRITICAL (write2out)
write ( 6 , * ) 'negative dislocation density at ' , g , ip , el
write ( 6 , * )
!$OMPEND CRITICAL (write2out)
endif
dotState ( g , ip , el ) % p ( i ) = NaN ! ... assign NaN and enforce a cutback
endif
endif
enddo
2009-08-28 19:20:47 +05:30
2010-03-19 19:44:08 +05:30
if ( verboseDebugger . and . selectiveDebugger ) then
2009-10-07 21:01:52 +05:30
!$OMP CRITICAL (write2out)
2010-05-21 14:21:15 +05:30
write ( 6 , '(a,/,8(12(e12.5,x),/))' ) 'dislocation remobilization' , rhoDotRemobilization ( : , 1 : 8 ) * timestep
write ( 6 , '(a,/,4(12(e12.5,x),/))' ) 'dislocation multiplication' , rhoDotMultiplication ( : , 1 : 4 ) * timestep
write ( 6 , '(a,/,8(12(e12.5,x),/))' ) 'dislocation flux' , rhoDotFlux ( : , 1 : 8 ) * timestep
write ( 6 , '(a,/,10(12(e12.5,x),/))' ) 'dipole formation by glide' , rhoDotSingle2DipoleGlide * timestep
write ( 6 , '(a,/,2(12(e12.5,x),/))' ) 'athermal dipole annihilation' , rhoDotAthermalAnnihilation ( : , 1 : 2 ) * timestep
write ( 6 , '(a,/,2(12(e12.5,x),/))' ) 'thermally activated dipole annihilation' , rhoDotThermalAnnihilation ( : , 9 : 10 ) * timestep
! write(6,'(a,/,10(12(e12.5,x),/))') 'dipole dissociation by stress increase', rhoDotDipole2SingleStressChange * timestep
! write(6,'(a,/,10(12(e12.5,x),/))') 'dipole formation by stress decrease', rhoDotSingle2DipoleStressChange * timestep
write ( 6 , '(a,/,10(12(e12.5,x),/))' ) 'total density change' , rhoDot * timestep
2009-12-15 13:50:31 +05:30
!$OMPEND CRITICAL (write2out)
2009-10-07 21:01:52 +05:30
endif
2009-08-11 22:01:57 +05:30
endsubroutine
2009-12-15 13:50:31 +05:30
!*********************************************************************
!* transmissivity of IP interface *
!*********************************************************************
2010-05-21 14:21:15 +05:30
function constitutive_nonlocal_transmissivity ( disorientation )
2009-12-15 13:50:31 +05:30
use prec , only : pReal , &
2009-12-18 21:16:33 +05:30
pInt
2010-05-21 14:21:15 +05:30
use math , only : math_QuaternionToAxisAngle
2009-12-18 21:16:33 +05:30
2009-12-15 13:50:31 +05:30
implicit none
!* input variables
2010-05-21 14:21:15 +05:30
real ( pReal ) , dimension ( 4 ) , intent ( in ) :: disorientation ! disorientation as quaternion
2009-12-15 13:50:31 +05:30
!* output variables
2009-12-18 21:16:33 +05:30
real ( pReal ) constitutive_nonlocal_transmissivity ! transmissivity of an IP interface for dislocations
2009-12-15 13:50:31 +05:30
!* local variables
2010-05-21 14:21:15 +05:30
real ( pReal ) disorientationAngle
real ( pReal ) , dimension ( 3 ) :: disorientationAxis
real ( pReal ) , dimension ( 4 ) :: disorientationAxisAngle
2009-12-18 21:16:33 +05:30
2010-03-18 17:53:17 +05:30
2010-05-21 14:21:15 +05:30
disorientationAxisAngle = math_QuaternionToAxisAngle ( disorientation )
2010-03-18 17:53:17 +05:30
2010-05-21 14:21:15 +05:30
disorientationAxis = disorientationAxisAngle ( 1 : 3 )
disorientationAngle = disorientationAxisAngle ( 4 )
if ( disorientationAngle < 3.0_pReal ) then
2009-12-18 21:16:33 +05:30
constitutive_nonlocal_transmissivity = 1.0_pReal
else
2010-05-21 14:21:15 +05:30
constitutive_nonlocal_transmissivity = 0.5_pReal
2009-12-18 21:16:33 +05:30
endif
2009-12-15 13:50:31 +05:30
endfunction
2009-08-11 22:01:57 +05:30
!*********************************************************************
!* rate of change of temperature *
!*********************************************************************
pure function constitutive_nonlocal_dotTemperature ( Tstar_v , Temperature , state , g , ip , el )
use prec , only : pReal , &
pInt , &
p_vec
use mesh , only : mesh_NcpElems , &
mesh_maxNips
use material , only : homogenization_maxNgrains
implicit none
!* input variables
integer ( pInt ) , intent ( in ) :: g , & ! current grain ID
ip , & ! current integration point
el ! current element
real ( pReal ) , intent ( in ) :: Temperature ! temperature
real ( pReal ) , dimension ( 6 ) , intent ( in ) :: Tstar_v ! 2nd Piola-Kirchhoff stress in Mandel notation
type ( p_vec ) , dimension ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
state ! microstructural state
!* output variables
real ( pReal ) constitutive_nonlocal_dotTemperature ! evolution of Temperature
!* local variables
constitutive_nonlocal_dotTemperature = 0.0_pReal
endfunction
!*********************************************************************
!* return array of constitutive results *
!*********************************************************************
2010-05-21 14:21:15 +05:30
function constitutive_nonlocal_postResults ( Tstar_v , previousTstar_v , Fe , Fp , Temperature , disorientation , dt , dt_previous , &
2009-12-15 13:50:31 +05:30
state , previousState , dotState , g , ip , el )
2009-08-11 22:01:57 +05:30
2009-08-24 13:46:01 +05:30
use prec , only : pReal , &
pInt , &
p_vec
2009-12-15 13:50:31 +05:30
use math , only : math_norm3 , &
math_mul6x6 , &
math_mul3x3 , &
math_mul33x3 , &
math_mul33x33 , &
math_inv3x3 , &
math_det3x3 , &
math_Mandel6to33 , &
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
pi
2009-08-24 13:46:01 +05:30
use mesh , only : mesh_NcpElems , &
2009-12-15 13:50:31 +05:30
mesh_maxNips , &
2009-12-18 21:16:33 +05:30
mesh_maxNipNeighbors , &
2009-12-15 13:50:31 +05:30
mesh_element , &
FE_NipNeighbors , &
mesh_ipNeighborhood , &
mesh_ipVolume , &
mesh_ipArea , &
mesh_ipAreaNormal
2009-08-24 13:46:01 +05:30
use material , only : homogenization_maxNgrains , &
material_phase , &
phase_constitutionInstance , &
phase_Noutput
2009-12-15 13:50:31 +05:30
use lattice , only : lattice_Sslip , &
lattice_Sslip_v , &
lattice_sd , &
lattice_sn , &
lattice_st , &
lattice_maxNslipFamily , &
2009-08-24 13:46:01 +05:30
lattice_NslipSystem
2009-08-11 22:01:57 +05:30
implicit none
2009-08-24 13:46:01 +05:30
!*** input variables
2009-12-15 13:50:31 +05:30
integer ( pInt ) , intent ( in ) :: g , & ! current grain number
ip , & ! current integration point
el ! current element number
real ( pReal ) , intent ( in ) :: Temperature , & ! temperature
dt , & ! time increment
dt_previous ! time increment between previous and current state
real ( pReal ) , dimension ( 6 ) , intent ( in ) :: Tstar_v , & ! current 2nd Piola-Kirchhoff stress in Mandel notation
previousTstar_v ! previous 2nd Piola-Kirchhoff stress in Mandel notation
2009-12-18 21:16:33 +05:30
real ( pReal ) , dimension ( 4 , mesh_maxNipNeighbors ) , intent ( in ) :: &
2010-05-21 14:21:15 +05:30
disorientation ! crystal disorientation between me and my neighbor (axis, angle pair)
2009-12-15 13:50:31 +05:30
real ( pReal ) , dimension ( 3 , 3 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
Fe , & ! elastic deformation gradient
Fp ! plastic deformation gradient
type ( p_vec ) , dimension ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
state , & ! current microstructural state
previousState , & ! previous microstructural state
dotState ! evolution rate of microstructural state
2009-08-24 13:46:01 +05:30
!*** output variables
real ( pReal ) , dimension ( constitutive_nonlocal_sizePostResults ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) ) :: &
2009-12-18 21:16:33 +05:30
constitutive_nonlocal_postResults
2009-08-11 22:01:57 +05:30
2009-08-24 13:46:01 +05:30
!*** local variables
2009-12-15 13:50:31 +05:30
integer ( pInt ) myInstance , & ! current instance of this constitution
myStructure , & ! current lattice structure
ns , & ! short notation for the total number of active slip systems
neighboring_el , & ! element number of my neighbor
neighboring_ip , & ! integration point of my neighbor
c , & ! character of dislocation
cs , & ! constitutive result index
n , & ! index of my current neighbor
o , & ! index of current output
t , & ! type of dislocation
s , & ! index of my current slip system
sLattice ! index of my current slip system according to lattice order
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 6 , 4 ) :: &
fluxes ! outgoing fluxes per slipsystem, neighbor and dislocation type
2010-01-05 21:37:24 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 8 ) :: &
rhoSgl , & ! current single dislocation densities (positive/negative screw and edge without dipoles)
previousRhoSgl , & ! previous single dislocation densities (positive/negative screw and edge without dipoles)
rhoDotSgl ! evolution rate of single dislocation densities (positive/negative screw and edge without dipoles)
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 4 ) :: &
2009-12-15 13:50:31 +05:30
gdot , & ! shear rates
lineLength ! dislocation line length leaving the current interface
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) ) :: &
2009-12-15 13:50:31 +05:30
rhoForest , & ! forest dislocation density
2010-02-17 18:51:36 +05:30
tauThreshold , & ! threshold shear stress
tau , & ! current resolved shear stress
previousTau , & ! previous resolved shear stress
2009-12-15 13:50:31 +05:30
invLambda , & ! inverse of mean free path for dislocations
vClimb ! climb velocity of edge dipoles
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 2 ) :: &
2009-12-15 13:50:31 +05:30
rhoDip , & ! current dipole dislocation densities (screw and edge dipoles)
previousRhoDip , & ! previous dipole dislocation densities (screw and edge dipoles)
2010-01-05 21:37:24 +05:30
rhoDotDip , & ! evolution rate of dipole dislocation densities (screw and edge dipoles)
2009-12-15 13:50:31 +05:30
dLower , & ! minimum stable dipole distance for edges and screws
dUpper , & ! current maximum stable dipole distance for edges and screws
previousDUpper , & ! previous maximum stable dipole distance for edges and screws
dUpperDot ! rate of change of the maximum stable dipole distance for edges and screws
2010-02-17 18:51:36 +05:30
real ( pReal ) , dimension ( 3 , constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 2 ) :: &
m , & ! direction of dislocation motion for edge and screw (unit vector)
m_currentconf ! direction of dislocation motion for edge and screw (unit vector) in current configuration
2009-12-15 13:50:31 +05:30
real ( pReal ) , dimension ( 3 , 3 ) :: F , & ! total deformation gradient
neighboring_F , & ! total deformation gradient of my neighbor
Favg ! average total deformation gradient of me and my neighbor
real ( pReal ) , dimension ( 6 ) :: Tdislocation_v , & ! current dislocation stress (resulting from the neighboring excess dislocation densities) as 2nd Piola-Kirchhoff stress
previousTdislocation_v ! previous dislocation stress (resulting from the neighboring excess dislocation densities) as 2nd Piola-Kirchhoff stress
real ( pReal ) , dimension ( 3 ) :: surfaceNormal , & ! surface normal in lattice configuration
surfaceNormal_currentconf ! surface normal in current configuration
real ( pReal ) area , & ! area of the current interface
detFe , & ! determinant of elastic defornmation gradient
D ! self diffusion
2009-08-24 13:46:01 +05:30
myInstance = phase_constitutionInstance ( material_phase ( g , ip , el ) )
myStructure = constitutive_nonlocal_structure ( myInstance )
ns = constitutive_nonlocal_totalNslip ( myInstance )
2009-08-11 22:01:57 +05:30
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = 0_pInt
2009-08-11 22:01:57 +05:30
constitutive_nonlocal_postResults = 0.0_pReal
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
2010-01-06 15:24:00 +05:30
!* short hand notations for state variables
2010-01-05 21:37:24 +05:30
forall ( t = 1 : 8 ) rhoSgl ( : , t ) = state ( g , ip , el ) % p ( ( t - 1 ) * ns + 1 : t * ns )
forall ( t = 1 : 8 ) previousRhoSgl ( : , t ) = previousState ( g , ip , el ) % p ( ( t - 1 ) * ns + 1 : t * ns )
forall ( c = 1 : 2 ) rhoDip ( : , c ) = state ( g , ip , el ) % p ( ( 7 + c ) * ns + 1 : ( 8 + c ) * ns )
forall ( c = 1 : 2 ) previousRhoDip ( : , c ) = previousState ( g , ip , el ) % p ( ( 7 + c ) * ns + 1 : ( 8 + c ) * ns )
rhoForest = state ( g , ip , el ) % p ( 10 * ns + 1 : 11 * ns )
2010-02-17 18:51:36 +05:30
tauThreshold = state ( g , ip , el ) % p ( 11 * ns + 1 : 12 * ns )
2010-01-05 21:37:24 +05:30
Tdislocation_v = state ( g , ip , el ) % p ( 12 * ns + 1 : 12 * ns + 6 )
previousTdislocation_v = previousState ( g , ip , el ) % p ( 12 * ns + 1 : 12 * ns + 6 )
forall ( t = 1 : 8 ) rhoDotSgl ( : , t ) = dotState ( g , ip , el ) % p ( ( t - 1 ) * ns + 1 : t * ns )
forall ( c = 1 : 2 ) rhoDotDip ( : , c ) = dotState ( g , ip , el ) % p ( ( 7 + c ) * ns + 1 : ( 8 + c ) * ns )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
2010-01-06 15:24:00 +05:30
!* Calculate shear rate
do t = 1 , 4
do s = 1 , ns
2010-02-17 18:51:36 +05:30
if ( rhoSgl ( s , t + 4 ) * constitutive_nonlocal_v ( s , t , g , ip , el ) < 0.0_pReal ) then
2010-01-06 15:24:00 +05:30
rhoSgl ( s , t ) = rhoSgl ( s , t ) + abs ( rhoSgl ( s , t + 4 ) ) ! remobilization of immobile singles for changing sign of v (bauschinger effect)
rhoSgl ( s , t + 4 ) = 0.0_pReal ! remobilization of immobile singles for changing sign of v (bauschinger effect)
endif
enddo
enddo
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
2010-02-17 18:51:36 +05:30
forall ( t = 1 : 4 ) &
gdot ( : , t ) = rhoSgl ( : , t ) * constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance ) * constitutive_nonlocal_v ( : , t , g , ip , el )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
2010-01-06 15:24:00 +05:30
!* calculate limits for stable dipole height and its rate of change
2010-02-17 18:51:36 +05:30
do s = 1 , ns
sLattice = constitutive_nonlocal_slipSystemLattice ( s , myInstance )
tau ( s ) = math_mul6x6 ( Tstar_v + Tdislocation_v , lattice_Sslip_v ( : , sLattice , myStructure ) )
previousTau ( s ) = math_mul6x6 ( previousTstar_v + previousTdislocation_v , lattice_Sslip_v ( : , sLattice , myStructure ) )
enddo
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
dLower ( : , 1 ) = constitutive_nonlocal_dLowerEdgePerSlipSystem ( : , myInstance )
dLower ( : , 2 ) = constitutive_nonlocal_dLowerScrewPerSlipSystem ( : , myInstance )
dUpper ( : , 2 ) = min ( constitutive_nonlocal_Gmod ( myInstance ) * constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance ) &
2010-02-17 18:51:36 +05:30
/ ( 8.0_pReal * pi * abs ( tau ) ) , &
2010-01-05 21:37:24 +05:30
1.0_pReal / sqrt ( sum ( abs ( rhoSgl ) , 2 ) + sum ( rhoDip , 2 ) ) )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
dUpper ( : , 1 ) = dUpper ( : , 2 ) / ( 1.0_pReal - constitutive_nonlocal_nu ( myInstance ) )
2009-12-15 13:50:31 +05:30
previousDUpper ( : , 2 ) = min ( constitutive_nonlocal_Gmod ( myInstance ) * constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance ) &
2010-02-17 18:51:36 +05:30
/ ( 8.0_pReal * pi * abs ( previousTau ) ) , &
2010-01-05 21:37:24 +05:30
1.0_pReal / sqrt ( sum ( abs ( previousRhoSgl ) , 2 ) + sum ( previousRhoDip , 2 ) ) )
2009-12-15 13:50:31 +05:30
previousDUpper ( : , 1 ) = previousDUpper ( : , 2 ) / ( 1.0_pReal - constitutive_nonlocal_nu ( myInstance ) )
if ( dt_previous > 0.0_pReal ) then
dUpperDot = ( dUpper - previousDUpper ) / dt_previous
else
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
dUpperDot = 0.0_pReal
endif
2009-12-15 13:50:31 +05:30
2010-02-17 18:51:36 +05:30
!*** dislocation motion
2009-12-15 13:50:31 +05:30
2010-02-17 18:51:36 +05:30
m ( : , : , 1 ) = lattice_sd ( : , constitutive_nonlocal_slipSystemLattice ( : , myInstance ) , myStructure )
m ( : , : , 2 ) = lattice_st ( : , constitutive_nonlocal_slipSystemLattice ( : , myInstance ) , myStructure )
forall ( c = 1 : 2 , s = 1 : ns ) &
m_currentconf ( : , s , c ) = math_mul33x3 ( Fe ( : , : , g , ip , el ) , m ( : , s , c ) )
2009-12-15 13:50:31 +05:30
2009-08-24 13:46:01 +05:30
do o = 1 , phase_Noutput ( material_phase ( g , ip , el ) )
select case ( constitutive_nonlocal_output ( o , myInstance ) )
case ( 'rho' )
2010-01-05 21:37:24 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ) , 2 ) + sum ( rhoDip , 2 )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
2010-01-05 21:37:24 +05:30
case ( 'rho_sgl' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ) , 2 )
cs = cs + ns
case ( 'rho_sgl_mobile' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ( : , 1 : 4 ) ) , 2 )
cs = cs + ns
case ( 'rho_sgl_immobile' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ( : , 5 : 8 ) ) , 2 )
cs = cs + ns
case ( 'rho_dip' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( rhoDip , 2 )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
2009-08-24 13:46:01 +05:30
case ( 'rho_edge' )
2010-01-05 21:37:24 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ( : , ( / 1 , 2 , 5 , 6 / ) ) ) , 2 ) + rhoDip ( : , 1 )
cs = cs + ns
case ( 'rho_sgl_edge' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ( : , ( / 1 , 2 , 5 , 6 / ) ) ) , 2 )
cs = cs + ns
case ( 'rho_sgl_edge_mobile' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( rhoSgl ( : , 1 : 2 ) , 2 )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
2009-08-24 13:46:01 +05:30
2010-01-05 21:37:24 +05:30
case ( 'rho_sgl_edge_immobile' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ( : , 5 : 6 ) ) , 2 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-01-05 21:37:24 +05:30
case ( 'rho_sgl_edge_pos' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 1 ) + abs ( rhoSgl ( : , 5 ) )
cs = cs + ns
case ( 'rho_sgl_edge_pos_mobile' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 1 )
cs = cs + ns
case ( 'rho_sgl_edge_pos_immobile' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = abs ( rhoSgl ( : , 5 ) )
cs = cs + ns
case ( 'rho_sgl_edge_neg' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 2 ) + abs ( rhoSgl ( : , 6 ) )
cs = cs + ns
case ( 'rho_sgl_edge_neg_mobile' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 2 )
cs = cs + ns
case ( 'rho_sgl_edge_neg_immobile' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = abs ( rhoSgl ( : , 6 ) )
cs = cs + ns
case ( 'rho_dip_edge' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoDip ( : , 1 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2009-08-24 13:46:01 +05:30
case ( 'rho_screw' )
2010-01-05 21:37:24 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ( : , ( / 3 , 4 , 7 , 8 / ) ) ) , 2 ) + rhoDip ( : , 2 )
cs = cs + ns
case ( 'rho_sgl_screw' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ( : , ( / 3 , 4 , 7 , 8 / ) ) ) , 2 )
cs = cs + ns
case ( 'rho_sgl_screw_mobile' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( rhoSgl ( : , 3 : 4 ) , 2 )
cs = cs + ns
case ( 'rho_sgl_screw_immobile' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ( : , 7 : 8 ) ) , 2 )
cs = cs + ns
case ( 'rho_sgl_screw_pos' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 3 ) + abs ( rhoSgl ( : , 7 ) )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
2009-08-24 13:46:01 +05:30
2010-01-05 21:37:24 +05:30
case ( 'rho_sgl_screw_pos_mobile' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 3 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-01-05 21:37:24 +05:30
case ( 'rho_sgl_screw_pos_immobile' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = abs ( rhoSgl ( : , 7 ) )
cs = cs + ns
case ( 'rho_sgl_screw_neg' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 4 ) + abs ( rhoSgl ( : , 8 ) )
cs = cs + ns
case ( 'rho_sgl_screw_neg_mobile' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 4 )
cs = cs + ns
case ( 'rho_sgl_screw_neg_immobile' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = abs ( rhoSgl ( : , 8 ) )
cs = cs + ns
case ( 'rho_dip_screw' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoDip ( : , 2 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2009-08-28 19:20:47 +05:30
case ( 'excess_rho' )
2010-01-05 21:37:24 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = ( rhoSgl ( : , 1 ) + abs ( rhoSgl ( : , 5 ) ) ) - ( rhoSgl ( : , 2 ) + abs ( rhoSgl ( : , 6 ) ) ) &
+ ( rhoSgl ( : , 3 ) + abs ( rhoSgl ( : , 7 ) ) ) - ( rhoSgl ( : , 4 ) + abs ( rhoSgl ( : , 8 ) ) )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
2009-08-28 19:20:47 +05:30
2010-05-21 14:21:15 +05:30
case ( 'excess_rho_edge' )
2010-01-05 21:37:24 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = ( rhoSgl ( : , 1 ) + abs ( rhoSgl ( : , 5 ) ) ) - ( rhoSgl ( : , 2 ) + abs ( rhoSgl ( : , 6 ) ) )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
2009-08-24 13:46:01 +05:30
2010-05-21 14:21:15 +05:30
case ( 'excess_rho_screw' )
2010-01-05 21:37:24 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = ( rhoSgl ( : , 3 ) + abs ( rhoSgl ( : , 7 ) ) ) - ( rhoSgl ( : , 4 ) + abs ( rhoSgl ( : , 8 ) ) )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
2009-08-24 13:46:01 +05:30
case ( 'rho_forest' )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoForest
cs = cs + ns
2009-08-28 19:20:47 +05:30
2010-01-05 21:37:24 +05:30
case ( 'delta' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = 1.0_pReal / sqrt ( sum ( abs ( rhoSgl ) , 2 ) + sum ( rhoDip , 2 ) )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
2010-01-05 21:37:24 +05:30
case ( 'delta_sgl' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = 1.0_pReal / sqrt ( sum ( abs ( rhoSgl ) , 2 ) )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
2009-08-28 19:20:47 +05:30
2010-01-05 21:37:24 +05:30
case ( 'delta_dip' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = 1.0_pReal / sqrt ( sum ( rhoDip , 2 ) )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
2009-08-24 13:46:01 +05:30
case ( 'shearrate' )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( gdot ) , 2 )
cs = cs + ns
2009-08-24 13:46:01 +05:30
case ( 'resolvedstress' )
do s = 1 , ns
sLattice = constitutive_nonlocal_slipSystemLattice ( s , myInstance )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
constitutive_nonlocal_postResults ( cs + s ) = math_mul6x6 ( Tstar_v + Tdislocation_v , lattice_Sslip_v ( : , sLattice , myStructure ) )
2009-08-24 13:46:01 +05:30
enddo
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
2009-08-24 13:46:01 +05:30
2010-02-17 18:51:36 +05:30
case ( 'resolvedstress_internal' )
do s = 1 , ns
sLattice = constitutive_nonlocal_slipSystemLattice ( s , myInstance )
constitutive_nonlocal_postResults ( cs + s ) = math_mul6x6 ( Tdislocation_v , lattice_Sslip_v ( : , sLattice , myStructure ) )
enddo
cs = cs + ns
case ( 'resolvedstress_external' )
do s = 1 , ns
sLattice = constitutive_nonlocal_slipSystemLattice ( s , myInstance )
constitutive_nonlocal_postResults ( cs + s ) = math_mul6x6 ( Tstar_v , lattice_Sslip_v ( : , sLattice , myStructure ) )
enddo
cs = cs + ns
2009-08-24 13:46:01 +05:30
case ( 'resistance' )
2010-02-17 18:51:36 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = tauThreshold
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
case ( 'rho_dot' )
2010-01-05 21:37:24 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( rhoDotSgl , 2 ) + sum ( rhoDotDip , 2 )
cs = cs + ns
case ( 'rho_dot_sgl' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( rhoDotSgl , 2 )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
case ( 'rho_dot_dip' )
2010-01-05 21:37:24 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( rhoDotDip , 2 )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
case ( 'rho_dot_gen' )
2010-01-05 21:37:24 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( gdot ) , 2 ) * sqrt ( rhoForest ) &
/ constitutive_nonlocal_lambda0PerSlipSystem ( : , myInstance ) &
/ constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance )
cs = cs + ns
case ( 'rho_dot_gen_edge' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( gdot ( : , 3 : 4 ) ) , 2 ) * sqrt ( rhoForest ) &
/ constitutive_nonlocal_lambda0PerSlipSystem ( : , myInstance ) &
/ constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance )
cs = cs + ns
case ( 'rho_dot_gen_screw' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( gdot ( : , 1 : 2 ) ) , 2 ) * sqrt ( rhoForest ) &
/ constitutive_nonlocal_lambda0PerSlipSystem ( : , myInstance ) &
/ constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
case ( 'rho_dot_sgl2dip' )
do c = 1 , 2 ! dipole formation by glide
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) + &
2010-02-17 18:51:36 +05:30
2.0_pReal * dUpper ( : , c ) / constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance ) &
* ( 2.0_pReal * ( rhoSgl ( : , 2 * c - 1 ) * abs ( gdot ( : , 2 * c ) ) + rhoSgl ( : , 2 * c ) * abs ( gdot ( : , 2 * c - 1 ) ) ) & ! was single hitting single
+ 2.0_pReal * ( abs ( rhoSgl ( : , 2 * c + 3 ) ) * abs ( gdot ( : , 2 * c ) ) + abs ( rhoSgl ( : , 2 * c + 4 ) ) * abs ( gdot ( : , 2 * c - 1 ) ) ) ) ! was single hitting immobile/used single
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
enddo
2010-05-21 14:21:15 +05:30
! do c=1,2
! forall (s=1:ns, dUpperDot(s,c) > 0.0_pReal) & ! dipole formation by stress decrease
! constitutive_nonlocal_postResults(cs+s) = constitutive_nonlocal_postResults(cs+s) + &
! 8.0_pReal * rhoSgl(s,2*c-1) * rhoSgl(s,2*c) * previousDUpper(s,c) * dUpperDot(s,c)
! enddo
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
case ( 'rho_dot_dip2sgl' )
do c = 1 , 2
2009-12-15 13:50:31 +05:30
forall ( s = 1 : ns , dUpperDot ( s , c ) < 0.0_pReal ) &
2010-03-10 15:19:40 +05:30
constitutive_nonlocal_postResults ( cs + s ) = constitutive_nonlocal_postResults ( cs + s ) - &
rhoDip ( s , c ) * dUpperDot ( s , c ) / ( previousDUpper ( s , c ) - dLower ( s , c ) )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
enddo
cs = cs + ns
case ( 'rho_dot_ann_ath' )
do c = 1 , 2
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) + &
2010-02-17 18:51:36 +05:30
2.0_pReal * dLower ( : , c ) / constitutive_nonlocal_burgersPerSlipSystem ( : , myInstance ) &
* ( 2.0_pReal * ( rhoSgl ( : , 2 * c - 1 ) * abs ( gdot ( : , 2 * c ) ) + rhoSgl ( : , 2 * c ) * abs ( gdot ( : , 2 * c - 1 ) ) ) & ! was single hitting single
+ 2.0_pReal * ( abs ( rhoSgl ( : , 2 * c + 3 ) ) * abs ( gdot ( : , 2 * c ) ) + abs ( rhoSgl ( : , 2 * c + 4 ) ) * abs ( gdot ( : , 2 * c - 1 ) ) ) & ! was single hitting immobile/used single
2010-03-04 22:44:47 +05:30
+ rhoDip ( : , c ) * ( abs ( gdot ( : , 2 * c - 1 ) ) + abs ( gdot ( : , 2 * c ) ) ) ) ! single knocks dipole constituent
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
enddo
cs = cs + ns
case ( 'rho_dot_ann_the' )
D = constitutive_nonlocal_D0 ( myInstance ) * exp ( - constitutive_nonlocal_Qsd ( myInstance ) / ( kB * Temperature ) )
2009-08-11 22:01:57 +05:30
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
vClimb = constitutive_nonlocal_atomicVolume ( myInstance ) * D / ( kB * Temperature ) &
* constitutive_nonlocal_Gmod ( myInstance ) / ( 2.0_pReal * pi * ( 1.0_pReal - constitutive_nonlocal_nu ( myInstance ) ) ) &
* 2.0_pReal / ( dUpper ( : , 1 ) + dLower ( : , 1 ) )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = 4.0_pReal * rhoDip ( : , 1 ) * vClimb / ( dUpper ( : , 1 ) - dLower ( : , 1 ) )
! !!! cross-slip of screws missing !!!
cs = cs + ns
2010-02-23 22:53:07 +05:30
2010-03-10 15:19:40 +05:30
case ( 'rho_dot_flux' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( constitutive_nonlocal_rhoDotFlux ( : , 1 : 4 , g , ip , el ) , 2 ) &
+ sum ( abs ( constitutive_nonlocal_rhoDotFlux ( : , 5 : 8 , g , ip , el ) ) , 2 )
cs = cs + ns
2010-05-21 14:21:15 +05:30
case ( 'rho_dot_flux_edge' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( constitutive_nonlocal_rhoDotFlux ( : , 1 : 2 , g , ip , el ) , 2 ) &
+ sum ( abs ( constitutive_nonlocal_rhoDotFlux ( : , 5 : 6 , g , ip , el ) ) , 2 )
cs = cs + ns
2010-03-10 15:19:40 +05:30
2010-05-21 14:21:15 +05:30
case ( 'rho_dot_flux_screw' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( constitutive_nonlocal_rhoDotFlux ( : , 3 : 4 , g , ip , el ) , 2 ) &
+ sum ( abs ( constitutive_nonlocal_rhoDotFlux ( : , 7 : 8 , g , ip , el ) ) , 2 )
cs = cs + ns
2010-02-23 22:53:07 +05:30
case ( 'dislocationvelocity' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = constitutive_nonlocal_v ( : , 1 , g , ip , el )
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_edge_pos_x' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 1 ) * constitutive_nonlocal_v ( : , 1 , g , ip , el ) * m_currentconf ( 1 , : , 1 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_edge_pos_y' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 1 ) * constitutive_nonlocal_v ( : , 1 , g , ip , el ) * m_currentconf ( 2 , : , 1 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_edge_pos_z' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 1 ) * constitutive_nonlocal_v ( : , 1 , g , ip , el ) * m_currentconf ( 3 , : , 1 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_edge_neg_x' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 2 ) * constitutive_nonlocal_v ( : , 2 , g , ip , el ) * m_currentconf ( 1 , : , 2 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_edge_neg_y' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 2 ) * constitutive_nonlocal_v ( : , 2 , g , ip , el ) * m_currentconf ( 2 , : , 2 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_edge_neg_z' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 2 ) * constitutive_nonlocal_v ( : , 2 , g , ip , el ) * m_currentconf ( 3 , : , 2 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_screw_pos_x' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 3 ) * constitutive_nonlocal_v ( : , 3 , g , ip , el ) * m_currentconf ( 1 , : , 3 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_screw_pos_y' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 3 ) * constitutive_nonlocal_v ( : , 3 , g , ip , el ) * m_currentconf ( 2 , : , 3 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_screw_pos_z' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 3 ) * constitutive_nonlocal_v ( : , 3 , g , ip , el ) * m_currentconf ( 3 , : , 3 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_screw_neg_x' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 4 ) * constitutive_nonlocal_v ( : , 4 , g , ip , el ) * m_currentconf ( 1 , : , 4 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_screw_neg_y' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 4 ) * constitutive_nonlocal_v ( : , 4 , g , ip , el ) * m_currentconf ( 2 , : , 4 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_screw_neg_z' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( : , 4 ) * constitutive_nonlocal_v ( : , 4 , g , ip , el ) * m_currentconf ( 3 , : , 4 )
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
case ( 'd_upper_edge' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = dUpper ( : , 1 )
cs = cs + ns
case ( 'd_upper_screw' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = dUpper ( : , 2 )
cs = cs + ns
case ( 'd_upper_dot_edge' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = dUpperDot ( : , 1 )
cs = cs + ns
case ( 'd_upper_dot_screw' )
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = dUpperDot ( : , 2 )
cs = cs + ns
2009-08-11 22:01:57 +05:30
end select
enddo
endfunction
2009-08-28 19:20:47 +05:30
END MODULE