2009-08-31 20:39:15 +05:30
!* $Id$
2010-10-26 19:19:58 +05:30
!************************************
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_atomicVolume , & ! atomic volume
2011-01-26 15:47:42 +05:30
constitutive_nonlocal_Dsd0 , & ! 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-10-26 18:46:37 +05:30
constitutive_nonlocal_aTolRho , & ! absolute tolerance for dislocation density in state integration
2011-01-26 15:47:42 +05:30
constitutive_nonlocal_R , & ! cutoff radius for dislocation stress
constitutive_nonlocal_d0 , & ! wall depth as multiple of b
constitutive_nonlocal_tauObs , & ! obstacle strength in Pa
constitutive_nonlocal_fattack , & ! attack frequency in Hz
2011-02-04 21:11:32 +05:30
constitutive_nonlocal_vs , & ! maximum dislocation velocity = velocity of sound
2011-02-16 22:05:38 +05:30
constitutive_nonlocal_rhoSglScatter , & ! standard deviation of scatter in initial dislocation density
constitutive_nonlocal_surfaceTransmissivity ! transmissivity at free surface
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_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
2011-01-26 15:47:42 +05:30
constitutive_nonlocal_Qeff0 , & ! prefactor for activation enthalpy for dislocation glide in J
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
2010-10-15 18:49:26 +05:30
real ( pReal ) , dimension ( : , : , : , : , : , : ) , allocatable :: constitutive_nonlocal_compatibility ! slip system compatibility between me and my neighbors
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 , &
2010-10-12 18:38:54 +05:30
mesh_maxNips , &
FE_maxNipNeighbors
2010-02-17 18:51:36 +05:30
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 ) )
allocate ( constitutive_nonlocal_atomicVolume ( maxNinstance ) )
2011-01-26 15:47:42 +05:30
allocate ( constitutive_nonlocal_Dsd0 ( maxNinstance ) )
2009-08-28 19:20:47 +05:30
allocate ( constitutive_nonlocal_Qsd ( maxNinstance ) )
2010-10-26 18:46:37 +05:30
allocate ( constitutive_nonlocal_aTolRho ( 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_R ( maxNinstance ) )
2011-01-26 15:47:42 +05:30
allocate ( constitutive_nonlocal_d0 ( maxNinstance ) )
allocate ( constitutive_nonlocal_tauObs ( maxNinstance ) )
allocate ( constitutive_nonlocal_vs ( maxNinstance ) )
allocate ( constitutive_nonlocal_fattack ( maxNinstance ) )
2011-02-04 21:11:32 +05:30
allocate ( constitutive_nonlocal_rhoSglScatter ( maxNinstance ) )
2011-02-16 22:05:38 +05:30
allocate ( constitutive_nonlocal_surfaceTransmissivity ( 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_atomicVolume = 0.0_pReal
2011-01-26 15:47:42 +05:30
constitutive_nonlocal_Dsd0 = 0.0_pReal
2009-08-28 19:20:47 +05:30
constitutive_nonlocal_Qsd = 0.0_pReal
2010-10-26 18:46:37 +05:30
constitutive_nonlocal_aTolRho = 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
2011-01-26 15:47:42 +05:30
constitutive_nonlocal_R = - 1.0_pReal
constitutive_nonlocal_d0 = 0.0_pReal
constitutive_nonlocal_tauObs = 0.0_pReal
constitutive_nonlocal_vs = 0.0_pReal
constitutive_nonlocal_fattack = 0.0_pReal
2011-02-04 21:11:32 +05:30
constitutive_nonlocal_rhoSglScatter = 0.0_pReal
2011-02-16 22:05:38 +05:30
constitutive_nonlocal_surfaceTransmissivity = 1.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_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_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
2011-02-16 22:05:38 +05:30
cycle
2009-08-11 22:01:57 +05:30
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 )
2011-02-16 22:05:38 +05:30
case ( 'constitution' , '/nonlocal/' )
cycle
2009-08-11 22:01:57 +05:30
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-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 ( '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 )
2009-08-28 19:20:47 +05:30
case ( 'atomicvolume' )
constitutive_nonlocal_atomicVolume ( i ) = IO_floatValue ( line , positions , 2 )
2011-01-26 15:47:42 +05:30
case ( 'dsd0' )
constitutive_nonlocal_Dsd0 ( i ) = IO_floatValue ( line , positions , 2 )
2009-08-28 19:20:47 +05:30
case ( 'qsd' )
constitutive_nonlocal_Qsd ( i ) = IO_floatValue ( line , positions , 2 )
2010-10-26 18:46:37 +05:30
case ( 'atol_rho' )
constitutive_nonlocal_aTolRho ( 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 )
2011-01-26 15:47:42 +05:30
case ( 'd0' )
constitutive_nonlocal_d0 ( i ) = IO_floatValue ( line , positions , 2 )
case ( 'tauobs' )
constitutive_nonlocal_tauObs ( i ) = IO_floatValue ( line , positions , 2 )
case ( 'vs' )
constitutive_nonlocal_vs ( i ) = IO_floatValue ( line , positions , 2 )
case ( 'fattack' )
constitutive_nonlocal_fattack ( i ) = IO_floatValue ( line , positions , 2 )
2011-02-04 21:11:32 +05:30
case ( 'rhosglscatter' )
constitutive_nonlocal_rhoSglScatter ( i ) = IO_floatValue ( line , positions , 2 )
2011-02-16 22:05:38 +05:30
case ( 'surfacetransmissivity' )
constitutive_nonlocal_surfaceTransmissivity ( i ) = IO_floatValue ( line , positions , 2 )
case default
call IO_error ( 236 , ext_msg = tag )
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
2011-02-16 22:05:38 +05:30
if ( myStructure < 1 . or . myStructure > 3 ) call IO_error ( 205 )
if ( sum ( constitutive_nonlocal_Nslip ( : , i ) ) < = 0_pInt ) call IO_error ( 235 , ext_msg = 'Nslip' )
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 )
2011-02-16 22:05:38 +05:30
if ( len ( constitutive_nonlocal_output ( o , i ) ) > 64 ) call IO_error ( 666 )
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
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
2011-02-16 22:05:38 +05:30
if ( constitutive_nonlocal_rhoSglEdgePos0 ( f , i ) < 0.0_pReal ) call IO_error ( 235 , ext_msg = 'rhoSglEdgePos0' )
if ( constitutive_nonlocal_rhoSglEdgeNeg0 ( f , i ) < 0.0_pReal ) call IO_error ( 235 , ext_msg = 'rhoSglEdgeNeg0' )
if ( constitutive_nonlocal_rhoSglScrewPos0 ( f , i ) < 0.0_pReal ) call IO_error ( 235 , ext_msg = 'rhoSglScrewPos0' )
if ( constitutive_nonlocal_rhoSglScrewNeg0 ( f , i ) < 0.0_pReal ) call IO_error ( 235 , ext_msg = 'rhoSglScrewNeg0' )
if ( constitutive_nonlocal_rhoDipEdge0 ( f , i ) < 0.0_pReal ) call IO_error ( 235 , ext_msg = 'rhoDipEdge0' )
if ( constitutive_nonlocal_rhoDipScrew0 ( f , i ) < 0.0_pReal ) call IO_error ( 235 , ext_msg = 'rhoDipScrew0' )
if ( constitutive_nonlocal_burgersPerSlipFamily ( f , i ) < = 0.0_pReal ) call IO_error ( 235 , ext_msg = 'burgers' )
if ( constitutive_nonlocal_lambda0PerSlipFamily ( f , i ) < = 0.0_pReal ) call IO_error ( 235 , ext_msg = 'lambda0' )
if ( constitutive_nonlocal_dLowerEdgePerSlipFamily ( f , i ) < = 0.0_pReal ) call IO_error ( 235 , ext_msg = 'dDipMinEdge' )
if ( constitutive_nonlocal_dLowerScrewPerSlipFamily ( f , i ) < = 0.0_pReal ) call IO_error ( 235 , ext_msg = 'dDipMinScrew' )
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 ) ) &
2011-02-16 22:05:38 +05:30
call IO_error ( 235 , ext_msg = 'interaction_SlipSlip' )
if ( constitutive_nonlocal_R ( i ) < 0.0_pReal ) call IO_error ( 235 , ext_msg = 'r' )
if ( constitutive_nonlocal_atomicVolume ( i ) < = 0.0_pReal ) call IO_error ( 235 , ext_msg = 'atomicVolume' )
if ( constitutive_nonlocal_Dsd0 ( i ) < = 0.0_pReal ) call IO_error ( 235 , ext_msg = 'Dsd0' )
if ( constitutive_nonlocal_Qsd ( i ) < = 0.0_pReal ) call IO_error ( 235 , ext_msg = 'Qsd' )
if ( constitutive_nonlocal_aTolRho ( i ) < = 0.0_pReal ) call IO_error ( 235 , ext_msg = 'aTol_rho' )
if ( constitutive_nonlocal_d0 ( i ) < = 0.0_pReal ) call IO_error ( 235 , ext_msg = 'd0' )
if ( constitutive_nonlocal_tauObs ( i ) < = 0.0_pReal ) call IO_error ( 235 , ext_msg = 'tauObs' )
if ( constitutive_nonlocal_vs ( i ) < = 0.0_pReal ) call IO_error ( 235 , ext_msg = 'vs' )
if ( constitutive_nonlocal_fattack ( i ) < = 0.0_pReal ) call IO_error ( 235 , ext_msg = 'fAttack' )
if ( constitutive_nonlocal_rhoSglScatter ( i ) < 0.0_pReal ) call IO_error ( 235 , ext_msg = 'rhoSglScatter' )
if ( constitutive_nonlocal_surfaceTransmissivity ( i ) < 0.0_pReal &
. or . constitutive_nonlocal_surfaceTransmissivity ( i ) > 1.0_pReal ) call IO_error ( 235 , ext_msg = 'surfaceTransmissivity' )
2011-01-26 15:47:42 +05:30
2009-08-11 22:01:57 +05:30
!*** determine total number of active slip systems
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_Nslip ( 1 : lattice_maxNslipFamily , i ) = min ( lattice_NslipSystem ( 1 : lattice_maxNslipFamily , myStructure ) , &
constitutive_nonlocal_Nslip ( 1 : lattice_maxNslipFamily , i ) ) ! we can't use more slip systems per family than specified in lattice
constitutive_nonlocal_totalNslip ( i ) = sum ( constitutive_nonlocal_Nslip ( 1 : lattice_maxNslipFamily , i ) )
2009-08-11 22:01:57 +05:30
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_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
2011-01-26 15:47:42 +05:30
allocate ( constitutive_nonlocal_Qeff0 ( maxTotalNslip , maxNinstance ) )
constitutive_nonlocal_Qeff0 = 0.0_pReal
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
2011-02-09 13:58:47 +05:30
allocate ( constitutive_nonlocal_rhoDotFlux ( maxTotalNslip , 10 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
2010-03-10 15:19:40 +05:30
constitutive_nonlocal_rhoDotFlux = 0.0_pReal
2010-10-15 18:49:26 +05:30
allocate ( constitutive_nonlocal_compatibility ( 2 , maxTotalNslip , maxTotalNslip , FE_maxNipNeighbors , mesh_maxNips , mesh_NcpElems ) )
2010-10-12 18:38:54 +05:30
constitutive_nonlocal_compatibility = 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 &
2011-01-26 15:47:42 +05:30
+ ( size ( constitutive_nonlocal_listDependentStates ) - 1_pInt ) * ns + 6_pInt
2009-09-18 21:07:14 +05:30
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
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_Cslip_66 ( 1 : 6 , 1 : 6 , i ) = math_Mandel3333to66 ( math_Voigt66to3333 ( constitutive_nonlocal_Cslip_66 ( 1 : 6 , 1 : 6 , i ) ) )
constitutive_nonlocal_Cslip_3333 ( 1 : 3 , 1 : 3 , 1 : 3 , 1 : 3 , i ) = math_Voigt66to3333 ( constitutive_nonlocal_Cslip_66 ( 1 : 6 , 1 : 6 , i ) )
2009-08-11 22:01:57 +05:30
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
2011-01-26 15:47:42 +05:30
!*** burgers vector, 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_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 ) &
2011-02-09 18:42:46 +05:30
= abs ( math_mul3x3 ( lattice_sn ( 1 : 3 , constitutive_nonlocal_slipSystemLattice ( s1 , i ) , myStructure ) , &
lattice_st ( 1 : 3 , 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 ) &
2011-02-09 18:42:46 +05:30
= abs ( math_mul3x3 ( lattice_sn ( 1 : 3 , constitutive_nonlocal_slipSystemLattice ( s1 , i ) , myStructure ) , &
lattice_sd ( 1 : 3 , 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
2009-08-11 22:01:57 +05:30
!*** 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
2011-01-26 15:47:42 +05:30
!*** calculation of prefactor for activation enthalpy for dislocation glide
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_Qeff0 ( 1 : ns , i ) = constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , i ) ** 3.0_pReal &
2011-01-26 15:47:42 +05:30
* dsqrt ( 0.5_pReal * constitutive_nonlocal_d0 ( i ) ** 3.0_pReal &
* constitutive_nonlocal_Gmod ( i ) * constitutive_nonlocal_tauObs ( i ) )
2009-10-07 21:01:52 +05:30
2009-08-11 22:01:57 +05:30
enddo
endsubroutine
!*********************************************************************
!* initial microstructural state (just the "basic" states) *
!*********************************************************************
2011-02-04 21:11:32 +05:30
function constitutive_nonlocal_stateInit ( myInstance )
2009-08-11 22:01:57 +05:30
use prec , only : pReal , &
pInt
use lattice , only : lattice_maxNslipFamily
2011-02-04 21:11:32 +05:30
use math , only : math_sampleGaussVar
2009-08-11 22:01:57 +05:30
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 , &
2011-02-04 21:11:32 +05:30
s , & ! index of slip system
i
real ( pReal ) , dimension ( 2 ) :: noise
2009-08-11 22:01:57 +05:30
constitutive_nonlocal_stateInit = 0.0_pReal
ns = constitutive_nonlocal_totalNslip ( myInstance )
!*** set the basic state variables
do f = 1 , lattice_maxNslipFamily
2011-02-04 21:11:32 +05:30
from = 1 + sum ( constitutive_nonlocal_Nslip ( 1 : f - 1 , myInstance ) )
2009-10-07 21:01:52 +05:30
upto = sum ( constitutive_nonlocal_Nslip ( 1 : f , myInstance ) )
2011-02-04 21:11:32 +05:30
do s = from , upto
do i = 1 , 2
noise ( i ) = math_sampleGaussVar ( 0.0_pReal , constitutive_nonlocal_rhoSglScatter ( myInstance ) )
enddo
rhoSglEdgePos ( s ) = constitutive_nonlocal_rhoSglEdgePos0 ( f , myInstance ) + noise ( 1 )
rhoSglEdgeNeg ( s ) = constitutive_nonlocal_rhoSglEdgeNeg0 ( f , myInstance ) + noise ( 1 )
rhoSglScrewPos ( s ) = constitutive_nonlocal_rhoSglScrewPos0 ( f , myInstance ) + noise ( 2 )
rhoSglScrewNeg ( s ) = constitutive_nonlocal_rhoSglScrewNeg0 ( f , myInstance ) + noise ( 2 )
enddo
2010-01-05 21:37:24 +05:30
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
!*********************************************************************
2010-10-26 18:46:37 +05:30
!* absolute state tolerance *
2009-09-18 21:07:14 +05:30
!*********************************************************************
2010-10-26 18:46:37 +05:30
pure function constitutive_nonlocal_aTolState ( myInstance )
2009-09-18 21:07:14 +05:30
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 ) ) :: &
2010-10-26 18:46:37 +05:30
constitutive_nonlocal_aTolState ! absolute state tolerance for the current instance of this constitution
2009-09-18 21:07:14 +05:30
!*** local variables
2010-10-26 18:46:37 +05:30
constitutive_nonlocal_aTolState = constitutive_nonlocal_aTolRho ( myInstance )
2009-09-18 21:07:14 +05:30
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 ) )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_homogenizedC = constitutive_nonlocal_Cslip_66 ( 1 : 6 , 1 : 6 , myInstance )
2009-08-11 22:01:57 +05:30
endfunction
!*********************************************************************
!* calculates quantities characterizing the microstructure *
!*********************************************************************
2010-10-12 18:38:54 +05:30
subroutine constitutive_nonlocal_microstructure ( state , Temperature , Tstar_v , Fe , Fp , 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 , &
2011-02-23 13:38:06 +05:30
math_transpose3x3 , &
2009-08-11 22:01:57 +05:30
pi
2010-02-17 18:51:36 +05:30
use debug , only : debugger , &
2010-11-03 22:52:48 +05:30
verboseDebugger
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 , &
2010-10-12 18:38:54 +05:30
phase_localConstitution , &
2009-08-11 22:01:57 +05:30
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
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
2011-02-23 13:38:06 +05:30
myPhase , &
2009-08-11 22:01:57 +05:30
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
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
2010-06-21 21:28:56 +05:30
real ( pReal ) nu ! poisson's ratio
real ( pReal ) , dimension ( 3 , 2 ) :: rhoExcessDifference , & ! finite differences of excess density (in 3 directions for edge and screw)
disloGradients ! spatial gradient in excess dislocation density (in 3 directions for edge and screw)
real ( pReal ) , dimension ( 3 , 3 ) :: sigma , & ! dislocation stress for one slip system in its slip system frame
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
F , & ! total deformation gradient
2010-06-21 21:28:56 +05:30
neighboring_F , & ! total deformation gradient of neighbor
invFe , & ! inverse elastic deformation gradient
2011-02-23 13:38:06 +05:30
Q ! inverse transpose of 3x3 matrix with finite differences of opposing position vectors
2010-10-26 19:12:18 +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-10-12 18:38:54 +05:30
real ( pReal ) , dimension ( 2 , constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) ) :: &
rhoExcess ! central excess density
2010-06-21 21:28:56 +05:30
real ( pReal ) , dimension ( 6 , 2 , constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) ) :: &
neighboring_rhoExcess ! excess density for each neighbor, dislo character and slip system
2011-02-23 13:38:06 +05:30
real ( pReal ) , dimension ( 3 , 6 ) :: neighboring_position ! position vector of each neighbor when seen from the centreal material point's lattice frame
2010-01-05 21:37:24 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 8 ) :: &
2010-06-21 21:28:56 +05:30
rhoSgl ! single dislocation density (edge+, edge-, screw+, screw-, used edge+, used edge-, used screw+, used screw-)
2010-01-05 21:37:24 +05:30
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 ) ) ) ) :: &
2010-10-26 19:12:18 +05:30
transmissivity , & ! transmissivity
2009-08-11 22:01:57 +05:30
rhoForest , & ! forest dislocation density
2010-02-17 18:51:36 +05:30
tauThreshold , & ! threshold shear stress
2010-06-21 21:28:56 +05:30
tau ! resolved shear stress
2009-08-11 22:01:57 +05:30
2011-02-23 13:38:06 +05:30
myPhase = material_phase ( g , ip , el )
myInstance = phase_constitutionInstance ( myPhase )
2009-08-11 22:01:57 +05:30
myStructure = constitutive_nonlocal_structure ( myInstance )
ns = constitutive_nonlocal_totalNslip ( myInstance )
!**********************************************************************
!*** get basic states
2011-02-09 18:42:46 +05:30
forall ( t = 1 : 4 ) rhoSgl ( 1 : ns , t ) = max ( state ( g , ip , el ) % p ( ( t - 1 ) * ns + 1 : t * ns ) , 0.0_pReal ) ! ensure positive single mobile densities
forall ( t = 5 : 8 ) rhoSgl ( 1 : ns , t ) = state ( g , ip , el ) % p ( ( t - 1 ) * ns + 1 : t * ns )
forall ( c = 1 : 2 ) rhoDip ( 1 : ns , c ) = max ( state ( g , ip , el ) % p ( ( c + 7 ) * ns + 1 : ( c + 8 ) * ns ) , 0.0_pReal ) ! ensure positive dipole densities
where ( rhoSgl ( 1 : ns , 1 : 4 ) < min ( 0.1 , 0.01 * constitutive_nonlocal_aTolRho ( myInstance ) ) ) &
rhoSgl ( 1 : ns , 1 : 4 ) = 0.0_pReal ! delete non-significant single density
2009-08-11 22:01:57 +05:30
!**********************************************************************
!*** calculate dependent states
!*** calculate the forest dislocation density
forall ( s = 1 : ns ) &
2011-02-09 18:42:46 +05:30
rhoForest ( s ) = dot_product ( ( sum ( abs ( rhoSgl ( 1 : ns , ( / 1 , 2 , 5 , 6 / ) ) ) , 2 ) + rhoDip ( 1 : ns , 1 ) ) , &
2010-01-05 21:37:24 +05:30
constitutive_nonlocal_forestProjectionEdge ( s , 1 : ns , myInstance ) ) &
2011-02-09 18:42:46 +05:30
+ dot_product ( ( sum ( abs ( rhoSgl ( 1 : ns , ( / 3 , 4 , 7 , 8 / ) ) ) , 2 ) + rhoDip ( 1 : ns , 2 ) ) , &
2010-10-26 19:12:18 +05:30
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
2011-02-04 21:11:32 +05:30
2011-02-23 13:38:06 +05:30
if ( . not . phase_localConstitution ( myPhase ) ) then ! only calculate dislocation stress for nonlocal material
2011-02-04 21:11:32 +05:30
2011-02-09 18:42:46 +05:30
F = math_mul33x33 ( Fe ( 1 : 3 , 1 : 3 , g , ip , el ) , Fp ( 1 : 3 , 1 : 3 , g , ip , el ) )
invFe = math_inv3x3 ( Fe ( 1 : 3 , 1 : 3 , g , ip , el ) )
2011-02-04 21:11:32 +05:30
nu = constitutive_nonlocal_nu ( myInstance )
forall ( s = 1 : ns , c = 1 : 2 ) &
rhoExcess ( c , s ) = state ( g , ip , el ) % p ( ( 2 * c - 2 ) * ns + s ) + abs ( state ( g , ip , el ) % p ( ( 2 * c + 2 ) * ns + s ) ) &
- state ( g , ip , el ) % p ( ( 2 * c - 1 ) * ns + s ) - abs ( state ( g , ip , el ) % p ( ( 2 * c + 3 ) * ns + s ) )
do n = 1 , 6
neighboring_el = mesh_ipNeighborhood ( 1 , n , ip , el )
neighboring_ip = mesh_ipNeighborhood ( 2 , n , ip , el )
if ( neighboring_ip == 0 . or . neighboring_el == 0 ) then ! at free surfaces ...
neighboring_el = el ! ... use central values instead of neighboring values
2010-10-12 18:38:54 +05:30
neighboring_ip = ip
2011-02-23 13:38:06 +05:30
neighboring_position ( 1 : 3 , n ) = 0.0_pReal
2011-02-09 18:42:46 +05:30
neighboring_rhoExcess ( n , 1 : 2 , 1 : ns ) = rhoExcess
2011-02-04 21:11:32 +05:30
elseif ( phase_localConstitution ( material_phase ( 1 , neighboring_ip , neighboring_el ) ) ) then ! for neighbors with local constitution
neighboring_el = el ! ... use central values instead of neighboring values
neighboring_ip = ip
2011-02-23 13:38:06 +05:30
neighboring_position ( 1 : 3 , n ) = 0.0_pReal
2011-02-09 18:42:46 +05:30
neighboring_rhoExcess ( n , 1 : 2 , 1 : ns ) = rhoExcess
2011-02-23 13:38:06 +05:30
elseif ( myPhase / = material_phase ( 1 , neighboring_ip , neighboring_el ) ) then ! for neighbors with different phase
2011-02-04 21:11:32 +05:30
neighboring_el = el ! ... use central values instead of neighboring values
neighboring_ip = ip
2011-02-23 13:38:06 +05:30
neighboring_position ( 1 : 3 , n ) = 0.0_pReal
2011-02-09 18:42:46 +05:30
neighboring_rhoExcess ( n , 1 : 2 , 1 : ns ) = rhoExcess
2011-02-04 21:11:32 +05:30
else
2011-02-09 18:42:46 +05:30
transmissivity = sum ( constitutive_nonlocal_compatibility ( 2 , 1 : ns , 1 : ns , n , ip , el ) ** 2.0_pReal , 1 )
2011-02-23 13:38:06 +05:30
if ( any ( transmissivity < 0.9_pReal ) ) then ! at grain boundary (=significantly decreased transmissivity) ...
2011-02-04 21:11:32 +05:30
neighboring_el = el ! ... use central values instead of neighboring values
neighboring_ip = ip
2011-02-23 13:38:06 +05:30
neighboring_position ( 1 : 3 , n ) = 0.0_pReal
2011-02-09 18:42:46 +05:30
neighboring_rhoExcess ( n , 1 : 2 , 1 : ns ) = rhoExcess
2011-02-04 21:11:32 +05:30
else
2011-02-09 18:42:46 +05:30
neighboring_F = math_mul33x33 ( Fe ( 1 : 3 , 1 : 3 , g , neighboring_ip , neighboring_el ) , Fp ( 1 : 3 , 1 : 3 , g , neighboring_ip , neighboring_el ) )
2011-02-23 13:38:06 +05:30
neighboring_position ( 1 : 3 , n ) = &
2011-02-09 18:42:46 +05:30
0.5_pReal * math_mul33x3 ( math_mul33x33 ( invFe , neighboring_F ) + Fp ( 1 : 3 , 1 : 3 , g , ip , el ) , &
mesh_ipCenterOfGravity ( 1 : 3 , neighboring_ip , neighboring_el ) - mesh_ipCenterOfGravity ( 1 : 3 , ip , el ) )
2011-02-23 13:38:06 +05:30
forall ( s = 1 : ns , c = 1 : 2 ) &
neighboring_rhoExcess ( n , c , s ) = state ( g , neighboring_ip , neighboring_el ) % p ( ( 2 * c - 2 ) * ns + s ) &
+ abs ( state ( g , neighboring_ip , neighboring_el ) % p ( ( 2 * c + 2 ) * ns + s ) ) &
- state ( g , neighboring_ip , neighboring_el ) % p ( ( 2 * c - 1 ) * ns + s ) &
- abs ( state ( g , neighboring_ip , neighboring_el ) % p ( ( 2 * c + 3 ) * ns + s ) )
2011-02-04 21:11:32 +05:30
endif
endif
enddo
2010-06-21 21:28:56 +05:30
2011-02-23 13:38:06 +05:30
Q = math_inv3x3 ( math_transpose3x3 ( neighboring_position ( 1 : 3 , ( / 1 , 3 , 5 / ) ) - neighboring_position ( 1 : 3 , ( / 2 , 4 , 6 / ) ) ) )
2010-06-21 21:28:56 +05:30
2011-02-04 21:11:32 +05:30
do s = 1 , ns
2011-02-23 13:38:06 +05:30
lattice2slip = math_transpose3x3 ( reshape ( ( / &
lattice_sd ( 1 : 3 , constitutive_nonlocal_slipSystemLattice ( s , myInstance ) , myStructure ) , &
- lattice_st ( 1 : 3 , constitutive_nonlocal_slipSystemLattice ( s , myInstance ) , myStructure ) , &
lattice_sn ( 1 : 3 , constitutive_nonlocal_slipSystemLattice ( s , myInstance ) , myStructure ) / ) , ( / 3 , 3 / ) ) )
2011-02-04 21:11:32 +05:30
2011-02-09 18:42:46 +05:30
rhoExcessDifference = neighboring_rhoExcess ( ( / 1 , 3 , 5 / ) , 1 : 2 , s ) - neighboring_rhoExcess ( ( / 2 , 4 , 6 / ) , 1 : 2 , s )
2011-02-04 21:11:32 +05:30
forall ( c = 1 : 2 ) &
2011-02-23 13:38:06 +05:30
disloGradients ( 1 : 3 , c ) = math_mul33x3 ( lattice2slip , math_mul33x3 ( Q , rhoExcessDifference ( 1 : 3 , c ) ) )
2010-11-03 22:52:48 +05:30
2011-02-04 21:11:32 +05:30
sigma = 0.0_pReal
2011-02-23 13:38:06 +05:30
sigma ( 1 , 1 ) = + 0.375_pReal / ( 1.0_pReal - nu ) * disloGradients ( 3 , 1 )
sigma ( 2 , 2 ) = + 0.5_pReal * nu / ( 1.0_pReal - nu ) * disloGradients ( 3 , 1 )
sigma ( 3 , 3 ) = + 0.125_pReal / ( 1.0_pReal - nu ) * disloGradients ( 3 , 1 )
sigma ( 1 , 2 ) = + 0.25_pReal * disloGradients ( 3 , 2 )
sigma ( 1 , 3 ) = - 0.125_pReal / ( 1.0_pReal - nu ) * disloGradients ( 1 , 1 ) - 0.25_pReal * disloGradients ( 2 , 2 )
2011-02-04 21:11:32 +05:30
sigma ( 2 , 1 ) = sigma ( 1 , 2 )
2011-02-23 13:38:06 +05:30
sigma ( 3 , 1 ) = sigma ( 1 , 3 )
2011-02-04 21:11:32 +05:30
forall ( i = 1 : 3 , j = 1 : 3 ) &
sigma ( i , j ) = sigma ( i , j ) * constitutive_nonlocal_Gmod ( myInstance ) * constitutive_nonlocal_burgersPerSlipSystem ( s , myInstance ) &
* constitutive_nonlocal_R ( myInstance ) ** 2.0_pReal
2011-02-23 13:38:06 +05:30
Tdislocation_v = Tdislocation_v + math_Mandel33to6 ( math_mul33x33 ( math_transpose3x3 ( lattice2slip ) , &
math_mul33x33 ( sigma , lattice2slip ) ) )
2011-02-04 21:11:32 +05:30
enddo
endif
2009-08-11 22:01:57 +05:30
2011-01-26 15:47:42 +05:30
2009-08-11 22:01:57 +05:30
!**********************************************************************
2010-10-26 19:12:18 +05:30
!*** set states
2009-08-11 22:01:57 +05:30
2010-10-26 19:12:18 +05:30
state ( g , ip , el ) % p ( 1 : 8 * ns ) = reshape ( rhoSgl , ( / 8 * ns / ) ) ! ensure positive single mobile densities
state ( g , ip , el ) % p ( 8 * ns + 1 : 10 * ns ) = reshape ( rhoDip , ( / 2 * ns / ) ) ! ensure positive dipole densities
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
endsubroutine
!*********************************************************************
!* calculates kinetics *
!*********************************************************************
2010-10-01 17:48:49 +05:30
subroutine constitutive_nonlocal_kinetics ( Tstar_v , Temperature , state , g , ip , el , dv_dtau )
2010-02-17 18:51:36 +05:30
use prec , only : pReal , &
pInt , &
p_vec
use math , only : math_mul6x6 , &
math_Mandel6to33
use debug , only : debugger , &
2010-11-03 22:52:48 +05:30
verboseDebugger , &
debug_g , &
debug_i , &
debug_e
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
2010-10-26 19:12:18 +05:30
type ( p_vec ) , intent ( in ) :: state ! microstructural state
2010-02-17 18:51:36 +05:30
real ( pReal ) , dimension ( 6 ) , intent ( in ) :: Tstar_v ! 2nd Piola-Kirchhoff stress in Mandel notation
!*** output variables
2010-10-01 17:48:49 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) ) , &
intent ( out ) , optional :: dv_dtau ! velocity derivative with respect to resolved shear stress
2010-02-17 18:51:36 +05:30
!*** 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
2010-10-01 17:48:49 +05:30
tau , & ! resolved shear stress
rhoForest ! forest dislocation density
2011-01-26 15:47:42 +05:30
real ( pReal ) boltzmannProbability , &
tauRel , & ! relative thermally active resolved shear stress
wallFunc , & ! functions reflecting the shape of the obstacle wall (see PhD thesis Mohles p.53)
timeRatio ! ratio of travel to dwell time
2010-02-17 18:51:36 +05:30
myInstance = phase_constitutionInstance ( material_phase ( g , ip , el ) )
myStructure = constitutive_nonlocal_structure ( myInstance )
ns = constitutive_nonlocal_totalNslip ( myInstance )
2010-10-26 19:12:18 +05:30
rhoForest = state % p ( 10 * ns + 1 : 11 * ns )
tauThreshold = state % p ( 11 * ns + 1 : 12 * ns )
Tdislocation_v = state % p ( 12 * ns + 1 : 12 * ns + 6 )
2010-02-17 18:51:36 +05:30
tau = 0.0_pReal
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_v ( 1 : ns , 1 : 4 , g , ip , el ) = 0.0_pReal
2010-10-01 17:48:49 +05:30
if ( present ( dv_dtau ) ) dv_dtau = 0.0_pReal
2010-02-17 18:51:36 +05:30
2011-01-26 15:47:42 +05:30
if ( Temperature > 0.0_pReal ) then
2010-10-01 17:48:49 +05:30
do s = 1 , ns
2010-02-17 18:51:36 +05:30
2011-01-26 15:47:42 +05:30
tau ( s ) = math_mul6x6 ( Tstar_v + Tdislocation_v , &
lattice_Sslip_v ( : , constitutive_nonlocal_slipSystemLattice ( s , myInstance ) , myStructure ) )
2010-10-26 19:12:18 +05:30
2011-02-08 18:18:50 +05:30
!*** Only if the resolved shear stress exceeds the threshold stress, dislocations are able to cut the dislocation forest.
!*** In contrast to small atomic obstacles the forest can't be overcome by thermal activation.
!***
!*** mean travel distance
!*** The mean dislocation velocity is calculated as: --------------------------
!*** dwell time + travel time
!***
!*** with : mean travel distance = inverse of the root of forest density
!*** dwell time = inverse of attack frequency times probability of success
!*** travel time = mean travel distance over velocity of sound
2011-01-26 15:47:42 +05:30
tauRel = ( abs ( tau ( s ) ) - tauThreshold ( s ) ) / constitutive_nonlocal_tauObs ( myInstance )
if ( tauRel > 0.0_pReal . and . tauRel < 1.0_pReal ) then
wallFunc = 4.0_pReal * dsqrt ( 2.0_pReal ) / 3.0_pReal * dsqrt ( 1.0_pReal - tauRel ) / tauRel
boltzmannProbability = dexp ( - constitutive_nonlocal_Qeff0 ( s , myInstance ) * wallFunc / ( kB * Temperature ) )
timeRatio = boltzmannProbability * constitutive_nonlocal_fattack ( myInstance ) &
/ ( constitutive_nonlocal_vs ( myInstance ) * dsqrt ( rhoForest ( s ) ) )
constitutive_nonlocal_v ( s , : , g , ip , el ) = sign ( constitutive_nonlocal_vs ( myInstance ) , tau ( s ) ) * timeRatio / ( 1.0_pReal + timeRatio )
2010-10-26 19:12:18 +05:30
2011-01-26 15:47:42 +05:30
if ( present ( dv_dtau ) ) then
dv_dtau ( s ) = abs ( constitutive_nonlocal_v ( s , 1 , g , ip , el ) ) * constitutive_nonlocal_Qeff0 ( s , myInstance ) &
/ ( kB * Temperature * ( 1.0_pReal + timeRatio ) ) &
* 0.5_pReal * wallFunc * ( 2.0_pReal - tauRel ) &
/ ( ( 1.0_pReal - tauRel ) * ( abs ( tau ( s ) ) - tauThreshold ( s ) ) )
endif
2011-02-08 18:18:50 +05:30
!*** If resolved stress exceeds threshold plus obstacle stress, the probability for thermal activation is 1.
!*** The tangent is zero, since no dependency of tau.
2011-01-26 15:47:42 +05:30
elseif ( tauRel > = 1.0_pReal ) then
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_v ( s , 1 : 4 , g , ip , el ) = sign ( constitutive_nonlocal_vs ( myInstance ) , tau ( s ) ) &
* constitutive_nonlocal_fattack ( myInstance ) &
/ ( constitutive_nonlocal_vs ( myInstance ) * dsqrt ( rhoForest ( s ) ) &
+ constitutive_nonlocal_fattack ( myInstance ) )
2010-10-01 17:48:49 +05:30
endif
enddo
endif
2010-02-17 18:51:36 +05:30
2010-11-03 22:52:48 +05:30
!if (verboseDebugger .and. s) then
2010-10-26 19:12:18 +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-10-26 19:12:18 +05:30
! write(6,'(a,/,12(f12.5,x),/)') 'tau / MPa', tau/1e6_pReal
! write(6,'(a,/,12(e12.5,x),/)') 'rhoForest / 1/m**2', rhoForest
! write(6,'(a,/,4(12(f12.5,x),/))') 'v / 1e-3m/s', constitutive_nonlocal_v(:,:,g,ip,el)*1e3
2010-11-03 22:52:48 +05:30
! !$OMP END CRITICAL (write2out)
2010-10-26 19:12:18 +05:30
!endif
2010-02-17 18:51:36 +05:30
2009-08-11 22:01:57 +05:30
endsubroutine
!*********************************************************************
!* calculates plastic velocity gradient and its tangent *
!*********************************************************************
2010-10-26 18:46:37 +05:30
subroutine constitutive_nonlocal_LpAndItsTangent ( Lp , dLp_dTstar99 , Tstar_v , Temperature , state , g , ip , el )
2009-08-11 22:01:57 +05:30
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-11-03 22:52:48 +05:30
verboseDebugger , &
debug_g , &
debug_i , &
debug_e
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 ) :: &
2010-10-26 18:46:37 +05:30
state ! microstructural state
2009-08-11 22:01:57 +05:30
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
2010-10-01 17:48:49 +05:30
dv_dtau , & ! velocity derivative with respect to the shear stress
dgdotTotal_dtau , & ! derivative of the shear rate with respect to the shear stress
rhoForest ! forest dislocation density
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 ) &
2011-02-09 18:42:46 +05:30
rhoSgl ( 1 : ns , t ) = state ( g , ip , el ) % p ( ( t - 1 ) * ns + 1 : t * ns )
2010-08-04 05:17:00 +05:30
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
2010-02-17 18:51:36 +05:30
rhoSgl ( s , t - 4 ) = rhoSgl ( s , t - 4 ) + abs ( rhoSgl ( s , t ) )
2009-08-28 19:20:47 +05:30
2010-10-01 17:48:49 +05:30
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 )
2009-08-28 19:20:47 +05:30
2010-10-26 19:12:18 +05:30
call constitutive_nonlocal_kinetics ( Tstar_v , Temperature , state ( g , ip , el ) , g , ip , el , dv_dtau ) ! update dislocation velocity
2009-08-28 19:20:47 +05:30
!*** Calculation of gdot and its tangent
2010-10-26 18:46:37 +05:30
forall ( t = 1 : 4 ) &
2011-02-09 18:42:46 +05:30
gdot ( 1 : ns , t ) = rhoSgl ( 1 : ns , t ) * constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) &
* constitutive_nonlocal_v ( 1 : ns , t , g , ip , el )
2010-02-17 18:51:36 +05:30
gdotTotal = sum ( gdot , 2 )
2009-08-28 19:20:47 +05:30
2011-02-09 18:42:46 +05:30
dgdotTotal_dtau = sum ( rhoSgl , 2 ) * constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) * dv_dtau
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 )
2011-02-09 18:42:46 +05:30
Lp = Lp + gdotTotal ( s ) * lattice_Sslip ( 1 : 3 , 1 : 3 , 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-11-03 22:52:48 +05:30
!if (verboseDebugger .and. (debug_g==g .and. debug_i==i .and. debug_e==e)) then
2010-05-21 14:21:15 +05:30
! !$OMP CRITICAL (write2out)
! write(6,*) '::: LpandItsTangent',g,ip,el
! write(6,*)
2010-10-26 19:12:18 +05:30
! write(6,'(a,/,12(f12.5,x),/)') 'v / 1e-3m/s', constitutive_nonlocal_v(:,:,g,ip,el)*1e3
! 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
2010-05-21 14:21:15 +05:30
! write(6,'(a,/,3(3(f12.7,x)/))') 'Lp',Lp
! ! call flush(6)
2010-11-03 22:52:48 +05:30
! !$OMP END CRITICAL (write2out)
2010-05-21 14:21:15 +05:30
!endif
2009-08-11 22:01:57 +05:30
endsubroutine
!*********************************************************************
!* rate of change of microstructure *
!*********************************************************************
2010-10-12 18:38:54 +05:30
subroutine constitutive_nonlocal_dotState ( dotState , Tstar_v , previousTstar_v , Fe , Fp , Temperature , dt_previous , &
2010-10-26 18:46:37 +05:30
state , previousState , aTolState , timestep , orientation , g , ip , el )
2009-08-11 22:01:57 +05:30
use prec , only : pReal , &
pInt , &
p_vec
2011-02-24 15:31:41 +05:30
use numerics , only : numerics_integrationMode
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-11-03 22:52:48 +05:30
debug_g , &
debug_i , &
debug_e , &
2010-03-19 19:44:08 +05:30
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-10-15 18:49:26 +05:30
math_QuaternionDisorientation , &
math_qRot , &
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 , &
2010-10-01 17:48:49 +05:30
lattice_NslipSystem
2010-10-26 19:12:18 +05:30
use FEsolving , only : theInc , &
FEsolving_execElem , &
FEsolving_execIP
2009-08-11 22:01:57 +05:30
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-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
2010-10-15 18:49:26 +05:30
real ( pReal ) , dimension ( 4 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
orientation ! crystal lattice orientation
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
2010-10-26 18:46:37 +05:30
aTolState ! absolute state tolerance
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
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-10-26 19:12:18 +05:30
neighboring_el , & ! element number of my neighbor
neighboring_ip , & ! integration point of my neighbor
2011-02-16 22:05:38 +05:30
neighboring_n , & ! neighbor index pointing to me when looking from my 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
2010-10-12 18:38:54 +05:30
topp , & ! type of dislocation with opposite sign to t
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 ) :: &
2011-02-16 22:05:38 +05:30
rhoDot , & ! density evolution
rhoDotRemobilization , & ! density evolution by remobilization
rhoDotMultiplication , & ! density evolution by multiplication
rhoDotFlux , & ! density evolution by flux
neighboring_rhoDotFlux , & ! density evolution by flux at neighbor
rhoDotSingle2DipoleGlide , & ! density evolution by dipole formation (by glide)
2010-05-21 14:21:15 +05:30
rhoDotAthermalAnnihilation , & ! density evolution by athermal annihilation
2011-02-16 22:05:38 +05:30
rhoDotThermalAnnihilation , & ! density evolution by thermal annihilation
2010-05-21 14:21:15 +05:30
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 ) :: &
2011-02-16 22:05:38 +05:30
rhoSgl , & ! current single dislocation densities (positive/negative screw and edge without dipoles)
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 ) :: &
2011-02-16 22:05:38 +05:30
fluxdensity , & ! flux density at central material point
neighboring_fluxdensity , & ! flux density at neighboring material point
gdot ! shear rates
2009-08-11 22:01:57 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) ) :: &
2011-02-16 22:05:38 +05:30
rhoForest , & ! forest dislocation density
tauThreshold , & ! threshold shear stress
tau , & ! current resolved shear stress
previousTau , & ! previous resolved shear stress
invLambda , & ! inverse of mean free path for dislocations
vClimb ! climb velocity of edge dipoles
2009-08-28 19:20:47 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 2 ) :: &
2011-02-16 22:05:38 +05:30
rhoDip , & ! current dipole dislocation densities (screw and edge dipoles)
previousRhoDip , & ! previous dipole dislocation densities (screw and edge dipoles)
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
2009-08-28 19:20:47 +05:30
real ( pReal ) , dimension ( 3 , constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( g , ip , el ) ) ) , 4 ) :: &
2011-02-16 22:05:38 +05:30
m ! direction of dislocation motion
real ( pReal ) , dimension ( 3 , 3 ) :: my_F , & ! my total deformation gradient
neighboring_F , & ! total deformation gradient of my neighbor
my_Fe , & ! my elastic deformation gradient
neighboring_Fe , & ! elastic 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 ) :: normal_neighbor2me , & ! interface normal pointing from my neighbor to me in neighbor's lattice configuration
normal_neighbor2me_defConf , & ! interface normal pointing from my neighbor to me in shared deformed configuration
normal_me2neighbor , & ! interface normal pointing from me to my neighbor in my lattice configuration
normal_me2neighbor_defConf ! interface normal pointing from me to my neighbor in shared deformed configuration
real ( pReal ) area , & ! area of the current interface
transmissivity , & ! overall transmissivity of dislocation flux to neighboring material point
lineLength , & ! dislocation line length leaving the current interface
D , & ! self diffusion
2010-10-26 19:12:18 +05:30
correction
2011-02-16 22:05:38 +05:30
logical considerEnteringFlux , &
considerLeavingFlux
2010-03-04 22:44:47 +05:30
2010-11-03 22:52:48 +05:30
if ( verboseDebugger . and . ( debug_g == g . and . debug_i == ip . and . debug_e == el ) ) then
2010-03-04 22:44:47 +05:30
!$OMP CRITICAL (write2out)
write ( 6 , * ) '::: constitutive_nonlocal_dotState at ' , g , ip , el
write ( 6 , * )
2010-11-03 22:52:48 +05:30
!$OMP END CRITICAL (write2out)
2010-03-04 22:44:47 +05:30
endif
2009-12-15 13:50:31 +05:30
2010-08-20 04:30:26 +05:30
select case ( mesh_element ( 2 , el ) )
case ( 1 , 6 , 7 , 8 , 9 )
! all fine
case default
call IO_error ( - 1 , el , ip , g , 'element type not supported for nonlocal constitution' )
end select
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
2011-02-09 18:42:46 +05:30
forall ( t = 1 : 8 ) rhoSgl ( 1 : ns , t ) = state ( g , ip , el ) % p ( ( t - 1 ) * ns + 1 : t * ns )
forall ( t = 1 : 8 ) previousRhoSgl ( 1 : ns , t ) = previousState ( g , ip , el ) % p ( ( t - 1 ) * ns + 1 : t * ns )
forall ( c = 1 : 2 ) rhoDip ( 1 : ns , c ) = state ( g , ip , el ) % p ( ( 7 + c ) * ns + 1 : ( 8 + c ) * ns )
forall ( c = 1 : 2 ) previousRhoDip ( 1 : ns , c ) = previousState ( g , ip , el ) % p ( ( 7 + c ) * ns + 1 : ( 8 + c ) * ns )
2010-01-05 21:37:24 +05:30
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...
2010-10-12 18:38:54 +05:30
dotState ( g , ip , el ) % p = 0.0_pReal ! ...return without doing anything (-> zero dotState)
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
2010-10-26 19:12:18 +05:30
call constitutive_nonlocal_kinetics ( Tstar_v , Temperature , state ( g , ip , el ) , g , ip , el ) ! get velocities
2009-08-28 19:20:47 +05:30
forall ( t = 1 : 4 ) &
2011-02-09 18:42:46 +05:30
gdot ( 1 : ns , t ) = rhoSgl ( 1 : ns , t ) * constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) &
* constitutive_nonlocal_v ( 1 : ns , t , g , ip , el )
2010-02-17 18:51:36 +05:30
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
2010-11-03 22:52:48 +05:30
if ( verboseDebugger . and . ( debug_g == g . and . debug_i == ip . and . debug_e == el ) ) then
2010-10-26 19:12:18 +05:30
!$OMP CRITICAL (write2out)
write ( 6 , '(a,/,10(12(e12.5,x),/))' ) 'rho / 1/m^2' , rhoSgl , rhoDip
write ( 6 , '(a,/,4(12(e12.5,x),/))' ) 'v / m/s' , constitutive_nonlocal_v ( : , : , g , ip , el )
write ( 6 , '(a,/,4(12(e12.5,x),/))' ) 'gdot / 1/s' , gdot
2010-11-03 22:52:48 +05:30
!$OMP END CRITICAL (write2out)
2010-10-26 19:12:18 +05:30
endif
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 )
2011-02-09 18:42:46 +05:30
tau ( s ) = math_mul6x6 ( Tstar_v + Tdislocation_v , lattice_Sslip_v ( 1 : 6 , sLattice , myStructure ) )
previousTau ( s ) = math_mul6x6 ( previousTstar_v + previousTdislocation_v , lattice_Sslip_v ( 1 : 6 , 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
2011-02-09 18:42:46 +05:30
dLower ( 1 : ns , 1 ) = constitutive_nonlocal_dLowerEdgePerSlipSystem ( 1 : ns , myInstance )
dLower ( 1 : ns , 2 ) = constitutive_nonlocal_dLowerScrewPerSlipSystem ( 1 : ns , myInstance )
dUpper ( 1 : ns , 2 ) = min ( 1.0_pReal / sqrt ( sum ( abs ( rhoSgl ) , 2 ) + sum ( rhoDip , 2 ) ) , &
constitutive_nonlocal_Gmod ( myInstance ) * constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) &
/ ( 8.0_pReal * pi * abs ( tau ) ) )
dUpper ( 1 : ns , 1 ) = dUpper ( 1 : ns , 2 ) / ( 1.0_pReal - constitutive_nonlocal_nu ( myInstance ) )
previousDUpper ( 1 : ns , 2 ) = min ( 1.0_pReal / sqrt ( sum ( abs ( previousRhoSgl ) , 2 ) + sum ( previousRhoDip , 2 ) ) , &
constitutive_nonlocal_Gmod ( myInstance ) * constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) &
/ ( 8.0_pReal * pi * abs ( previousTau ) ) )
previousDUpper ( 1 : ns , 1 ) = previousDUpper ( 1 : ns , 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-10-26 19:12:18 +05:30
rhoDotMultiplication = 0.0_pReal
2011-02-09 18:42:46 +05:30
where ( rhoSgl ( 1 : ns , 3 : 4 ) > 0.0_pReal ) &
rhoDotMultiplication ( 1 : ns , 1 : 2 ) = spread ( 0.5_pReal * sum ( abs ( gdot ( 1 : ns , 3 : 4 ) ) , 2 ) * sqrt ( rhoForest ) &
/ constitutive_nonlocal_lambda0PerSlipSystem ( 1 : ns , myInstance ) &
/ constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) , 2 , 2 )
where ( rhoSgl ( 1 : ns , 1 : 2 ) > 0.0_pReal ) &
rhoDotMultiplication ( 1 : ns , 3 : 4 ) = spread ( 0.5_pReal * sum ( abs ( gdot ( 1 : ns , 1 : 2 ) ) , 2 ) * sqrt ( rhoForest ) &
/ constitutive_nonlocal_lambda0PerSlipSystem ( 1 : ns , myInstance ) &
/ constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) , 2 , 2 )
2009-08-11 22:01:57 +05:30
2009-08-12 16:52:02 +05:30
!****************************************************************************
2011-01-11 20:25:36 +05:30
!*** calculate dislocation fluxes (only for nonlocal constitution)
2009-08-12 16:52:02 +05:30
2010-05-21 14:21:15 +05:30
rhoDotFlux = 0.0_pReal
2009-10-07 21:01:52 +05:30
2011-01-11 20:25:36 +05:30
if ( . not . phase_localConstitution ( material_phase ( g , ip , el ) ) ) then ! only for nonlocal constitution
2011-02-23 13:38:06 +05:30
!*** take care of the definition of lattice_st = lattice_sd x lattice_sn !!!
!*** opposite sign to our p vector in the (s,p,n) triplet !!!
2011-02-09 18:42:46 +05:30
m ( 1 : 3 , 1 : ns , 1 ) = lattice_sd ( 1 : 3 , constitutive_nonlocal_slipSystemLattice ( 1 : ns , myInstance ) , myStructure )
m ( 1 : 3 , 1 : ns , 2 ) = - lattice_sd ( 1 : 3 , constitutive_nonlocal_slipSystemLattice ( 1 : ns , myInstance ) , myStructure )
2011-02-23 13:38:06 +05:30
m ( 1 : 3 , 1 : ns , 3 ) = - lattice_st ( 1 : 3 , constitutive_nonlocal_slipSystemLattice ( 1 : ns , myInstance ) , myStructure )
m ( 1 : 3 , 1 : ns , 4 ) = lattice_st ( 1 : 3 , constitutive_nonlocal_slipSystemLattice ( 1 : ns , myInstance ) , myStructure )
2010-10-15 18:49:26 +05:30
2011-02-16 22:05:38 +05:30
my_Fe = Fe ( 1 : 3 , 1 : 3 , g , ip , el )
my_F = math_mul33x33 ( my_Fe , Fp ( 1 : 3 , 1 : 3 , 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
2011-02-09 18:42:46 +05:30
fluxdensity = rhoSgl ( 1 : ns , 1 : 4 ) * constitutive_nonlocal_v ( 1 : ns , 1 : 4 , g , ip , el )
2011-01-11 20:25:36 +05:30
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 )
2011-02-16 22:05:38 +05:30
if ( neighboring_el > 0_pInt . and . neighboring_ip > 0_pInt ) then ! if neighbor exists ...
do neighboring_n = 1 , FE_NipNeighbors ( mesh_element ( 2 , neighboring_el ) ) ! find neighboring index that points from my neighbor to myself
if ( el == mesh_ipNeighborhood ( 1 , neighboring_n , neighboring_ip , neighboring_el ) &
2011-02-24 15:31:41 +05:30
. and . ip == mesh_ipNeighborhood ( 2 , neighboring_n , neighboring_ip , neighboring_el ) ) then ! possible candidate
if ( math_mul3x3 ( mesh_ipAreaNormal ( 1 : 3 , n , ip , el ) , &
mesh_ipAreaNormal ( 1 : 3 , neighboring_n , neighboring_ip , neighboring_el ) ) < 0.0_pReal ) then ! area normals have opposite orientation (we have to check that because of special case for single element with two ips and periodicity. In this case the neighbor is identical in two different directions.)
exit
endif
endif
2011-02-16 22:05:38 +05:30
enddo
endif
2011-01-11 20:25:36 +05:30
opposite_n = n + mod ( n , 2 ) - mod ( n + 1 , 2 )
opposite_el = mesh_ipNeighborhood ( 1 , opposite_n , ip , el )
opposite_ip = mesh_ipNeighborhood ( 2 , opposite_n , ip , el )
2011-02-16 22:05:38 +05:30
if ( neighboring_el > 0_pInt . and . neighboring_ip > 0_pInt ) then ! if neighbor exists, average deformation gradient
neighboring_Fe = Fe ( 1 : 3 , 1 : 3 , g , neighboring_ip , neighboring_el )
neighboring_F = math_mul33x33 ( neighboring_Fe , Fp ( 1 : 3 , 1 : 3 , g , neighboring_ip , neighboring_el ) )
Favg = 0.5_pReal * ( my_F + neighboring_F )
2011-01-11 20:25:36 +05:30
else ! if no neighbor, take my value as average
2011-02-16 22:05:38 +05:30
Favg = my_F
2011-01-11 20:25:36 +05:30
endif
2011-02-16 22:05:38 +05:30
!* FLUX FROM ME TO MY NEIGHBOR
!* This is not considered, if my opposite neighbor has a local constitution.
!* Then, we assume, that the opposite(!) neighbor sends an equal amount of dislocations to me.
!* So the net flux in the direction of my neighbor is equal to zero:
!* leaving flux to neighbor == entering flux from opposite neighbor
!* In case of reduced transmissivity, part of the leaving flux is stored as dead dislocation density.
!* That means for an interface of zero transmissivity the leaving flux is fully converted to dead dislocations.
2011-01-11 23:30:29 +05:30
2011-02-16 22:05:38 +05:30
considerLeavingFlux = . true .
if ( opposite_el > 0 . and . opposite_ip > 0 ) then
if ( phase_localConstitution ( material_phase ( 1 , opposite_ip , opposite_el ) ) ) &
considerLeavingFlux = . false .
endif
if ( considerLeavingFlux ) then
normal_me2neighbor_defConf = math_det3x3 ( Favg ) * math_mul33x3 ( math_inv3x3 ( transpose ( Favg ) ) , mesh_ipAreaNormal ( 1 : 3 , n , ip , el ) ) ! calculate the normal of the interface in (average) deformed configuration (pointing from me to my neighbor!!!)
normal_me2neighbor = math_mul33x3 ( transpose ( my_Fe ) , normal_me2neighbor_defConf ) / math_det3x3 ( my_Fe ) ! interface normal in my lattice configuration
area = mesh_ipArea ( n , ip , el ) * math_norm3 ( normal_me2neighbor )
normal_me2neighbor = normal_me2neighbor / math_norm3 ( normal_me2neighbor ) ! normalize the surface normal to unit length
do s = 1 , ns
do t = 1 , 4
c = ( t + 1 ) / 2
if ( fluxdensity ( s , t ) * math_mul3x3 ( m ( 1 : 3 , s , t ) , normal_me2neighbor ) > 0.0_pReal ) then ! flux from me to my neighbor == leaving flux for me (might also be a pure flux from my mobile density to dead density if interface not at all transmissive)
lineLength = fluxdensity ( s , t ) * math_mul3x3 ( m ( 1 : 3 , s , t ) , normal_me2neighbor ) * area ! positive line length that wants to leave through this interface
transmissivity = sum ( constitutive_nonlocal_compatibility ( c , 1 : ns , s , n , ip , el ) ** 2.0_pReal ) ! overall transmissivity from this slip system to my neighbor
rhoDotFlux ( s , t ) = rhoDotFlux ( s , t ) - lineLength / mesh_ipVolume ( ip , el ) ! subtract dislocation flux from current mobile type
rhoDotFlux ( s , t + 4 ) = rhoDotFlux ( s , t + 4 ) + lineLength / mesh_ipVolume ( ip , el ) * ( 1.0_pReal - transmissivity ) &
* sign ( 1.0_pReal , fluxdensity ( s , t ) ) ! dislocation flux that is not able to leave through interface (because of low transmissivity) will remain as immobile single density at the material point
2011-01-11 20:25:36 +05:30
endif
2011-02-16 22:05:38 +05:30
enddo
enddo
endif
!* FLUX FROM MY NEIGHBOR TO ME
!* This is only considered, if I have a neighbor of nonlocal constitution that is at least a little bit compatible.
!* If it's not at all compatible, no flux is arriving, because everything is dammed in front of my neighbor's interface.
!* The entering flux from my neighbor will be distributed on my slip systems according to the compatibility
considerEnteringFlux = . false .
if ( neighboring_el > 0_pInt . or . neighboring_ip > 0_pInt ) then
if ( . not . phase_localConstitution ( material_phase ( 1 , neighboring_ip , neighboring_el ) ) &
. and . any ( constitutive_nonlocal_compatibility ( : , : , : , n , ip , el ) > 0.0_pReal ) ) &
considerEnteringFlux = . true .
endif
if ( considerEnteringFlux ) then
forall ( t = 1 : 4 ) &
neighboring_fluxdensity ( 1 : ns , t ) = state ( g , neighboring_ip , neighboring_el ) % p ( ( t - 1 ) * ns + 1 : t * ns ) &
* constitutive_nonlocal_v ( 1 : ns , t , g , neighboring_ip , neighboring_el )
normal_neighbor2me_defConf = math_det3x3 ( Favg ) &
* math_mul33x3 ( math_inv3x3 ( transpose ( Favg ) ) , mesh_ipAreaNormal ( 1 : 3 , neighboring_n , neighboring_ip , neighboring_el ) ) ! calculate the normal of the interface in (average) deformed configuration (now pointing from my neighbor to me!!!)
normal_neighbor2me = math_mul33x3 ( transpose ( neighboring_Fe ) , normal_neighbor2me_defConf ) / math_det3x3 ( neighboring_Fe ) ! interface normal in the lattice configuration of my neighbor
area = mesh_ipArea ( neighboring_n , neighboring_ip , neighboring_el ) * math_norm3 ( normal_neighbor2me )
normal_neighbor2me = normal_neighbor2me / math_norm3 ( normal_neighbor2me ) ! normalize the surface normal to unit length
do s = 1 , ns
do t = 1 , 4
c = ( t + 1 ) / 2
topp = t + mod ( t , 2 ) - mod ( t + 1 , 2 )
if ( neighboring_fluxdensity ( s , t ) * math_mul3x3 ( m ( 1 : 3 , s , t ) , normal_neighbor2me ) > 0.0_pReal ) then ! flux from my neighbor to me == entering flux for me
lineLength = neighboring_fluxdensity ( s , t ) * math_mul3x3 ( m ( 1 : 3 , s , t ) , normal_neighbor2me ) * area ! positive line length that wants to enter through this interface
where ( constitutive_nonlocal_compatibility ( c , 1 : ns , s , n , ip , el ) > 0.0_pReal ) & ! positive compatibility...
rhoDotFlux ( 1 : ns , t ) = rhoDotFlux ( 1 : ns , t ) + lineLength / mesh_ipVolume ( ip , el ) & ! ... transferring to equally signed dislocation type
* constitutive_nonlocal_compatibility ( c , 1 : ns , s , n , ip , el ) ** 2.0_pReal
where ( constitutive_nonlocal_compatibility ( c , 1 : ns , s , n , ip , el ) < 0.0_pReal ) & ! ..negative compatibility...
rhoDotFlux ( 1 : ns , topp ) = rhoDotFlux ( 1 : ns , topp ) + lineLength / mesh_ipVolume ( ip , el ) & ! ... transferring to opposite signed dislocation type
2011-02-23 13:59:51 +05:30
* constitutive_nonlocal_compatibility ( c , 1 : ns , s , n , ip , el ) ** 2.0_pReal
2011-01-11 20:25:36 +05:30
endif
2011-02-16 22:05:38 +05:30
enddo
enddo
2011-01-11 20:25:36 +05:30
endif
2011-02-16 22:05:38 +05:30
2011-02-24 15:31:41 +05:30
enddo ! neighbor loop
2010-10-26 19:12:18 +05:30
endif
2009-08-28 19:20:47 +05:30
2011-02-24 15:31:41 +05:30
if ( numerics_integrationMode == 1_pInt ) &
constitutive_nonlocal_rhoDotFlux ( 1 : ns , 1 : 10 , g , ip , el ) = rhoDotFlux ( 1 : ns , 1 : 10 ) ! save flux calculation for output (if in central integration mode)
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
2011-02-09 18:42:46 +05:30
rhoDotSingle2DipoleGlide ( 1 : ns , 2 * c - 1 ) = - 2.0_pReal * dUpper ( 1 : ns , c ) / constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) &
* ( rhoSgl ( 1 : ns , 2 * c - 1 ) * abs ( gdot ( 1 : ns , 2 * c ) ) & ! negative mobile --> positive mobile
+ rhoSgl ( 1 : ns , 2 * c ) * abs ( gdot ( 1 : ns , 2 * c - 1 ) ) & ! positive mobile --> negative mobile
+ abs ( rhoSgl ( 1 : ns , 2 * c + 4 ) ) * abs ( gdot ( 1 : ns , 2 * c - 1 ) ) ) ! positive mobile --> negative immobile
2010-02-17 18:51:36 +05:30
2011-02-09 18:42:46 +05:30
rhoDotSingle2DipoleGlide ( 1 : ns , 2 * c ) = - 2.0_pReal * dUpper ( 1 : ns , c ) / constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) &
* ( rhoSgl ( 1 : ns , 2 * c - 1 ) * abs ( gdot ( 1 : ns , 2 * c ) ) & ! negative mobile --> positive mobile
+ rhoSgl ( 1 : ns , 2 * c ) * abs ( gdot ( 1 : ns , 2 * c - 1 ) ) & ! positive mobile --> negative mobile
+ abs ( rhoSgl ( 1 : ns , 2 * c + 3 ) ) * abs ( gdot ( 1 : ns , 2 * c ) ) ) ! negative mobile --> positive immobile
2010-02-17 18:51:36 +05:30
2011-02-09 18:42:46 +05:30
rhoDotSingle2DipoleGlide ( 1 : ns , 2 * c + 3 ) = - 2.0_pReal * dUpper ( 1 : ns , c ) / constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) &
* rhoSgl ( 1 : ns , 2 * c + 3 ) * abs ( gdot ( 1 : ns , 2 * c ) ) ! negative mobile --> positive immobile
2010-02-17 18:51:36 +05:30
2011-02-09 18:42:46 +05:30
rhoDotSingle2DipoleGlide ( 1 : ns , 2 * c + 4 ) = - 2.0_pReal * dUpper ( 1 : ns , c ) / constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) &
* rhoSgl ( 1 : ns , 2 * c + 4 ) * abs ( gdot ( 1 : ns , 2 * c - 1 ) ) ! positive mobile --> negative immobile
2010-02-17 18:51:36 +05:30
2011-02-09 18:42:46 +05:30
rhoDotSingle2DipoleGlide ( 1 : ns , c + 8 ) = - rhoDotSingle2DipoleGlide ( 1 : ns , 2 * c - 1 ) - rhoDotSingle2DipoleGlide ( 1 : ns , 2 * c ) &
+ abs ( rhoDotSingle2DipoleGlide ( 1 : ns , 2 * c + 3 ) ) + abs ( rhoDotSingle2DipoleGlide ( 1 : ns , 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 ) &
2011-02-09 18:42:46 +05:30
rhoDotAthermalAnnihilation ( 1 : ns , c + 8 ) = - 2.0_pReal * dLower ( 1 : ns , c ) / constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) &
* ( 2.0_pReal * ( rhoSgl ( 1 : ns , 2 * c - 1 ) * abs ( gdot ( 1 : ns , 2 * c ) ) + rhoSgl ( 1 : ns , 2 * c ) * abs ( gdot ( 1 : ns , 2 * c - 1 ) ) ) & ! was single hitting single
+ 2.0_pReal * ( abs ( rhoSgl ( 1 : ns , 2 * c + 3 ) ) * abs ( gdot ( 1 : ns , 2 * c ) ) + abs ( rhoSgl ( 1 : ns , 2 * c + 4 ) ) * abs ( gdot ( 1 : ns , 2 * c - 1 ) ) ) & ! was single hitting immobile single or was immobile single hit by single
+ rhoDip ( 1 : ns , c ) * ( abs ( gdot ( 1 : ns , 2 * c - 1 ) ) + abs ( gdot ( 1 : ns , 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
2011-01-26 15:47:42 +05:30
D = constitutive_nonlocal_Dsd0 ( myInstance ) * exp ( - constitutive_nonlocal_Qsd ( myInstance ) / ( kB * Temperature ) )
2009-08-28 19:20:47 +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 ) ) ) &
2011-02-09 18:42:46 +05:30
* 2.0_pReal / ( dUpper ( 1 : ns , 1 ) + dLower ( 1 : ns , 1 ) )
2009-08-28 19:20:47 +05:30
2011-02-09 18:42:46 +05:30
rhoDotThermalAnnihilation ( 1 : ns , 9 ) = - 4.0_pReal * rhoDip ( 1 : ns , 1 ) * vClimb / ( dUpper ( 1 : ns , 1 ) - dLower ( 1 : ns , 1 ) ) ! edge climb
rhoDotThermalAnnihilation ( 1 : ns , 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 ) &
2011-02-09 18:42:46 +05:30
rhoDotDipole2SingleStressChange ( 1 : ns , t ) = - 0.5_pReal * rhoDotDipole2SingleStressChange ( 1 : ns , ( 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 ) &
2011-02-09 18:42:46 +05:30
rhoDotSingle2DipoleStressChange ( 1 : ns , 8 + c ) = abs ( rhoDotSingle2DipoleStressChange ( 1 : ns , 2 * ( c - 1 ) + 1 ) ) &
+ abs ( rhoDotSingle2DipoleStressChange ( 1 : ns , 2 * ( c - 1 ) + 2 ) ) &
+ abs ( rhoDotSingle2DipoleStressChange ( 1 : ns , 2 * ( c - 1 ) + 5 ) ) &
+ abs ( rhoDotSingle2DipoleStressChange ( 1 : ns , 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 ) &
2011-02-09 18:42:46 +05:30
rhoDot ( 1 : ns , t ) = rhoDotFlux ( 1 : ns , t ) &
+ rhoDotMultiplication ( 1 : ns , t ) &
+ rhoDotRemobilization ( 1 : ns , t ) &
+ rhoDotSingle2DipoleGlide ( 1 : ns , t ) &
+ rhoDotAthermalAnnihilation ( 1 : ns , t ) &
+ rhoDotThermalAnnihilation ( 1 : ns , t )
! + rhoDotDipole2SingleStressChange(1:ns,t)
! + rhoDotSingle2DipoleStressChange(1:ns,t)
2010-05-21 14:21:15 +05:30
2010-11-03 22:52:48 +05:30
if ( verboseDebugger . and . ( debug_g == g . and . debug_i == ip . and . debug_e == el ) ) then
2009-10-07 21:01:52 +05:30
!$OMP CRITICAL (write2out)
2011-02-09 18:42:46 +05:30
write ( 6 , '(a,/,8(12(e12.5,x),/))' ) 'dislocation remobilization' , rhoDotRemobilization ( 1 : ns , 1 : 8 ) * timestep
write ( 6 , '(a,/,4(12(e12.5,x),/))' ) 'dislocation multiplication' , rhoDotMultiplication ( 1 : ns , 1 : 4 ) * timestep
2011-02-23 13:38:06 +05:30
write ( 6 , '(a,/,8(12(e12.5,x),/))' ) 'dislocation flux' , rhoDotFlux ( 1 : ns , 1 : 8 ) * timestep
2010-05-21 14:21:15 +05:30
write ( 6 , '(a,/,10(12(e12.5,x),/))' ) 'dipole formation by glide' , rhoDotSingle2DipoleGlide * timestep
2011-02-09 18:42:46 +05:30
write ( 6 , '(a,/,2(12(e12.5,x),/))' ) 'athermal dipole annihilation' , rhoDotAthermalAnnihilation ( 1 : ns , 1 : 2 ) * timestep
write ( 6 , '(a,/,2(12(e12.5,x),/))' ) 'thermally activated dipole annihilation' , rhoDotThermalAnnihilation ( 1 : ns , 9 : 10 ) * timestep
2010-05-21 14:21:15 +05:30
! 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
2011-02-09 18:42:46 +05:30
write ( 6 , '(a,/,10(12(f12.7,x),/))' ) 'relative density change' , rhoDot ( 1 : ns , 1 : 8 ) * timestep / ( abs ( rhoSgl ) + 1.0e-10 ) , &
rhoDot ( 1 : ns , 9 : 10 ) * timestep / ( rhoDip + 1.0e-10 )
2010-10-26 19:12:18 +05:30
write ( 6 , * )
2010-11-03 22:52:48 +05:30
!$OMP END CRITICAL (write2out)
2009-10-07 21:01:52 +05:30
endif
2009-08-11 22:01:57 +05:30
2010-10-26 19:12:18 +05:30
!$OMP CRITICAL (copy2dotState)
dotState ( g , ip , el ) % p ( 1 : 10 * ns ) = dotState ( g , ip , el ) % p ( 1 : 10 * ns ) + reshape ( rhoDot , ( / 10 * ns / ) )
2010-11-03 22:52:48 +05:30
!$OMP END CRITICAL (copy2dotState)
2010-10-26 19:12:18 +05:30
2009-08-11 22:01:57 +05:30
endsubroutine
2009-12-15 13:50:31 +05:30
!*********************************************************************
2010-10-15 18:49:26 +05:30
!* COMPATIBILITY UPDATE *
!* Compatibility is defined as normalized product of signed cosine *
!* of the angle between the slip plane normals and signed cosine of *
!* the angle between the slip directions. Only the largest values *
!* that sum up to a total of 1 are considered, all others are set to *
!* zero. *
2009-12-15 13:50:31 +05:30
!*********************************************************************
2010-10-12 18:38:54 +05:30
subroutine constitutive_nonlocal_updateCompatibility ( orientation , i , e )
use prec , only : pReal , &
pInt
use math , only : math_QuaternionDisorientation , &
math_mul3x3 , &
math_qRot
use material , only : material_phase , &
phase_constitution , &
phase_localConstitution , &
phase_constitutionInstance , &
homogenization_maxNgrains
use mesh , only : mesh_element , &
mesh_ipNeighborhood , &
FE_NipNeighbors , &
2011-02-16 22:08:18 +05:30
FE_maxNipNeighbors , &
2010-10-12 18:38:54 +05:30
mesh_maxNips , &
mesh_NcpElems
use lattice , only : lattice_sn , &
lattice_sd , &
2010-10-15 18:49:26 +05:30
lattice_st
2010-10-12 18:38:54 +05:30
use debug , only : debugger , &
debug_e , debug_i , debug_g , &
2010-11-03 22:52:48 +05:30
verboseDebugger
2009-12-18 21:16:33 +05:30
2009-12-15 13:50:31 +05:30
implicit none
!* input variables
2010-10-12 18:38:54 +05:30
integer ( pInt ) , intent ( in ) :: i , & ! ip index
e ! element index
real ( pReal ) , dimension ( 4 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
orientation ! crystal orientation in quaternions
2009-12-15 13:50:31 +05:30
!* output variables
!* local variables
2011-02-16 22:08:18 +05:30
integer ( pInt ) Nneighbors , & ! number of neighbors
n , & ! neighbor index
2010-10-12 18:38:54 +05:30
neighboring_e , & ! element index of my neighbor
neighboring_i , & ! integration point index of my neighbor
2011-02-16 22:08:18 +05:30
my_phase , &
neighboring_phase , &
my_structure , & ! lattice structure
my_instance , & ! instance of constitution
ns , & ! number of active slip systems
2010-10-12 18:38:54 +05:30
s1 , & ! slip system index (me)
s2 ! slip system index (my neighbor)
real ( pReal ) , dimension ( 4 ) :: absoluteMisorientation ! absolute misorientation (without symmetry) between me and my neighbor
2011-02-16 22:08:18 +05:30
real ( pReal ) , dimension ( 2 , constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( 1 , i , e ) ) ) ) :: &
compatibility ! compatibility of one specific slip system to all neighbors slip systems's for edges and screws
real ( pReal ) , dimension ( 3 , constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( 1 , i , e ) ) ) ) :: &
slipNormal , &
slipDirection
2010-10-15 18:49:26 +05:30
real ( pReal ) compatibilitySum , &
2011-02-16 22:08:18 +05:30
thresholdValue , &
nThresholdValues
logical , dimension ( constitutive_nonlocal_totalNslip ( phase_constitutionInstance ( material_phase ( 1 , i , e ) ) ) ) :: &
belowThreshold
2010-10-12 18:38:54 +05:30
2011-02-16 22:08:18 +05:30
Nneighbors = FE_NipNeighbors ( mesh_element ( 2 , e ) )
my_phase = material_phase ( 1 , i , e )
my_instance = phase_constitutionInstance ( my_phase )
my_structure = constitutive_nonlocal_structure ( my_instance )
ns = constitutive_nonlocal_totalNslip ( my_instance )
slipNormal ( 1 : 3 , 1 : ns ) = lattice_sn ( 1 : 3 , constitutive_nonlocal_slipSystemLattice ( 1 : ns , my_instance ) , my_structure )
slipDirection ( 1 : 3 , 1 : ns ) = lattice_sd ( 1 : 3 , constitutive_nonlocal_slipSystemLattice ( 1 : ns , my_instance ) , my_structure )
!*** start out fully compatible
constitutive_nonlocal_compatibility ( : , : , : , : , i , e ) = 0.0_pReal
forall ( s1 = 1 : maxval ( constitutive_nonlocal_totalNslip ) ) &
constitutive_nonlocal_compatibility ( 1 : 2 , s1 , s1 , 1 : Nneighbors , i , e ) = 1.0_pReal
!*** Loop thrugh neighbors and check whether there is any compatibility.
!*** This is only the case for
2010-10-12 18:38:54 +05:30
2011-02-16 22:08:18 +05:30
do n = 1 , Nneighbors
2010-10-12 18:38:54 +05:30
neighboring_e = mesh_ipNeighborhood ( 1 , n , i , e )
2011-02-16 22:08:18 +05:30
neighboring_i = mesh_ipNeighborhood ( 2 , n , i , e )
2010-10-12 18:38:54 +05:30
2011-02-16 22:08:18 +05:30
!* FREE SURFACE
!* Set surface transmissivity to the value specified in the material.config
if ( neighboring_e < = 0 . or . neighboring_i < = 0 ) then
forall ( s1 = 1 : ns ) &
constitutive_nonlocal_compatibility ( 1 : 2 , s1 , s1 , n , i , e ) = sqrt ( constitutive_nonlocal_surfaceTransmissivity ( my_instance ) )
cycle
endif
!* PHASE BOUNDARY
!* If we encounter a different nonlocal "cpfem" phase at the neighbor,
!* we consider this to be a real "physical" phase boundary, so fully incompatible.
!* If the neighboring "cpfem" phase has a local constitution,
!* we do not consider this to be a phase boundary, so fully compatible.
neighboring_phase = material_phase ( 1 , neighboring_i , neighboring_e )
if ( neighboring_phase / = my_phase ) then
if ( . not . phase_localConstitution ( neighboring_phase ) ) then
2010-10-15 18:49:26 +05:30
constitutive_nonlocal_compatibility ( : , : , : , n , i , e ) = 0.0_pReal
2010-10-12 18:38:54 +05:30
endif
2011-02-16 22:08:18 +05:30
cycle
2010-10-12 18:38:54 +05:30
endif
2010-03-18 17:53:17 +05:30
2011-02-16 22:08:18 +05:30
!* GRAIN BOUNDARY ?
!* The compatibility value is defined as the product of the slip normal projection and the slip direction projection.
!* Its sign is always positive for screws, for edges it has the same sign as the slip normal projection.
!* Since the sum for each slip system can easily exceed one (which would result in a transmissivity larger than one),
!* only values above or equal to a certain threshold value are considered. This threshold value is chosen, such that
!* the number of compatible slip systems is minimized with the sum of the original compatibility values exceeding one.
!* Finally the smallest compatibility value is decreased until the sum is exactly equal to one.
!* All values below the threshold are set to zero.
absoluteMisorientation = math_QuaternionDisorientation ( orientation ( 1 : 4 , 1 , i , e ) , &
orientation ( 1 : 4 , 1 , neighboring_i , neighboring_e ) , &
0_pInt ) ! no symmetry
do s1 = 1 , ns ! my slip systems
do s2 = 1 , ns ! my neighbor's slip systems
compatibility ( 1 , s2 ) = math_mul3x3 ( slipNormal ( 1 : 3 , s1 ) , math_qRot ( absoluteMisorientation , slipNormal ( 1 : 3 , s2 ) ) ) &
* abs ( math_mul3x3 ( slipDirection ( 1 : 3 , s1 ) , math_qRot ( absoluteMisorientation , slipDirection ( 1 : 3 , s2 ) ) ) )
compatibility ( 2 , s2 ) = abs ( math_mul3x3 ( slipNormal ( 1 : 3 , s1 ) , math_qRot ( absoluteMisorientation , slipNormal ( 1 : 3 , s2 ) ) ) ) &
* abs ( math_mul3x3 ( slipDirection ( 1 : 3 , s1 ) , math_qRot ( absoluteMisorientation , slipDirection ( 1 : 3 , s2 ) ) ) )
enddo
compatibilitySum = 0.0_pReal
belowThreshold = . true .
do while ( compatibilitySum < 1.0_pReal . and . any ( belowThreshold ( 1 : ns ) ) )
thresholdValue = maxval ( compatibility ( 2 , 1 : ns ) , belowThreshold ( 1 : ns ) ) ! screws always positive
nThresholdValues = dble ( count ( compatibility ( 2 , 1 : ns ) == thresholdValue ) )
where ( compatibility ( 2 , 1 : ns ) > = thresholdValue ) &
belowThreshold ( 1 : ns ) = . false .
if ( compatibilitySum + thresholdValue * nThresholdValues > 1.0_pReal ) &
where ( abs ( compatibility ( 1 : 2 , 1 : ns ) ) == thresholdValue ) &
compatibility ( 1 : 2 , 1 : ns ) = sign ( ( 1.0_pReal - compatibilitySum ) / nThresholdValues , compatibility ( 1 : 2 , 1 : ns ) )
compatibilitySum = compatibilitySum + nThresholdValues * thresholdValue
enddo
where ( belowThreshold ( 1 : ns ) ) compatibility ( 1 , 1 : ns ) = 0.0_pReal
where ( belowThreshold ( 1 : ns ) ) compatibility ( 2 , 1 : ns ) = 0.0_pReal
constitutive_nonlocal_compatibility ( 1 : 2 , 1 : ns , s1 , n , i , e ) = compatibility ( 1 : 2 , 1 : ns )
enddo ! my slip systems cycle
enddo ! neighbor cycle
2009-12-18 21:16:33 +05:30
2010-10-12 18:38:54 +05:30
endsubroutine
2009-12-15 13:50:31 +05:30
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 , &
2010-10-26 18:46:37 +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
2011-02-09 18:42:46 +05:30
forall ( t = 1 : 8 ) rhoSgl ( 1 : ns , t ) = state ( g , ip , el ) % p ( ( t - 1 ) * ns + 1 : t * ns )
forall ( t = 1 : 8 ) previousRhoSgl ( 1 : ns , t ) = previousState ( g , ip , el ) % p ( ( t - 1 ) * ns + 1 : t * ns )
forall ( c = 1 : 2 ) rhoDip ( 1 : ns , c ) = state ( g , ip , el ) % p ( ( 7 + c ) * ns + 1 : ( 8 + c ) * ns )
forall ( c = 1 : 2 ) previousRhoDip ( 1 : ns , c ) = previousState ( g , ip , el ) % p ( ( 7 + c ) * ns + 1 : ( 8 + c ) * ns )
2010-01-05 21:37:24 +05:30
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 )
2011-02-09 18:42:46 +05:30
forall ( t = 1 : 8 ) rhoDotSgl ( 1 : ns , t ) = dotState ( g , ip , el ) % p ( ( t - 1 ) * ns + 1 : t * ns )
forall ( c = 1 : 2 ) rhoDotDip ( 1 : ns , 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
2011-02-09 13:58:47 +05:30
call constitutive_nonlocal_kinetics ( Tstar_v , Temperature , state ( g , ip , el ) , g , ip , el ) ! need to calculate dislocation velocity again, because it was overwritten during stiffness calculation
2010-01-06 15:24:00 +05:30
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
2010-10-15 18:49:26 +05:30
2010-10-26 18:46:37 +05:30
forall ( t = 1 : 4 ) &
2011-02-09 18:42:46 +05:30
gdot ( 1 : ns , t ) = rhoSgl ( 1 : ns , t ) * constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) &
* constitutive_nonlocal_v ( 1 : ns , 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 )
2011-02-09 18:42:46 +05:30
tau ( s ) = math_mul6x6 ( Tstar_v + Tdislocation_v , lattice_Sslip_v ( 1 : 6 , sLattice , myStructure ) )
previousTau ( s ) = math_mul6x6 ( previousTstar_v + previousTdislocation_v , lattice_Sslip_v ( 1 : 6 , sLattice , myStructure ) )
2010-02-17 18:51:36 +05:30
enddo
2011-02-09 18:42:46 +05:30
dLower ( 1 : ns , 1 ) = constitutive_nonlocal_dLowerEdgePerSlipSystem ( 1 : ns , myInstance )
dLower ( 1 : ns , 2 ) = constitutive_nonlocal_dLowerScrewPerSlipSystem ( 1 : ns , myInstance )
dUpper ( 1 : ns , 2 ) = min ( constitutive_nonlocal_Gmod ( myInstance ) * constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) &
/ ( 8.0_pReal * pi * abs ( tau ) ) , &
1.0_pReal / sqrt ( sum ( abs ( rhoSgl ) , 2 ) + sum ( rhoDip , 2 ) ) )
dUpper ( 1 : ns , 1 ) = dUpper ( 1 : ns , 2 ) / ( 1.0_pReal - constitutive_nonlocal_nu ( myInstance ) )
previousDUpper ( 1 : ns , 2 ) = min ( constitutive_nonlocal_Gmod ( myInstance ) * constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) &
/ ( 8.0_pReal * pi * abs ( previousTau ) ) , &
1.0_pReal / sqrt ( sum ( abs ( previousRhoSgl ) , 2 ) + sum ( previousRhoDip , 2 ) ) )
previousDUpper ( 1 : ns , 1 ) = previousDUpper ( 1 : ns , 2 ) / ( 1.0_pReal - constitutive_nonlocal_nu ( myInstance ) )
2009-12-15 13:50:31 +05:30
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
2011-02-09 18:42:46 +05:30
m ( 1 : 3 , 1 : ns , 1 ) = lattice_sd ( 1 : 3 , constitutive_nonlocal_slipSystemLattice ( 1 : ns , myInstance ) , myStructure )
2011-02-23 13:38:06 +05:30
m ( 1 : 3 , 1 : ns , 2 ) = - lattice_st ( 1 : 3 , constitutive_nonlocal_slipSystemLattice ( 1 : ns , myInstance ) , myStructure )
2010-02-17 18:51:36 +05:30
forall ( c = 1 : 2 , s = 1 : ns ) &
2011-02-09 18:42:46 +05:30
m_currentconf ( 1 : 3 , s , c ) = math_mul33x3 ( Fe ( 1 : 3 , 1 : 3 , g , ip , el ) , m ( 1 : 3 , 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' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ( 1 : ns , 1 : 4 ) ) , 2 )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_immobile' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ( 1 : ns , 5 : 8 ) ) , 2 )
2010-01-05 21:37:24 +05:30
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' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ( 1 : ns , ( / 1 , 2 , 5 , 6 / ) ) ) , 2 ) + rhoDip ( 1 : ns , 1 )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_edge' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ( 1 : ns , ( / 1 , 2 , 5 , 6 / ) ) ) , 2 )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_edge_mobile' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( rhoSgl ( 1 : ns , 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' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ( 1 : ns , 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' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( 1 : ns , 1 ) + abs ( rhoSgl ( 1 : ns , 5 ) )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_edge_pos_mobile' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( 1 : ns , 1 )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_edge_pos_immobile' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = abs ( rhoSgl ( 1 : ns , 5 ) )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_edge_neg' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( 1 : ns , 2 ) + abs ( rhoSgl ( 1 : ns , 6 ) )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_edge_neg_mobile' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( 1 : ns , 2 )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_edge_neg_immobile' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = abs ( rhoSgl ( 1 : ns , 6 ) )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_dip_edge' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoDip ( 1 : ns , 1 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2009-08-24 13:46:01 +05:30
case ( 'rho_screw' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ( 1 : ns , ( / 3 , 4 , 7 , 8 / ) ) ) , 2 ) + rhoDip ( 1 : ns , 2 )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_screw' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ( 1 : ns , ( / 3 , 4 , 7 , 8 / ) ) ) , 2 )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_screw_mobile' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( rhoSgl ( 1 : ns , 3 : 4 ) , 2 )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_screw_immobile' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( rhoSgl ( 1 : ns , 7 : 8 ) ) , 2 )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_screw_pos' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( 1 : ns , 3 ) + abs ( rhoSgl ( 1 : ns , 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' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( 1 : ns , 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' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = abs ( rhoSgl ( 1 : ns , 7 ) )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_screw_neg' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( 1 : ns , 4 ) + abs ( rhoSgl ( 1 : ns , 8 ) )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_screw_neg_mobile' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( 1 : ns , 4 )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_screw_neg_immobile' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = abs ( rhoSgl ( 1 : ns , 8 ) )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_dip_screw' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoDip ( 1 : ns , 2 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2009-08-28 19:20:47 +05:30
case ( 'excess_rho' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = ( rhoSgl ( 1 : ns , 1 ) + abs ( rhoSgl ( 1 : ns , 5 ) ) ) &
- ( rhoSgl ( 1 : ns , 2 ) + abs ( rhoSgl ( 1 : ns , 6 ) ) ) &
+ ( rhoSgl ( 1 : ns , 3 ) + abs ( rhoSgl ( 1 : ns , 7 ) ) ) &
- ( rhoSgl ( 1 : ns , 4 ) + abs ( rhoSgl ( 1 : ns , 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' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = ( rhoSgl ( 1 : ns , 1 ) + abs ( rhoSgl ( 1 : ns , 5 ) ) ) &
- ( rhoSgl ( 1 : ns , 2 ) + abs ( rhoSgl ( 1 : ns , 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' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = ( rhoSgl ( 1 : ns , 3 ) + abs ( rhoSgl ( 1 : ns , 7 ) ) ) &
- ( rhoSgl ( 1 : ns , 4 ) + abs ( rhoSgl ( 1 : ns , 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' )
2011-02-09 18:42:46 +05:30
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' )
2011-02-09 18:42:46 +05:30
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' )
2011-02-09 18:42:46 +05:30
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' )
2011-02-11 15:49:41 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( gdot , 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 ( 'resolvedstress' )
do s = 1 , ns
sLattice = constitutive_nonlocal_slipSystemLattice ( s , myInstance )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + s ) = math_mul6x6 ( Tstar_v + Tdislocation_v , lattice_Sslip_v ( 1 : 6 , 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 )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + s ) = math_mul6x6 ( Tdislocation_v , lattice_Sslip_v ( 1 : 6 , sLattice , myStructure ) )
2010-02-17 18:51:36 +05:30
enddo
cs = cs + ns
case ( 'resolvedstress_external' )
do s = 1 , ns
sLattice = constitutive_nonlocal_slipSystemLattice ( s , myInstance )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + s ) = math_mul6x6 ( Tstar_v , lattice_Sslip_v ( 1 : 6 , sLattice , myStructure ) )
2010-02-17 18:51:36 +05:30
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 ) &
2011-02-09 18:42:46 +05:30
/ constitutive_nonlocal_lambda0PerSlipSystem ( 1 : ns , myInstance ) &
/ constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_dot_gen_edge' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( gdot ( 1 : ns , 3 : 4 ) ) , 2 ) * sqrt ( rhoForest ) &
/ constitutive_nonlocal_lambda0PerSlipSystem ( 1 : ns , myInstance ) &
/ constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_dot_gen_screw' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( abs ( gdot ( 1 : ns , 1 : 2 ) ) , 2 ) * sqrt ( rhoForest ) &
/ constitutive_nonlocal_lambda0PerSlipSystem ( 1 : ns , myInstance ) &
/ constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , 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' )
2011-02-09 18:42:46 +05:30
do c = 1 , 2 ! dipole formation by glide
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 ) = constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) + &
2011-02-09 18:42:46 +05:30
2.0_pReal * dUpper ( 1 : ns , c ) / constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) &
* ( 2.0_pReal * ( rhoSgl ( 1 : ns , 2 * c - 1 ) * abs ( gdot ( 1 : ns , 2 * c ) ) &
+ rhoSgl ( 1 : ns , 2 * c ) * abs ( gdot ( 1 : ns , 2 * c - 1 ) ) ) & ! was single hitting single
+ 2.0_pReal * ( abs ( rhoSgl ( 1 : ns , 2 * c + 3 ) ) * abs ( gdot ( 1 : ns , 2 * c ) ) &
+ abs ( rhoSgl ( 1 : ns , 2 * c + 4 ) ) * abs ( gdot ( 1 : ns , 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
2011-02-09 18:42:46 +05:30
! forall (s=1:ns, dUpperDot(s,c) > 0.0_pReal) & ! dipole formation by stress decrease
2010-05-21 14:21:15 +05:30
! 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 ) + &
2011-02-09 18:42:46 +05:30
2.0_pReal * dLower ( 1 : ns , c ) / constitutive_nonlocal_burgersPerSlipSystem ( 1 : ns , myInstance ) &
* ( 2.0_pReal * ( rhoSgl ( 1 : ns , 2 * c - 1 ) * abs ( gdot ( 1 : ns , 2 * c ) ) &
+ rhoSgl ( 1 : ns , 2 * c ) * abs ( gdot ( 1 : ns , 2 * c - 1 ) ) ) & ! was single hitting single
+ 2.0_pReal * ( abs ( rhoSgl ( 1 : ns , 2 * c + 3 ) ) * abs ( gdot ( 1 : ns , 2 * c ) ) &
+ abs ( rhoSgl ( 1 : ns , 2 * c + 4 ) ) * abs ( gdot ( 1 : ns , 2 * c - 1 ) ) ) & ! was single hitting immobile/used single
+ rhoDip ( 1 : ns , c ) * ( abs ( gdot ( 1 : ns , 2 * c - 1 ) ) + abs ( gdot ( 1 : ns , 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' )
2011-01-26 15:47:42 +05:30
D = constitutive_nonlocal_Dsd0 ( myInstance ) * exp ( - constitutive_nonlocal_Qsd ( myInstance ) / ( kB * Temperature ) )
2009-08-11 22:01:57 +05:30
2011-02-09 18:42:46 +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 : ns , 1 ) + dLower ( 1 : ns , 1 ) )
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
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = 4.0_pReal * rhoDip ( 1 : ns , 1 ) * vClimb / ( dUpper ( 1 : ns , 1 ) - dLower ( 1 : ns , 1 ) )
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
! !!! 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' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( constitutive_nonlocal_rhoDotFlux ( 1 : ns , 1 : 4 , g , ip , el ) , 2 ) &
+ sum ( abs ( constitutive_nonlocal_rhoDotFlux ( 1 : ns , 5 : 8 , g , ip , el ) ) , 2 )
2010-03-10 15:19:40 +05:30
cs = cs + ns
2010-05-21 14:21:15 +05:30
case ( 'rho_dot_flux_edge' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( constitutive_nonlocal_rhoDotFlux ( 1 : ns , 1 : 2 , g , ip , el ) , 2 ) &
+ sum ( abs ( constitutive_nonlocal_rhoDotFlux ( 1 : ns , 5 : 6 , g , ip , el ) ) , 2 )
2010-05-21 14:21:15 +05:30
cs = cs + ns
2010-03-10 15:19:40 +05:30
2010-05-21 14:21:15 +05:30
case ( 'rho_dot_flux_screw' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = sum ( constitutive_nonlocal_rhoDotFlux ( 1 : ns , 3 : 4 , g , ip , el ) , 2 ) &
+ sum ( abs ( constitutive_nonlocal_rhoDotFlux ( 1 : ns , 7 : 8 , g , ip , el ) ) , 2 )
2010-05-21 14:21:15 +05:30
cs = cs + ns
2010-02-23 22:53:07 +05:30
case ( 'dislocationvelocity' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = constitutive_nonlocal_v ( 1 : ns , 1 , g , ip , el )
2010-02-23 22:53:07 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_edge_pos_x' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( 1 : ns , 1 ) * constitutive_nonlocal_v ( 1 : ns , 1 , g , ip , el ) &
* m_currentconf ( 1 , 1 : ns , 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' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( 1 : ns , 1 ) * constitutive_nonlocal_v ( 1 : ns , 1 , g , ip , el ) &
* m_currentconf ( 2 , 1 : ns , 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' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( 1 : ns , 1 ) * constitutive_nonlocal_v ( 1 : ns , 1 , g , ip , el ) &
* m_currentconf ( 3 , 1 : ns , 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' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = - rhoSgl ( 1 : ns , 2 ) * constitutive_nonlocal_v ( 1 : ns , 2 , g , ip , el ) &
* m_currentconf ( 1 , 1 : ns , 1 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_edge_neg_y' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = - rhoSgl ( 1 : ns , 2 ) * constitutive_nonlocal_v ( 1 : ns , 2 , g , ip , el ) &
* m_currentconf ( 2 , 1 : ns , 1 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_edge_neg_z' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = - rhoSgl ( 1 : ns , 2 ) * constitutive_nonlocal_v ( 1 : ns , 2 , g , ip , el ) &
* m_currentconf ( 3 , 1 : ns , 1 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_screw_pos_x' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( 1 : ns , 3 ) * constitutive_nonlocal_v ( 1 : ns , 3 , g , ip , el ) &
* m_currentconf ( 1 , 1 : ns , 2 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_screw_pos_y' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( 1 : ns , 3 ) * constitutive_nonlocal_v ( 1 : ns , 3 , g , ip , el ) &
* m_currentconf ( 2 , 1 : ns , 2 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_screw_pos_z' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = rhoSgl ( 1 : ns , 3 ) * constitutive_nonlocal_v ( 1 : ns , 3 , g , ip , el ) &
* m_currentconf ( 3 , 1 : ns , 2 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_screw_neg_x' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = - rhoSgl ( 1 : ns , 4 ) * constitutive_nonlocal_v ( 1 : ns , 4 , g , ip , el ) &
* m_currentconf ( 1 , 1 : ns , 2 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_screw_neg_y' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = - rhoSgl ( 1 : ns , 4 ) * constitutive_nonlocal_v ( 1 : ns , 4 , g , ip , el ) &
* m_currentconf ( 2 , 1 : ns , 2 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2010-02-17 18:51:36 +05:30
case ( 'fluxdensity_screw_neg_z' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = - rhoSgl ( 1 : ns , 4 ) * constitutive_nonlocal_v ( 1 : ns , 4 , g , ip , el ) &
* m_currentconf ( 3 , 1 : ns , 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 ( 'd_upper_edge' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = dUpper ( 1 : ns , 1 )
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_screw' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = dUpper ( 1 : ns , 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 ( 'd_upper_dot_edge' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = dUpperDot ( 1 : ns , 1 )
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_dot_screw' )
2011-02-09 18:42:46 +05:30
constitutive_nonlocal_postResults ( cs + 1 : cs + ns ) = dUpperDot ( 1 : ns , 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-11 22:01:57 +05:30
end select
enddo
endfunction
2009-08-28 19:20:47 +05:30
END MODULE