2013-03-22 23:05:05 +05:30
! Copyright 2011-13 Max-Planck-Institut für Eisenforschung GmbH
2011-04-04 19:39:54 +05:30
!
! This file is part of DAMASK,
2011-04-07 12:50:28 +05:30
! the Düsseldorf Advanced MAterial Simulation Kit.
2011-04-04 19:39:54 +05:30
!
! DAMASK is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! DAMASK is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with DAMASK. If not, see <http://www.gnu.org/licenses/>.
!
!##############################################################
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
2013-05-23 17:55:56 +05:30
use prec , only : &
pReal , &
pInt , &
p_vec
2012-05-16 20:13:26 +05:30
2009-08-11 22:01:57 +05:30
implicit none
2012-05-16 20:13:26 +05:30
private
2009-08-11 22:01:57 +05:30
!* Definition of parameters
2012-05-16 20:13:26 +05:30
character ( len = * ) , parameter , public :: &
2013-05-24 01:26:36 +05:30
CONSTITUTIVE_NONLOCAL_LABEL = 'nonlocal'
2012-05-16 20:13:26 +05:30
2013-04-04 19:07:14 +05:30
character ( len = 22 ) , dimension ( 11 ) , parameter , private :: &
2013-05-24 01:26:36 +05:30
BASICSTATES = ( / 'rhoSglEdgePosMobile ' , &
'rhoSglEdgeNegMobile ' , &
'rhoSglScrewPosMobile ' , &
'rhoSglScrewNegMobile ' , &
'rhoSglEdgePosImmobile ' , &
'rhoSglEdgeNegImmobile ' , &
'rhoSglScrewPosImmobile' , &
'rhoSglScrewNegImmobile' , &
'rhoDipEdge ' , &
'rhoDipScrew ' , &
'accumulatedshear ' / ) !< list of "basic" microstructural state variables that are independent from other state variables
2012-05-16 20:13:26 +05:30
character ( len = 16 ) , dimension ( 3 ) , parameter , private :: &
2013-05-24 01:26:36 +05:30
DEPENDENTSTATES = ( / 'rhoForest ' , &
'tauThreshold ' , &
'tauBack ' / ) !< list of microstructural state variables that depend on other state variables
2012-05-16 20:13:26 +05:30
2012-05-18 20:05:52 +05:30
character ( len = 20 ) , dimension ( 6 ) , parameter , private :: &
2013-05-24 01:26:36 +05:30
OTHERSTATES = ( / 'velocityEdgePos ' , &
'velocityEdgeNeg ' , &
'velocityScrewPos ' , &
'velocityScrewNeg ' , &
'maxDipoleHeightEdge ' , &
'maxDipoleHeightScrew' / ) !< list of other dependent state variables that are not updated by microstructure
2012-05-16 20:13:26 +05:30
real ( pReal ) , parameter , private :: &
2013-05-24 01:26:36 +05:30
KB = 1.38e-23_pReal !< Physical parameter, Boltzmann constant in J/Kelvin
2012-05-16 20:13:26 +05:30
2009-08-11 22:01:57 +05:30
!* Definition of global variables
2011-08-02 16:47:45 +05:30
2012-05-16 20:13:26 +05:30
integer ( pInt ) , dimension ( : ) , allocatable , public :: &
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_sizeDotState , & !< number of dotStates = number of basic state variables
constitutive_nonlocal_sizeDependentState , & !< number of dependent state variables
constitutive_nonlocal_sizeState , & !< total number of state variables
constitutive_nonlocal_sizePostResults !< cumulative size of post results
2012-05-16 20:13:26 +05:30
integer ( pInt ) , dimension ( : , : ) , allocatable , target , public :: &
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_sizePostResult !< size of each post result output
2012-05-16 20:13:26 +05:30
character ( len = 64 ) , dimension ( : , : ) , allocatable , target , public :: &
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_output !< name of each post result output
2012-05-16 20:13:26 +05:30
integer ( pInt ) , dimension ( : ) , allocatable , private :: &
2013-05-24 01:26:36 +05:30
Noutput !< number of outputs per instance of this plasticity
2012-05-16 20:13:26 +05:30
2013-05-24 01:45:23 +05:30
integer ( pInt ) , dimension ( : , : ) , allocatable , private :: &
iRhoEPU , & !< state indices for density of Unblocked Positive Edges
iRhoENU , & !< state indices for density of Unblocked Negative Edges
iRhoSPU , & !< state indices for density of Unblocked Positive Screws
iRhoSNU , & !< state indices for density of Unblocked Negative Screws
iRhoEPB , & !< state indices for density of Blocked Positive Edges
iRhoENB , & !< state indices for density of Blocked Negative Edges
iRhoSPB , & !< state indices for density of Blocked Positive Screws
iRhoSNB , & !< state indices for density of Blocked Negative Screws
iRhoED , & !< state indices for density of Edge Dipoles
iRhoSD , & !< state indices for density of Screw Dipoles
iGamma , & !< state indices for accumulated shear
iRhoF , & !< state indices for forest density
iTau , & !< state indices for resolved stress
iTauB , & !< state indices for backstress
iVEP , & !< state indices for velocity of Positive Edges
iVEN , & !< state indices for velocity of Negative Edges
iVSP , & !< state indices for velocity of Positive Screws
iVSN , & !< state indices for velocity of Negative Screws
iDE , & !< state indices for stable edge dipole height
iDS !< state indices for stable screw dipole height
2013-01-22 03:27:26 +05:30
character ( len = 32 ) , dimension ( : ) , allocatable , public :: &
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_structureName !< name of the lattice structure
2012-05-16 20:13:26 +05:30
integer ( pInt ) , dimension ( : ) , allocatable , public :: &
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_structure !< number representing the kind of lattice structure
2012-05-16 20:13:26 +05:30
integer ( pInt ) , dimension ( : ) , allocatable , private :: &
2013-05-24 01:26:36 +05:30
totalNslip !< total number of active slip systems for each instance
2012-05-16 20:13:26 +05:30
integer ( pInt ) , dimension ( : , : ) , allocatable , private :: &
2013-05-24 01:26:36 +05:30
Nslip , & !< number of active slip systems for each family and instance
slipFamily , & !< lookup table relating active slip system to slip family for each instance
slipSystemLattice , & !< lookup table relating active slip system index to lattice slip system index for each instance
colinearSystem !< colinear system to the active slip system (only valid for fcc!)
2012-05-16 20:13:26 +05:30
real ( pReal ) , dimension ( : ) , allocatable , private :: &
2013-05-24 01:26:36 +05:30
CoverA , & !< c/a ratio for hex type lattice
mu , & !< shear modulus
nu , & !< poisson's ratio
atomicVolume , & !< atomic volume
Dsd0 , & !< prefactor for self-diffusion coefficient
selfDiffusionEnergy , & !< activation enthalpy for diffusion
aTolRho , & !< absolute tolerance for dislocation density in state integration
aTolShear , & !< absolute tolerance for accumulated shear in state integration
significantRho , & !< density considered significant
significantN , & !< number of dislocations considered significant
cutoffRadius , & !< cutoff radius for dislocation stress
doublekinkwidth , & !< width of a doubkle kink in multiples of the burgers vector length b
solidSolutionEnergy , & !< activation energy for solid solution in J
solidSolutionSize , & !< solid solution obstacle size in multiples of the burgers vector length
solidSolutionConcentration , & !< concentration of solid solution in atomic parts
pParam , & !< parameter for kinetic law (Kocks,Argon,Ashby)
qParam , & !< parameter for kinetic law (Kocks,Argon,Ashby)
viscosity , & !< viscosity for dislocation glide in Pa s
fattack , & !< attack frequency in Hz
rhoSglScatter , & !< standard deviation of scatter in initial dislocation density
surfaceTransmissivity , & !< transmissivity at free surface
grainboundaryTransmissivity , & !< transmissivity at grain boundary (identified by different texture)
CFLfactor , & !< safety factor for CFL flux condition
fEdgeMultiplication , & !< factor that determines how much edge dislocations contribute to multiplication (0...1)
rhoSglRandom , &
rhoSglRandomBinning , &
linetensionEffect , &
edgeJogFactor
2012-05-16 20:13:26 +05:30
real ( pReal ) , dimension ( : , : ) , allocatable , private :: &
2013-05-24 01:26:36 +05:30
rhoSglEdgePos0 , & !< initial edge_pos dislocation density per slip system for each family and instance
rhoSglEdgeNeg0 , & !< initial edge_neg dislocation density per slip system for each family and instance
rhoSglScrewPos0 , & !< initial screw_pos dislocation density per slip system for each family and instance
rhoSglScrewNeg0 , & !< initial screw_neg dislocation density per slip system for each family and instance
rhoDipEdge0 , & !< initial edge dipole dislocation density per slip system for each family and instance
rhoDipScrew0 , & !< initial screw dipole dislocation density per slip system for each family and instance
lambda0PerSlipFamily , & !< mean free path prefactor for each family and instance
lambda0 , & !< mean free path prefactor for each slip system and instance
burgersPerSlipFamily , & !< absolute length of burgers vector [m] for each family and instance
burgers , & !< absolute length of burgers vector [m] for each slip system and instance
interactionSlipSlip !< coefficients for slip-slip interaction for each interaction type and instance
2012-05-16 20:13:26 +05:30
real ( pReal ) , dimension ( : , : , : ) , allocatable , private :: &
2013-05-24 01:26:36 +05:30
Cslip66 , & !< elasticity matrix in Mandel notation for each instance
minDipoleHeightPerSlipFamily , & !< minimum stable edge/screw dipole height for each family and instance
minDipoleHeight , & !< minimum stable edge/screw dipole height for each slip system and instance
peierlsStressPerSlipFamily , & !< Peierls stress (edge and screw)
peierlsStress , & !< Peierls stress (edge and screw)
forestProjectionEdge , & !< matrix of forest projections of edge dislocations for each instance
forestProjectionScrew , & !< matrix of forest projections of screw dislocations for each instance
interactionMatrixSlipSlip !< interaction matrix of the different slip systems for each instance
2012-05-16 20:13:26 +05:30
real ( pReal ) , dimension ( : , : , : , : ) , allocatable , private :: &
2013-05-24 01:26:36 +05:30
lattice2slip , & !< orthogonal transformation matrix from lattice coordinate system to slip coordinate system (passive rotation !!!)
rhoDotEdgeJogsOutput , &
sourceProbability , &
shearrate
2012-08-16 16:33:22 +05:30
real ( pReal ) , dimension ( : , : , : , : , : ) , allocatable , private :: &
2013-05-24 01:26:36 +05:30
Cslip3333 , & !< elasticity matrix for each instance
rhoDotFluxOutput , &
rhoDotMultiplicationOutput , &
rhoDotSingle2DipoleGlideOutput , &
rhoDotAthermalAnnihilationOutput , &
rhoDotThermalAnnihilationOutput
2012-08-16 16:33:22 +05:30
real ( pReal ) , dimension ( : , : , : , : , : , : ) , allocatable , private :: &
2013-05-24 01:26:36 +05:30
compatibility !< slip system compatibility between me and my neighbors
2012-05-16 20:13:26 +05:30
2013-01-22 05:20:28 +05:30
real ( pReal ) , dimension ( : , : ) , allocatable , private :: &
2013-05-24 01:26:36 +05:30
nonSchmidCoeff
2013-01-22 05:20:28 +05:30
2012-05-16 20:13:26 +05:30
logical , dimension ( : ) , allocatable , private :: &
2013-05-24 01:26:36 +05:30
shortRangeStressCorrection , & !< flag indicating the use of the short range stress correction by a excess density gradient term
deadZoneScaling , &
probabilisticMultiplication
2012-05-16 20:13:26 +05:30
public :: &
constitutive_nonlocal_init , &
constitutive_nonlocal_stateInit , &
constitutive_nonlocal_aTolState , &
constitutive_nonlocal_homogenizedC , &
constitutive_nonlocal_microstructure , &
constitutive_nonlocal_LpAndItsTangent , &
constitutive_nonlocal_dotState , &
constitutive_nonlocal_deltaState , &
constitutive_nonlocal_dotTemperature , &
constitutive_nonlocal_updateCompatibility , &
constitutive_nonlocal_postResults
private :: &
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_kinetics , &
constitutive_nonlocal_dislocationstress
2009-08-11 22:01:57 +05:30
2012-05-16 20:13:26 +05:30
CONTAINS
2009-08-11 22:01:57 +05:30
!**************************************
!* Module initialization *
!**************************************
2012-02-23 22:13:17 +05:30
subroutine constitutive_nonlocal_init ( myFile )
2009-08-11 22:01:57 +05:30
2012-02-13 19:48:07 +05:30
use , intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
2009-08-11 22:01:57 +05:30
use math , only : math_Mandel3333to66 , &
math_Voigt66to3333 , &
2011-08-02 16:47:45 +05:30
math_mul3x3 , &
2012-01-26 19:20:00 +05:30
math_transpose33
2009-08-11 22:01:57 +05:30
use IO , only : IO_lc , &
IO_getTag , &
IO_isBlank , &
IO_stringPos , &
IO_stringValue , &
IO_floatValue , &
IO_intValue , &
2013-02-25 22:04:59 +05:30
IO_error , &
IO_timeStamp
2012-07-05 15:24:50 +05:30
use debug , only : debug_level , &
2012-03-09 01:55:28 +05:30
debug_constitutive , &
debug_levelBasic
2010-02-17 18:51:36 +05:30
use mesh , only : mesh_NcpElems , &
2010-10-12 18:38:54 +05:30
mesh_maxNips , &
2013-05-23 23:16:21 +05:30
mesh_maxNipNeighbors
2010-02-17 18:51:36 +05:30
use material , only : homogenization_maxNgrains , &
2012-03-12 19:39:37 +05:30
phase_plasticity , &
phase_plasticityInstance , &
2009-08-11 22:01:57 +05:30
phase_Noutput
2013-02-15 03:54:55 +05:30
use lattice
2009-08-11 22:01:57 +05:30
!*** output variables
!*** input variables
2012-02-23 22:13:17 +05:30
integer ( pInt ) , intent ( in ) :: myFile
2009-08-11 22:01:57 +05:30
!*** local variables
2012-02-23 22:13:17 +05:30
integer ( pInt ) , parameter :: maxNchunks = 21_pInt
integer ( pInt ) , &
dimension ( 1_pInt + 2_pInt * maxNchunks ) :: positions
2013-02-15 03:54:55 +05:30
integer ( pInt ) , dimension ( 6 ) :: configNchunks
2013-02-11 16:13:45 +05:30
integer ( pInt ) :: section , &
2009-08-11 22:01:57 +05:30
maxNinstance , &
maxTotalNslip , &
myStructure , &
f , & ! index of my slip family
2012-03-12 19:39:37 +05:30
i , & ! index of my instance of this plasticity
2009-08-11 22:01:57 +05:30
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
2013-03-27 18:34:01 +05:30
Nchunks_SlipSlip = 0_pInt , &
Nchunks_SlipFamilies = 0_pInt , &
2013-02-11 16:13:45 +05:30
mySize = 0_pInt ! to suppress warnings, safe as init is called only once
2009-08-11 22:01:57 +05:30
character ( len = 64 ) tag
2013-01-09 03:41:59 +05:30
character ( len = 1024 ) :: line = '' ! to start initialized
write ( 6 , * )
2013-05-24 01:26:36 +05:30
write ( 6 , * ) '<<<+- constitutive_' , trim ( CONSTITUTIVE_NONLOCAL_LABEL ) , ' init -+>>>'
2013-01-09 03:41:59 +05:30
write ( 6 , * ) '$Id$'
2013-02-25 22:04:59 +05:30
write ( 6 , '(a16,a)' ) ' Current time : ' , IO_timeStamp ( )
2012-02-01 00:48:55 +05:30
#include "compilation_info.f90"
2009-08-11 22:01:57 +05:30
2013-05-24 01:26:36 +05:30
maxNinstance = int ( count ( phase_plasticity == CONSTITUTIVE_NONLOCAL_LABEL ) , pInt )
2009-08-11 22:01:57 +05:30
if ( maxNinstance == 0 ) return ! we don't have to do anything if there's no instance for this constitutive law
2012-07-05 15:24:50 +05:30
if ( iand ( debug_level ( debug_constitutive ) , debug_levelBasic ) / = 0_pInt ) then
2013-01-09 03:41:59 +05:30
write ( 6 , '(a16,1x,i5)' ) '# instances:' , maxNinstance
2013-02-15 03:54:55 +05:30
write ( 6 , * )
2011-03-21 16:01:17 +05:30
endif
2013-02-15 03:54:55 +05:30
!*** memory allocation for global variables
2009-08-11 22:01:57 +05:30
2009-08-28 19:20:47 +05:30
allocate ( constitutive_nonlocal_sizeDotState ( maxNinstance ) )
2011-11-04 18:42:17 +05:30
allocate ( constitutive_nonlocal_sizeDependentState ( maxNinstance ) )
2009-08-28 19:20:47 +05:30
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 ) )
2013-05-24 01:26:36 +05:30
allocate ( Noutput ( maxNinstance ) )
2009-08-28 19:20:47 +05:30
constitutive_nonlocal_sizeDotState = 0_pInt
2011-11-04 18:42:17 +05:30
constitutive_nonlocal_sizeDependentState = 0_pInt
2009-08-28 19:20:47 +05:30
constitutive_nonlocal_sizeState = 0_pInt
constitutive_nonlocal_sizePostResults = 0_pInt
constitutive_nonlocal_sizePostResult = 0_pInt
constitutive_nonlocal_output = ''
2013-05-24 01:26:36 +05:30
Noutput = 0_pInt
2009-08-28 19:20:47 +05:30
allocate ( constitutive_nonlocal_structureName ( maxNinstance ) )
allocate ( constitutive_nonlocal_structure ( maxNinstance ) )
2013-05-24 01:26:36 +05:30
allocate ( Nslip ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( slipFamily ( lattice_maxNslip , maxNinstance ) )
allocate ( slipSystemLattice ( lattice_maxNslip , maxNinstance ) )
allocate ( totalNslip ( maxNinstance ) )
2009-08-28 19:20:47 +05:30
constitutive_nonlocal_structureName = ''
constitutive_nonlocal_structure = 0_pInt
2013-05-24 01:26:36 +05:30
Nslip = 0_pInt
slipFamily = 0_pInt
slipSystemLattice = 0_pInt
totalNslip = 0_pInt
allocate ( CoverA ( maxNinstance ) )
allocate ( mu ( maxNinstance ) )
allocate ( nu ( maxNinstance ) )
allocate ( atomicVolume ( maxNinstance ) )
allocate ( Dsd0 ( maxNinstance ) )
allocate ( selfDiffusionEnergy ( maxNinstance ) )
allocate ( aTolRho ( maxNinstance ) )
allocate ( aTolShear ( maxNinstance ) )
allocate ( significantRho ( maxNinstance ) )
allocate ( significantN ( maxNinstance ) )
allocate ( Cslip66 ( 6 , 6 , maxNinstance ) )
allocate ( Cslip3333 ( 3 , 3 , 3 , 3 , maxNinstance ) )
allocate ( cutoffRadius ( maxNinstance ) )
allocate ( doublekinkwidth ( maxNinstance ) )
allocate ( solidSolutionEnergy ( maxNinstance ) )
allocate ( solidSolutionSize ( maxNinstance ) )
allocate ( solidSolutionConcentration ( maxNinstance ) )
allocate ( pParam ( maxNinstance ) )
allocate ( qParam ( maxNinstance ) )
allocate ( viscosity ( maxNinstance ) )
allocate ( fattack ( maxNinstance ) )
allocate ( rhoSglScatter ( maxNinstance ) )
allocate ( rhoSglRandom ( maxNinstance ) )
allocate ( rhoSglRandomBinning ( maxNinstance ) )
allocate ( surfaceTransmissivity ( maxNinstance ) )
allocate ( grainboundaryTransmissivity ( maxNinstance ) )
allocate ( shortRangeStressCorrection ( maxNinstance ) )
allocate ( deadZoneScaling ( maxNinstance ) )
allocate ( probabilisticMultiplication ( maxNinstance ) )
allocate ( CFLfactor ( maxNinstance ) )
allocate ( fEdgeMultiplication ( maxNinstance ) )
allocate ( linetensionEffect ( maxNinstance ) )
allocate ( edgeJogFactor ( maxNinstance ) )
CoverA = 0.0_pReal
mu = 0.0_pReal
atomicVolume = 0.0_pReal
Dsd0 = - 1.0_pReal
selfDiffusionEnergy = 0.0_pReal
aTolRho = 0.0_pReal
aTolShear = 0.0_pReal
significantRho = 0.0_pReal
significantN = 0.0_pReal
nu = 0.0_pReal
Cslip66 = 0.0_pReal
Cslip3333 = 0.0_pReal
cutoffRadius = - 1.0_pReal
doublekinkwidth = 0.0_pReal
solidSolutionEnergy = 0.0_pReal
solidSolutionSize = 0.0_pReal
solidSolutionConcentration = 0.0_pReal
pParam = 1.0_pReal
qParam = 1.0_pReal
viscosity = 0.0_pReal
fattack = 0.0_pReal
rhoSglScatter = 0.0_pReal
rhoSglRandom = 0.0_pReal
rhoSglRandomBinning = 1.0_pReal
surfaceTransmissivity = 1.0_pReal
grainboundaryTransmissivity = - 1.0_pReal
CFLfactor = 2.0_pReal
fEdgeMultiplication = 0.0_pReal
linetensionEffect = 0.0_pReal
edgeJogFactor = 1.0_pReal
shortRangeStressCorrection = . false .
deadZoneScaling = . false .
probabilisticMultiplication = . false .
allocate ( rhoSglEdgePos0 ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( rhoSglEdgeNeg0 ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( rhoSglScrewPos0 ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( rhoSglScrewNeg0 ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( rhoDipEdge0 ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( rhoDipScrew0 ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( burgersPerSlipFamily ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( lambda0PerSlipFamily ( lattice_maxNslipFamily , maxNinstance ) )
allocate ( interactionSlipSlip ( lattice_maxNinteraction , maxNinstance ) )
rhoSglEdgePos0 = - 1.0_pReal
rhoSglEdgeNeg0 = - 1.0_pReal
rhoSglScrewPos0 = - 1.0_pReal
rhoSglScrewNeg0 = - 1.0_pReal
rhoDipEdge0 = - 1.0_pReal
rhoDipScrew0 = - 1.0_pReal
burgersPerSlipFamily = 0.0_pReal
lambda0PerSlipFamily = 0.0_pReal
interactionSlipSlip = 0.0_pReal
allocate ( minDipoleHeightPerSlipFamily ( lattice_maxNslipFamily , 2 , maxNinstance ) )
allocate ( peierlsStressPerSlipFamily ( lattice_maxNslipFamily , 2 , maxNinstance ) )
minDipoleHeightPerSlipFamily = - 1.0_pReal
peierlsStressPerSlipFamily = 0.0_pReal
allocate ( nonSchmidCoeff ( lattice_maxNonSchmid , maxNinstance ) )
nonSchmidCoeff = 0.0_pReal
2013-01-22 05:20:28 +05:30
2009-08-11 22:01:57 +05:30
!*** readout data from material.config file
2012-02-23 22:13:17 +05:30
rewind ( myFile )
2009-08-11 22:01:57 +05:30
line = ''
2012-02-13 19:48:07 +05:30
section = 0_pInt
2009-08-11 22:01:57 +05:30
2012-02-14 05:00:59 +05:30
do while ( IO_lc ( IO_getTag ( line , '<' , '>' ) ) / = 'phase' ) ! wind forward to <phase>
2012-02-23 22:13:17 +05:30
read ( myFile , '(a1024)' , END = 100 ) line
2009-08-11 22:01:57 +05:30
enddo
2012-02-14 05:00:59 +05:30
do ! read thru sections of phase part
2012-02-23 22:13:17 +05:30
read ( myFile , '(a1024)' , END = 100 ) line
2012-02-14 05:00:59 +05:30
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_pInt ! advance section counter
2011-02-16 22:05:38 +05:30
cycle
2009-08-11 22:01:57 +05:30
endif
2013-05-24 01:26:36 +05:30
if ( section > 0_pInt . and . phase_plasticity ( section ) == CONSTITUTIVE_NONLOCAL_LABEL ) then ! one of my sections
2012-03-12 19:39:37 +05:30
i = phase_plasticityInstance ( section ) ! which instance of my plasticity is present phase
2009-08-11 22:01:57 +05:30
positions = IO_stringPos ( line , maxNchunks )
2012-02-14 05:00:59 +05:30
tag = IO_lc ( IO_stringValue ( line , positions , 1_pInt ) ) ! extract key
2009-08-11 22:01:57 +05:30
select case ( tag )
2012-03-15 14:52:24 +05:30
case ( 'plasticity' , 'elasticity' , '/nonlocal/' )
2011-02-16 22:05:38 +05:30
cycle
2009-08-11 22:01:57 +05:30
case ( '(output)' )
2013-05-24 01:26:36 +05:30
Noutput ( i ) = Noutput ( i ) + 1_pInt
constitutive_nonlocal_output ( Noutput ( i ) , i ) = IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2009-08-11 22:01:57 +05:30
case ( 'lattice_structure' )
2012-02-13 19:48:07 +05:30
constitutive_nonlocal_structureName ( i ) = IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2013-02-15 03:54:55 +05:30
configNchunks = lattice_configNchunks ( constitutive_nonlocal_structureName ( i ) )
Nchunks_SlipFamilies = configNchunks ( 1 )
Nchunks_SlipSlip = configNchunks ( 3 )
2012-01-25 22:34:37 +05:30
case ( 'c/a_ratio' , 'covera_ratio' )
2013-05-24 01:26:36 +05:30
CoverA ( i ) = IO_floatValue ( line , positions , 2_pInt )
2013-01-22 03:27:26 +05:30
case ( 'c11' )
2013-05-24 01:26:36 +05:30
Cslip66 ( 1 , 1 , i ) = IO_floatValue ( line , positions , 2_pInt )
2013-01-22 03:27:26 +05:30
case ( 'c12' )
2013-05-24 01:26:36 +05:30
Cslip66 ( 1 , 2 , i ) = IO_floatValue ( line , positions , 2_pInt )
2013-01-22 03:27:26 +05:30
case ( 'c13' )
2013-05-24 01:26:36 +05:30
Cslip66 ( 1 , 3 , i ) = IO_floatValue ( line , positions , 2_pInt )
2013-01-22 03:27:26 +05:30
case ( 'c22' )
2013-05-24 01:26:36 +05:30
Cslip66 ( 2 , 2 , i ) = IO_floatValue ( line , positions , 2_pInt )
2013-01-22 03:27:26 +05:30
case ( 'c23' )
2013-05-24 01:26:36 +05:30
Cslip66 ( 2 , 3 , i ) = IO_floatValue ( line , positions , 2_pInt )
2013-01-22 03:27:26 +05:30
case ( 'c33' )
2013-05-24 01:26:36 +05:30
Cslip66 ( 3 , 3 , i ) = IO_floatValue ( line , positions , 2_pInt )
2013-01-22 03:27:26 +05:30
case ( 'c44' )
2013-05-24 01:26:36 +05:30
Cslip66 ( 4 , 4 , i ) = IO_floatValue ( line , positions , 2_pInt )
2013-01-22 03:27:26 +05:30
case ( 'c55' )
2013-05-24 01:26:36 +05:30
Cslip66 ( 5 , 5 , i ) = IO_floatValue ( line , positions , 2_pInt )
2013-01-22 03:27:26 +05:30
case ( 'c66' )
2013-05-24 01:26:36 +05:30
Cslip66 ( 6 , 6 , i ) = IO_floatValue ( line , positions , 2_pInt )
2009-08-11 22:01:57 +05:30
case ( 'nslip' )
2013-02-15 03:54:55 +05:30
do f = 1_pInt , Nchunks_SlipFamilies
2013-05-24 01:26:36 +05:30
Nslip ( f , i ) = IO_intValue ( line , positions , 1_pInt + f )
2013-02-06 22:15:34 +05:30
enddo
2010-01-05 21:37:24 +05:30
case ( 'rhosgledgepos0' )
2013-02-15 03:54:55 +05:30
do f = 1_pInt , Nchunks_SlipFamilies
2013-05-24 01:26:36 +05:30
rhoSglEdgePos0 ( f , i ) = IO_floatValue ( line , positions , 1_pInt + f )
2013-02-06 22:15:34 +05:30
enddo
2010-01-05 21:37:24 +05:30
case ( 'rhosgledgeneg0' )
2013-02-15 03:54:55 +05:30
do f = 1_pInt , Nchunks_SlipFamilies
2013-05-24 01:26:36 +05:30
rhoSglEdgeNeg0 ( f , i ) = IO_floatValue ( line , positions , 1_pInt + f )
2013-02-06 22:15:34 +05:30
enddo
2010-01-05 21:37:24 +05:30
case ( 'rhosglscrewpos0' )
2013-02-15 03:54:55 +05:30
do f = 1_pInt , Nchunks_SlipFamilies
2013-05-24 01:26:36 +05:30
rhoSglScrewPos0 ( f , i ) = IO_floatValue ( line , positions , 1_pInt + f )
2013-02-06 22:15:34 +05:30
enddo
2010-01-05 21:37:24 +05:30
case ( 'rhosglscrewneg0' )
2013-02-15 03:54:55 +05:30
do f = 1_pInt , Nchunks_SlipFamilies
2013-05-24 01:26:36 +05:30
rhoSglScrewNeg0 ( f , i ) = IO_floatValue ( line , positions , 1_pInt + f )
2013-02-06 22:15:34 +05:30
enddo
2010-01-05 21:37:24 +05:30
case ( 'rhodipedge0' )
2013-02-15 03:54:55 +05:30
do f = 1_pInt , Nchunks_SlipFamilies
2013-05-24 01:26:36 +05:30
rhoDipEdge0 ( f , i ) = IO_floatValue ( line , positions , 1_pInt + f )
2013-02-06 22:15:34 +05:30
enddo
2010-01-05 21:37:24 +05:30
case ( 'rhodipscrew0' )
2013-02-15 03:54:55 +05:30
do f = 1_pInt , Nchunks_SlipFamilies
2013-05-24 01:26:36 +05:30
rhoDipScrew0 ( f , i ) = IO_floatValue ( line , positions , 1_pInt + f )
2013-02-06 22:15:34 +05:30
enddo
2009-08-12 16:52:02 +05:30
case ( 'lambda0' )
2013-02-15 03:54:55 +05:30
do f = 1_pInt , Nchunks_SlipFamilies
2013-05-24 01:26:36 +05:30
lambda0PerSlipFamily ( f , i ) = IO_floatValue ( line , positions , 1_pInt + f )
2013-02-06 22:15:34 +05:30
enddo
2009-08-11 22:01:57 +05:30
case ( 'burgers' )
2013-02-15 03:54:55 +05:30
do f = 1_pInt , Nchunks_SlipFamilies
2013-05-24 01:26:36 +05:30
burgersPerSlipFamily ( f , i ) = IO_floatValue ( line , positions , 1_pInt + f )
2013-02-06 22:15:34 +05:30
enddo
2012-01-25 22:34:37 +05:30
case ( 'cutoffradius' , 'r' )
2013-05-24 01:26:36 +05:30
cutoffRadius ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-01-25 22:34:37 +05:30
case ( 'minimumdipoleheightedge' , 'ddipminedge' )
2013-02-15 03:54:55 +05:30
do f = 1_pInt , Nchunks_SlipFamilies
2013-05-24 01:26:36 +05:30
minDipoleHeightPerSlipFamily ( f , 1_pInt , i ) = IO_floatValue ( line , positions , 1_pInt + f )
2013-02-06 22:15:34 +05:30
enddo
2012-01-25 22:34:37 +05:30
case ( 'minimumdipoleheightscrew' , 'ddipminscrew' )
2013-02-15 03:54:55 +05:30
do f = 1_pInt , Nchunks_SlipFamilies
2013-05-24 01:26:36 +05:30
minDipoleHeightPerSlipFamily ( f , 2_pInt , i ) = IO_floatValue ( line , positions , 1_pInt + f )
2013-02-06 22:15:34 +05:30
enddo
2009-08-28 19:20:47 +05:30
case ( 'atomicvolume' )
2013-05-24 01:26:36 +05:30
atomicVolume ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-01-25 22:34:37 +05:30
case ( 'selfdiffusionprefactor' , 'dsd0' )
2013-05-24 01:26:36 +05:30
Dsd0 ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-01-25 22:34:37 +05:30
case ( 'selfdiffusionenergy' , 'qsd' )
2013-05-24 01:26:36 +05:30
selfDiffusionEnergy ( i ) = IO_floatValue ( line , positions , 2_pInt )
2013-04-04 19:07:14 +05:30
case ( 'atol_rho' , 'atol_density' , 'absolutetolerancedensity' , 'absolutetolerance_density' )
2013-05-24 01:26:36 +05:30
aTolRho ( i ) = IO_floatValue ( line , positions , 2_pInt )
2013-04-04 19:07:14 +05:30
case ( 'atol_shear' , 'atol_plasticshear' , 'atol_accumulatedshear' , 'absolutetoleranceshear' , 'absolutetolerance_shear' )
2013-05-24 01:26:36 +05:30
aTolShear ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-08-23 11:18:21 +05:30
case ( 'significantrho' , 'significant_rho' , 'significantdensity' , 'significant_density' )
2013-05-24 01:26:36 +05:30
significantRho ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-10-02 18:27:24 +05:30
case ( 'significantn' , 'significant_n' , 'significantdislocations' , 'significant_dislcations' )
2013-05-24 01:26:36 +05:30
significantN ( i ) = IO_floatValue ( line , positions , 2_pInt )
2009-08-11 22:01:57 +05:30
case ( 'interaction_slipslip' )
2013-02-15 03:54:55 +05:30
do it = 1_pInt , Nchunks_SlipSlip
2013-05-24 01:26:36 +05:30
interactionSlipSlip ( it , i ) = IO_floatValue ( line , positions , 1_pInt + it )
2013-02-06 22:15:34 +05:30
enddo
2012-10-05 20:12:41 +05:30
case ( 'linetension' , 'linetensioneffect' , 'linetension_effect' )
2013-05-24 01:26:36 +05:30
linetensionEffect ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-12-23 18:26:15 +05:30
case ( 'edgejog' , 'edgejogs' , 'edgejogeffect' , 'edgejog_effect' )
2013-05-24 01:26:36 +05:30
edgeJogFactor ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-08-23 11:18:21 +05:30
case ( 'peierlsstressedge' , 'peierlsstress_edge' )
2013-02-15 03:54:55 +05:30
do f = 1_pInt , Nchunks_SlipFamilies
2013-05-24 01:26:36 +05:30
peierlsStressPerSlipFamily ( f , 1_pInt , i ) = IO_floatValue ( line , positions , 1_pInt + f )
2013-02-06 22:15:34 +05:30
enddo
2012-08-23 11:18:21 +05:30
case ( 'peierlsstressscrew' , 'peierlsstress_screw' )
2013-02-15 03:54:55 +05:30
do f = 1_pInt , Nchunks_SlipFamilies
2013-05-24 01:26:36 +05:30
peierlsStressPerSlipFamily ( f , 2_pInt , i ) = IO_floatValue ( line , positions , 1_pInt + f )
2013-02-06 22:15:34 +05:30
enddo
2012-02-03 18:20:54 +05:30
case ( 'doublekinkwidth' )
2013-05-24 01:26:36 +05:30
doublekinkwidth ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-01-25 22:34:37 +05:30
case ( 'solidsolutionenergy' )
2013-05-24 01:26:36 +05:30
solidSolutionEnergy ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-02-03 18:20:54 +05:30
case ( 'solidsolutionsize' )
2013-05-24 01:26:36 +05:30
solidSolutionSize ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-02-03 18:20:54 +05:30
case ( 'solidsolutionconcentration' )
2013-05-24 01:26:36 +05:30
solidSolutionConcentration ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-01-25 22:34:37 +05:30
case ( 'p' )
2013-05-24 01:26:36 +05:30
pParam ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-01-25 22:34:37 +05:30
case ( 'q' )
2013-05-24 01:26:36 +05:30
qParam ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-01-25 22:34:37 +05:30
case ( 'viscosity' , 'glideviscosity' )
2013-05-24 01:26:36 +05:30
viscosity ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-01-25 22:34:37 +05:30
case ( 'attackfrequency' , 'fattack' )
2013-05-24 01:26:36 +05:30
fattack ( i ) = IO_floatValue ( line , positions , 2_pInt )
2011-02-04 21:11:32 +05:30
case ( 'rhosglscatter' )
2013-05-24 01:26:36 +05:30
rhoSglScatter ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-10-02 18:27:24 +05:30
case ( 'rhosglrandom' )
2013-05-24 01:26:36 +05:30
rhoSglRandom ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-10-02 18:27:24 +05:30
case ( 'rhosglrandombinning' )
2013-05-24 01:26:36 +05:30
rhoSglRandomBinning ( i ) = IO_floatValue ( line , positions , 2_pInt )
2011-02-16 22:05:38 +05:30
case ( 'surfacetransmissivity' )
2013-05-24 01:26:36 +05:30
surfaceTransmissivity ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-08-03 20:02:49 +05:30
case ( 'grainboundarytransmissivity' )
2013-05-24 01:26:36 +05:30
grainboundaryTransmissivity ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-08-16 14:43:38 +05:30
case ( 'cflfactor' )
2013-05-24 01:26:36 +05:30
CFLfactor ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-09-04 22:26:37 +05:30
case ( 'fedgemultiplication' , 'edgemultiplicationfactor' , 'edgemultiplication' )
2013-05-24 01:26:36 +05:30
fEdgeMultiplication ( i ) = IO_floatValue ( line , positions , 2_pInt )
2012-03-15 20:28:12 +05:30
case ( 'shortrangestresscorrection' )
2013-05-24 01:26:36 +05:30
shortRangeStressCorrection ( i ) = IO_floatValue ( line , positions , 2_pInt ) > 0.0_pReal
2013-01-22 05:20:28 +05:30
case ( 'nonschmid_coefficients' )
2013-02-06 22:15:34 +05:30
do f = 1_pInt , lattice_maxNonSchmid
2013-05-24 01:26:36 +05:30
nonSchmidCoeff ( f , i ) = IO_floatValue ( line , positions , 1_pInt + f )
2013-02-06 22:15:34 +05:30
enddo
2012-10-29 18:19:28 +05:30
case ( 'deadzonescaling' , 'deadzone' , 'deadscaling' )
2013-05-24 01:26:36 +05:30
deadZoneScaling ( i ) = IO_floatValue ( line , positions , 2_pInt ) > 0.0_pReal
2012-12-03 18:29:38 +05:30
case ( 'probabilisticmultiplication' , 'randomsources' , 'randommultiplication' , 'discretesources' )
2013-05-24 01:26:36 +05:30
probabilisticMultiplication ( i ) = IO_floatValue ( line , positions , 2_pInt ) > 0.0_pReal
2012-02-14 14:52:37 +05:30
case default
2013-05-24 01:26:36 +05:30
call IO_error ( 210_pInt , ext_msg = tag / / ' (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
2009-08-11 22:01:57 +05:30
end select
endif
enddo
2012-02-23 22:13:17 +05:30
100 do i = 1_pInt , maxNinstance
2009-08-11 22:01:57 +05:30
constitutive_nonlocal_structure ( i ) = &
2013-05-24 01:26:36 +05:30
lattice_initializeStructure ( constitutive_nonlocal_structureName ( i ) , 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
2011-03-29 12:57:19 +05:30
!*** sanity checks
2009-08-11 22:01:57 +05:30
2013-05-24 01:26:36 +05:30
if ( myStructure < 1_pInt ) &
call IO_error ( 205_pInt , e = i )
if ( sum ( Nslip ( : , i ) ) < = 0_pInt ) &
call IO_error ( 211_pInt , ext_msg = 'Nslip (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
2012-02-23 22:13:17 +05:30
do o = 1_pInt , maxval ( phase_Noutput )
2013-05-24 01:26:36 +05:30
if ( len ( constitutive_nonlocal_output ( o , i ) ) > 64_pInt ) &
call IO_error ( 666_pInt )
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
2012-02-23 22:13:17 +05:30
do f = 1_pInt , lattice_maxNslipFamily
2013-05-24 01:26:36 +05:30
if ( Nslip ( f , i ) > 0_pInt ) then
if ( rhoSglEdgePos0 ( f , i ) < 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'rhoSglEdgePos0 (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( rhoSglEdgeNeg0 ( f , i ) < 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'rhoSglEdgeNeg0 (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( rhoSglScrewPos0 ( f , i ) < 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'rhoSglScrewPos0 (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( rhoSglScrewNeg0 ( f , i ) < 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'rhoSglScrewNeg0 (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( rhoDipEdge0 ( f , i ) < 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'rhoDipEdge0 (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( rhoDipScrew0 ( f , i ) < 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'rhoDipScrew0 (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( burgersPerSlipFamily ( f , i ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'Burgers (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( lambda0PerSlipFamily ( f , i ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'lambda0 (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( minDipoleHeightPerSlipFamily ( f , 1 , i ) < 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'minimumDipoleHeightEdge (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( minDipoleHeightPerSlipFamily ( f , 2 , i ) < 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'minimumDipoleHeightScrew (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( peierlsStressPerSlipFamily ( f , 1 , i ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'peierlsStressEdge (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( peierlsStressPerSlipFamily ( f , 2 , i ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'peierlsStressScrew (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
2009-08-12 16:52:02 +05:30
endif
enddo
2013-05-24 01:26:36 +05:30
if ( any ( interactionSlipSlip ( 1 : maxval ( lattice_interactionSlipSlip ( : , : , myStructure ) ) , i ) < 0.0_pReal ) ) &
call IO_error ( 211_pInt , ext_msg = 'interaction_SlipSlip (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( linetensionEffect ( i ) < 0.0_pReal . or . linetensionEffect ( i ) > 1.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'linetension (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( edgeJogFactor ( i ) < 0.0_pReal . or . edgeJogFactor ( i ) > 1.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'edgejog (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( cutoffRadius ( i ) < 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'r (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( atomicVolume ( i ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'atomicVolume (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( Dsd0 ( i ) < 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'selfDiffusionPrefactor (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( selfDiffusionEnergy ( i ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'selfDiffusionEnergy (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( aTolRho ( i ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'aTol_rho (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( aTolShear ( i ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'aTol_shear (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( significantRho ( i ) < 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'significantRho (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( significantN ( i ) < 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'significantN (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( doublekinkwidth ( i ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'doublekinkwidth (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( solidSolutionEnergy ( i ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'solidSolutionEnergy (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( solidSolutionSize ( i ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'solidSolutionSize (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( solidSolutionConcentration ( i ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'solidSolutionConcentration (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( pParam ( i ) < = 0.0_pReal . or . pParam ( i ) > 1.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'p (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( qParam ( i ) < 1.0_pReal . or . qParam ( i ) > 2.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'q (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( viscosity ( i ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'viscosity (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( fattack ( i ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'attackFrequency (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( rhoSglScatter ( i ) < 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'rhoSglScatter (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( rhoSglRandom ( i ) < 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'rhoSglRandom (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( rhoSglRandomBinning ( i ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'rhoSglRandomBinning (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( surfaceTransmissivity ( i ) < 0.0_pReal . or . surfaceTransmissivity ( i ) > 1.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'surfaceTransmissivity (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( grainboundaryTransmissivity ( i ) > 1.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'grainboundaryTransmissivity (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( CFLfactor ( i ) < 0.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'CFLfactor (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
if ( fEdgeMultiplication ( i ) < 0.0_pReal . or . fEdgeMultiplication ( i ) > 1.0_pReal ) &
call IO_error ( 211_pInt , ext_msg = 'edgemultiplicationfactor (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
2011-01-26 15:47:42 +05:30
2009-08-11 22:01:57 +05:30
2011-03-29 12:57:19 +05:30
!*** determine total number of active slip systems
2009-08-11 22:01:57 +05:30
2013-05-24 01:26:36 +05:30
Nslip ( 1 : lattice_maxNslipFamily , i ) = min ( lattice_NslipSystem ( 1 : lattice_maxNslipFamily , myStructure ) , &
Nslip ( 1 : lattice_maxNslipFamily , i ) ) ! we can't use more slip systems per family than specified in lattice
totalNslip ( i ) = sum ( 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
2013-05-24 01:26:36 +05:30
maxTotalNslip = maxval ( totalNslip )
2009-08-28 19:20:47 +05:30
2013-05-24 01:45:23 +05:30
allocate ( iRhoEPU ( maxTotalNslip , maxNinstance ) )
allocate ( iRhoENU ( maxTotalNslip , maxNinstance ) )
allocate ( iRhoSPU ( maxTotalNslip , maxNinstance ) )
allocate ( iRhoSNU ( maxTotalNslip , maxNinstance ) )
allocate ( iRhoEPB ( maxTotalNslip , maxNinstance ) )
allocate ( iRhoENB ( maxTotalNslip , maxNinstance ) )
allocate ( iRhoSPB ( maxTotalNslip , maxNinstance ) )
allocate ( iRhoSNB ( maxTotalNslip , maxNinstance ) )
allocate ( iRhoED ( maxTotalNslip , maxNinstance ) )
allocate ( iRhoSD ( maxTotalNslip , maxNinstance ) )
allocate ( iGamma ( maxTotalNslip , maxNinstance ) )
allocate ( iRhoF ( maxTotalNslip , maxNinstance ) )
allocate ( iTau ( maxTotalNslip , maxNinstance ) )
allocate ( iTauB ( maxTotalNslip , maxNinstance ) )
allocate ( iVEP ( maxTotalNslip , maxNinstance ) )
allocate ( iVEN ( maxTotalNslip , maxNinstance ) )
allocate ( iVSP ( maxTotalNslip , maxNinstance ) )
allocate ( iVSN ( maxTotalNslip , maxNinstance ) )
allocate ( iDE ( maxTotalNslip , maxNinstance ) )
allocate ( iDS ( maxTotalNslip , maxNinstance ) )
iRhoEPU = 0_pInt
iRhoENU = 0_pInt
iRhoSPU = 0_pInt
iRhoSNU = 0_pInt
iRhoEPB = 0_pInt
iRhoENB = 0_pInt
iRhoSPB = 0_pInt
iRhoSNB = 0_pInt
iRhoED = 0_pInt
iRhoSD = 0_pInt
iGamma = 0_pInt
iRhoF = 0_pInt
iTau = 0_pInt
iTauB = 0_pInt
iVEP = 0_pInt
iVEN = 0_pInt
iVSP = 0_pInt
iVSN = 0_pInt
iDE = 0_pInt
iDS = 0_pInt
2013-05-24 01:26:36 +05:30
allocate ( burgers ( maxTotalNslip , maxNinstance ) )
burgers = 0.0_pReal
2009-08-28 19:20:47 +05:30
2013-05-24 01:26:36 +05:30
allocate ( lambda0 ( maxTotalNslip , maxNinstance ) )
lambda0 = 0.0_pReal
2009-08-28 19:20:47 +05:30
2013-05-24 01:26:36 +05:30
allocate ( minDipoleHeight ( maxTotalNslip , 2 , maxNinstance ) )
minDipoleHeight = - 1.0_pReal
2011-01-26 15:47:42 +05:30
2013-05-24 01:26:36 +05:30
allocate ( forestProjectionEdge ( maxTotalNslip , maxTotalNslip , maxNinstance ) )
forestProjectionEdge = 0.0_pReal
2009-08-28 19:20:47 +05:30
2013-05-24 01:26:36 +05:30
allocate ( forestProjectionScrew ( maxTotalNslip , maxTotalNslip , maxNinstance ) )
forestProjectionScrew = 0.0_pReal
2009-08-28 19:20:47 +05:30
2013-05-24 01:26:36 +05:30
allocate ( interactionMatrixSlipSlip ( maxTotalNslip , maxTotalNslip , maxNinstance ) )
interactionMatrixSlipSlip = 0.0_pReal
2009-08-28 19:20:47 +05:30
2013-05-24 01:26:36 +05:30
allocate ( lattice2slip ( 1 : 3 , 1 : 3 , maxTotalNslip , maxNinstance ) )
lattice2slip = 0.0_pReal
2011-08-02 16:47:45 +05:30
2013-05-24 01:26:36 +05:30
allocate ( sourceProbability ( maxTotalNslip , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
sourceProbability = 2.0_pReal
2012-10-19 17:10:17 +05:30
2013-05-24 01:26:36 +05:30
allocate ( shearrate ( maxTotalNslip , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
shearrate = 0.0_pReal
2013-05-21 15:34:52 +05:30
2013-05-24 01:26:36 +05:30
allocate ( rhoDotFluxOutput ( maxTotalNslip , 8 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
allocate ( rhoDotMultiplicationOutput ( maxTotalNslip , 2 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
allocate ( rhoDotSingle2DipoleGlideOutput ( maxTotalNslip , 2 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
allocate ( rhoDotAthermalAnnihilationOutput ( maxTotalNslip , 2 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
allocate ( rhoDotThermalAnnihilationOutput ( maxTotalNslip , 2 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
allocate ( rhoDotEdgeJogsOutput ( maxTotalNslip , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
rhoDotFluxOutput = 0.0_pReal
rhoDotMultiplicationOutput = 0.0_pReal
rhoDotSingle2DipoleGlideOutput = 0.0_pReal
rhoDotAthermalAnnihilationOutput = 0.0_pReal
rhoDotThermalAnnihilationOutput = 0.0_pReal
rhoDotEdgeJogsOutput = 0.0_pReal
2010-03-10 15:19:40 +05:30
2013-05-24 01:26:36 +05:30
allocate ( compatibility ( 2 , maxTotalNslip , maxTotalNslip , mesh_maxNipNeighbors , mesh_maxNips , mesh_NcpElems ) )
compatibility = 0.0_pReal
2010-10-12 18:38:54 +05:30
2013-05-24 01:26:36 +05:30
allocate ( peierlsStress ( maxTotalNslip , 2 , maxNinstance ) )
peierlsStress = 0.0_pReal
2012-01-25 22:34:37 +05:30
2013-05-24 01:26:36 +05:30
allocate ( colinearSystem ( maxTotalNslip , maxNinstance ) )
colinearSystem = 0_pInt
2012-08-14 17:56:20 +05:30
2009-08-11 22:01:57 +05:30
do i = 1 , maxNinstance
myStructure = constitutive_nonlocal_structure ( i ) ! lattice structure of this instance
2011-03-29 12:57:19 +05:30
!*** Inverse lookup of my slip system family and the slip system in lattice
2009-08-11 22:01:57 +05:30
l = 0_pInt
2012-02-23 22:13:17 +05:30
do f = 1_pInt , lattice_maxNslipFamily
2013-05-24 01:26:36 +05:30
do s = 1_pInt , Nslip ( f , i )
2012-02-23 22:13:17 +05:30
l = l + 1_pInt
2013-05-24 01:26:36 +05:30
slipFamily ( l , i ) = f
slipSystemLattice ( l , i ) = sum ( lattice_NslipSystem ( 1 : f - 1_pInt , myStructure ) ) + s
2009-08-11 22:01:57 +05:30
enddo ; enddo
2011-03-29 12:57:19 +05:30
!*** determine size of state array
2009-08-11 22:01:57 +05:30
2013-05-24 01:26:36 +05:30
ns = totalNslip ( i )
constitutive_nonlocal_sizeDotState ( i ) = int ( size ( BASICSTATES ) , pInt ) * ns
constitutive_nonlocal_sizeDependentState ( i ) = int ( size ( DEPENDENTSTATES ) , pInt ) * ns
2011-11-04 18:42:17 +05:30
constitutive_nonlocal_sizeState ( i ) = constitutive_nonlocal_sizeDotState ( i ) &
+ constitutive_nonlocal_sizeDependentState ( i ) &
2013-05-24 01:26:36 +05:30
+ int ( size ( OTHERSTATES ) , pInt ) * ns
2011-11-04 18:42:17 +05:30
2013-05-24 01:45:23 +05:30
!*** determine indices to state array
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iRhoEPU ( s , i ) = s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iRhoENU ( s , i ) = iRhoEPU ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iRhoSPU ( s , i ) = iRhoENU ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iRhoSNU ( s , i ) = iRhoSPU ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iRhoEPB ( s , i ) = iRhoSNU ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iRhoENB ( s , i ) = iRhoEPB ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iRhoSPB ( s , i ) = iRhoENB ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iRhoSNB ( s , i ) = iRhoSPB ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iRhoED ( s , i ) = iRhoSNB ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iRhoSD ( s , i ) = iRhoED ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iGamma ( s , i ) = iRhoSD ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iRhoF ( s , i ) = iGamma ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iTau ( s , i ) = iRhoF ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iTauB ( s , i ) = iTau ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iVEP ( s , i ) = iTauB ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iVEN ( s , i ) = iVEP ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iVSP ( s , i ) = iVEN ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iVSN ( s , i ) = iVSP ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iDE ( s , i ) = iVSN ( ns , i ) + s
2013-05-24 01:45:23 +05:30
forall ( s = 1 : ns ) &
2013-05-24 02:00:06 +05:30
iDS ( s , i ) = iDE ( ns , i ) + s
2013-05-24 02:40:31 +05:30
if ( iDS ( ns , i ) / = constitutive_nonlocal_sizeState ( i ) ) & ! check if last index is equal to size of state
call IO_error ( 0_pInt , ext_msg = 'state indices not properly set (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
2009-08-11 22:01:57 +05:30
2013-05-24 01:45:23 +05:30
2011-03-29 12:57:19 +05:30
!*** determine size of postResults array
2009-08-11 22:01:57 +05:30
2013-05-24 01:26:36 +05:30
do o = 1_pInt , Noutput ( i )
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_external' , &
2012-01-17 15:56:57 +05:30
'resolvedstress_back' , &
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' , &
2012-08-27 21:27:31 +05:30
'rho_dot_sgl2dip_edge' , &
'rho_dot_sgl2dip_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_ann_ath' , &
'rho_dot_ann_the' , &
2012-08-27 18:11:57 +05:30
'rho_dot_ann_the_edge' , &
'rho_dot_ann_the_screw' , &
'rho_dot_edgejogs' , &
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' , &
2012-01-26 13:13:36 +05:30
'velocity_edge_pos' , &
'velocity_edge_neg' , &
'velocity_screw_pos' , &
'velocity_screw_neg' , &
2013-05-23 13:49:36 +05:30
'slipdirection.x' , &
'slipdirection.y' , &
'slipdirection.z' , &
'slipnormal.x' , &
'slipnormal.y' , &
'slipnormal.z' , &
'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' , &
2012-01-26 18:20:04 +05:30
'maximumdipoleheight_edge' , &
'maximumdipoleheight_screw' , &
2012-10-29 18:19:28 +05:30
'accumulatedshear' , &
'boundarylayer' )
2013-05-24 01:26:36 +05:30
mySize = totalNslip ( i )
2012-01-17 15:56:57 +05:30
case ( 'dislocationstress' )
2011-09-07 17:00:28 +05:30
mySize = 6_pInt
2009-08-11 22:01:57 +05:30
case default
2013-05-24 01:26:36 +05:30
call IO_error ( 212_pInt , ext_msg = constitutive_nonlocal_output ( o , i ) / / ' &
( '//CONSTITUTIVE_NONLOCAL_LABEL//' ) ' )
2009-08-11 22:01:57 +05:30
end select
2013-05-24 01:26:36 +05:30
if ( mySize > 0_pInt ) then ! any meaningful output found
2009-08-11 22:01:57 +05:30
constitutive_nonlocal_sizePostResult ( o , i ) = mySize
constitutive_nonlocal_sizePostResults ( i ) = constitutive_nonlocal_sizePostResults ( i ) + mySize
endif
enddo
2011-03-29 12:57:19 +05:30
!*** elasticity matrix and shear modulus according to material.config
2009-08-11 22:01:57 +05:30
2013-05-24 01:26:36 +05:30
Cslip66 ( : , : , i ) = lattice_symmetrizeC66 ( constitutive_nonlocal_structureName ( i ) , Cslip66 ( : , : , i ) )
mu ( i ) = 0.2_pReal * ( Cslip66 ( 1 , 1 , i ) - Cslip66 ( 1 , 2 , i ) + 3.0_pReal * Cslip66 ( 4 , 4 , i ) ) ! (C11iso-C12iso)/2 with C11iso=(3*C11+2*C12+4*C44)/5 and C12iso=(C11+4*C12-2*C44)/5
nu ( i ) = ( Cslip66 ( 1 , 1 , i ) + 4.0_pReal * Cslip66 ( 1 , 2 , i ) - 2.0_pReal * Cslip66 ( 1 , 2 , i ) ) &
/ ( 4.0_pReal * Cslip66 ( 1 , 1 , i ) + 6.0_pReal * Cslip66 ( 1 , 2 , i ) + 2.0_pReal * Cslip66 ( 4 , 4 , i ) ) ! C12iso/(C11iso+C12iso) with C11iso=(3*C11+2*C12+4*C44)/5 and C12iso=(C11+4*C12-2*C44)/5
Cslip66 ( 1 : 6 , 1 : 6 , i ) = math_Mandel3333to66 ( math_Voigt66to3333 ( Cslip66 ( 1 : 6 , 1 : 6 , i ) ) )
Cslip3333 ( 1 : 3 , 1 : 3 , 1 : 3 , 1 : 3 , i ) = math_Voigt66to3333 ( Cslip66 ( 1 : 6 , 1 : 6 , i ) )
2009-08-11 22:01:57 +05:30
2012-02-13 19:48:07 +05:30
do s1 = 1_pInt , ns
2013-05-24 01:26:36 +05:30
f = slipFamily ( s1 , i )
2009-08-12 16:52:02 +05:30
2011-03-29 12:57:19 +05:30
!*** burgers vector, mean free path prefactor and minimum dipole distance for each slip system
2009-08-11 22:01:57 +05:30
2013-05-24 01:26:36 +05:30
burgers ( s1 , i ) = burgersPerSlipFamily ( f , i )
lambda0 ( s1 , i ) = lambda0PerSlipFamily ( f , i )
minDipoleHeight ( s1 , 1 : 2 , i ) = minDipoleHeightPerSlipFamily ( f , 1 : 2 , i )
peierlsStress ( s1 , 1 : 2 , i ) = peierlsStressPerSlipFamily ( f , 1 : 2 , i )
2009-10-07 21:01:52 +05:30
2012-02-23 22:13:17 +05:30
do s2 = 1_pInt , ns
2009-08-11 22:01:57 +05:30
2011-03-29 12:57:19 +05:30
!*** calculation of forest projections for edge and screw dislocations. s2 acts as forest for s1
2009-10-07 21:01:52 +05:30
2013-05-24 01:26:36 +05:30
forestProjectionEdge ( s1 , s2 , i ) &
= abs ( math_mul3x3 ( lattice_sn ( 1 : 3 , slipSystemLattice ( s1 , i ) , myStructure ) , &
lattice_st ( 1 : 3 , 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
2013-05-24 01:26:36 +05:30
forestProjectionScrew ( s1 , s2 , i ) &
= abs ( math_mul3x3 ( lattice_sn ( 1 : 3 , slipSystemLattice ( s1 , i ) , myStructure ) , &
lattice_sd ( 1 : 3 , 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
2011-03-29 12:57:19 +05:30
!*** calculation of interaction matrices
2009-10-07 21:01:52 +05:30
2013-05-24 01:26:36 +05:30
interactionMatrixSlipSlip ( s1 , s2 , i ) &
= interactionSlipSlip ( lattice_interactionSlipSlip ( slipSystemLattice ( s1 , i ) , &
slipSystemLattice ( s2 , i ) , &
myStructure ) , i )
2012-08-14 17:56:20 +05:30
!*** colinear slip system (only makes sense for fcc like it is defined here)
2013-05-24 01:26:36 +05:30
if ( lattice_interactionSlipSlip ( slipSystemLattice ( s1 , i ) , &
slipSystemLattice ( s2 , i ) , &
2012-08-14 17:56:20 +05:30
myStructure ) == 3_pInt ) then
2013-05-24 01:26:36 +05:30
colinearSystem ( s1 , i ) = s2
2012-08-14 17:56:20 +05:30
endif
2011-03-29 12:57:19 +05:30
enddo
2011-08-02 16:47:45 +05:30
!*** rotation matrix from lattice configuration to slip system
2013-05-24 01:26:36 +05:30
lattice2slip ( 1 : 3 , 1 : 3 , s1 , i ) &
= math_transpose33 ( reshape ( [ lattice_sd ( 1 : 3 , slipSystemLattice ( s1 , i ) , myStructure ) , &
- lattice_st ( 1 : 3 , slipSystemLattice ( s1 , i ) , myStructure ) , &
lattice_sn ( 1 : 3 , slipSystemLattice ( s1 , i ) , myStructure ) ] , [ 3 , 3 ] ) )
2011-03-29 12:57:19 +05:30
enddo
2009-08-11 22:01:57 +05:30
enddo
endsubroutine
!*********************************************************************
!* initial microstructural state (just the "basic" states) *
!*********************************************************************
2012-10-02 18:27:24 +05:30
subroutine constitutive_nonlocal_stateInit ( state )
2009-08-11 22:01:57 +05:30
2013-05-24 02:40:31 +05:30
use IO , only : IO_error
2009-08-11 22:01:57 +05:30
use lattice , only : lattice_maxNslipFamily
2011-02-04 21:11:32 +05:30
use math , only : math_sampleGaussVar
2012-10-02 18:27:24 +05:30
use mesh , only : mesh_ipVolume , &
mesh_NcpElems , &
mesh_maxNips , &
2012-11-16 04:15:20 +05:30
mesh_element , &
2012-10-02 18:27:24 +05:30
FE_Nips , &
2012-11-16 04:15:20 +05:30
FE_geomtype
2012-10-02 18:27:24 +05:30
use material , only : material_phase , &
phase_plasticityInstance , &
2013-05-24 02:40:31 +05:30
phase_plasticity , &
homogenization_Ngrains
2011-02-04 21:11:32 +05:30
2009-08-11 22:01:57 +05:30
implicit none
2012-10-02 18:27:24 +05:30
!*** input/output variables
type ( p_vec ) , dimension ( 1 , mesh_maxNips , mesh_NcpElems ) , intent ( inout ) :: &
state ! microstructural state
2009-08-11 22:01:57 +05:30
!*** local variables
2012-10-02 18:27:24 +05:30
integer ( pInt ) el , &
ip , &
2013-05-24 02:40:31 +05:30
e , &
i , &
g , &
idx , &
2012-10-02 18:27:24 +05:30
ns , & ! short notation for total number of active slip systems
2009-08-11 22:01:57 +05:30
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
2012-10-02 18:27:24 +05:30
t , &
2013-05-24 02:40:31 +05:30
j , &
2012-10-02 18:27:24 +05:30
myInstance , &
maxNinstance
2011-02-04 21:11:32 +05:30
real ( pReal ) , dimension ( 2 ) :: noise
2012-10-02 18:27:24 +05:30
real ( pReal ) , dimension ( 4 ) :: rnd
real ( pReal ) meanDensity , &
totalVolume , &
2012-10-02 20:56:58 +05:30
densityBinning , &
2012-10-02 19:05:34 +05:30
minimumIpVolume
2009-08-11 22:01:57 +05:30
2013-05-24 01:26:36 +05:30
maxNinstance = int ( count ( phase_plasticity == CONSTITUTIVE_NONLOCAL_LABEL ) , pInt )
2009-08-11 22:01:57 +05:30
2013-05-24 02:40:31 +05:30
! ititalize all states to zero
do e = 1_pInt , mesh_NcpElems
do i = 1_pInt , FE_Nips ( FE_geomtype ( mesh_element ( 2 , e ) ) )
do g = 1_pInt , homogenization_Ngrains ( mesh_element ( 3 , e ) )
state ( g , i , e ) % p = 0.0_pReal
enddo
enddo
enddo
2012-10-02 18:27:24 +05:30
do myInstance = 1_pInt , maxNinstance
2013-05-24 01:26:36 +05:30
ns = totalNslip ( myInstance )
2009-08-11 22:01:57 +05:30
2012-10-02 18:27:24 +05:30
! randomly distribute dislocation segments on random slip system and of random type in the volume
2013-05-24 01:26:36 +05:30
if ( rhoSglRandom ( myInstance ) > 0.0_pReal ) then
2009-08-11 22:01:57 +05:30
2013-05-24 02:40:31 +05:30
! get the total volume of the instance
2009-08-11 22:01:57 +05:30
2012-10-02 19:05:34 +05:30
minimumIpVolume = 1e99_pReal
2013-03-27 18:34:01 +05:30
totalVolume = 0.0_pReal
2013-05-24 02:40:31 +05:30
do e = 1_pInt , mesh_NcpElems
do i = 1_pInt , FE_Nips ( FE_geomtype ( mesh_element ( 2 , e ) ) )
if ( CONSTITUTIVE_NONLOCAL_LABEL == phase_plasticity ( material_phase ( 1 , i , e ) ) &
. and . myInstance == phase_plasticityInstance ( material_phase ( 1 , i , e ) ) ) then
totalVolume = totalVolume + mesh_ipVolume ( i , e )
minimumIpVolume = min ( minimumIpVolume , mesh_ipVolume ( i , e ) )
2012-10-02 18:27:24 +05:30
endif
enddo
enddo
2013-05-24 01:26:36 +05:30
densityBinning = rhoSglRandomBinning ( myInstance ) / minimumIpVolume ** ( 2.0_pReal / 3.0_pReal )
2009-08-11 22:01:57 +05:30
2012-10-02 18:27:24 +05:30
! subsequently fill random ips with dislocation segments until we reach the desired overall density
meanDensity = 0.0_pReal
2013-05-24 01:26:36 +05:30
do while ( meanDensity < rhoSglRandom ( myInstance ) )
2012-10-02 18:27:24 +05:30
call random_number ( rnd )
el = nint ( rnd ( 1 ) * real ( mesh_NcpElems , pReal ) + 0.5_pReal , pInt )
2012-11-16 04:15:20 +05:30
ip = nint ( rnd ( 2 ) * real ( FE_Nips ( FE_geomtype ( mesh_element ( 2 , el ) ) ) , pReal ) + 0.5_pReal , pInt )
2013-05-24 01:26:36 +05:30
if ( CONSTITUTIVE_NONLOCAL_LABEL == phase_plasticity ( material_phase ( 1 , ip , el ) ) &
2012-10-02 18:27:24 +05:30
. and . myInstance == phase_plasticityInstance ( material_phase ( 1 , ip , el ) ) ) then
s = nint ( rnd ( 3 ) * real ( ns , pReal ) + 0.5_pReal , pInt )
t = nint ( rnd ( 4 ) * 4.0_pReal + 0.5_pReal , pInt )
2012-10-02 20:56:58 +05:30
meanDensity = meanDensity + densityBinning * mesh_ipVolume ( ip , el ) / totalVolume
2013-05-24 02:40:31 +05:30
if ( t == 1_pInt ) then
idx = iRhoEPU ( s , myInstance )
elseif ( t == 2_pInt ) then
idx = iRhoENU ( s , myInstance )
elseif ( t == 3_pInt ) then
idx = iRhoSPU ( s , myInstance )
elseif ( t == 4_pInt ) then
idx = iRhoSNU ( s , myInstance )
else
call IO_error ( - 1 , ext_msg = 'state init failed (' / / CONSTITUTIVE_NONLOCAL_LABEL / / ')' )
endif
state ( 1 , ip , el ) % p ( idx ) = state ( 1 , ip , el ) % p ( idx ) + densityBinning
2012-10-02 18:27:24 +05:30
endif
enddo
! homogeneous distribution of density with some noise
else
2013-05-24 02:40:31 +05:30
do e = 1_pInt , mesh_NcpElems
do i = 1_pInt , FE_Nips ( FE_geomtype ( mesh_element ( 2 , e ) ) )
if ( CONSTITUTIVE_NONLOCAL_LABEL == phase_plasticity ( material_phase ( 1 , i , e ) ) &
. and . myInstance == phase_plasticityInstance ( material_phase ( 1 , i , e ) ) ) then
2012-10-02 18:27:24 +05:30
do f = 1_pInt , lattice_maxNslipFamily
2013-05-24 01:26:36 +05:30
from = 1_pInt + sum ( Nslip ( 1 : f - 1_pInt , myInstance ) )
upto = sum ( Nslip ( 1 : f , myInstance ) )
2012-10-02 18:27:24 +05:30
do s = from , upto
2013-05-24 02:40:31 +05:30
do j = 1_pInt , 2_pInt
noise ( j ) = math_sampleGaussVar ( 0.0_pReal , rhoSglScatter ( myInstance ) )
2012-10-02 18:27:24 +05:30
enddo
2013-05-24 02:40:31 +05:30
state ( 1 , i , e ) % p ( iRhoEPU ( s , myInstance ) ) = rhoSglEdgePos0 ( f , myInstance ) + noise ( 1 )
state ( 1 , i , e ) % p ( iRhoENU ( s , myInstance ) ) = rhoSglEdgeNeg0 ( f , myInstance ) + noise ( 1 )
state ( 1 , i , e ) % p ( iRhoSPU ( s , myInstance ) ) = rhoSglScrewPos0 ( f , myInstance ) + noise ( 2 )
state ( 1 , i , e ) % p ( iRhoSNU ( s , myInstance ) ) = rhoSglScrewNeg0 ( f , myInstance ) + noise ( 2 )
2012-10-02 18:27:24 +05:30
enddo
2013-05-24 02:40:31 +05:30
state ( 1 , i , e ) % p ( iRhoED ( from : upto , myInstance ) ) = rhoDipEdge0 ( f , myInstance )
state ( 1 , i , e ) % p ( iRhoSD ( from : upto , myInstance ) ) = rhoDipScrew0 ( f , myInstance )
2012-10-02 18:27:24 +05:30
enddo
endif
enddo
enddo
endif
enddo
endsubroutine
2009-08-11 22:01:57 +05:30
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
implicit none
!*** input variables
2013-04-04 19:07:14 +05:30
integer ( pInt ) , intent ( in ) :: myInstance ! number specifying the current instance of the plasticity
2009-09-18 21:07:14 +05:30
!*** output variables
real ( pReal ) , dimension ( constitutive_nonlocal_sizeState ( myInstance ) ) :: &
2012-03-12 19:39:37 +05:30
constitutive_nonlocal_aTolState ! absolute state tolerance for the current instance of this plasticity
2009-09-18 21:07:14 +05:30
!*** local variables
2013-04-04 19:07:14 +05:30
integer ( pInt ) :: ns
2009-09-18 21:07:14 +05:30
2013-05-24 01:26:36 +05:30
ns = totalNslip ( myInstance )
2013-04-04 19:07:14 +05:30
constitutive_nonlocal_aTolState = 0.0_pReal
2013-05-24 02:43:56 +05:30
constitutive_nonlocal_aTolState ( iRhoEPU ( 1 : ns , myInstance ) ) = aTolRho ( myInstance )
constitutive_nonlocal_aTolState ( iRhoENU ( 1 : ns , myInstance ) ) = aTolRho ( myInstance )
constitutive_nonlocal_aTolState ( iRhoSPU ( 1 : ns , myInstance ) ) = aTolRho ( myInstance )
constitutive_nonlocal_aTolState ( iRhoSNU ( 1 : ns , myInstance ) ) = aTolRho ( myInstance )
constitutive_nonlocal_aTolState ( iRhoEPB ( 1 : ns , myInstance ) ) = aTolRho ( myInstance )
constitutive_nonlocal_aTolState ( iRhoENB ( 1 : ns , myInstance ) ) = aTolRho ( myInstance )
constitutive_nonlocal_aTolState ( iRhoSPB ( 1 : ns , myInstance ) ) = aTolRho ( myInstance )
constitutive_nonlocal_aTolState ( iRhoSNB ( 1 : ns , myInstance ) ) = aTolRho ( myInstance )
constitutive_nonlocal_aTolState ( iRhoED ( 1 : ns , myInstance ) ) = aTolRho ( myInstance )
constitutive_nonlocal_aTolState ( iRhoSD ( 1 : ns , myInstance ) ) = aTolRho ( myInstance )
constitutive_nonlocal_aTolState ( iGamma ( 1 : ns , myInstance ) ) = aTolShear ( 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 mesh , only : mesh_NcpElems , &
mesh_maxNips
use material , only : homogenization_maxNgrains , &
material_phase , &
2012-03-12 19:39:37 +05:30
phase_plasticityInstance
2009-08-11 22:01:57 +05:30
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
2012-03-12 19:39:37 +05:30
integer ( pInt ) myInstance ! current instance of this plasticity
2009-08-11 22:01:57 +05:30
2012-03-12 19:39:37 +05:30
myInstance = phase_plasticityInstance ( material_phase ( g , ip , el ) )
2009-08-11 22:01:57 +05:30
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_homogenizedC = Cslip66 ( 1 : 6 , 1 : 6 , myInstance )
2009-08-11 22:01:57 +05:30
endfunction
!*********************************************************************
!* calculates quantities characterizing the microstructure *
!*********************************************************************
2013-05-23 17:55:56 +05:30
subroutine constitutive_nonlocal_microstructure ( state , Temperature , Fe , Fp , gr , ip , el )
use IO , only : &
IO_error
use math , only : &
pi , &
math_mul33x3 , &
math_mul3x3 , &
math_norm3 , &
math_invert33 , &
math_transpose33
use debug , only : &
debug_level , &
debug_constitutive , &
debug_levelBasic , &
debug_levelExtensive , &
debug_levelSelective , &
debug_g , &
debug_i , &
debug_e
use mesh , only : &
mesh_NcpElems , &
mesh_maxNips , &
mesh_element , &
mesh_ipNeighborhood , &
mesh_ipCoordinates , &
mesh_ipVolume , &
mesh_ipAreaNormal , &
mesh_ipArea , &
FE_NipNeighbors , &
2013-05-23 23:16:21 +05:30
mesh_maxNipNeighbors , &
2013-05-23 17:55:56 +05:30
FE_geomtype , &
FE_celltype
use material , only : &
homogenization_maxNgrains , &
material_phase , &
phase_localPlasticity , &
phase_plasticityInstance
use lattice , only : &
lattice_sd , &
lattice_st , &
lattice_interactionSlipSlip
2009-08-11 22:01:57 +05:30
implicit none
!*** input variables
2013-05-23 17:55:56 +05:30
integer ( pInt ) , intent ( in ) :: gr , & ! current grain ID
2011-03-29 13:04:33 +05:30
ip , & ! current integration point
el ! current element
real ( pReal ) , intent ( in ) :: Temperature ! temperature
2012-01-17 15:56:57 +05:30
real ( pReal ) , dimension ( 3 , 3 ) , intent ( in ) :: &
Fe , & ! elastic deformation gradient
Fp ! elastic deformation gradient
2009-08-11 22:01:57 +05:30
2011-11-04 18:42:17 +05:30
!*** input/output variables
2009-08-11 22:01:57 +05:30
type ( p_vec ) , dimension ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( inout ) :: &
2011-03-29 13:04:33 +05:30
state ! microstructural state
2011-11-04 18:42:17 +05:30
!*** output variables
2011-03-29 13:04:33 +05:30
2011-11-04 18:42:17 +05:30
!*** local variables
2011-03-29 13:04:33 +05:30
integer ( pInt ) neighboring_el , & ! element number of neighboring material point
neighboring_ip , & ! integration point of neighboring material point
2012-03-12 19:39:37 +05:30
instance , & ! my instance of this plasticity
neighboring_instance , & ! instance of this plasticity of neighboring material point
2011-03-29 13:04:33 +05:30
latticeStruct , & ! my lattice structure
neighboring_latticeStruct , & ! lattice structure of neighboring material point
phase , &
neighboring_phase , &
ns , & ! total number of active slip systems at my material point
neighboring_ns , & ! total number of active slip systems at neighboring material point
c , & ! index of dilsocation character (edge, screw)
s , & ! slip system index
2012-10-04 23:38:40 +05:30
s2 , & ! slip system index
2011-03-29 13:04:33 +05:30
t , & ! index of dilsocation type (e+, e-, s+, s-, used e+, used e-, used s+, used s-)
dir , &
2012-10-04 23:38:40 +05:30
n , &
2013-03-27 18:34:01 +05:30
nRealNeighbors , & ! number of really existing neighbors
2012-10-04 23:38:40 +05:30
interactionCoefficient
2012-01-17 15:56:57 +05:30
integer ( pInt ) , dimension ( 2 ) :: neighbor
2013-05-24 01:26:36 +05:30
real ( pReal ) detFe , &
2012-01-17 15:56:57 +05:30
detFp , &
2012-03-15 20:28:12 +05:30
FVsize , &
2012-10-04 23:38:40 +05:30
temp , &
correction , &
myRhoForest
2012-03-14 20:54:19 +05:30
real ( pReal ) , dimension ( 2 ) :: rhoExcessGradient , &
rhoExcessGradient_over_rho , &
rhoTotal
2013-05-23 18:06:48 +05:30
real ( pReal ) , dimension ( 3 ) :: rhoExcessDifferences , &
normal_latticeConf
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( gr , ip , el ) ) ) ) :: &
2011-03-29 13:04:33 +05:30
rhoForest , & ! forest dislocation density
2012-01-17 15:56:57 +05:30
tauBack , & ! back stress from pileup on same slip system
2011-04-13 19:46:22 +05:30
tauThreshold ! threshold shear stress
2012-01-17 15:56:57 +05:30
real ( pReal ) , dimension ( 3 , 3 ) :: invFe , & ! inverse of elastic deformation gradient
2012-03-14 20:54:19 +05:30
invFp , & ! inverse of plastic deformation gradient
2012-03-15 20:28:12 +05:30
connections , &
invConnections
2013-05-23 23:16:21 +05:30
real ( pReal ) , dimension ( 3 , mesh_maxNipNeighbors ) :: &
2012-03-15 15:38:08 +05:30
connection_latticeConf
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( 2 , totalNslip ( phase_plasticityInstance ( material_phase ( gr , ip , el ) ) ) ) :: &
2012-01-17 15:56:57 +05:30
rhoExcess
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( gr , ip , el ) ) ) , 2 ) :: &
2012-01-17 15:56:57 +05:30
rhoDip ! dipole dislocation density (edge, screw)
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( gr , ip , el ) ) ) , 8 ) :: &
2012-01-17 15:56:57 +05:30
rhoSgl ! single dislocation density (edge+, edge-, screw+, screw-, used edge+, used edge-, used screw+, used screw-)
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( gr , ip , el ) ) ) , &
totalNslip ( phase_plasticityInstance ( material_phase ( gr , ip , el ) ) ) ) :: &
2012-10-05 21:35:51 +05:30
myInteractionMatrix ! corrected slip interaction matrix
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( 2 , maxval ( totalNslip ) , mesh_maxNipNeighbors ) :: &
2013-03-27 18:34:01 +05:30
neighboring_rhoExcess , & ! excess density at neighboring material point
neighboring_rhoTotal ! total density at neighboring material point
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( 3 , totalNslip ( phase_plasticityInstance ( material_phase ( gr , ip , el ) ) ) , 2 ) :: &
2012-01-17 15:56:57 +05:30
m ! direction of dislocation motion
2011-09-07 17:00:28 +05:30
logical inversionError
2011-03-29 13:04:33 +05:30
2012-01-17 15:56:57 +05:30
2013-05-23 17:55:56 +05:30
phase = material_phase ( gr , ip , el )
2012-03-12 19:39:37 +05:30
instance = phase_plasticityInstance ( phase )
2011-03-29 13:04:33 +05:30
latticeStruct = constitutive_nonlocal_structure ( instance )
2013-05-24 01:26:36 +05:30
ns = totalNslip ( instance )
2011-03-29 13:04:33 +05:30
2009-08-11 22:01:57 +05:30
!*** get basic states
2013-05-24 02:58:45 +05:30
forall ( s = 1_pInt : ns )
rhoSgl ( s , 1 ) = max ( state ( gr , ip , el ) % p ( iRhoEPU ( s , instance ) ) , 0.0_pReal ) ! ensure positive single mobile densities
rhoSgl ( s , 2 ) = max ( state ( gr , ip , el ) % p ( iRhoENU ( s , instance ) ) , 0.0_pReal ) ! ensure positive single mobile densities
rhoSgl ( s , 3 ) = max ( state ( gr , ip , el ) % p ( iRhoSPU ( s , instance ) ) , 0.0_pReal ) ! ensure positive single mobile densities
rhoSgl ( s , 4 ) = max ( state ( gr , ip , el ) % p ( iRhoSNU ( s , instance ) ) , 0.0_pReal ) ! ensure positive single mobile densities
endforall
rhoSgl ( 1 : ns , 5 ) = state ( gr , ip , el ) % p ( iRhoEPB ( 1 : ns , instance ) )
rhoSgl ( 1 : ns , 6 ) = state ( gr , ip , el ) % p ( iRhoENB ( 1 : ns , instance ) )
rhoSgl ( 1 : ns , 7 ) = state ( gr , ip , el ) % p ( iRhoSPB ( 1 : ns , instance ) )
rhoSgl ( 1 : ns , 8 ) = state ( gr , ip , el ) % p ( iRhoSNB ( 1 : ns , instance ) )
forall ( s = 1_pInt : ns )
rhoDip ( s , 1 ) = max ( state ( gr , ip , el ) % p ( iRhoED ( s , instance ) ) , 0.0_pReal ) ! ensure positive dipole densities
rhoDip ( s , 2 ) = max ( state ( gr , ip , el ) % p ( iRhoSD ( s , instance ) ) , 0.0_pReal ) ! ensure positive dipole densities
endforall
2013-05-24 01:26:36 +05:30
where ( abs ( rhoSgl ) * mesh_ipVolume ( ip , el ) ** 0.667_pReal < significantN ( instance ) &
. or . abs ( rhoSgl ) < significantRho ( instance ) ) &
2012-10-02 18:27:24 +05:30
rhoSgl = 0.0_pReal
2013-05-24 01:26:36 +05:30
where ( abs ( rhoDip ) * mesh_ipVolume ( ip , el ) ** 0.667_pReal < significantN ( instance ) &
. or . abs ( rhoDip ) < significantRho ( instance ) ) &
2012-10-02 18:27:24 +05:30
rhoDip = 0.0_pReal
2009-08-11 22:01:57 +05:30
!*** calculate the forest dislocation density
2011-03-29 13:04:33 +05:30
!*** (= projection of screw and edge dislocations)
2009-08-11 22:01:57 +05:30
2012-03-14 20:48:36 +05:30
forall ( s = 1_pInt : ns ) &
2012-03-15 15:38:08 +05:30
rhoForest ( s ) = dot_product ( ( sum ( abs ( rhoSgl ( 1 : ns , [ 1 , 2 , 5 , 6 ] ) ) , 2 ) + rhoDip ( 1 : ns , 1 ) ) , &
2013-05-24 01:26:36 +05:30
forestProjectionEdge ( s , 1 : ns , instance ) ) &
2012-03-15 15:38:08 +05:30
+ dot_product ( ( sum ( abs ( rhoSgl ( 1 : ns , [ 3 , 4 , 7 , 8 ] ) ) , 2 ) + rhoDip ( 1 : ns , 2 ) ) , &
2013-05-24 01:26:36 +05:30
forestProjectionScrew ( s , 1 : ns , instance ) )
2011-03-29 13:04:33 +05:30
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
2012-10-05 21:35:51 +05:30
myInteractionMatrix = 0.0_pReal
2013-05-24 01:26:36 +05:30
myInteractionMatrix ( 1 : ns , 1 : ns ) = interactionMatrixSlipSlip ( 1 : ns , 1 : ns , instance )
2013-05-23 17:55:56 +05:30
if ( latticeStruct == 1_pInt ) then ! in case of fcc: coefficients are corrected for the line tension effect (see Kubin,Devincre,Hoc; 2008; Modeling dislocation storage rates and mean free paths in face-centered cubic crystals)
2012-10-04 23:38:40 +05:30
do s = 1_pInt , ns
2013-05-24 01:26:36 +05:30
myRhoForest = max ( rhoForest ( s ) , significantRho ( instance ) )
correction = ( 1.0_pReal - linetensionEffect ( instance ) &
+ linetensionEffect ( instance ) &
* log ( 0.35_pReal * burgers ( s , instance ) * sqrt ( myRhoForest ) ) &
/ log ( 0.35_pReal * burgers ( s , instance ) * 1e6_pReal ) ) ** 2.0_pReal
2012-10-04 23:38:40 +05:30
do s2 = 1_pInt , ns
2013-05-23 17:55:56 +05:30
interactionCoefficient = &
2013-05-24 01:26:36 +05:30
lattice_interactionSlipSlip ( slipSystemLattice ( s , instance ) , &
slipSystemLattice ( s2 , instance ) , &
2013-05-23 17:55:56 +05:30
latticeStruct )
2012-10-04 23:38:40 +05:30
select case ( interactionCoefficient )
2013-05-23 17:55:56 +05:30
case ( 4_pInt , 5_pInt , 6_pInt ) ! only correct junction forming interactions (4,5,6)
2012-10-05 21:35:51 +05:30
myInteractionMatrix ( s , s2 ) = correction * myInteractionMatrix ( s , s2 )
2012-10-04 23:38:40 +05:30
endselect
enddo
enddo
endif
2012-03-14 20:48:36 +05:30
forall ( s = 1_pInt : ns ) &
2013-05-24 01:26:36 +05:30
tauThreshold ( s ) = mu ( instance ) * burgers ( s , instance ) &
2012-10-05 21:35:51 +05:30
* sqrt ( dot_product ( ( sum ( abs ( rhoSgl ) , 2 ) + sum ( abs ( rhoDip ) , 2 ) ) , myInteractionMatrix ( s , 1 : ns ) ) )
2011-03-29 13:04:33 +05:30
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
2012-03-12 19:39:37 +05:30
!*** zero for material points of local plasticity
2011-03-29 13:04:33 +05:30
2012-01-17 15:56:57 +05:30
tauBack = 0.0_pReal
2009-08-11 22:01:57 +05:30
2013-05-24 01:26:36 +05:30
if ( . not . phase_localPlasticity ( phase ) . and . shortRangeStressCorrection ( instance ) ) then
2012-01-26 19:20:00 +05:30
call math_invert33 ( Fe , invFe , detFe , inversionError )
call math_invert33 ( Fp , invFp , detFp , inversionError )
2012-01-17 15:56:57 +05:30
rhoExcess ( 1 , 1 : ns ) = rhoSgl ( 1 : ns , 1 ) - rhoSgl ( 1 : ns , 2 )
rhoExcess ( 2 , 1 : ns ) = rhoSgl ( 1 : ns , 3 ) - rhoSgl ( 1 : ns , 4 )
FVsize = mesh_ipVolume ( ip , el ) ** ( 1.0_pReal / 3.0_pReal )
2011-02-04 21:11:32 +05:30
2012-01-17 15:56:57 +05:30
!* loop through my neighborhood and get the connection vectors (in lattice frame) and the excess densities
2013-03-27 18:34:01 +05:30
nRealNeighbors = 0_pInt
neighboring_rhoTotal = 0.0_pReal
2013-04-22 19:05:35 +05:30
do n = 1_pInt , FE_NipNeighbors ( FE_celltype ( FE_geomtype ( mesh_element ( 2 , el ) ) ) )
2012-01-17 15:56:57 +05:30
neighboring_el = mesh_ipNeighborhood ( 1 , n , ip , el )
neighboring_ip = mesh_ipNeighborhood ( 2 , n , ip , el )
if ( neighboring_el > 0 . and . neighboring_ip > 0 ) then
2013-05-23 17:55:56 +05:30
neighboring_phase = material_phase ( gr , neighboring_ip , neighboring_el )
2012-03-12 19:39:37 +05:30
neighboring_instance = phase_plasticityInstance ( neighboring_phase )
2011-03-29 13:04:33 +05:30
neighboring_latticeStruct = constitutive_nonlocal_structure ( neighboring_instance )
2013-05-24 01:26:36 +05:30
neighboring_ns = totalNslip ( neighboring_instance )
2012-03-12 19:39:37 +05:30
if ( . not . phase_localPlasticity ( neighboring_phase ) &
2012-01-17 15:56:57 +05:30
. and . neighboring_latticeStruct == latticeStruct &
. and . neighboring_instance == instance ) then
if ( neighboring_ns == ns ) then
2013-05-23 18:06:48 +05:30
nRealNeighbors = nRealNeighbors + 1_pInt
2013-05-24 02:58:45 +05:30
forall ( s = 1_pInt : ns )
neighboring_rhoExcess ( 1 , s , n ) = &
max ( state ( gr , neighboring_ip , neighboring_el ) % p ( iRhoEPU ( s , neighboring_instance ) ) , 0.0_pReal ) & ! positive mobiles
- max ( state ( gr , neighboring_ip , neighboring_el ) % p ( iRhoENU ( s , neighboring_instance ) ) , 0.0_pReal ) ! negative mobiles
neighboring_rhoExcess ( 2 , s , n ) = &
max ( state ( gr , neighboring_ip , neighboring_el ) % p ( iRhoSPU ( s , neighboring_instance ) ) , 0.0_pReal ) & ! positive mobiles
- max ( state ( gr , neighboring_ip , neighboring_el ) % p ( iRhoSNU ( s , neighboring_instance ) ) , 0.0_pReal ) ! negative mobiles
neighboring_rhoTotal ( 1 , s , n ) = &
max ( state ( gr , neighboring_ip , neighboring_el ) % p ( iRhoEPU ( s , neighboring_instance ) ) , 0.0_pReal ) & ! positive mobiles
+ max ( state ( gr , neighboring_ip , neighboring_el ) % p ( iRhoENU ( s , neighboring_instance ) ) , 0.0_pReal ) & ! negative mobiles
+ abs ( state ( gr , neighboring_ip , neighboring_el ) % p ( iRhoEPB ( s , neighboring_instance ) ) ) & ! positive deads
+ abs ( state ( gr , neighboring_ip , neighboring_el ) % p ( iRhoENB ( s , neighboring_instance ) ) ) & ! negative deads
+ max ( state ( gr , neighboring_ip , neighboring_el ) % p ( iRhoED ( s , neighboring_instance ) ) , 0.0_pReal ) ! dipoles
neighboring_rhoTotal ( 2 , s , n ) = &
max ( state ( gr , neighboring_ip , neighboring_el ) % p ( iRhoSPU ( s , neighboring_instance ) ) , 0.0_pReal ) & ! positive mobiles
+ max ( state ( gr , neighboring_ip , neighboring_el ) % p ( iRhoSNU ( s , neighboring_instance ) ) , 0.0_pReal ) & ! negative mobiles
+ abs ( state ( gr , neighboring_ip , neighboring_el ) % p ( iRhoSPB ( s , neighboring_instance ) ) ) & ! positive deads
+ abs ( state ( gr , neighboring_ip , neighboring_el ) % p ( iRhoSNB ( s , neighboring_instance ) ) ) & ! negative deads
+ max ( state ( gr , neighboring_ip , neighboring_el ) % p ( iRhoSD ( s , neighboring_instance ) ) , 0.0_pReal ) ! dipoles
2013-05-23 18:06:48 +05:30
endforall
connection_latticeConf ( 1 : 3 , n ) = &
math_mul33x3 ( invFe , mesh_ipCoordinates ( 1 : 3 , neighboring_ip , neighboring_el ) &
- mesh_ipCoordinates ( 1 : 3 , ip , el ) )
normal_latticeConf = math_mul33x3 ( math_transpose33 ( invFp ) , mesh_ipAreaNormal ( 1 : 3 , n , ip , el ) )
if ( math_mul3x3 ( normal_latticeConf , connection_latticeConf ( 1 : 3 , n ) ) < 0.0_pReal ) then ! neighbor connection points in opposite direction to face normal: must be periodic image
connection_latticeConf ( 1 : 3 , n ) = normal_latticeConf * mesh_ipVolume ( ip , el ) &
/ mesh_ipArea ( n , ip , el ) ! instead take the surface normal scaled with the diameter of the cell
2012-01-17 15:56:57 +05:30
endif
else
! different number of active slip systems
2012-02-13 19:48:07 +05:30
call IO_error ( - 1_pInt , ext_msg = 'different number of active slip systems in neighboring IPs of same crystal structure' )
2012-01-17 15:56:57 +05:30
endif
else
2012-03-15 15:38:08 +05:30
! local neighbor or different lattice structure or different constitution instance -> use central values instead
connection_latticeConf ( 1 : 3 , n ) = 0.0_pReal
2012-01-17 15:56:57 +05:30
neighboring_rhoExcess ( 1 : 2 , 1 : ns , n ) = rhoExcess
endif
else
2012-03-15 15:38:08 +05:30
! free surface -> use central values instead
connection_latticeConf ( 1 : 3 , n ) = 0.0_pReal
2012-01-17 15:56:57 +05:30
neighboring_rhoExcess ( 1 : 2 , 1 : ns , n ) = rhoExcess
endif
enddo
2012-03-14 20:54:19 +05:30
!* loop through the slip systems and calculate the dislocation gradient by
!* 1. interpolation of the excess density in the neighorhood
!* 2. interpolation of the dead dislocation density in the central volume
2012-01-17 15:56:57 +05:30
2013-05-24 01:26:36 +05:30
m ( 1 : 3 , 1 : ns , 1 ) = lattice_sd ( 1 : 3 , slipSystemLattice ( 1 : ns , instance ) , latticeStruct )
m ( 1 : 3 , 1 : ns , 2 ) = - lattice_st ( 1 : 3 , slipSystemLattice ( 1 : ns , instance ) , latticeStruct )
2011-03-29 13:04:33 +05:30
2012-02-23 22:13:17 +05:30
do s = 1_pInt , ns
2012-01-17 15:56:57 +05:30
2012-03-14 20:54:19 +05:30
!* gradient from interpolation of neighboring excess density
2012-01-17 15:56:57 +05:30
2012-03-14 20:54:19 +05:30
do c = 1_pInt , 2_pInt
2012-02-23 22:13:17 +05:30
do dir = 1_pInt , 3_pInt
2012-03-14 20:54:19 +05:30
neighbor ( 1 ) = 2_pInt * dir - 1_pInt
neighbor ( 2 ) = 2_pInt * dir
2013-05-23 18:06:48 +05:30
connections ( dir , 1 : 3 ) = connection_latticeConf ( 1 : 3 , neighbor ( 1 ) ) &
- connection_latticeConf ( 1 : 3 , neighbor ( 2 ) )
rhoExcessDifferences ( dir ) = neighboring_rhoExcess ( c , s , neighbor ( 1 ) ) &
- neighboring_rhoExcess ( c , s , neighbor ( 2 ) )
2012-01-17 15:56:57 +05:30
enddo
2012-03-15 20:28:12 +05:30
call math_invert33 ( connections , invConnections , temp , inversionError )
if ( inversionError ) then
call IO_error ( - 1_pInt , ext_msg = 'back stress calculation: inversion error' )
endif
2013-05-23 17:55:56 +05:30
rhoExcessGradient ( c ) = math_mul3x3 ( m ( 1 : 3 , s , c ) , &
math_mul33x3 ( invConnections , rhoExcessDifferences ) )
2012-03-14 20:54:19 +05:30
enddo
2012-01-17 15:56:57 +05:30
2012-03-14 20:54:19 +05:30
!* plus gradient from deads
do t = 1_pInt , 4_pInt
c = ( t - 1_pInt ) / 2_pInt + 1_pInt
rhoExcessGradient ( c ) = rhoExcessGradient ( c ) + rhoSgl ( s , t + 4_pInt ) / FVsize
2012-01-17 15:56:57 +05:30
enddo
2012-03-14 20:54:19 +05:30
!* normalized with the total density
2012-01-17 15:56:57 +05:30
2012-03-14 20:54:19 +05:30
rhoExcessGradient_over_rho = 0.0_pReal
2013-03-27 18:34:01 +05:30
forall ( c = 1_pInt : 2_pInt ) &
rhoTotal ( c ) = ( sum ( abs ( rhoSgl ( s , [ 2 * c - 1 , 2 * c , 2 * c + 3 , 2 * c + 4 ] ) ) ) + rhoDip ( s , c ) + sum ( neighboring_rhoTotal ( c , s , : ) ) ) &
2013-05-08 14:53:47 +05:30
/ real ( 1_pInt + nRealNeighbors , pReal )
2012-03-14 20:54:19 +05:30
forall ( c = 1_pInt : 2_pInt , rhoTotal ( c ) > 0.0_pReal ) &
rhoExcessGradient_over_rho ( c ) = rhoExcessGradient ( c ) / rhoTotal ( c )
!* gives the local stress correction when multiplied with a factor
2013-05-24 01:26:36 +05:30
tauBack ( s ) = - mu ( instance ) * burgers ( s , instance ) / ( 2.0_pReal * pi ) &
* ( rhoExcessGradient_over_rho ( 1 ) / ( 1.0_pReal - nu ( instance ) ) + rhoExcessGradient_over_rho ( 2 ) )
2011-03-29 13:04:33 +05:30
2012-01-17 15:56:57 +05:30
enddo
endif
2011-03-29 13:04:33 +05:30
2011-05-26 15:05:42 +05:30
2012-01-17 15:56:57 +05:30
!*** set dependent states
2009-08-11 22:01:57 +05:30
2013-05-24 02:58:45 +05:30
state ( gr , ip , el ) % p ( iRhoF ( 1 : ns , instance ) ) = rhoForest
state ( gr , ip , el ) % p ( iTau ( 1 : ns , instance ) ) = tauThreshold
state ( gr , ip , el ) % p ( iTauB ( 1 : ns , instance ) ) = tauBack
2009-08-11 22:01:57 +05:30
2011-03-29 12:57:19 +05:30
#ifndef _OPENMP
2012-10-22 13:29:35 +05:30
if ( iand ( debug_level ( debug_constitutive ) , debug_levelExtensive ) / = 0_pInt &
2013-05-23 17:55:56 +05:30
. and . ( ( debug_e == el . and . debug_i == ip . and . debug_g == gr ) &
2012-07-05 15:24:50 +05:30
. or . . not . iand ( debug_level ( debug_constitutive ) , debug_levelSelective ) / = 0_pInt ) ) then
2011-03-29 12:57:19 +05:30
write ( 6 , * )
2013-05-23 17:55:56 +05:30
write ( 6 , '(a,i8,1x,i2,1x,i1)' ) '<< CONST >> nonlocal_microstructure at el ip g' , el , ip , gr
2011-03-29 12:57:19 +05:30
write ( 6 , * )
2012-02-02 01:50:05 +05:30
write ( 6 , '(a,/,12x,12(e10.3,1x))' ) '<< CONST >> rhoForest' , rhoForest
write ( 6 , '(a,/,12x,12(f10.5,1x))' ) '<< CONST >> tauThreshold / MPa' , tauThreshold / 1e6
write ( 6 , '(a,/,12x,12(f10.5,1x))' ) '<< CONST >> tauBack / MPa' , tauBack / 1e6
2012-10-19 17:10:17 +05:30
write ( 6 , * )
2011-03-29 12:57:19 +05:30
endif
#endif
2010-02-17 18:51:36 +05:30
endsubroutine
!*********************************************************************
!* calculates kinetics *
!*********************************************************************
2012-01-25 22:34:37 +05:30
subroutine constitutive_nonlocal_kinetics ( v , tau , c , Temperature , state , g , ip , el , dv_dtau )
2010-02-17 18:51:36 +05:30
2012-07-05 15:24:50 +05:30
use debug , only : debug_level , &
2012-03-09 01:55:28 +05:30
debug_constitutive , &
debug_levelBasic , &
2012-10-22 13:29:35 +05:30
debug_levelExtensive , &
2012-03-09 01:55:28 +05:30
debug_levelSelective , &
2010-11-03 22:52:48 +05:30
debug_g , &
debug_i , &
debug_e
2012-02-23 22:50:57 +05:30
use material , only : material_phase , &
2012-03-12 19:39:37 +05:30
phase_plasticityInstance
2010-02-17 18:51:36 +05:30
implicit none
!*** input variables
integer ( pInt ) , intent ( in ) :: g , & ! current grain number
ip , & ! current integration point
2012-01-25 22:34:37 +05:30
el , & ! current element number
c ! dislocation character (1:edge, 2:screw)
2010-02-17 18:51:36 +05:30
real ( pReal ) , intent ( in ) :: Temperature ! temperature
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) ) , &
2012-01-25 22:34:37 +05:30
intent ( in ) :: tau ! resolved external shear stress (for bcc this already contains non Schmid effects)
type ( p_vec ) , intent ( in ) :: state ! microstructural state
2010-02-17 18:51:36 +05:30
2011-11-04 18:42:17 +05:30
!*** input/output variables
2010-02-17 18:51:36 +05:30
!*** output variables
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) ) , &
2011-11-04 18:42:17 +05:30
intent ( out ) :: v ! velocity
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) ) , &
2010-10-01 17:48:49 +05:30
intent ( out ) , optional :: dv_dtau ! velocity derivative with respect to resolved shear stress
2010-02-17 18:51:36 +05:30
!*** local variables
2013-02-11 16:13:45 +05:30
integer ( pInt ) :: instance , & ! current instance of this plasticity
2010-02-17 18:51:36 +05:30
ns , & ! short notation for the total number of active slip systems
2013-02-11 16:13:45 +05:30
s ! index of my current slip system
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) ) :: &
2012-03-14 20:48:36 +05:30
tauThreshold , & ! threshold shear stress
tauEff ! effective shear stress
2012-02-03 18:20:54 +05:30
real ( pReal ) tauRel_P , &
tauRel_S , &
2012-01-25 22:34:37 +05:30
tPeierls , & ! waiting time in front of a peierls barriers
2012-02-03 18:20:54 +05:30
tSolidSolution , & ! waiting time in front of a solid solution obstacle
vViscous , & ! viscous glide velocity
2012-01-25 22:34:37 +05:30
dtPeierls_dtau , & ! derivative with respect to resolved shear stress
2012-02-03 18:20:54 +05:30
dtSolidSolution_dtau , & ! derivative with respect to resolved shear stress
meanfreepath_S , & ! mean free travel distance for dislocations between two solid solution obstacles
meanfreepath_P , & ! mean free travel distance for dislocations between two Peierls barriers
jumpWidth_P , & ! depth of activated area
jumpWidth_S , & ! depth of activated area
activationLength_P , & ! length of activated dislocation line
activationLength_S , & ! length of activated dislocation line
activationVolume_P , & ! volume that needs to be activated to overcome barrier
activationVolume_S , & ! volume that needs to be activated to overcome barrier
activationEnergy_P , & ! energy that is needed to overcome barrier
activationEnergy_S , & ! energy that is needed to overcome barrier
criticalStress_P , & ! maximum obstacle strength
criticalStress_S , & ! maximum obstacle strength
mobility ! dislocation mobility
2012-03-12 19:39:37 +05:30
instance = phase_plasticityInstance ( material_phase ( g , ip , el ) )
2013-05-24 01:26:36 +05:30
ns = totalNslip ( instance )
2010-02-17 18:51:36 +05:30
2013-04-04 19:07:14 +05:30
tauThreshold = state % p ( 12_pInt * ns + 1 : 13_pInt * ns )
2012-03-14 20:48:36 +05:30
tauEff = abs ( tau ) - tauThreshold
2012-01-25 22:34:37 +05:30
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
v = 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
2012-02-23 22:13:17 +05:30
do s = 1_pInt , ns
2012-03-14 20:48:36 +05:30
if ( tauEff ( s ) > 0.0_pReal ) then
2010-10-26 19:12:18 +05:30
2012-01-25 22:34:37 +05:30
!* Peierls contribution
!* The derivative only gives absolute values; the correct sign is taken care of in the formula for the derivative of the velocity
2012-02-03 18:20:54 +05:30
2013-05-24 01:26:36 +05:30
meanfreepath_P = burgers ( s , instance )
jumpWidth_P = burgers ( s , instance )
activationLength_P = doublekinkwidth ( instance ) * burgers ( s , instance )
activationVolume_P = activationLength_P * jumpWidth_P * burgers ( s , instance )
criticalStress_P = peierlsStress ( s , c , instance )
2012-02-03 18:20:54 +05:30
activationEnergy_P = criticalStress_P * activationVolume_P
2012-08-30 13:03:13 +05:30
tauRel_P = min ( 1.0_pReal , tauEff ( s ) / criticalStress_P ) ! ensure that the activation probability cannot become greater than one
2013-05-24 01:26:36 +05:30
tPeierls = 1.0_pReal / fattack ( instance ) &
* exp ( activationEnergy_P / ( KB * Temperature ) &
* ( 1.0_pReal - tauRel_P ** pParam ( instance ) ) ** qParam ( instance ) )
2011-01-26 15:47:42 +05:30
if ( present ( dv_dtau ) ) then
2012-08-30 13:03:13 +05:30
if ( tauEff ( s ) < criticalStress_P ) then
2013-05-24 01:26:36 +05:30
dtPeierls_dtau = tPeierls * pParam ( instance ) * qParam ( instance ) * activationVolume_P / ( KB * Temperature ) &
* ( 1.0_pReal - tauRel_P ** pParam ( instance ) ) ** ( qParam ( instance ) - 1.0_pReal ) &
* tauRel_P ** ( pParam ( instance ) - 1.0_pReal )
2012-08-30 13:03:13 +05:30
else
dtPeierls_dtau = 0.0_pReal
endif
2011-01-26 15:47:42 +05:30
endif
2012-01-25 22:34:37 +05:30
!* Contribution from solid solution strengthening
!* The derivative only gives absolute values; the correct sign is taken care of in the formula for the derivative of the velocity
2013-05-24 01:26:36 +05:30
meanfreepath_S = burgers ( s , instance ) / sqrt ( solidSolutionConcentration ( instance ) )
jumpWidth_S = solidSolutionSize ( instance ) * burgers ( s , instance )
activationLength_S = burgers ( s , instance ) / sqrt ( solidSolutionConcentration ( instance ) )
activationVolume_S = activationLength_S * jumpWidth_S * burgers ( s , instance )
activationEnergy_S = solidSolutionEnergy ( instance )
2012-02-03 18:20:54 +05:30
criticalStress_S = activationEnergy_S / activationVolume_S
2012-08-30 13:03:13 +05:30
tauRel_S = min ( 1.0_pReal , tauEff ( s ) / criticalStress_S ) ! ensure that the activation probability cannot become greater than one
2013-05-24 01:26:36 +05:30
tSolidSolution = 1.0_pReal / fattack ( instance ) &
* exp ( activationEnergy_S / ( KB * Temperature ) &
* ( 1.0_pReal - tauRel_S ** pParam ( instance ) ) ** qParam ( instance ) )
2012-01-25 22:34:37 +05:30
if ( present ( dv_dtau ) ) then
2012-08-30 13:03:13 +05:30
if ( tauEff ( s ) < criticalStress_S ) then
2013-05-24 01:26:36 +05:30
dtSolidSolution_dtau = tSolidSolution * pParam ( instance ) * qParam ( instance ) &
* activationVolume_S / ( KB * Temperature ) &
* ( 1.0_pReal - tauRel_S ** pParam ( instance ) ) ** ( qParam ( instance ) - 1.0_pReal ) &
* tauRel_S ** ( pParam ( instance ) - 1.0_pReal )
2012-08-30 13:03:13 +05:30
else
dtSolidSolution_dtau = 0.0_pReal
endif
2012-01-25 22:34:37 +05:30
endif
2012-02-03 18:20:54 +05:30
!* viscous glide velocity
2012-01-25 22:34:37 +05:30
2013-05-24 01:26:36 +05:30
mobility = burgers ( s , instance ) / viscosity ( instance )
2012-03-14 20:48:36 +05:30
vViscous = mobility * tauEff ( s )
2012-01-25 22:34:37 +05:30
2012-02-03 18:20:54 +05:30
!* Mean velocity results from waiting time at peierls barriers and solid solution obstacles with respective meanfreepath of
2013-03-21 18:22:29 +05:30
!* free flight at glide velocity in between.
!* adopt sign from resolved stress
2012-08-30 13:03:13 +05:30
2013-05-24 01:26:36 +05:30
v ( s ) = sign ( 1.0_pReal , tau ( s ) ) &
/ ( tPeierls / meanfreepath_P + tSolidSolution / meanfreepath_S + 1.0_pReal / vViscous )
2012-08-30 13:03:13 +05:30
if ( present ( dv_dtau ) ) then
2013-05-24 01:26:36 +05:30
dv_dtau ( s ) = v ( s ) * v ( s ) &
* ( dtPeierls_dtau / meanfreepath_P &
+ dtSolidSolution_dtau / meanfreepath_S &
+ 1.0_pReal / ( mobility * tauEff ( s ) * tauEff ( s ) ) )
2012-08-30 13:03:13 +05:30
endif
2010-10-01 17:48:49 +05:30
endif
enddo
endif
2012-01-25 22:34:37 +05:30
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
2011-03-29 12:57:19 +05:30
#ifndef _OPENMP
2012-10-22 13:29:35 +05:30
if ( iand ( debug_level ( debug_constitutive ) , debug_levelExtensive ) / = 0_pInt &
2012-03-09 01:55:28 +05:30
. and . ( ( debug_e == el . and . debug_i == ip . and . debug_g == g ) &
2012-07-05 15:24:50 +05:30
. or . . not . iand ( debug_level ( debug_constitutive ) , debug_levelSelective ) / = 0_pInt ) ) then
2011-03-21 16:01:17 +05:30
write ( 6 , * )
2012-02-02 01:50:05 +05:30
write ( 6 , '(a,i8,1x,i2,1x,i1)' ) '<< CONST >> nonlocal_kinetics at el ip g' , el , ip , g
2011-03-21 16:01:17 +05:30
write ( 6 , * )
2012-02-02 01:50:05 +05:30
write ( 6 , '(a,/,12x,12(f12.5,1x))' ) '<< CONST >> tau / MPa' , tau / 1e6_pReal
2012-03-14 20:48:36 +05:30
write ( 6 , '(a,/,12x,12(f12.5,1x))' ) '<< CONST >> tauEff / MPa' , tauEff / 1e6_pReal
2012-02-03 18:20:54 +05:30
write ( 6 , '(a,/,12x,12(f12.5,1x))' ) '<< CONST >> v / 1e-3m/s' , v * 1e3
2012-08-21 20:10:01 +05:30
if ( present ( dv_dtau ) ) then
write ( 6 , '(a,/,12x,12(e12.5,1x))' ) '<< CONST >> dv_dtau' , dv_dtau
endif
2011-03-29 12:57:19 +05:30
endif
#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 math , only : math_Plain3333to99 , &
2013-01-22 05:20:28 +05:30
math_mul6x6 , &
math_Mandel6to33
2012-07-05 15:24:50 +05:30
use debug , only : debug_level , &
2012-03-09 01:55:28 +05:30
debug_constitutive , &
debug_levelBasic , &
2012-10-22 13:29:35 +05:30
debug_levelExtensive , &
2012-03-09 01:55:28 +05:30
debug_levelSelective , &
2010-11-03 22:52:48 +05:30
debug_g , &
debug_i , &
debug_e
2009-08-11 22:01:57 +05:30
use material , only : homogenization_maxNgrains , &
material_phase , &
2012-03-12 19:39:37 +05:30
phase_plasticityInstance
2009-08-11 22:01:57 +05:30
use lattice , only : lattice_Sslip , &
2013-01-22 05:20:28 +05:30
lattice_Sslip_v , &
NnonSchmid
2012-09-04 22:26:37 +05:30
use mesh , only : mesh_ipVolume
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
real ( pReal ) , intent ( in ) :: Temperature ! temperature
real ( pReal ) , dimension ( 6 ) , intent ( in ) :: Tstar_v ! 2nd Piola-Kirchhoff stress in Mandel notation
2011-11-04 18:42:17 +05:30
!*** input/output variables
type ( p_vec ) , intent ( inout ) :: state ! microstructural state
2009-08-11 22:01:57 +05:30
!*** 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
2012-03-12 19:39:37 +05:30
integer ( pInt ) myInstance , & ! current instance of this plasticity
2009-08-11 22:01:57 +05:30
myStructure , & ! current lattice structure
ns , & ! short notation for the total number of active slip systems
2012-01-25 22:34:37 +05:30
c , &
2009-08-11 22:01:57 +05:30
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)
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( 3 , 3 , 2 , totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) ) :: &
2013-05-11 03:59:12 +05:30
nonSchmidTensor
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) , 8 ) :: &
2013-04-03 21:59:48 +05:30
rhoSgl ! single dislocation densities (including blocked)
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) , 4 ) :: &
2011-11-04 18:42:17 +05:30
v , & ! velocity
2013-01-22 05:20:28 +05:30
tau , & ! resolved shear stress including non Schmid and backstress terms
2013-04-03 21:59:48 +05:30
dgdot_dtau , & ! derivative of the shear rate with respect to the shear stress
2011-09-07 17:00:28 +05:30
dv_dtau ! velocity derivative with respect to the shear stress
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) ) :: &
2010-02-17 18:51:36 +05:30
gdotTotal , & ! shear rate
2012-10-29 18:19:28 +05:30
tauBack , & ! back stress from dislocation gradients on same slip system
deadZoneSize
2009-08-11 22:01:57 +05:30
!*** initialize local variables
Lp = 0.0_pReal
dLp_dTstar3333 = 0.0_pReal
2013-05-11 03:59:12 +05:30
nonSchmidTensor = 0.0_pReal
2009-08-11 22:01:57 +05:30
2012-03-12 19:39:37 +05:30
myInstance = phase_plasticityInstance ( material_phase ( g , ip , el ) )
2009-08-11 22:01:57 +05:30
myStructure = constitutive_nonlocal_structure ( myInstance )
2013-05-24 01:26:36 +05:30
ns = totalNslip ( myInstance )
2009-08-11 22:01:57 +05:30
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
2009-08-11 22:01:57 +05:30
!*** shortcut to state variables
2012-02-23 22:13:17 +05:30
forall ( s = 1_pInt : ns , t = 1_pInt : 4_pInt ) &
rhoSgl ( s , t ) = max ( state % p ( ( t - 1_pInt ) * ns + s ) , 0.0_pReal )
2012-08-23 11:18:21 +05:30
forall ( s = 1_pInt : ns , t = 5_pInt : 8_pInt ) &
rhoSgl ( s , t ) = state % p ( ( t - 1_pInt ) * ns + s )
2013-04-04 19:07:14 +05:30
tauBack = state % p ( 13_pInt * ns + 1 : 14_pInt * ns )
2013-05-24 01:26:36 +05:30
where ( abs ( rhoSgl ) * mesh_ipVolume ( ip , el ) ** 0.667_pReal < significantN ( myInstance ) &
. or . abs ( rhoSgl ) < significantRho ( myInstance ) ) &
2012-10-02 18:27:24 +05:30
rhoSgl = 0.0_pReal
2012-01-25 22:34:37 +05:30
2012-08-23 11:18:21 +05:30
2012-01-25 22:34:37 +05:30
!*** get effective resolved shear stress
2013-05-11 03:59:12 +05:30
!*** add non schmid contributions to ONLY screw components if present (i.e. if NnonSchmid(myStructure) > 0)
2012-01-25 22:34:37 +05:30
2012-02-23 22:13:17 +05:30
do s = 1_pInt , ns
2013-05-24 01:26:36 +05:30
sLattice = slipSystemLattice ( s , myInstance )
2013-05-11 03:59:12 +05:30
tau ( s , 1 : 4 ) = math_mul6x6 ( Tstar_v , lattice_Sslip_v ( 1 : 6 , 1 , sLattice , myStructure ) ) + tauBack ( s )
nonSchmidTensor ( 1 : 3 , 1 : 3 , 1 , s ) = lattice_Sslip ( 1 : 3 , 1 : 3 , sLattice , myStructure )
nonSchmidTensor ( 1 : 3 , 1 : 3 , 2 , s ) = nonSchmidTensor ( 1 : 3 , 1 : 3 , 1 , s )
2013-01-22 05:20:28 +05:30
do k = 1_pInt , NnonSchmid ( myStructure )
2013-05-24 01:26:36 +05:30
tau ( s , 3 ) = tau ( s , 3 ) + nonSchmidCoeff ( k , myInstance ) &
2013-05-11 03:59:12 +05:30
* math_mul6x6 ( Tstar_v , lattice_Sslip_v ( 1 : 6 , 2 * k , sLattice , myStructure ) )
2013-05-24 01:26:36 +05:30
tau ( s , 4 ) = tau ( s , 4 ) + nonSchmidCoeff ( k , myInstance ) &
2013-05-11 03:59:12 +05:30
* math_mul6x6 ( Tstar_v , lattice_Sslip_v ( 1 : 6 , 2 * k + 1 , sLattice , myStructure ) )
nonSchmidTensor ( 1 : 3 , 1 : 3 , 1 , s ) = nonSchmidTensor ( 1 : 3 , 1 : 3 , 1 , s ) &
2013-05-24 01:26:36 +05:30
+ nonSchmidCoeff ( k , myInstance ) &
2013-05-11 03:59:12 +05:30
* math_Mandel6to33 ( lattice_Sslip_v ( 1 : 6 , 2 * k , sLattice , myStructure ) )
nonSchmidTensor ( 1 : 3 , 1 : 3 , 2 , s ) = nonSchmidTensor ( 1 : 3 , 1 : 3 , 2 , s ) &
2013-05-24 01:26:36 +05:30
+ nonSchmidCoeff ( k , myInstance ) &
2013-05-11 03:59:12 +05:30
* math_Mandel6to33 ( lattice_Sslip_v ( 1 : 6 , 2 * k + 1 , sLattice , myStructure ) )
2013-01-22 05:20:28 +05:30
enddo
2012-01-25 22:34:37 +05:30
enddo
!*** get dislocation velocity and its tangent and store the velocity in the state array
2013-05-11 03:59:12 +05:30
if ( myStructure == 1_pInt . and . NnonSchmid ( myStructure ) == 0_pInt ) then ! for fcc all velcities are equal
call constitutive_nonlocal_kinetics ( v ( 1 : ns , 1 ) , tau ( 1 : ns , 1 ) , 1_pInt , Temperature , state , &
g , ip , el , dv_dtau ( 1 : ns , 1 ) )
2012-02-13 19:48:07 +05:30
do t = 1_pInt , 4_pInt
2012-01-26 13:13:36 +05:30
v ( 1 : ns , t ) = v ( 1 : ns , 1 )
dv_dtau ( 1 : ns , t ) = dv_dtau ( 1 : ns , 1 )
2013-04-04 19:07:14 +05:30
state % p ( ( 13_pInt + t ) * ns + 1 : ( 14_pInt + t ) * ns ) = v ( 1 : ns , 1 )
2012-01-26 13:13:36 +05:30
enddo
2013-05-11 03:59:12 +05:30
else ! for all other lattice structures the velocities may vary with character and sign
2012-02-13 19:48:07 +05:30
do t = 1_pInt , 4_pInt
c = ( t - 1_pInt ) / 2_pInt + 1_pInt
2013-05-11 03:59:12 +05:30
call constitutive_nonlocal_kinetics ( v ( 1 : ns , t ) , tau ( 1 : ns , t ) , c , Temperature , state , &
g , ip , el , dv_dtau ( 1 : ns , t ) )
2013-04-04 19:07:14 +05:30
state % p ( ( 13 + t ) * ns + 1 : ( 14 + t ) * ns ) = v ( 1 : ns , t )
2012-01-26 13:13:36 +05:30
enddo
endif
2012-01-25 22:34:37 +05:30
!*** Bauschinger effect
2012-08-23 11:18:21 +05:30
forall ( s = 1_pInt : ns , t = 5_pInt : 8_pInt , rhoSgl ( s , t ) * v ( s , t - 4_pInt ) < 0.0_pReal ) &
rhoSgl ( s , t - 4_pInt ) = rhoSgl ( s , t - 4_pInt ) + abs ( rhoSgl ( s , t ) )
2009-08-28 19:20:47 +05:30
!*** Calculation of gdot and its tangent
2012-10-29 18:19:28 +05:30
deadZoneSize = 0.0_pReal
2013-05-24 01:26:36 +05:30
if ( deadZoneScaling ( myInstance ) ) then
2012-10-29 18:19:28 +05:30
forall ( s = 1_pInt : ns , sum ( abs ( rhoSgl ( s , 1 : 8 ) ) ) > 0.0_pReal ) &
deadZoneSize ( s ) = maxval ( abs ( rhoSgl ( s , 5 : 8 ) ) / ( rhoSgl ( s , 1 : 4 ) + abs ( rhoSgl ( s , 5 : 8 ) ) ) )
endif
2013-05-24 01:26:36 +05:30
gdotTotal = sum ( rhoSgl ( 1 : ns , 1 : 4 ) * v , 2 ) * burgers ( 1 : ns , myInstance ) * ( 1.0_pReal - deadZoneSize )
2013-01-22 05:20:28 +05:30
do t = 1_pInt , 4_pInt
2013-05-24 01:26:36 +05:30
dgdot_dtau ( : , t ) = rhoSgl ( 1 : ns , t ) * dv_dtau ( 1 : ns , t ) * burgers ( 1 : ns , myInstance ) * ( 1.0_pReal - deadZoneSize )
2013-01-22 05:20:28 +05:30
enddo
2013-05-24 01:26:36 +05:30
shearrate ( 1 : ns , g , ip , el ) = gdotTotal
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
2013-05-11 03:59:12 +05:30
2009-08-28 19:20:47 +05:30
!*** Calculation of Lp and its tangent
2009-08-24 13:46:01 +05:30
2012-02-23 22:13:17 +05:30
do s = 1_pInt , ns
2013-05-24 01:26:36 +05:30
sLattice = slipSystemLattice ( s , myInstance )
2011-02-09 18:42:46 +05:30
Lp = Lp + gdotTotal ( s ) * lattice_Sslip ( 1 : 3 , 1 : 3 , sLattice , myStructure )
2012-02-23 22:13:17 +05:30
forall ( i = 1_pInt : 3_pInt , j = 1_pInt : 3_pInt , k = 1_pInt : 3_pInt , l = 1_pInt : 3_pInt ) &
2013-05-11 03:59:12 +05:30
dLp_dTstar3333 ( i , j , k , l ) = dLp_dTstar3333 ( i , j , k , l ) &
+ dgdot_dtau ( s , 1 ) * lattice_Sslip ( i , j , sLattice , myStructure ) * lattice_Sslip ( k , l , sLattice , myStructure ) &
+ dgdot_dtau ( s , 2 ) * lattice_Sslip ( i , j , sLattice , myStructure ) * lattice_Sslip ( k , l , sLattice , myStructure ) &
+ dgdot_dtau ( s , 3 ) * lattice_Sslip ( i , j , sLattice , myStructure ) * nonSchmidTensor ( k , l , 1 , s ) &
+ dgdot_dtau ( s , 4 ) * lattice_Sslip ( i , j , sLattice , myStructure ) * nonSchmidTensor ( k , l , 2 , s )
2009-08-11 22:01:57 +05:30
enddo
2009-08-12 16:52:02 +05:30
dLp_dTstar99 = math_Plain3333to99 ( dLp_dTstar3333 )
2012-01-25 22:34:37 +05:30
2011-03-29 12:57:19 +05:30
#ifndef _OPENMP
2012-10-22 13:29:35 +05:30
if ( iand ( debug_level ( debug_constitutive ) , debug_levelExtensive ) / = 0_pInt &
2012-03-09 01:55:28 +05:30
. and . ( ( debug_e == el . and . debug_i == ip . and . debug_g == g ) &
2012-07-05 15:24:50 +05:30
. or . . not . iand ( debug_level ( debug_constitutive ) , debug_levelSelective ) / = 0_pInt ) ) then
2011-03-21 16:01:17 +05:30
write ( 6 , * )
2012-02-02 01:50:05 +05:30
write ( 6 , '(a,i8,1x,i2,1x,i1)' ) '<< CONST >> nonlocal_LpandItsTangent at el ip g ' , el , ip , g
2011-03-21 16:01:17 +05:30
write ( 6 , * )
2012-02-02 01:50:05 +05:30
write ( 6 , '(a,/,12x,12(f12.5,1x))' ) '<< CONST >> gdot total / 1e-3' , gdotTotal * 1e3_pReal
2013-05-11 03:59:12 +05:30
write ( 6 , '(a,/,3(12x,3(f12.7,1x),/))' ) '<< CONST >> Lp' , transpose ( Lp )
2011-03-29 12:57:19 +05:30
endif
#endif
2009-08-11 22:01:57 +05:30
endsubroutine
2012-05-16 20:13:26 +05:30
!*********************************************************************
!* incremental change of microstructure *
!*********************************************************************
2012-05-18 20:05:52 +05:30
subroutine constitutive_nonlocal_deltaState ( deltaState , state , Tstar_v , Temperature , g , ip , el )
2012-05-16 20:13:26 +05:30
2012-07-05 15:24:50 +05:30
use debug , only : debug_level , &
2012-05-18 19:05:44 +05:30
debug_constitutive , &
debug_levelBasic , &
2012-10-22 13:29:35 +05:30
debug_levelExtensive , &
2012-05-18 19:05:44 +05:30
debug_levelSelective , &
debug_g , &
debug_i , &
debug_e
2012-05-18 20:05:52 +05:30
use math , only : pi , &
math_mul6x6
use lattice , only : lattice_Sslip_v
2012-05-16 20:13:26 +05:30
use mesh , only : mesh_NcpElems , &
2012-09-04 22:26:37 +05:30
mesh_maxNips , &
mesh_ipVolume
2012-05-16 20:13:26 +05:30
use material , only : homogenization_maxNgrains , &
material_phase , &
phase_plasticityInstance
implicit none
!*** input variables
integer ( pInt ) , intent ( in ) :: g , & ! current grain number
ip , & ! current integration point
el ! current element number
real ( pReal ) , intent ( in ) :: Temperature ! temperature
real ( pReal ) , dimension ( 6 ) , intent ( in ) :: Tstar_v ! current 2nd Piola-Kirchhoff stress in Mandel notation
2012-05-18 20:05:52 +05:30
!*** input/output variables
type ( p_vec ) , dimension ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( inout ) :: &
2012-05-16 20:13:26 +05:30
state ! current microstructural state
!*** output variables
2012-05-18 20:05:52 +05:30
type ( p_vec ) , intent ( out ) :: deltaState ! change of state variables / microstructure
2012-05-16 20:13:26 +05:30
!*** local variables
2012-05-18 19:05:44 +05:30
integer ( pInt ) myInstance , & ! current instance of this plasticity
myStructure , & ! current lattice structure
ns , & ! short notation for the total number of active slip systems
c , & ! character of dislocation
t , & ! type of dislocation
2012-05-18 20:05:52 +05:30
s , & ! index of my current slip system
sLattice ! index of my current slip system according to lattice order
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) , 10 ) :: &
2012-05-18 19:05:44 +05:30
deltaRho , & ! density increment
2012-05-18 20:05:52 +05:30
deltaRhoRemobilization , & ! density increment by remobilization
2012-11-28 17:39:48 +05:30
deltaRhoDipole2SingleStress ! density increment by dipole dissociation (by stress change)
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) , 8 ) :: &
2012-05-18 19:05:44 +05:30
rhoSgl ! current single dislocation densities (positive/negative screw and edge without dipoles)
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) , 4 ) :: &
2012-05-18 19:05:44 +05:30
v ! dislocation glide velocity
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) ) :: &
2012-05-18 20:05:52 +05:30
tau , & ! current resolved shear stress
2012-11-28 17:39:48 +05:30
tauBack ! current back stress from pileups on same slip system
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) , 2 ) :: &
2012-05-18 20:05:52 +05:30
rhoDip , & ! current 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
dUpperOld , & ! old maximum stable dipole distance for edges and screws
deltaDUpper ! change in maximum stable dipole distance for edges and screws
2012-05-18 19:05:44 +05:30
#ifndef _OPENMP
2012-07-05 15:24:50 +05:30
if ( iand ( debug_level ( debug_constitutive ) , debug_levelBasic ) / = 0_pInt &
2012-05-18 19:05:44 +05:30
. and . ( ( debug_e == el . and . debug_i == ip . and . debug_g == g ) &
2012-07-05 15:24:50 +05:30
. or . . not . iand ( debug_level ( debug_constitutive ) , debug_levelSelective ) / = 0_pInt ) ) then
2012-05-18 19:05:44 +05:30
write ( 6 , * )
2012-05-30 13:11:22 +05:30
write ( 6 , '(a,i8,1x,i2,1x,i1)' ) '<< CONST >> nonlocal_deltaState at el ip g ' , el , ip , g
2012-05-18 19:05:44 +05:30
write ( 6 , * )
endif
#endif
2012-05-16 20:13:26 +05:30
2012-05-18 19:05:44 +05:30
myInstance = phase_plasticityInstance ( material_phase ( g , ip , el ) )
myStructure = constitutive_nonlocal_structure ( myInstance )
2013-05-24 01:26:36 +05:30
ns = totalNslip ( myInstance )
2012-05-18 19:05:44 +05:30
!*** shortcut to state variables
forall ( s = 1_pInt : ns , t = 1_pInt : 4_pInt ) &
rhoSgl ( s , t ) = max ( state ( g , ip , el ) % p ( ( t - 1_pInt ) * ns + s ) , 0.0_pReal )
forall ( s = 1_pInt : ns , t = 5_pInt : 8_pInt ) &
rhoSgl ( s , t ) = state ( g , ip , el ) % p ( ( t - 1_pInt ) * ns + s )
forall ( s = 1_pInt : ns , c = 1_pInt : 2_pInt ) &
rhoDip ( s , c ) = max ( state ( g , ip , el ) % p ( ( 7_pInt + c ) * ns + s ) , 0.0_pReal )
2013-04-04 19:07:14 +05:30
tauBack = state ( g , ip , el ) % p ( 13_pInt * ns + 1 : 14_pInt * ns )
2012-05-18 19:05:44 +05:30
forall ( t = 1_pInt : 4_pInt ) &
2013-04-04 19:07:14 +05:30
v ( 1_pInt : ns , t ) = state ( g , ip , el ) % p ( ( 13_pInt + t ) * ns + 1_pInt : ( 14_pInt + t ) * ns )
2012-05-18 20:05:52 +05:30
forall ( c = 1_pInt : 2_pInt ) &
2013-04-04 19:07:14 +05:30
dUpperOld ( 1_pInt : ns , c ) = state ( g , ip , el ) % p ( ( 17_pInt + c ) * ns + 1_pInt : ( 18_pInt + c ) * ns )
2013-05-24 01:26:36 +05:30
where ( abs ( rhoSgl ) * mesh_ipVolume ( ip , el ) ** 0.667_pReal < significantN ( myInstance ) &
. or . abs ( rhoSgl ) < significantRho ( myInstance ) ) &
2012-10-02 18:27:24 +05:30
rhoSgl = 0.0_pReal
2013-05-24 01:26:36 +05:30
where ( abs ( rhoDip ) * mesh_ipVolume ( ip , el ) ** 0.667_pReal < significantN ( myInstance ) &
. or . abs ( rhoDip ) < significantRho ( myInstance ) ) &
2012-10-02 18:27:24 +05:30
rhoDip = 0.0_pReal
2012-05-18 19:05:44 +05:30
!****************************************************************************
!*** dislocation remobilization (bauschinger effect)
deltaRhoRemobilization = 0.0_pReal
do t = 1_pInt , 4_pInt
do s = 1_pInt , ns
if ( rhoSgl ( s , t + 4_pInt ) * v ( s , t ) < 0.0_pReal ) then
deltaRhoRemobilization ( s , t ) = abs ( rhoSgl ( s , t + 4_pInt ) )
rhoSgl ( s , t ) = rhoSgl ( s , t ) + abs ( rhoSgl ( s , t + 4_pInt ) )
deltaRhoRemobilization ( s , t + 4_pInt ) = - rhoSgl ( s , t + 4_pInt )
rhoSgl ( s , t + 4_pInt ) = 0.0_pReal
endif
enddo
enddo
!****************************************************************************
2012-05-18 20:05:52 +05:30
!*** calculate dipole formation and dissociation by stress change
!*** calculate limits for stable dipole height
do s = 1_pInt , ns
2013-05-24 01:26:36 +05:30
sLattice = slipSystemLattice ( s , myInstance )
2013-01-22 04:41:16 +05:30
tau ( s ) = math_mul6x6 ( Tstar_v , lattice_Sslip_v ( 1 : 6 , 1 , sLattice , myStructure ) ) + tauBack ( s )
2012-05-18 20:05:52 +05:30
if ( abs ( tau ( s ) ) < 1.0e-15_pReal ) tau ( s ) = 1.0e-15_pReal
enddo
2013-05-24 01:26:36 +05:30
dLower = minDipoleHeight ( 1 : ns , 1 : 2 , myInstance )
dUpper ( 1 : ns , 1 ) = mu ( myInstance ) * burgers ( 1 : ns , myInstance ) &
/ ( 8.0_pReal * pi * ( 1.0_pReal - nu ( myInstance ) ) * abs ( tau ) )
dUpper ( 1 : ns , 2 ) = mu ( myInstance ) * burgers ( 1 : ns , myInstance ) / ( 4.0_pReal * pi * abs ( tau ) )
2012-07-24 20:20:11 +05:30
forall ( c = 1_pInt : 2_pInt ) &
2012-10-29 18:32:01 +05:30
dUpper ( 1 : ns , c ) = min ( 1.0_pReal / sqrt ( rhoSgl ( 1 : ns , 2 * c - 1 ) + rhoSgl ( 1 : ns , 2 * c ) &
2013-05-24 01:26:36 +05:30
+ abs ( rhoSgl ( 1 : ns , 2 * c + 3 ) ) + abs ( rhoSgl ( 1 : ns , 2 * c + 4 ) ) + rhoDip ( 1 : ns , c ) ) , &
2012-10-29 18:32:01 +05:30
dUpper ( 1 : ns , c ) )
2012-05-20 19:27:35 +05:30
dUpper = max ( dUpper , dLower )
2012-05-18 20:05:52 +05:30
deltaDUpper = dUpper - dUpperOld
2012-11-28 17:39:48 +05:30
!*** dissociation by stress increase
2012-05-18 20:05:52 +05:30
deltaRhoDipole2SingleStress = 0.0_pReal
2012-11-28 17:39:48 +05:30
forall ( c = 1_pInt : 2_pInt , s = 1_pInt : ns , deltaDUpper ( s , c ) < 0.0_pReal ) &
deltaRhoDipole2SingleStress ( s , 8_pInt + c ) = rhoDip ( s , c ) * deltaDUpper ( s , c ) / ( dUpperOld ( s , c ) - dLower ( s , c ) )
forall ( t = 1_pInt : 4_pInt ) &
2012-05-18 20:05:52 +05:30
deltaRhoDipole2SingleStress ( 1_pInt : ns , t ) = - 0.5_pReal * deltaRhoDipole2SingleStress ( 1_pInt : ns , ( t - 1_pInt ) / 2_pInt + 9_pInt )
2012-11-28 17:39:48 +05:30
2012-07-24 12:27:37 +05:30
2012-05-18 20:05:52 +05:30
!*** store new maximum dipole height in state
forall ( c = 1_pInt : 2_pInt ) &
2013-04-04 19:07:14 +05:30
state ( g , ip , el ) % p ( ( 17_pInt + c ) * ns + 1_pInt : ( 18_pInt + c ) * ns ) = dUpper ( 1_pInt : ns , c )
2012-05-18 20:05:52 +05:30
!****************************************************************************
2012-08-14 17:56:20 +05:30
!*** assign the changes in the dislocation densities to deltaState
2012-05-18 19:05:44 +05:30
deltaRho = 0.0_pReal
2012-05-18 20:05:52 +05:30
deltaRho = deltaRhoRemobilization &
2012-11-28 17:39:48 +05:30
+ deltaRhoDipole2SingleStress
2012-05-18 19:05:44 +05:30
2012-05-18 20:05:52 +05:30
deltaState % p = reshape ( deltaRho , ( / 10_pInt * ns / ) )
2012-05-18 19:05:44 +05:30
#ifndef _OPENMP
2012-10-22 13:29:35 +05:30
if ( iand ( debug_level ( debug_constitutive ) , debug_levelExtensive ) / = 0_pInt &
2012-05-18 19:05:44 +05:30
. and . ( ( debug_e == el . and . debug_i == ip . and . debug_g == g ) &
2012-07-05 15:24:50 +05:30
. or . . not . iand ( debug_level ( debug_constitutive ) , debug_levelSelective ) / = 0_pInt ) ) then
2012-05-18 19:05:44 +05:30
write ( 6 , '(a,/,8(12x,12(e12.5,1x),/))' ) '<< CONST >> dislocation remobilization' , deltaRhoRemobilization ( 1 : ns , 1 : 8 )
2012-05-30 13:35:36 +05:30
write ( 6 , '(a,/,10(12x,12(e12.5,1x),/))' ) '<< CONST >> dipole dissociation by stress increase' , deltaRhoDipole2SingleStress
2012-05-18 19:05:44 +05:30
write ( 6 , * )
endif
#endif
2012-05-16 20:13:26 +05:30
2012-05-18 20:05:52 +05:30
endsubroutine
2012-05-16 20:13:26 +05:30
2009-08-11 22:01:57 +05:30
!*********************************************************************
!* rate of change of microstructure *
!*********************************************************************
2012-11-30 00:14:00 +05:30
function constitutive_nonlocal_dotState ( Tstar_v , Fe , Fp , Temperature , state , state0 , timestep , subfrac , g , ip , el )
2009-08-11 22:01:57 +05:30
2013-05-23 17:55:56 +05:30
use prec , only : DAMASK_NaN
2012-11-28 00:06:55 +05:30
use numerics , only : numerics_integrationMode , &
numerics_timeSyncing
2010-03-04 22:44:47 +05:30
use IO , only : IO_error
2012-07-05 15:24:50 +05:30
use debug , only : debug_level , &
2012-03-09 01:55:28 +05:30
debug_constitutive , &
debug_levelBasic , &
2012-10-19 17:10:17 +05:30
debug_levelExtensive , &
2012-03-09 01:55:28 +05:30
debug_levelSelective , &
2010-11-03 22:52:48 +05:30
debug_g , &
debug_i , &
2011-03-21 16:01:17 +05:30
debug_e
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 , &
2012-01-26 19:20:00 +05:30
math_inv33 , &
math_det33 , &
math_transpose33 , &
2013-04-04 19:07:14 +05:30
pi
2009-08-11 22:01:57 +05:30
use mesh , only : mesh_NcpElems , &
mesh_maxNips , &
mesh_element , &
mesh_ipNeighborhood , &
mesh_ipVolume , &
mesh_ipArea , &
2012-11-16 04:15:20 +05:30
mesh_ipAreaNormal , &
FE_NipNeighbors , &
2013-04-22 19:05:35 +05:30
FE_geomtype , &
FE_celltype
2009-08-11 22:01:57 +05:30
use material , only : homogenization_maxNgrains , &
material_phase , &
2012-03-12 19:39:37 +05:30
phase_plasticityInstance , &
phase_localPlasticity , &
phase_plasticity
2012-02-23 22:50:57 +05:30
use lattice , only : lattice_Sslip_v , &
2009-08-11 22:01:57 +05:30
lattice_sd , &
2012-02-23 22:50:57 +05:30
lattice_st
2010-10-26 19:12:18 +05:30
2009-08-11 22:01:57 +05:30
implicit none
!*** input variables
2013-01-22 16:36:39 +05:30
integer ( pInt ) , intent ( in ) :: g , & !< current grain number
ip , & !< current integration point
el !< current element number
real ( pReal ) , intent ( in ) :: Temperature , & !< temperature
timestep !< substepped crystallite time increment
real ( pReal ) , dimension ( 6 ) , intent ( in ) :: Tstar_v !< current 2nd Piola-Kirchhoff stress in Mandel notation
2012-11-28 00:06:55 +05:30
real ( pReal ) , dimension ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
2013-01-22 16:36:39 +05:30
subfrac !< fraction of timestep at the beginning of the substepped crystallite time increment
2009-10-07 21:01:52 +05:30
real ( pReal ) , dimension ( 3 , 3 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
2013-01-22 16:36:39 +05:30
Fe , & !< elastic deformation gradient
Fp !< plastic deformation gradient
2009-08-11 22:01:57 +05:30
type ( p_vec ) , dimension ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
2013-01-22 16:36:39 +05:30
state , & !< current microstructural state
state0 !< microstructural state at beginning of crystallite increment
2012-11-28 00:06:55 +05:30
2009-08-11 22:01:57 +05:30
!*** input/output variables
!*** output variables
2012-05-16 21:05:14 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_sizeDotState ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) ) :: &
2013-01-22 16:36:39 +05:30
constitutive_nonlocal_dotState !< evolution of state variables / microstructure
2009-08-11 22:01:57 +05:30
!*** local variables
2013-01-22 16:36:39 +05:30
integer ( pInt ) myInstance , & !< current instance of this plasticity
myStructure , & !< current lattice structure
ns , & !< short notation for the total number of active slip systems
c , & !< character of dislocation
n , & !< index of my current neighbor
neighboring_el , & !< element number of my neighbor
neighboring_ip , & !< integration point of my neighbor
neighboring_n , & !< neighbor index pointing to me when looking from my neighbor
opposite_neighbor , & !< index of my opposite neighbor
opposite_ip , & !< ip of my opposite neighbor
opposite_el , & !< element index of my opposite neighbor
opposite_n , & !< neighbor index pointing to me when looking from my opposite neighbor
t , & !< type of dislocation
topp , & !< type of dislocation with opposite sign to t
s , & !< index of my current slip system
sLattice , & !< index of my current slip system according to lattice order
2012-03-14 21:02:50 +05:30
deads
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) , 10 ) :: &
2013-01-22 16:36:39 +05:30
rhoDot , & !< density evolution
rhoDotMultiplication , & !< density evolution by multiplication
rhoDotFlux , & !< density evolution by flux
rhoDotSingle2DipoleGlide , & !< density evolution by dipole formation (by glide)
rhoDotAthermalAnnihilation , & !< density evolution by athermal annihilation
rhoDotThermalAnnihilation !< density evolution by thermal annihilation
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) , 8 ) :: &
2013-01-22 16:36:39 +05:30
rhoSgl , & !< current single dislocation densities (positive/negative screw and edge without dipoles)
2012-11-30 00:20:25 +05:30
rhoSglOriginal , &
2013-05-17 18:24:47 +05:30
neighboring_rhoSgl , & !< current single dislocation densities of neighboring ip (positive/negative screw and edge without dipoles)
2013-01-22 16:36:39 +05:30
rhoSgl0 , & !< single dislocation densities at start of cryst inc (positive/negative screw and edge without dipoles)
2013-05-08 00:17:17 +05:30
rhoSglMe !< single dislocation densities of central ip (positive/negative screw and edge without dipoles)
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) , 4 ) :: &
2013-01-22 16:36:39 +05:30
v , & !< current dislocation glide velocity
v0 , & !< dislocation glide velocity at start of cryst inc
vMe , & !< dislocation glide velocity of central ip
neighboring_v , & !< dislocation glide velocity of enighboring ip
gdot !< shear rates
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) ) :: &
2013-01-22 16:36:39 +05:30
rhoForest , & !< forest dislocation density
tauThreshold , & !< threshold shear stress
tau , & !< current resolved shear stress
tauBack , & !< current back stress from pileups on same slip system
vClimb , & !< climb velocity of edge dipoles
2012-11-30 00:20:25 +05:30
nSources
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) , 2 ) :: &
2013-01-22 16:36:39 +05:30
rhoDip , & !< current dipole dislocation densities (screw and edge dipoles)
2012-12-06 22:44:35 +05:30
rhoDipOriginal , &
2013-01-22 16:36:39 +05:30
dLower , & !< minimum stable dipole distance for edges and screws
dUpper !< current maximum stable dipole distance for edges and screws
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( 3 , totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) , 4 ) :: &
2013-01-22 16:36:39 +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 ( 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
2013-05-24 01:26:36 +05:30
selfDiffusion , & !< self diffusion
2012-11-30 00:20:25 +05:30
rnd , &
meshlength
2011-02-16 22:05:38 +05:30
logical considerEnteringFlux , &
2012-11-30 00:20:25 +05:30
considerLeavingFlux
2010-03-04 22:44:47 +05:30
2011-03-29 12:57:19 +05:30
#ifndef _OPENMP
2012-07-05 15:24:50 +05:30
if ( iand ( debug_level ( debug_constitutive ) , debug_levelBasic ) / = 0_pInt &
2012-03-09 01:55:28 +05:30
. and . ( ( debug_e == el . and . debug_i == ip . and . debug_g == g ) &
2012-07-05 15:24:50 +05:30
. or . . not . iand ( debug_level ( debug_constitutive ) , debug_levelSelective ) / = 0_pInt ) ) then
2011-03-21 16:01:17 +05:30
write ( 6 , * )
2012-02-02 01:50:05 +05:30
write ( 6 , '(a,i8,1x,i2,1x,i1)' ) '<< CONST >> nonlocal_dotState at el ip g ' , el , ip , g
2010-03-04 22:44:47 +05:30
write ( 6 , * )
2011-03-29 12:57:19 +05:30
endif
#endif
2009-12-15 13:50:31 +05:30
2009-08-11 22:01:57 +05:30
2012-03-12 19:39:37 +05:30
myInstance = phase_plasticityInstance ( material_phase ( g , ip , el ) )
2009-08-11 22:01:57 +05:30
myStructure = constitutive_nonlocal_structure ( myInstance )
2013-05-24 01:26:36 +05:30
ns = totalNslip ( myInstance )
2009-08-11 22:01:57 +05:30
2010-02-17 18:51:36 +05:30
tau = 0.0_pReal
2009-08-12 16:52:02 +05:30
gdot = 0.0_pReal
2009-08-11 22:01:57 +05:30
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
2009-08-11 22:01:57 +05:30
!*** shortcut to state variables
2012-02-13 19:48:07 +05:30
forall ( s = 1_pInt : ns , t = 1_pInt : 4_pInt ) &
rhoSgl ( s , t ) = max ( state ( g , ip , el ) % p ( ( t - 1_pInt ) * ns + s ) , 0.0_pReal )
forall ( s = 1_pInt : ns , t = 5_pInt : 8_pInt ) &
rhoSgl ( s , t ) = state ( g , ip , el ) % p ( ( t - 1_pInt ) * ns + s )
forall ( s = 1_pInt : ns , c = 1_pInt : 2_pInt ) &
rhoDip ( s , c ) = max ( state ( g , ip , el ) % p ( ( 7_pInt + c ) * ns + s ) , 0.0_pReal )
2013-04-04 19:07:14 +05:30
rhoForest = state ( g , ip , el ) % p ( 11_pInt * ns + 1 : 12_pInt * ns )
tauThreshold = state ( g , ip , el ) % p ( 12_pInt * ns + 1_pInt : 13_pInt * ns )
tauBack = state ( g , ip , el ) % p ( 13_pInt * ns + 1 : 14_pInt * ns )
2012-02-13 19:48:07 +05:30
forall ( t = 1_pInt : 4_pInt ) &
2013-04-04 19:07:14 +05:30
v ( 1_pInt : ns , t ) = state ( g , ip , el ) % p ( ( 13_pInt + t ) * ns + 1_pInt : ( 14_pInt + t ) * ns )
2012-11-30 00:20:25 +05:30
rhoSglOriginal = rhoSgl
2012-12-06 22:44:35 +05:30
rhoDipOriginal = rhoDip
2013-05-24 01:26:36 +05:30
where ( abs ( rhoSgl ) * mesh_ipVolume ( ip , el ) ** 0.667_pReal < significantN ( myInstance ) &
. or . abs ( rhoSgl ) < significantRho ( myInstance ) ) &
2012-10-02 18:27:24 +05:30
rhoSgl = 0.0_pReal
2013-05-24 01:26:36 +05:30
where ( abs ( rhoDip ) * mesh_ipVolume ( ip , el ) ** 0.667_pReal < significantN ( myInstance ) &
. or . abs ( rhoDip ) < significantRho ( myInstance ) ) &
2012-10-02 18:27:24 +05:30
rhoDip = 0.0_pReal
2009-08-11 22:01:57 +05:30
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
2010-03-04 22:44:47 +05:30
!*** sanity check for timestep
if ( timestep < = 0.0_pReal ) then ! if illegal timestep...
2012-05-16 21:05:14 +05:30
constitutive_nonlocal_dotState = 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
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
2009-08-12 16:52:02 +05:30
!****************************************************************************
!*** Calculate shear rate
2012-02-13 19:48:07 +05:30
forall ( t = 1_pInt : 4_pInt ) &
2013-05-24 01:26:36 +05:30
gdot ( 1_pInt : ns , t ) = rhoSgl ( 1_pInt : ns , t ) * burgers ( 1 : ns , myInstance ) * v ( 1 : ns , t )
2010-01-05 21:37:24 +05:30
2011-03-29 12:57:19 +05:30
#ifndef _OPENMP
2012-07-05 15:24:50 +05:30
if ( iand ( debug_level ( debug_constitutive ) , debug_levelBasic ) / = 0_pInt &
2012-03-09 01:55:28 +05:30
. and . ( ( debug_e == el . and . debug_i == ip . and . debug_g == g ) &
2012-07-05 15:24:50 +05:30
. or . . not . iand ( debug_level ( debug_constitutive ) , debug_levelSelective ) / = 0_pInt ) ) then
2012-02-02 01:50:05 +05:30
write ( 6 , '(a,/,10(12x,12(e12.5,1x),/))' ) '<< CONST >> rho / 1/m^2' , rhoSgl , rhoDip
write ( 6 , '(a,/,4(12x,12(e12.5,1x),/))' ) '<< CONST >> gdot / 1/s' , gdot
2011-03-29 12:57:19 +05:30
endif
#endif
2010-10-26 19:12:18 +05:30
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
2009-08-12 16:52:02 +05:30
!****************************************************************************
2011-02-25 15:23:20 +05:30
!*** calculate limits for stable dipole height
2010-02-17 18:51:36 +05:30
2012-02-23 22:13:17 +05:30
do s = 1_pInt , ns ! loop over slip systems
2013-05-24 01:26:36 +05:30
sLattice = slipSystemLattice ( s , myInstance )
2013-01-22 04:41:16 +05:30
tau ( s ) = math_mul6x6 ( Tstar_v , lattice_Sslip_v ( 1 : 6 , 1 , sLattice , myStructure ) ) + tauBack ( s )
2012-05-08 12:46:00 +05:30
if ( abs ( tau ( s ) ) < 1.0e-15_pReal ) tau ( s ) = 1.0e-15_pReal
2010-02-17 18:51:36 +05:30
enddo
2013-05-24 01:26:36 +05:30
dLower = minDipoleHeight ( 1 : ns , 1 : 2 , myInstance )
dUpper ( 1 : ns , 1 ) = mu ( myInstance ) * burgers ( 1 : ns , myInstance ) &
/ ( 8.0_pReal * pi * ( 1.0_pReal - nu ( myInstance ) ) * abs ( tau ) )
dUpper ( 1 : ns , 2 ) = mu ( myInstance ) * burgers ( 1 : ns , myInstance ) &
2012-07-24 20:20:11 +05:30
/ ( 4.0_pReal * pi * abs ( tau ) )
forall ( c = 1_pInt : 2_pInt ) &
2012-10-29 18:32:01 +05:30
dUpper ( 1 : ns , c ) = min ( 1.0_pReal / sqrt ( rhoSgl ( 1 : ns , 2 * c - 1 ) + rhoSgl ( 1 : ns , 2 * c ) &
2013-05-24 01:26:36 +05:30
+ abs ( rhoSgl ( 1 : ns , 2 * c + 3 ) ) + abs ( rhoSgl ( 1 : ns , 2 * c + 4 ) ) + rhoDip ( 1 : ns , c ) ) , &
2012-10-29 18:32:01 +05:30
dUpper ( 1 : ns , c ) )
2012-05-20 19:27:35 +05:30
dUpper = max ( dUpper , dLower )
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-04-06 14:37:36 +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 dislocation multiplication
2009-10-07 21:01:52 +05:30
2010-10-26 19:12:18 +05:30
rhoDotMultiplication = 0.0_pReal
2013-05-24 01:26:36 +05:30
if ( probabilisticMultiplication ( myInstance ) ) then
2012-12-03 18:29:38 +05:30
meshlength = mesh_ipVolume ( ip , el ) ** 0.333_pReal
where ( sum ( rhoSgl ( 1 : ns , 1 : 4 ) , 2 ) > 0.0_pReal )
2013-05-24 01:26:36 +05:30
nSources = ( sum ( rhoSgl ( 1 : ns , 1 : 2 ) , 2 ) * fEdgeMultiplication ( myInstance ) + sum ( rhoSgl ( 1 : ns , 3 : 4 ) , 2 ) ) &
/ sum ( rhoSgl ( 1 : ns , 1 : 4 ) , 2 ) * meshlength / lambda0 ( 1 : ns , myInstance ) * sqrt ( rhoForest ( 1 : ns ) )
2012-12-03 18:29:38 +05:30
elsewhere
2013-05-24 01:26:36 +05:30
nSources = meshlength / lambda0 ( 1 : ns , myInstance ) * sqrt ( rhoForest ( 1 : ns ) )
2012-12-03 18:29:38 +05:30
endwhere
do s = 1_pInt , ns
if ( nSources ( s ) < 1.0_pReal ) then
2013-05-24 01:26:36 +05:30
if ( sourceProbability ( s , g , ip , el ) > 1.0_pReal ) then
2012-12-03 18:29:38 +05:30
call random_number ( rnd )
2013-05-24 01:26:36 +05:30
sourceProbability ( s , g , ip , el ) = rnd
!$OMP FLUSH(sourceProbability)
2012-12-03 18:29:38 +05:30
endif
2013-05-24 01:26:36 +05:30
if ( sourceProbability ( s , g , ip , el ) > 1.0_pReal - nSources ( s ) ) then
2012-12-06 19:34:18 +05:30
rhoDotMultiplication ( s , 1 : 4 ) = sum ( rhoSglOriginal ( s , 1 : 4 ) * abs ( v ( s , 1 : 4 ) ) ) / meshlength
2012-12-03 18:29:38 +05:30
endif
else
2013-05-24 01:26:36 +05:30
sourceProbability ( s , g , ip , el ) = 2.0_pReal
2012-12-03 18:29:38 +05:30
rhoDotMultiplication ( s , 1 : 4 ) = &
2013-05-24 01:26:36 +05:30
( sum ( abs ( gdot ( s , 1 : 2 ) ) ) * fEdgeMultiplication ( myInstance ) + sum ( abs ( gdot ( s , 3 : 4 ) ) ) ) &
/ burgers ( s , myInstance ) * sqrt ( rhoForest ( s ) ) / lambda0 ( s , myInstance )
2012-11-30 00:20:25 +05:30
endif
2012-12-03 18:29:38 +05:30
enddo
2012-10-19 17:10:17 +05:30
#ifndef _OPENMP
if ( iand ( debug_level ( debug_constitutive ) , debug_levelExtensive ) / = 0_pInt &
. and . ( ( debug_e == el . and . debug_i == ip . and . debug_g == g ) &
. or . . not . iand ( debug_level ( debug_constitutive ) , debug_levelSelective ) / = 0_pInt ) ) then
2012-11-30 00:20:25 +05:30
write ( 6 , '(a,/,4(12x,12(f12.5,1x),/))' ) '<< CONST >> sources' , nSources
2012-10-19 17:10:17 +05:30
write ( 6 , * )
endif
#endif
2012-12-03 18:29:38 +05:30
else
rhoDotMultiplication ( 1 : ns , 1 : 4 ) = spread ( &
2013-05-24 01:26:36 +05:30
( sum ( abs ( gdot ( 1 : ns , 1 : 2 ) ) , 2 ) * fEdgeMultiplication ( myInstance ) + sum ( abs ( gdot ( 1 : ns , 3 : 4 ) ) , 2 ) ) &
* sqrt ( rhoForest ( 1 : ns ) ) / lambda0 ( 1 : ns , myInstance ) / burgers ( 1 : ns , myInstance ) , 2 , 4 )
2012-12-03 18:29:38 +05:30
endif
2009-08-11 22:01:57 +05:30
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
2009-08-12 16:52:02 +05:30
!****************************************************************************
2012-03-12 19:39:37 +05:30
!*** calculate dislocation fluxes (only for nonlocal plasticity)
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
2012-03-12 19:39:37 +05:30
if ( . not . phase_localPlasticity ( material_phase ( g , ip , el ) ) ) then ! only for nonlocal plasticity
2011-02-23 13:38:06 +05:30
2012-08-16 14:43:38 +05:30
!*** check CFL (Courant-Friedrichs-Lewy) condition for flux
if ( any ( abs ( gdot ) > 0.0_pReal & ! any active slip system ...
2013-05-24 01:26:36 +05:30
. and . CFLfactor ( myInstance ) * abs ( v ) * timestep &
2012-08-16 14:43:38 +05:30
> mesh_ipVolume ( ip , el ) / maxval ( mesh_ipArea ( : , ip , el ) ) ) ) then ! ...with velocity above critical value (we use the reference volume and area for simplicity here)
#ifndef _OPENMP
2012-12-03 18:29:38 +05:30
if ( iand ( debug_level ( debug_constitutive ) , debug_levelExtensive ) / = 0_pInt ) then
2012-08-16 14:43:38 +05:30
write ( 6 , '(a,i5,a,i2)' ) '<< CONST >> CFL condition not fullfilled at el ' , el , ' ip ' , ip
2012-09-05 16:49:46 +05:30
write ( 6 , '(a,e10.3,a,e10.3)' ) '<< CONST >> velocity is at ' , &
2013-05-24 01:26:36 +05:30
maxval ( abs ( v ) , abs ( gdot ) > 0.0_pReal . and . CFLfactor ( myInstance ) * abs ( v ) * timestep &
2012-09-05 16:49:46 +05:30
> mesh_ipVolume ( ip , el ) / maxval ( mesh_ipArea ( : , ip , el ) ) ) , &
' at a timestep of ' , timestep
2012-08-16 14:43:38 +05:30
write ( 6 , '(a)' ) '<< CONST >> enforcing cutback !!!'
endif
#endif
constitutive_nonlocal_dotState = DAMASK_NaN ! -> return NaN and, hence, enforce cutback
return
endif
2012-11-28 00:06:55 +05:30
if ( numerics_timeSyncing ) then
forall ( t = 1_pInt : 4_pInt ) &
v0 ( 1_pInt : ns , t ) = state0 ( g , ip , el ) % p ( ( 12_pInt + t ) * ns + 1_pInt : ( 13_pInt + t ) * ns )
forall ( t = 1_pInt : 8_pInt ) &
rhoSgl0 ( 1_pInt : ns , t ) = state0 ( g , ip , el ) % p ( ( t - 1_pInt ) * ns + 1_pInt : t * ns )
2013-05-24 01:26:36 +05:30
where ( abs ( rhoSgl0 ) * mesh_ipVolume ( ip , el ) ** 0.667_pReal < significantN ( myInstance ) &
. or . abs ( rhoSgl0 ) < significantRho ( myInstance ) ) &
2012-11-28 00:06:55 +05:30
rhoSgl0 = 0.0_pReal
endif
2012-08-16 14:43:38 +05:30
!*** be aware of the definition of lattice_st = lattice_sd x lattice_sn !!!
2011-02-23 13:38:06 +05:30
!*** opposite sign to our p vector in the (s,p,n) triplet !!!
2013-05-24 01:26:36 +05:30
m ( 1 : 3 , 1 : ns , 1 ) = lattice_sd ( 1 : 3 , slipSystemLattice ( 1 : ns , myInstance ) , myStructure )
m ( 1 : 3 , 1 : ns , 2 ) = - lattice_sd ( 1 : 3 , slipSystemLattice ( 1 : ns , myInstance ) , myStructure )
m ( 1 : 3 , 1 : ns , 3 ) = - lattice_st ( 1 : 3 , slipSystemLattice ( 1 : ns , myInstance ) , myStructure )
m ( 1 : 3 , 1 : ns , 4 ) = lattice_st ( 1 : 3 , 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
2013-04-22 19:05:35 +05:30
do n = 1_pInt , FE_NipNeighbors ( FE_celltype ( FE_geomtype ( mesh_element ( 2 , el ) ) ) ) ! loop through my neighbors
2011-01-11 20:25:36 +05:30
neighboring_el = mesh_ipNeighborhood ( 1 , n , ip , el )
neighboring_ip = mesh_ipNeighborhood ( 2 , n , ip , el )
2012-10-29 18:19:28 +05:30
neighboring_n = mesh_ipNeighborhood ( 3 , n , ip , el )
2011-02-16 22:05:38 +05:30
2012-10-29 18:19:28 +05:30
opposite_neighbor = n + mod ( n , 2_pInt ) - mod ( n + 1_pInt , 2_pInt )
opposite_el = mesh_ipNeighborhood ( 1 , opposite_neighbor , ip , el )
opposite_ip = mesh_ipNeighborhood ( 2 , opposite_neighbor , ip , el )
opposite_n = mesh_ipNeighborhood ( 3 , opposite_neighbor , ip , el )
2011-01-11 20:25:36 +05:30
2012-10-29 18:19:28 +05:30
if ( neighboring_n > 0_pInt ) then ! if neighbor exists, average deformation gradient
2011-02-16 22:05:38 +05:30
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 MY NEIGHBOR TO ME
2012-03-12 19:39:37 +05:30
!* This is only considered, if I have a neighbor of nonlocal plasticity (also nonlocal constitutive law with local properties) that is at least a little bit compatible.
2011-02-16 22:05:38 +05:30
!* 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 .
2012-03-14 21:02:50 +05:30
neighboring_v = 0.0_pReal ! needed for check of sign change in flux density below
neighboring_rhoSgl = 0.0_pReal
2012-10-29 18:19:28 +05:30
if ( neighboring_n > 0_pInt ) then
2013-05-24 01:26:36 +05:30
if ( phase_plasticity ( material_phase ( 1 , neighboring_ip , neighboring_el ) ) == CONSTITUTIVE_NONLOCAL_LABEL &
. and . any ( compatibility ( : , : , : , n , ip , el ) > 0.0_pReal ) ) &
2011-08-02 16:47:45 +05:30
considerEnteringFlux = . true .
2011-02-16 22:05:38 +05:30
endif
if ( considerEnteringFlux ) then
2012-12-11 19:08:36 +05:30
if ( numerics_timeSyncing . and . ( subfrac ( g , neighboring_ip , neighboring_el ) / = subfrac ( g , ip , el ) ) ) then ! for timesyncing: in case of a timestep at the interface we have to use "state0" to make sure that fluxes n both sides are equal
2013-04-03 21:52:55 +05:30
forall ( t = 1_pInt : 4_pInt )
2013-04-04 19:07:14 +05:30
neighboring_v ( 1_pInt : ns , t ) = state0 ( g , neighboring_ip , neighboring_el ) % p ( ( 13_pInt + t ) * ns + 1_pInt : ( 14_pInt + t ) * ns )
2013-04-03 21:52:55 +05:30
neighboring_rhoSgl ( 1_pInt : ns , t ) = max ( state0 ( g , neighboring_ip , neighboring_el ) % p ( ( t - 1_pInt ) * ns + 1_pInt : t * ns ) , 0.0_pReal )
endforall
2013-05-20 00:53:31 +05:30
forall ( t = 5_pInt : 8_pInt ) &
neighboring_rhoSgl ( 1_pInt : ns , t ) = state0 ( g , neighboring_ip , neighboring_el ) % p ( ( t - 1_pInt ) * ns + 1_pInt : t * ns )
2012-11-28 00:06:55 +05:30
else
2013-04-03 21:52:55 +05:30
forall ( t = 1_pInt : 4_pInt )
2013-04-04 19:07:14 +05:30
neighboring_v ( 1_pInt : ns , t ) = state ( g , neighboring_ip , neighboring_el ) % p ( ( 13_pInt + t ) * ns + 1_pInt : ( 14_pInt + t ) * ns )
2013-04-03 21:52:55 +05:30
neighboring_rhoSgl ( 1_pInt : ns , t ) = max ( state ( g , neighboring_ip , neighboring_el ) % p ( ( t - 1_pInt ) * ns + 1_pInt : t * ns ) , 0.0_pReal )
endforall
2013-05-20 00:53:31 +05:30
forall ( t = 5_pInt : 8_pInt ) &
neighboring_rhoSgl ( 1_pInt : ns , t ) = state ( g , neighboring_ip , neighboring_el ) % p ( ( t - 1_pInt ) * ns + 1_pInt : t * ns )
2012-11-28 00:06:55 +05:30
endif
2012-10-02 18:27:24 +05:30
where ( abs ( neighboring_rhoSgl ) * mesh_ipVolume ( neighboring_ip , neighboring_el ) ** 0.667_pReal &
2013-05-24 01:26:36 +05:30
< significantN ( myInstance ) &
. or . abs ( neighboring_rhoSgl ) < significantRho ( myInstance ) ) &
2012-09-04 22:26:37 +05:30
neighboring_rhoSgl = 0.0_pReal
2013-05-24 01:26:36 +05:30
normal_neighbor2me_defConf = math_det33 ( Favg ) * math_mul33x3 ( math_inv33 ( 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!!!)
2012-01-26 19:20:00 +05:30
normal_neighbor2me = math_mul33x3 ( transpose ( neighboring_Fe ) , normal_neighbor2me_defConf ) / math_det33 ( neighboring_Fe ) ! interface normal in the lattice configuration of my neighbor
2011-02-16 22:05:38 +05:30
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
2012-02-23 22:13:17 +05:30
do s = 1_pInt , ns
do t = 1_pInt , 4_pInt
c = ( t + 1_pInt ) / 2
topp = t + mod ( t , 2_pInt ) - mod ( t + 1_pInt , 2_pInt )
2012-03-14 21:02:50 +05:30
if ( neighboring_v ( s , t ) * math_mul3x3 ( m ( 1 : 3 , s , t ) , normal_neighbor2me ) > 0.0_pReal & ! flux from my neighbor to me == entering flux for me
2013-05-10 14:12:42 +05:30
. and . v ( s , t ) * neighboring_v ( s , t ) > 0.0_pReal ) then ! ... only if no sign change in flux density
2013-05-17 18:24:47 +05:30
do deads = 0_pInt , 4_pInt , 4_pInt
lineLength = abs ( neighboring_rhoSgl ( s , t + deads ) ) * neighboring_v ( s , t ) &
* math_mul3x3 ( m ( 1 : 3 , s , t ) , normal_neighbor2me ) * area ! positive line length that wants to enter through this interface
2013-05-24 01:26:36 +05:30
where ( compatibility ( c , 1_pInt : ns , s , n , ip , el ) > 0.0_pReal ) & ! positive compatibility...
2013-05-17 18:24:47 +05:30
rhoDotFlux ( 1_pInt : ns , t ) = rhoDotFlux ( 1_pInt : ns , t ) + lineLength / mesh_ipVolume ( ip , el ) & ! ... transferring to equally signed mobile dislocation type
2013-05-24 01:26:36 +05:30
* compatibility ( c , 1_pInt : ns , s , n , ip , el ) ** 2.0_pReal
where ( compatibility ( c , 1_pInt : ns , s , n , ip , el ) < 0.0_pReal ) & ! ..negative compatibility...
2013-05-17 18:24:47 +05:30
rhoDotFlux ( 1_pInt : ns , topp ) = rhoDotFlux ( 1_pInt : ns , topp ) + lineLength / mesh_ipVolume ( ip , el ) & ! ... transferring to opposite signed mobile dislocation type
2013-05-24 01:26:36 +05:30
* compatibility ( c , 1_pInt : ns , s , n , ip , el ) ** 2.0_pReal
2013-05-17 18:24:47 +05:30
enddo
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-08-02 16:47:45 +05:30
!* FLUX FROM ME TO MY NEIGHBOR
2011-09-07 17:00:28 +05:30
!* This is not considered, if my opposite neighbor has a different constitutive law than nonlocal (still considered for nonlocal law with lcal properties).
2011-08-02 16:47:45 +05:30
!* 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.
considerLeavingFlux = . true .
2012-10-29 18:19:28 +05:30
if ( opposite_n > 0_pInt ) then
2013-05-24 01:26:36 +05:30
if ( phase_plasticity ( material_phase ( 1 , opposite_ip , opposite_el ) ) / = CONSTITUTIVE_NONLOCAL_LABEL ) &
2011-08-02 16:47:45 +05:30
considerLeavingFlux = . false .
endif
if ( considerLeavingFlux ) then
2012-12-11 19:08:36 +05:30
!* timeSyncing mode: If the central ip has zero subfraction, always use "state0". This is needed in case of
!* a synchronization step for the central ip, because then "state" contains the values at the end of the
!* previously converged full time step. Also, if either me or my neighbor has zero subfraction, we have to
!* use "state0" to make sure that fluxes on both sides of the (potential) timestep are equal.
rhoSglMe = rhoSgl
vMe = v
if ( numerics_timeSyncing ) then
if ( subfrac ( g , ip , el ) == 0.0_pReal ) then
2012-12-09 17:54:32 +05:30
rhoSglMe = rhoSgl0
vMe = v0
2012-12-11 19:08:36 +05:30
elseif ( neighboring_n > 0_pInt ) then
if ( subfrac ( g , neighboring_ip , neighboring_el ) == 0.0_pReal ) then
rhoSglMe = rhoSgl0
vMe = v0
endif
2012-12-09 17:54:32 +05:30
endif
2012-11-28 00:06:55 +05:30
endif
2012-12-11 19:08:36 +05:30
2012-02-03 18:20:54 +05:30
normal_me2neighbor_defConf = math_det33 ( Favg ) * math_mul33x3 ( math_inv33 ( math_transpose33 ( Favg ) ) , &
mesh_ipAreaNormal ( 1 : 3 , n , ip , el ) ) ! calculate the normal of the interface in (average) deformed configuration (pointing from me to my neighbor!!!)
2012-01-30 19:22:41 +05:30
normal_me2neighbor = math_mul33x3 ( math_transpose33 ( my_Fe ) , normal_me2neighbor_defConf ) / math_det33 ( my_Fe ) ! interface normal in my lattice configuration
2011-08-02 16:47:45 +05:30
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
2012-02-23 22:13:17 +05:30
do s = 1_pInt , ns
do t = 1_pInt , 4_pInt
2012-11-28 00:06:55 +05:30
c = ( t + 1_pInt ) / 2_pInt
if ( vMe ( 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)
2013-05-10 14:12:42 +05:30
if ( vMe ( s , t ) * neighboring_v ( s , t ) > 0.0_pReal ) then ! no sign change in flux density
2013-05-24 01:26:36 +05:30
transmissivity = sum ( compatibility ( c , 1_pInt : ns , s , n , ip , el ) ** 2.0_pReal ) ! overall transmissivity from this slip system to my neighbor
2011-08-02 16:47:45 +05:30
else ! sign change in flux density means sign change in stress which does not allow for dislocations to arive at the neighbor
transmissivity = 0.0_pReal
endif
2012-11-28 00:06:55 +05:30
lineLength = rhoSglMe ( s , t ) * vMe ( s , t ) * math_mul3x3 ( m ( 1 : 3 , s , t ) , normal_me2neighbor ) * area ! positive line length of mobiles that wants to leave through this interface
2012-03-14 21:02:50 +05:30
rhoDotFlux ( s , t ) = rhoDotFlux ( s , t ) - lineLength / mesh_ipVolume ( ip , el ) ! subtract dislocation flux from current type
2012-02-23 22:13:17 +05:30
rhoDotFlux ( s , t + 4_pInt ) = rhoDotFlux ( s , t + 4_pInt ) + lineLength / mesh_ipVolume ( ip , el ) * ( 1.0_pReal - transmissivity ) &
2012-11-28 00:06:55 +05:30
* sign ( 1.0_pReal , vMe ( 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
2013-05-17 18:24:47 +05:30
lineLength = rhoSglMe ( s , t + 4_pInt ) * vMe ( s , t ) * math_mul3x3 ( m ( 1 : 3 , s , t ) , normal_me2neighbor ) * area ! positive line length of deads that wants to leave through this interface
rhoDotFlux ( s , t + 4_pInt ) = rhoDotFlux ( s , t + 4_pInt ) - lineLength / mesh_ipVolume ( ip , el ) * transmissivity ! dead dislocations leaving through this interface
2011-08-02 16:47:45 +05:30
endif
enddo
enddo
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
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
2009-08-28 19:20:47 +05:30
!****************************************************************************
!*** calculate dipole formation and annihilation
!*** formation by glide
2012-02-23 22:13:17 +05:30
do c = 1_pInt , 2_pInt
2010-02-17 18:51:36 +05:30
2013-05-24 01:26:36 +05:30
rhoDotSingle2DipoleGlide ( 1 : ns , 2 * c - 1 ) = - 2.0_pReal * dUpper ( 1 : ns , c ) / burgers ( 1 : ns , myInstance ) &
2011-02-09 18:42:46 +05:30
* ( 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
2013-05-24 01:26:36 +05:30
rhoDotSingle2DipoleGlide ( 1 : ns , 2 * c ) = - 2.0_pReal * dUpper ( 1 : ns , c ) / burgers ( 1 : ns , myInstance ) &
2011-02-09 18:42:46 +05:30
* ( 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
2013-05-24 01:26:36 +05:30
rhoDotSingle2DipoleGlide ( 1 : ns , 2 * c + 3 ) = - 2.0_pReal * dUpper ( 1 : ns , c ) / burgers ( 1 : ns , myInstance ) &
2011-02-09 18:42:46 +05:30
* rhoSgl ( 1 : ns , 2 * c + 3 ) * abs ( gdot ( 1 : ns , 2 * c ) ) ! negative mobile --> positive immobile
2010-02-17 18:51:36 +05:30
2013-05-24 01:26:36 +05:30
rhoDotSingle2DipoleGlide ( 1 : ns , 2 * c + 4 ) = - 2.0_pReal * dUpper ( 1 : ns , c ) / burgers ( 1 : ns , myInstance ) &
2011-02-09 18:42:46 +05:30
* 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
2012-11-28 17:39:48 +05:30
!*** athermal annihilation
2009-08-28 19:20:47 +05:30
2010-05-21 14:21:15 +05:30
rhoDotAthermalAnnihilation = 0.0_pReal
2012-11-28 17:39:48 +05:30
forall ( c = 1_pInt : 2_pInt ) &
2013-05-24 01:26:36 +05:30
rhoDotAthermalAnnihilation ( 1 : ns , c + 8_pInt ) = - 2.0_pReal * dLower ( 1 : ns , c ) / burgers ( 1 : ns , myInstance ) &
2012-11-28 17:39:48 +05:30
* ( 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
! annihilated screw dipoles leave edge jogs behind on the colinear system
if ( myStructure == 1_pInt ) then ! only fcc
2013-05-24 01:26:36 +05:30
forall ( s = 1 : ns , colinearSystem ( s , myInstance ) > 0_pInt ) &
rhoDotAthermalAnnihilation ( colinearSystem ( s , myInstance ) , 1 : 2 ) = - rhoDotAthermalAnnihilation ( s , 10 ) &
* 0.25_pReal * sqrt ( rhoForest ( s ) ) * ( dUpper ( s , 2 ) + dLower ( s , 2 ) ) * edgeJogFactor ( myInstance )
2012-11-28 17:39:48 +05:30
endif
2009-08-28 19:20:47 +05:30
2012-11-17 19:20:20 +05:30
!*** thermally activated annihilation of edge dipoles by climb
2009-10-07 21:01:52 +05:30
2010-05-21 14:21:15 +05:30
rhoDotThermalAnnihilation = 0.0_pReal
2013-05-24 01:26:36 +05:30
selfDiffusion = Dsd0 ( myInstance ) * exp ( - selfDiffusionEnergy ( myInstance ) / ( KB * Temperature ) )
vClimb = atomicVolume ( myInstance ) * selfDiffusion / ( KB * Temperature ) &
* mu ( myInstance ) / ( 2.0_pReal * PI * ( 1.0_pReal - nu ( myInstance ) ) ) &
2011-02-09 18:42:46 +05:30
* 2.0_pReal / ( dUpper ( 1 : ns , 1 ) + dLower ( 1 : ns , 1 ) )
2012-10-04 23:38:40 +05:30
forall ( s = 1_pInt : ns , dUpper ( s , 1 ) > dLower ( s , 1 ) ) &
rhoDotThermalAnnihilation ( s , 9 ) = max ( - 4.0_pReal * rhoDip ( s , 1 ) * vClimb ( s ) / ( dUpper ( s , 1 ) - dLower ( s , 1 ) ) , &
- rhoDip ( s , 1 ) / timestep - rhoDotAthermalAnnihilation ( s , 9 ) - rhoDotSingle2DipoleGlide ( s , 9 ) ) ! make sure that we do not annihilate more dipoles than we have
2012-08-14 17:56:20 +05:30
2009-08-28 19:20:47 +05:30
!****************************************************************************
!*** assign the rates of dislocation densities to my dotState
2012-02-22 21:38:22 +05:30
!*** if evolution rates lead to negative densities, a cutback is enforced
2009-08-28 19:20:47 +05:30
2010-05-21 14:21:15 +05:30
rhoDot = 0.0_pReal
2011-08-02 16:47:45 +05:30
rhoDot = rhoDotFlux &
+ rhoDotMultiplication &
+ rhoDotSingle2DipoleGlide &
+ rhoDotAthermalAnnihilation &
+ rhoDotThermalAnnihilation
2010-05-21 14:21:15 +05:30
2012-08-16 16:33:22 +05:30
if ( numerics_integrationMode == 1_pInt ) then ! save rates for output if in central integration mode
2013-05-24 01:26:36 +05:30
rhoDotFluxOutput ( 1 : ns , 1 : 8 , g , ip , el ) = rhoDotFlux ( 1 : ns , 1 : 8 )
rhoDotMultiplicationOutput ( 1 : ns , 1 : 2 , g , ip , el ) = rhoDotMultiplication ( 1 : ns , [ 1 , 3 ] )
rhoDotSingle2DipoleGlideOutput ( 1 : ns , 1 : 2 , g , ip , el ) = rhoDotSingle2DipoleGlide ( 1 : ns , 9 : 10 )
rhoDotAthermalAnnihilationOutput ( 1 : ns , 1 : 2 , g , ip , el ) = rhoDotAthermalAnnihilation ( 1 : ns , 9 : 10 )
rhoDotThermalAnnihilationOutput ( 1 : ns , 1 : 2 , g , ip , el ) = rhoDotThermalAnnihilation ( 1 : ns , 9 : 10 )
rhoDotEdgeJogsOutput ( 1 : ns , g , ip , el ) = 2.0_pReal * rhoDotThermalAnnihilation ( 1 : ns , 1 )
2012-08-16 16:33:22 +05:30
endif
2011-03-29 12:57:19 +05:30
#ifndef _OPENMP
2012-10-22 13:29:35 +05:30
if ( iand ( debug_level ( debug_constitutive ) , debug_levelExtensive ) / = 0_pInt &
2012-03-09 01:55:28 +05:30
. and . ( ( debug_e == el . and . debug_i == ip . and . debug_g == g ) &
2012-07-05 15:24:50 +05:30
. or . . not . iand ( debug_level ( debug_constitutive ) , debug_levelSelective ) / = 0_pInt ) ) then
2012-02-02 01:50:05 +05:30
write ( 6 , '(a,/,4(12x,12(e12.5,1x),/))' ) '<< CONST >> dislocation multiplication' , rhoDotMultiplication ( 1 : ns , 1 : 4 ) * timestep
write ( 6 , '(a,/,8(12x,12(e12.5,1x),/))' ) '<< CONST >> dislocation flux' , rhoDotFlux ( 1 : ns , 1 : 8 ) * timestep
write ( 6 , '(a,/,10(12x,12(e12.5,1x),/))' ) '<< CONST >> dipole formation by glide' , rhoDotSingle2DipoleGlide * timestep
2012-11-28 17:39:48 +05:30
write ( 6 , '(a,/,10(12x,12(e12.5,1x),/))' ) '<< CONST >> athermal dipole annihilation' , &
rhoDotAthermalAnnihilation * timestep
2012-11-17 19:20:20 +05:30
write ( 6 , '(a,/,2(12x,12(e12.5,1x),/))' ) '<< CONST >> thermally activated dipole annihilation' , &
rhoDotThermalAnnihilation ( 1 : ns , 9 : 10 ) * timestep
2012-02-02 01:50:05 +05:30
write ( 6 , '(a,/,10(12x,12(e12.5,1x),/))' ) '<< CONST >> total density change' , rhoDot * timestep
2012-12-09 17:54:32 +05:30
write ( 6 , '(a,/,10(12x,12(f12.5,1x),/))' ) '<< CONST >> relative density change' , &
rhoDot ( 1 : ns , 1 : 8 ) * timestep / ( abs ( rhoSglOriginal ) + 1.0e-10 ) , &
rhoDot ( 1 : ns , 9 : 10 ) * timestep / ( rhoDipOriginal + 1.0e-10 )
2012-01-17 15:56:57 +05:30
write ( 6 , * )
2011-03-29 12:57:19 +05:30
endif
#endif
2010-10-26 19:12:18 +05:30
2012-08-23 11:18:21 +05:30
2013-05-24 01:26:36 +05:30
if ( any ( rhoSglOriginal ( 1 : ns , 1 : 4 ) + rhoDot ( 1 : ns , 1 : 4 ) * timestep < - aTolRho ( myInstance ) ) &
. or . any ( rhoDipOriginal ( 1 : ns , 1 : 2 ) + rhoDot ( 1 : ns , 9 : 10 ) * timestep < - aTolRho ( myInstance ) ) ) then
2012-08-23 11:18:21 +05:30
#ifndef _OPENMP
2012-12-03 18:29:38 +05:30
if ( iand ( debug_level ( debug_constitutive ) , debug_levelExtensive ) / = 0_pInt ) then
2012-08-23 11:18:21 +05:30
write ( 6 , '(a,i5,a,i2)' ) '<< CONST >> evolution rate leads to negative density at el ' , el , ' ip ' , ip
write ( 6 , '(a)' ) '<< CONST >> enforcing cutback !!!'
endif
#endif
constitutive_nonlocal_dotState = DAMASK_NaN
return
else
constitutive_nonlocal_dotState ( 1 : 10_pInt * ns ) = reshape ( rhoDot , ( / 10_pInt * ns / ) )
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_dotState ( 10_pInt * ns + 1 : 11_pInt * ns ) = shearrate ( 1 : ns , g , ip , el )
2012-08-23 11:18:21 +05:30
endif
2012-05-16 21:05:14 +05:30
endfunction
2009-08-11 22:01:57 +05:30
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 )
2013-01-31 21:58:08 +05:30
use math , only : math_qDisorientation , &
2010-10-12 18:38:54 +05:30
math_mul3x3 , &
math_qRot
use material , only : material_phase , &
2012-08-03 20:02:49 +05:30
material_texture , &
2012-03-12 19:39:37 +05:30
phase_localPlasticity , &
phase_plasticityInstance , &
2010-10-12 18:38:54 +05:30
homogenization_maxNgrains
use mesh , only : mesh_element , &
mesh_ipNeighborhood , &
mesh_maxNips , &
2012-11-16 04:15:20 +05:30
mesh_NcpElems , &
FE_NipNeighbors , &
2013-04-22 19:05:35 +05:30
FE_geomtype , &
FE_celltype
2010-10-12 18:38:54 +05:30
use lattice , only : lattice_sn , &
2012-02-23 22:50:57 +05:30
lattice_sd
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 , &
2012-08-03 20:02:49 +05:30
my_texture , &
neighboring_texture , &
2011-02-16 22:08:18 +05:30
my_structure , & ! lattice structure
2012-03-12 19:39:37 +05:30
my_instance , & ! instance of plasticity
2011-02-16 22:08:18 +05:30
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
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( 2 , totalNslip ( phase_plasticityInstance ( material_phase ( 1 , i , e ) ) ) , &
totalNslip ( phase_plasticityInstance ( material_phase ( 1 , i , e ) ) ) , &
2013-04-22 19:05:35 +05:30
FE_NipNeighbors ( FE_celltype ( FE_geomtype ( mesh_element ( 2 , e ) ) ) ) ) :: &
2013-05-24 01:26:36 +05:30
myCompatibility ! myCompatibility for current element and ip
real ( pReal ) , dimension ( 3 , totalNslip ( phase_plasticityInstance ( material_phase ( 1 , i , e ) ) ) ) :: &
2011-02-16 22:08:18 +05:30
slipNormal , &
slipDirection
2013-05-24 01:26:36 +05:30
real ( pReal ) myCompatibilitySum , &
2011-02-16 22:08:18 +05:30
thresholdValue , &
nThresholdValues
2013-05-24 01:26:36 +05:30
logical , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( 1 , i , e ) ) ) ) :: &
2011-02-16 22:08:18 +05:30
belowThreshold
2010-10-12 18:38:54 +05:30
2013-04-22 19:05:35 +05:30
Nneighbors = FE_NipNeighbors ( FE_celltype ( FE_geomtype ( mesh_element ( 2 , e ) ) ) )
2012-11-17 19:24:22 +05:30
my_phase = material_phase ( 1 , i , e )
my_texture = material_texture ( 1 , i , e )
my_instance = phase_plasticityInstance ( my_phase )
2011-02-16 22:08:18 +05:30
my_structure = constitutive_nonlocal_structure ( my_instance )
2013-05-24 01:26:36 +05:30
ns = totalNslip ( my_instance )
slipNormal ( 1 : 3 , 1 : ns ) = lattice_sn ( 1 : 3 , slipSystemLattice ( 1 : ns , my_instance ) , my_structure )
slipDirection ( 1 : 3 , 1 : ns ) = lattice_sd ( 1 : 3 , slipSystemLattice ( 1 : ns , my_instance ) , my_structure )
2011-02-16 22:08:18 +05:30
!*** start out fully compatible
2013-05-24 01:26:36 +05:30
myCompatibility = 0.0_pReal
2012-02-23 22:13:17 +05:30
forall ( s1 = 1_pInt : ns ) &
2013-05-24 01:26:36 +05:30
myCompatibility ( 1 : 2 , s1 , s1 , 1 : Nneighbors ) = 1.0_pReal
2011-02-16 22:08:18 +05:30
2013-05-24 01:26:36 +05:30
!*** Loop thrugh neighbors and check whether there is any myCompatibility.
2012-01-17 15:56:57 +05:30
2012-02-23 22:13:17 +05:30
do n = 1_pInt , Nneighbors
2012-01-17 15:56:57 +05:30
neighboring_e = mesh_ipNeighborhood ( 1 , n , i , e )
neighboring_i = mesh_ipNeighborhood ( 2 , n , i , e )
!* FREE SURFACE
!* Set surface transmissivity to the value specified in the material.config
2012-02-23 22:13:17 +05:30
if ( neighboring_e < = 0_pInt . or . neighboring_i < = 0_pInt ) then
forall ( s1 = 1_pInt : ns ) &
2013-05-24 01:26:36 +05:30
myCompatibility ( 1 : 2 , s1 , s1 , n ) = sqrt ( surfaceTransmissivity ( my_instance ) )
2012-01-17 15:56:57 +05:30
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 completely incompatible.
2012-09-04 22:26:37 +05:30
!* If one of the two "CPFEM" phases has a local plasticity law,
2012-01-17 15:56:57 +05:30
!* we do not consider this to be a phase boundary, so completely compatible.
neighboring_phase = material_phase ( 1 , neighboring_i , neighboring_e )
if ( neighboring_phase / = my_phase ) then
2012-09-04 22:26:37 +05:30
if ( . not . phase_localPlasticity ( neighboring_phase ) . and . . not . phase_localPlasticity ( my_phase ) ) then
2012-02-23 22:13:17 +05:30
forall ( s1 = 1_pInt : ns ) &
2013-05-24 01:26:36 +05:30
myCompatibility ( 1 : 2 , s1 , s1 , n ) = 0.0_pReal ! = sqrt(0.0)
2012-01-17 15:56:57 +05:30
endif
cycle
endif
2012-08-03 20:02:49 +05:30
!* GRAIN BOUNDARY !
!* fixed transmissivity for adjacent ips with different texture (only if explicitly given in material.config)
2013-05-24 01:26:36 +05:30
if ( grainboundaryTransmissivity ( my_instance ) > = 0.0_pReal ) then
2012-08-03 20:02:49 +05:30
neighboring_texture = material_texture ( 1 , neighboring_i , neighboring_e )
if ( neighboring_texture / = my_texture ) then
if ( . not . phase_localPlasticity ( neighboring_phase ) ) then
forall ( s1 = 1_pInt : ns ) &
2013-05-24 01:26:36 +05:30
myCompatibility ( 1 : 2 , s1 , s1 , n ) = sqrt ( grainboundaryTransmissivity ( my_instance ) )
2012-08-03 20:02:49 +05:30
endif
cycle
endif
2012-01-17 15:56:57 +05:30
!* GRAIN BOUNDARY ?
2012-08-03 20:02:49 +05:30
!* Compatibility defined by relative orientation of slip systems:
2013-05-24 01:26:36 +05:30
!* The myCompatibility value is defined as the product of the slip normal projection and the slip direction projection.
2012-01-17 15:56:57 +05:30
!* 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
2013-05-24 01:26:36 +05:30
!* the number of compatible slip systems is minimized with the sum of the original myCompatibility values exceeding one.
!* Finally the smallest myCompatibility value is decreased until the sum is exactly equal to one.
2012-01-17 15:56:57 +05:30
!* All values below the threshold are set to zero.
2012-08-03 20:02:49 +05:30
else
2013-01-31 21:58:08 +05:30
absoluteMisorientation = math_qDisorientation ( orientation ( 1 : 4 , 1 , i , e ) , &
2013-05-24 01:26:36 +05:30
orientation ( 1 : 4 , 1 , neighboring_i , neighboring_e ) , &
0_pInt ) ! no symmetry
2012-08-03 20:02:49 +05:30
do s1 = 1_pInt , ns ! my slip systems
do s2 = 1_pInt , ns ! my neighbor's slip systems
2013-05-24 01:26:36 +05:30
myCompatibility ( 1 , s2 , s1 , n ) = 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 ) ) ) )
myCompatibility ( 2 , s2 , s1 , n ) = 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 ) ) ) )
2012-08-03 20:02:49 +05:30
enddo
2013-05-24 01:26:36 +05:30
myCompatibilitySum = 0.0_pReal
2012-08-03 20:02:49 +05:30
belowThreshold = . true .
2013-05-24 01:26:36 +05:30
do while ( myCompatibilitySum < 1.0_pReal . and . any ( belowThreshold ( 1 : ns ) ) )
thresholdValue = maxval ( myCompatibility ( 2 , 1 : ns , s1 , n ) , belowThreshold ( 1 : ns ) ) ! screws always positive
nThresholdValues = real ( count ( myCompatibility ( 2 , 1 : ns , s1 , n ) == thresholdValue ) , pReal )
where ( myCompatibility ( 2 , 1 : ns , s1 , n ) > = thresholdValue ) &
2012-08-03 20:02:49 +05:30
belowThreshold ( 1 : ns ) = . false .
2013-05-24 01:26:36 +05:30
if ( myCompatibilitySum + thresholdValue * nThresholdValues > 1.0_pReal ) &
where ( abs ( myCompatibility ( 1 : 2 , 1 : ns , s1 , n ) ) == thresholdValue ) &
myCompatibility ( 1 : 2 , 1 : ns , s1 , n ) = sign ( ( 1.0_pReal - myCompatibilitySum ) &
/ nThresholdValues , myCompatibility ( 1 : 2 , 1 : ns , s1 , n ) )
myCompatibilitySum = myCompatibilitySum + nThresholdValues * thresholdValue
2012-08-03 20:02:49 +05:30
enddo
2013-05-24 01:26:36 +05:30
where ( belowThreshold ( 1 : ns ) ) myCompatibility ( 1 , 1 : ns , s1 , n ) = 0.0_pReal
where ( belowThreshold ( 1 : ns ) ) myCompatibility ( 2 , 1 : ns , s1 , n ) = 0.0_pReal
2012-08-03 20:02:49 +05:30
enddo ! my slip systems cycle
endif
2012-01-17 15:56:57 +05:30
enddo ! neighbor cycle
2013-05-24 01:26:36 +05:30
compatibility ( 1 : 2 , 1 : ns , 1 : ns , 1 : Nneighbors , i , e ) = myCompatibility
2012-01-17 15:56:57 +05:30
endsubroutine
!*********************************************************************
!* rate of change of temperature *
!*********************************************************************
pure function constitutive_nonlocal_dotTemperature ( Tstar_v , Temperature , state , g , ip , el )
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
!*********************************************************************
!* calculates quantities characterizing the microstructure *
!*********************************************************************
function constitutive_nonlocal_dislocationstress ( state , Fe , g , ip , el )
use math , only : math_mul33x33 , &
math_mul33x3 , &
2012-01-26 19:20:00 +05:30
math_invert33 , &
math_transpose33 , &
2012-01-17 15:56:57 +05:30
pi
use mesh , only : mesh_NcpElems , &
mesh_maxNips , &
mesh_element , &
mesh_node0 , &
2012-11-06 20:07:13 +05:30
mesh_cellCenterCoordinates , &
2012-01-17 15:56:57 +05:30
mesh_ipVolume , &
2012-11-16 04:15:20 +05:30
mesh_periodicSurface , &
FE_Nips , &
FE_geomtype
2012-01-17 15:56:57 +05:30
use material , only : homogenization_maxNgrains , &
material_phase , &
2012-03-12 19:39:37 +05:30
phase_localPlasticity , &
phase_plasticityInstance
2012-01-17 15:56:57 +05:30
implicit none
!*** input variables
integer ( pInt ) , intent ( in ) :: g , & ! current grain ID
ip , & ! current integration point
el ! current element
real ( pReal ) , dimension ( 3 , 3 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
Fe ! elastic deformation gradient
type ( p_vec ) , dimension ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
state ! microstructural state
!*** input/output variables
!*** output variables
real ( pReal ) , dimension ( 3 , 3 ) :: constitutive_nonlocal_dislocationstress
!*** local variables
integer ( pInt ) neighboring_el , & ! element number of neighboring material point
neighboring_ip , & ! integration point of neighboring material point
2012-03-12 19:39:37 +05:30
instance , & ! my instance of this plasticity
neighboring_instance , & ! instance of this plasticity of neighboring material point
2012-01-17 15:56:57 +05:30
latticeStruct , & ! my lattice structure
neighboring_latticeStruct , & ! lattice structure of neighboring material point
phase , &
neighboring_phase , &
ns , & ! total number of active slip systems at my material point
neighboring_ns , & ! total number of active slip systems at neighboring material point
c , & ! index of dilsocation character (edge, screw)
s , & ! slip system index
t , & ! index of dilsocation type (e+, e-, s+, s-, used e+, used e-, used s+, used s-)
dir , &
deltaX , deltaY , deltaZ , &
side , &
j
integer ( pInt ) , dimension ( 2 , 3 ) :: periodicImages
2013-05-24 01:26:36 +05:30
real ( pReal ) x , y , z , & ! coordinates of connection vector in neighboring lattice frame
2012-01-17 15:56:57 +05:30
xsquare , ysquare , zsquare , & ! squares of respective coordinates
distance , & ! length of connection vector
segmentLength , & ! segment length of dislocations
lambda , &
R , Rsquare , Rcube , &
denominator , &
flipSign , &
neighboring_ipVolumeSideLength , &
detFe
real ( pReal ) , dimension ( 3 ) :: connection , & ! connection vector between me and my neighbor in the deformed configuration
connection_neighboringLattice , & ! connection vector between me and my neighbor in the lattice configuration of my neighbor
connection_neighboringSlip , & ! connection vector between me and my neighbor in the slip system frame of my neighbor
maxCoord , minCoord , &
meshSize , &
2012-11-06 20:07:13 +05:30
coords , & ! x,y,z coordinates of cell center of ip volume
neighboring_coords ! x,y,z coordinates of cell center of neighboring ip volume
2012-01-17 15:56:57 +05:30
real ( pReal ) , dimension ( 3 , 3 ) :: sigma , & ! dislocation stress for one slip system in neighboring material point's slip system frame
Tdislo_neighboringLattice , & ! dislocation stress as 2nd Piola-Kirchhoff stress at neighboring material point
invFe , & ! inverse of my elastic deformation gradient
neighboring_invFe , &
neighboringLattice2myLattice ! mapping from neighboring MPs lattice configuration to my lattice configuration
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( 2 , 2 , maxval ( totalNslip ) ) :: &
2012-01-17 15:56:57 +05:30
neighboring_rhoExcess ! excess density at neighboring material point (edge/screw,mobile/dead,slipsystem)
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( 2 , maxval ( totalNslip ) ) :: &
2012-01-17 15:56:57 +05:30
rhoExcessDead
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) , 8 ) :: &
2012-01-17 15:56:57 +05:30
rhoSgl ! single dislocation density (edge+, edge-, screw+, screw-, used edge+, used edge-, used screw+, used screw-)
logical inversionError
phase = material_phase ( g , ip , el )
2012-03-12 19:39:37 +05:30
instance = phase_plasticityInstance ( phase )
2012-01-17 15:56:57 +05:30
latticeStruct = constitutive_nonlocal_structure ( instance )
2013-05-24 01:26:36 +05:30
ns = totalNslip ( instance )
2012-01-17 15:56:57 +05:30
!*** get basic states
2012-02-23 22:13:17 +05:30
forall ( s = 1_pInt : ns , t = 1_pInt : 4_pInt ) &
rhoSgl ( s , t ) = max ( state ( g , ip , el ) % p ( ( t - 1_pInt ) * ns + s ) , 0.0_pReal ) ! ensure positive single mobile densities
forall ( t = 5_pInt : 8_pInt ) &
rhoSgl ( 1 : ns , t ) = state ( g , ip , el ) % p ( ( t - 1_pInt ) * ns + 1_pInt : t * ns )
2012-01-17 15:56:57 +05:30
!*** calculate the dislocation stress of the neighboring excess dislocation densities
2012-03-12 19:39:37 +05:30
!*** zero for material points of local plasticity
2012-01-17 15:56:57 +05:30
constitutive_nonlocal_dislocationstress = 0.0_pReal
2012-03-12 19:39:37 +05:30
if ( . not . phase_localPlasticity ( phase ) ) then
2012-02-03 18:20:54 +05:30
call math_invert33 ( Fe ( 1 : 3 , 1 : 3 , g , ip , el ) , invFe , detFe , inversionError )
2012-01-17 15:56:57 +05:30
!* in case of periodic surfaces we have to find out how many periodic images in each direction we need
2012-02-23 22:13:17 +05:30
do dir = 1_pInt , 3_pInt
2012-01-17 15:56:57 +05:30
maxCoord ( dir ) = maxval ( mesh_node0 ( dir , : ) )
minCoord ( dir ) = minval ( mesh_node0 ( dir , : ) )
enddo
meshSize = maxCoord - minCoord
2012-11-06 20:07:13 +05:30
coords = mesh_cellCenterCoordinates ( ip , el )
2012-01-17 15:56:57 +05:30
periodicImages = 0_pInt
2012-02-23 22:13:17 +05:30
do dir = 1_pInt , 3_pInt
2012-01-17 15:56:57 +05:30
if ( mesh_periodicSurface ( dir ) ) then
2013-05-24 01:26:36 +05:30
periodicImages ( 1 , dir ) = floor ( ( coords ( dir ) - cutoffRadius ( instance ) - minCoord ( dir ) ) / meshSize ( dir ) , pInt )
periodicImages ( 2 , dir ) = ceiling ( ( coords ( dir ) + cutoffRadius ( instance ) - maxCoord ( dir ) ) / meshSize ( dir ) , pInt )
2012-01-17 15:56:57 +05:30
endif
enddo
!* loop through all material points (also through their periodic images if present),
!* but only consider nonlocal neighbors within a certain cutoff radius R
2012-02-23 22:13:17 +05:30
do neighboring_el = 1_pInt , mesh_NcpElems
2012-11-16 04:15:20 +05:30
ipLoop : do neighboring_ip = 1_pInt , FE_Nips ( FE_geomtype ( mesh_element ( 2 , neighboring_el ) ) )
2012-01-17 15:56:57 +05:30
neighboring_phase = material_phase ( g , neighboring_ip , neighboring_el )
2012-03-12 19:39:37 +05:30
if ( phase_localPlasticity ( neighboring_phase ) ) then
2012-01-17 15:56:57 +05:30
cycle
endif
2012-03-12 19:39:37 +05:30
neighboring_instance = phase_plasticityInstance ( neighboring_phase )
2012-01-17 15:56:57 +05:30
neighboring_latticeStruct = constitutive_nonlocal_structure ( neighboring_instance )
2013-05-24 01:26:36 +05:30
neighboring_ns = totalNslip ( neighboring_instance )
2012-01-26 19:20:00 +05:30
call math_invert33 ( Fe ( 1 : 3 , 1 : 3 , 1 , neighboring_ip , neighboring_el ) , neighboring_invFe , detFe , inversionError )
2012-01-17 15:56:57 +05:30
neighboring_ipVolumeSideLength = mesh_ipVolume ( neighboring_ip , neighboring_el ) ** ( 1.0_pReal / 3.0_pReal ) ! reference volume used here
2012-02-23 22:13:17 +05:30
forall ( s = 1_pInt : neighboring_ns , c = 1_pInt : 2_pInt ) &
neighboring_rhoExcess ( c , 1 , s ) = state ( g , neighboring_ip , neighboring_el ) % p ( ( 2_pInt * c - 2_pInt ) * neighboring_ns + s ) & ! positive mobiles
- state ( g , neighboring_ip , neighboring_el ) % p ( ( 2_pInt * c - 1_pInt ) * neighboring_ns + s ) ! negative mobiles
forall ( s = 1_pInt : neighboring_ns , c = 1_pInt : 2_pInt ) &
neighboring_rhoExcess ( c , 2 , s ) = abs ( state ( g , neighboring_ip , neighboring_el ) % p ( ( 2_pInt * c + 2_pInt ) * neighboring_ns + s ) ) & ! positive deads
- abs ( state ( g , neighboring_ip , neighboring_el ) % p ( ( 2_pInt * c + 3_pInt ) * neighboring_ns + s ) ) ! negative deads
2012-01-17 15:56:57 +05:30
Tdislo_neighboringLattice = 0.0_pReal
do deltaX = periodicImages ( 1 , 1 ) , periodicImages ( 2 , 1 )
do deltaY = periodicImages ( 1 , 2 ) , periodicImages ( 2 , 2 )
do deltaZ = periodicImages ( 1 , 3 ) , periodicImages ( 2 , 3 )
!* regular case
if ( neighboring_el / = el . or . neighboring_ip / = ip &
. or . deltaX / = 0_pInt . or . deltaY / = 0_pInt . or . deltaZ / = 0_pInt ) then
2012-11-06 20:07:13 +05:30
neighboring_coords = mesh_cellCenterCoordinates ( neighboring_ip , neighboring_el ) &
+ ( / real ( deltaX , pReal ) , real ( deltaY , pReal ) , real ( deltaZ , pReal ) / ) * meshSize
connection = neighboring_coords - coords
2012-01-17 15:56:57 +05:30
distance = sqrt ( sum ( connection * connection ) )
2013-05-24 01:26:36 +05:30
if ( distance > cutoffRadius ( instance ) ) then
2012-01-17 15:56:57 +05:30
cycle
endif
!* the segment length is the minimum of the third root of the control volume and the ip distance
!* this ensures, that the central MP never sits on a neighboring dislocation segment
connection_neighboringLattice = math_mul33x3 ( neighboring_invFe , connection )
segmentLength = min ( neighboring_ipVolumeSideLength , distance )
2010-10-12 18:38:54 +05:30
2012-01-17 15:56:57 +05:30
!* loop through all slip systems of the neighboring material point
!* and add up the stress contributions from egde and screw excess on these slip systems (if significant)
2012-02-23 22:13:17 +05:30
do s = 1_pInt , neighboring_ns
2013-05-24 01:26:36 +05:30
if ( all ( abs ( neighboring_rhoExcess ( : , : , s ) ) < significantRho ( instance ) ) ) then
2012-01-17 15:56:57 +05:30
cycle ! not significant
endif
!* map the connection vector from the lattice into the slip system frame
2013-05-24 01:26:36 +05:30
connection_neighboringSlip = math_mul33x3 ( lattice2slip ( 1 : 3 , 1 : 3 , s , neighboring_instance ) , &
2012-01-17 15:56:57 +05:30
connection_neighboringLattice )
!* edge contribution to stress
sigma = 0.0_pReal
x = connection_neighboringSlip ( 1 )
y = connection_neighboringSlip ( 2 )
z = connection_neighboringSlip ( 3 )
xsquare = x * x
ysquare = y * y
zsquare = z * z
2012-02-23 22:13:17 +05:30
do j = 1_pInt , 2_pInt
2013-05-24 01:26:36 +05:30
if ( abs ( neighboring_rhoExcess ( 1 , j , s ) ) < significantRho ( instance ) ) then
2012-01-17 15:56:57 +05:30
cycle
2012-02-23 22:13:17 +05:30
elseif ( j > 1_pInt ) then
2012-01-17 15:56:57 +05:30
x = connection_neighboringSlip ( 1 ) + sign ( 0.5_pReal * segmentLength , &
state ( g , neighboring_ip , neighboring_el ) % p ( 4 * neighboring_ns + s ) &
- state ( g , neighboring_ip , neighboring_el ) % p ( 5 * neighboring_ns + s ) )
xsquare = x * x
endif
flipSign = sign ( 1.0_pReal , - y )
2012-02-23 22:13:17 +05:30
do side = 1_pInt , - 1_pInt , - 2_pInt
2012-01-17 15:56:57 +05:30
lambda = real ( side , pReal ) * 0.5_pReal * segmentLength - y
R = sqrt ( xsquare + zsquare + lambda * lambda )
Rsquare = R * R
Rcube = Rsquare * R
denominator = R * ( R + flipSign * lambda )
if ( denominator == 0.0_pReal ) then
exit ipLoop
endif
2013-05-24 01:26:36 +05:30
sigma ( 1 , 1 ) = sigma ( 1 , 1 ) - real ( side , pReal ) &
* flipSign * z / denominator &
* ( 1.0_pReal + xsquare / Rsquare + xsquare / denominator ) &
* neighboring_rhoExcess ( 1 , j , s )
sigma ( 2 , 2 ) = sigma ( 2 , 2 ) - real ( side , pReal ) &
* ( flipSign * 2.0_pReal * nu ( instance ) * z / denominator + z * lambda / Rcube ) &
* neighboring_rhoExcess ( 1 , j , s )
sigma ( 3 , 3 ) = sigma ( 3 , 3 ) + real ( side , pReal ) &
* flipSign * z / denominator &
* ( 1.0_pReal - zsquare / Rsquare - zsquare / denominator ) &
* neighboring_rhoExcess ( 1 , j , s )
sigma ( 1 , 2 ) = sigma ( 1 , 2 ) + real ( side , pReal ) &
* x * z / Rcube * neighboring_rhoExcess ( 1 , j , s )
sigma ( 1 , 3 ) = sigma ( 1 , 3 ) + real ( side , pReal ) &
* flipSign * x / denominator &
* ( 1.0_pReal - zsquare / Rsquare - zsquare / denominator ) &
* neighboring_rhoExcess ( 1 , j , s )
sigma ( 2 , 3 ) = sigma ( 2 , 3 ) - real ( side , pReal ) &
* ( nu ( instance ) / R - zsquare / Rcube ) * neighboring_rhoExcess ( 1 , j , s )
2012-01-17 15:56:57 +05:30
enddo
enddo
!* screw contribution to stress
x = connection_neighboringSlip ( 1 ) ! have to restore this value, because position might have been adapted for edge deads before
2012-02-23 22:13:17 +05:30
do j = 1_pInt , 2_pInt
2013-05-24 01:26:36 +05:30
if ( abs ( neighboring_rhoExcess ( 2 , j , s ) ) < significantRho ( instance ) ) then
2012-01-17 15:56:57 +05:30
cycle
2012-02-23 22:13:17 +05:30
elseif ( j > 1_pInt ) then
2012-01-17 15:56:57 +05:30
y = connection_neighboringSlip ( 2 ) + sign ( 0.5_pReal * segmentLength , &
2012-02-23 22:13:17 +05:30
state ( g , neighboring_ip , neighboring_el ) % p ( 6_pInt * neighboring_ns + s ) &
- state ( g , neighboring_ip , neighboring_el ) % p ( 7_pInt * neighboring_ns + s ) )
2012-01-17 15:56:57 +05:30
ysquare = y * y
endif
2010-03-18 17:53:17 +05:30
2012-01-17 15:56:57 +05:30
flipSign = sign ( 1.0_pReal , x )
2012-02-23 22:13:17 +05:30
do side = 1_pInt , - 1_pInt , - 2_pInt
2012-01-17 15:56:57 +05:30
lambda = x + real ( side , pReal ) * 0.5_pReal * segmentLength
R = sqrt ( ysquare + zsquare + lambda * lambda )
Rsquare = R * R
Rcube = Rsquare * R
denominator = R * ( R + flipSign * lambda )
if ( denominator == 0.0_pReal ) then
exit ipLoop
endif
2013-05-24 01:26:36 +05:30
sigma ( 1 , 2 ) = sigma ( 1 , 2 ) - real ( side , pReal ) * flipSign * z * ( 1.0_pReal - nu ( instance ) ) / denominator &
2012-01-17 15:56:57 +05:30
* neighboring_rhoExcess ( 2 , j , s )
2013-05-24 01:26:36 +05:30
sigma ( 1 , 3 ) = sigma ( 1 , 3 ) + real ( side , pReal ) * flipSign * y * ( 1.0_pReal - nu ( instance ) ) / denominator &
2012-01-17 15:56:57 +05:30
* neighboring_rhoExcess ( 2 , j , s )
enddo
enddo
if ( all ( abs ( sigma ) < 1.0e-10_pReal ) ) then ! SIGMA IS NOT A REAL STRESS, THATS WHY WE NEED A REALLY SMALL VALUE HERE
cycle
endif
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
2012-01-17 15:56:57 +05:30
!* copy symmetric parts
sigma ( 2 , 1 ) = sigma ( 1 , 2 )
sigma ( 3 , 1 ) = sigma ( 1 , 3 )
sigma ( 3 , 2 ) = sigma ( 2 , 3 )
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
2012-01-17 15:56:57 +05:30
!* scale stresses and map them into the neighboring material point's lattice configuration
2013-05-24 01:26:36 +05:30
sigma = sigma * mu ( neighboring_instance ) * burgers ( s , neighboring_instance ) &
/ ( 4.0_pReal * pi * ( 1.0_pReal - nu ( instance ) ) ) &
2012-01-17 15:56:57 +05:30
* mesh_ipVolume ( neighboring_ip , neighboring_el ) / segmentLength ! reference volume is used here (according to the segment length calculation)
Tdislo_neighboringLattice = Tdislo_neighboringLattice &
2013-05-24 01:26:36 +05:30
+ math_mul33x33 ( math_transpose33 ( lattice2slip ( 1 : 3 , 1 : 3 , s , neighboring_instance ) ) , &
math_mul33x33 ( sigma , lattice2slip ( 1 : 3 , 1 : 3 , s , neighboring_instance ) ) )
2012-01-17 15:56:57 +05:30
enddo ! slip system loop
2009-12-15 13:50:31 +05:30
2012-01-17 15:56:57 +05:30
!* special case of central ip volume
!* only consider dead dislocations
!* we assume that they all sit at a distance equal to half the third root of V
!* in direction of the according slip direction
else
2012-02-23 22:13:17 +05:30
forall ( s = 1_pInt : ns , c = 1_pInt : 2_pInt ) &
rhoExcessDead ( c , s ) = state ( g , ip , el ) % p ( ( 2_pInt * c + 2_pInt ) * ns + s ) & ! positive deads (here we use symmetry: if this has negative sign it is treated as negative density at positive position instead of positive density at negative position)
+ state ( g , ip , el ) % p ( ( 2_pInt * c + 3_pInt ) * ns + s ) ! negative deads (here we use symmetry: if this has negative sign it is treated as positive density at positive position instead of negative density at negative position)
do s = 1_pInt , ns
2013-05-24 01:26:36 +05:30
if ( all ( abs ( rhoExcessDead ( : , s ) ) < significantRho ( instance ) ) ) then
2012-01-17 15:56:57 +05:30
cycle ! not significant
endif
sigma = 0.0_pReal ! all components except for sigma13 are zero
2013-05-24 01:26:36 +05:30
sigma ( 1 , 3 ) = - ( rhoExcessDead ( 1 , s ) + rhoExcessDead ( 2 , s ) * ( 1.0_pReal - nu ( instance ) ) ) &
* neighboring_ipVolumeSideLength * mu ( instance ) * burgers ( s , instance ) &
/ ( sqrt ( 2.0_pReal ) * pi * ( 1.0_pReal - nu ( instance ) ) )
2012-01-17 15:56:57 +05:30
sigma ( 3 , 1 ) = sigma ( 1 , 3 )
Tdislo_neighboringLattice = Tdislo_neighboringLattice &
2013-05-24 01:26:36 +05:30
+ math_mul33x33 ( math_transpose33 ( lattice2slip ( 1 : 3 , 1 : 3 , s , instance ) ) , &
math_mul33x33 ( sigma , lattice2slip ( 1 : 3 , 1 : 3 , s , instance ) ) )
2012-01-17 15:56:57 +05:30
enddo ! slip system loop
2009-12-15 13:50:31 +05:30
2012-01-17 15:56:57 +05:30
endif
2009-08-11 22:01:57 +05:30
2012-01-17 15:56:57 +05:30
enddo ! deltaZ loop
enddo ! deltaY loop
enddo ! deltaX loop
2009-08-11 22:01:57 +05:30
2012-01-17 15:56:57 +05:30
!* map the stress from the neighboring MP's lattice configuration into the deformed configuration
!* and back into my lattice configuration
2009-08-11 22:01:57 +05:30
2012-01-17 15:56:57 +05:30
neighboringLattice2myLattice = math_mul33x33 ( invFe , Fe ( 1 : 3 , 1 : 3 , 1 , neighboring_ip , neighboring_el ) )
constitutive_nonlocal_dislocationstress = constitutive_nonlocal_dislocationstress &
+ math_mul33x33 ( neighboringLattice2myLattice , &
math_mul33x33 ( Tdislo_neighboringLattice , &
2012-01-26 19:20:00 +05:30
math_transpose33 ( neighboringLattice2myLattice ) ) )
2012-01-17 15:56:57 +05:30
enddo ipLoop
enddo ! element loop
endif
2009-08-11 22:01:57 +05:30
endfunction
!*********************************************************************
!* return array of constitutive results *
!*********************************************************************
2011-02-25 15:23:20 +05:30
function constitutive_nonlocal_postResults ( Tstar_v , Fe , Temperature , dt , state , dotState , g , ip , el )
2009-08-11 22:01:57 +05:30
2012-01-26 19:20:00 +05:30
use math , only : math_mul6x6 , &
2009-12-15 13:50:31 +05:30
math_mul33x3 , &
math_mul33x33 , &
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 , &
2012-09-04 22:26:37 +05:30
mesh_maxNips , &
mesh_ipVolume
2009-08-24 13:46:01 +05:30
use material , only : homogenization_maxNgrains , &
material_phase , &
2012-03-12 19:39:37 +05:30
phase_plasticityInstance , &
2009-08-24 13:46:01 +05:30
phase_Noutput
2012-02-23 22:50:57 +05:30
use lattice , only : lattice_Sslip_v , &
2009-12-15 13:50:31 +05:30
lattice_sd , &
2013-05-23 13:49:36 +05:30
lattice_st , &
lattice_sn
2012-01-17 15:56:57 +05:30
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
2011-02-25 15:23:20 +05:30
dt ! time increment
real ( pReal ) , dimension ( 6 ) , intent ( in ) :: Tstar_v ! current 2nd Piola-Kirchhoff stress in Mandel notation
2012-01-17 15:56:57 +05:30
real ( pReal ) , dimension ( 3 , 3 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
Fe ! elastic deformation gradient
2009-12-15 13:50:31 +05:30
type ( p_vec ) , dimension ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , intent ( in ) :: &
2012-01-17 15:56:57 +05:30
state ! current microstructural state
type ( p_vec ) , intent ( in ) :: dotState ! evolution rate of microstructural state
2009-08-24 13:46:01 +05:30
!*** output variables
2012-03-12 19:39:37 +05:30
real ( pReal ) , dimension ( constitutive_nonlocal_sizePostResults ( phase_plasticityInstance ( 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
2012-03-12 19:39:37 +05:30
integer ( pInt ) myInstance , & ! current instance of this plasticity
2009-12-15 13:50:31 +05:30
myStructure , & ! current lattice structure
ns , & ! short notation for the total number of active slip systems
c , & ! character of dislocation
cs , & ! constitutive result index
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
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) , 8 ) :: &
2010-01-05 21:37:24 +05:30
rhoSgl , & ! current single dislocation densities (positive/negative screw and edge without dipoles)
rhoDotSgl ! evolution rate of single dislocation densities (positive/negative screw and edge without dipoles)
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) , 4 ) :: &
2011-11-04 18:42:17 +05:30
gdot , & ! shear rates
v ! velocities
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( 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
2012-11-30 00:14:00 +05:30
tauBack ! back stress from pileups on same slip system
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) , 2 ) :: &
2009-12-15 13:50:31 +05:30
rhoDip , & ! current 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
2011-02-25 15:23:20 +05:30
dUpper ! current maximum stable dipole distance for edges and screws
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( 3 , totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) , 2 ) :: &
2010-02-17 18:51:36 +05:30
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
2013-05-24 01:26:36 +05:30
real ( pReal ) , dimension ( 3 , totalNslip ( phase_plasticityInstance ( material_phase ( g , ip , el ) ) ) ) :: &
2013-05-23 13:49:36 +05:30
n_currentconf ! slip system normal (unit vector) in current configuration
2011-09-07 17:00:28 +05:30
real ( pReal ) , dimension ( 3 , 3 ) :: sigma
2009-08-24 13:46:01 +05:30
2012-03-12 19:39:37 +05:30
myInstance = phase_plasticityInstance ( material_phase ( g , ip , el ) )
2009-08-24 13:46:01 +05:30
myStructure = constitutive_nonlocal_structure ( myInstance )
2013-05-24 01:26:36 +05:30
ns = 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
2012-08-23 11:18:21 +05:30
forall ( s = 1_pInt : ns , t = 1_pInt : 4_pInt ) &
rhoSgl ( s , t ) = max ( state ( g , ip , el ) % p ( ( t - 1_pInt ) * ns + s ) , 0.0_pReal )
forall ( s = 1_pInt : ns , t = 5_pInt : 8_pInt ) &
rhoSgl ( s , t ) = state ( g , ip , el ) % p ( ( t - 1_pInt ) * ns + s )
forall ( c = 1_pInt : 2_pInt ) &
rhoDip ( 1 : ns , c ) = max ( state ( g , ip , el ) % p ( ( 7_pInt + c ) * ns + 1_pInt : ( 8_pInt + c ) * ns ) , 0.0_pReal )
2013-04-04 19:07:14 +05:30
rhoForest = state ( g , ip , el ) % p ( 11_pInt * ns + 1 : 12_pInt * ns )
tauThreshold = state ( g , ip , el ) % p ( 12_pInt * ns + 1 : 13_pInt * ns )
tauBack = state ( g , ip , el ) % p ( 13_pInt * ns + 1 : 14_pInt * ns )
2012-02-23 22:13:17 +05:30
forall ( t = 1_pInt : 8_pInt ) rhoDotSgl ( 1 : ns , t ) = dotState % p ( ( t - 1_pInt ) * ns + 1_pInt : t * ns )
forall ( c = 1_pInt : 2_pInt ) rhoDotDip ( 1 : ns , c ) = dotState % p ( ( 7_pInt + c ) * ns + 1_pInt : ( 8_pInt + c ) * ns )
2013-04-04 19:07:14 +05:30
forall ( t = 1_pInt : 4_pInt ) v ( 1 : ns , t ) = state ( g , ip , el ) % p ( ( 13_pInt + t ) * ns + 1_pInt : ( 14_pInt + t ) * ns )
2013-05-24 01:26:36 +05:30
where ( abs ( rhoSgl ) * mesh_ipVolume ( ip , el ) ** 0.667_pReal < significantN ( myInstance ) &
. or . abs ( rhoSgl ) < significantRho ( myInstance ) ) &
2012-10-02 18:27:24 +05:30
rhoSgl = 0.0_pReal
2013-05-24 01:26:36 +05:30
where ( abs ( rhoDip ) * mesh_ipVolume ( ip , el ) ** 0.667_pReal < significantN ( myInstance ) &
. or . abs ( rhoDip ) < significantRho ( myInstance ) ) &
2012-10-02 18:27:24 +05:30
rhoDip = 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
2012-08-23 11:18:21 +05:30
2010-01-06 15:24:00 +05:30
!* Calculate shear rate
2012-02-23 22:13:17 +05:30
forall ( t = 1_pInt : 4_pInt ) &
2013-05-24 01:26:36 +05:30
gdot ( 1 : ns , t ) = rhoSgl ( 1 : ns , t ) * burgers ( 1 : ns , myInstance ) * v ( 1 : ns , 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
2011-11-04 18:42:17 +05:30
2011-02-25 15:23:20 +05:30
!* calculate limits for stable dipole height
2010-01-06 15:24:00 +05:30
2012-02-23 22:13:17 +05:30
do s = 1_pInt , ns
2013-05-24 01:26:36 +05:30
sLattice = slipSystemLattice ( s , myInstance )
2013-01-22 04:41:16 +05:30
tau ( s ) = math_mul6x6 ( Tstar_v , lattice_Sslip_v ( 1 : 6 , 1 , sLattice , myStructure ) ) + tauBack ( s )
2012-10-29 18:32:01 +05:30
if ( abs ( tau ( s ) ) < 1.0e-15_pReal ) tau ( s ) = 1.0e-15_pReal
2010-02-17 18:51:36 +05:30
enddo
2013-05-24 01:26:36 +05:30
dLower = minDipoleHeight ( 1 : ns , 1 : 2 , myInstance )
dUpper ( 1 : ns , 1 ) = mu ( myInstance ) * burgers ( 1 : ns , myInstance ) &
/ ( 8.0_pReal * pi * ( 1.0_pReal - nu ( myInstance ) ) * abs ( tau ) )
dUpper ( 1 : ns , 2 ) = mu ( myInstance ) * burgers ( 1 : ns , myInstance ) &
2012-07-24 20:20:11 +05:30
/ ( 4.0_pReal * pi * abs ( tau ) )
forall ( c = 1_pInt : 2_pInt ) &
2012-10-29 18:32:01 +05:30
dUpper ( 1 : ns , c ) = min ( 1.0_pReal / sqrt ( rhoSgl ( 1 : ns , 2 * c - 1 ) + rhoSgl ( 1 : ns , 2 * c ) &
2013-05-24 01:26:36 +05:30
+ abs ( rhoSgl ( 1 : ns , 2 * c + 3 ) ) + abs ( rhoSgl ( 1 : ns , 2 * c + 4 ) ) + rhoDip ( 1 : ns , c ) ) , &
2012-10-29 18:32:01 +05:30
dUpper ( 1 : ns , c ) )
2012-08-16 16:33:22 +05:30
dUpper = max ( dUpper , dLower )
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
2010-02-17 18:51:36 +05:30
!*** dislocation motion
2009-12-15 13:50:31 +05:30
2013-05-24 01:26:36 +05:30
m ( 1 : 3 , 1 : ns , 1 ) = lattice_sd ( 1 : 3 , slipSystemLattice ( 1 : ns , myInstance ) , myStructure )
m ( 1 : 3 , 1 : ns , 2 ) = - lattice_st ( 1 : 3 , slipSystemLattice ( 1 : ns , myInstance ) , myStructure )
2012-02-23 22:13:17 +05:30
forall ( c = 1_pInt : 2_pInt , s = 1_pInt : ns ) &
2013-05-23 20:22:57 +05:30
m_currentconf ( 1 : 3 , s , c ) = math_mul33x3 ( Fe ( 1 : 3 , 1 : 3 , g , ip , el ) , m ( 1 : 3 , s , c ) )
2013-05-23 13:49:36 +05:30
forall ( s = 1_pInt : ns ) &
2013-05-23 20:22:57 +05:30
n_currentconf ( 1 : 3 , s ) = math_mul33x3 ( Fe ( 1 : 3 , 1 : 3 , g , ip , el ) , &
2013-05-24 01:26:36 +05:30
lattice_sn ( 1 : 3 , slipSystemLattice ( s , myInstance ) , myStructure ) )
2009-12-15 13:50:31 +05:30
2012-02-23 22:13:17 +05:30
do o = 1_pInt , phase_Noutput ( material_phase ( g , ip , el ) )
2009-08-24 13:46:01 +05:30
select case ( constitutive_nonlocal_output ( o , myInstance ) )
case ( 'rho' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = sum ( abs ( rhoSgl ) , 2 )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_mobile' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = sum ( rhoSgl ( 1 : ns , 5 : 8 ) , 2 )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_dip' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = sum ( 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-08-23 11:18:21 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = state ( g , ip , el ) % p ( 1 : ns )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_edge_pos_immobile' )
2012-08-23 11:18:21 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = state ( g , ip , el ) % p ( 4 * ns + 1 : 5 * ns )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_edge_neg' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-08-23 11:18:21 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = state ( g , ip , el ) % p ( ns + 1 : 2 * ns )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_edge_neg_immobile' )
2012-08-23 11:18:21 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = state ( g , ip , el ) % p ( 5 * ns + 1 : 6 * ns )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_dip_edge' )
2012-08-23 11:18:21 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = state ( g , ip , el ) % p ( 8 * ns + 1 : 9 * ns )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2009-08-24 13:46:01 +05:30
case ( 'rho_screw' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = sum ( rhoSgl ( 1 : ns , 7 : 8 ) , 2 )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_screw_pos' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-08-23 11:18:21 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = state ( g , ip , el ) % p ( 2 * ns + 1 : 3 * ns )
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' )
2012-08-23 11:18:21 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = state ( g , ip , el ) % p ( 6 * ns + 1 : 7 * ns )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_screw_neg' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-08-23 11:18:21 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = state ( g , ip , el ) % p ( 3 * ns + 1 : 4 * ns )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_sgl_screw_neg_immobile' )
2012-08-23 11:18:21 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = state ( g , ip , el ) % p ( 7 * ns + 1 : 8 * ns )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_dip_screw' )
2012-08-23 11:18:21 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = state ( g , ip , el ) % p ( 9 * ns + 1 : 10 * ns )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2009-08-28 19:20:47 +05:30
case ( 'excess_rho' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoForest
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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = tau
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
cs = cs + ns
2009-08-24 13:46:01 +05:30
2012-01-17 15:56:57 +05:30
case ( 'resolvedstress_back' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = tauBack
2010-02-17 18:51:36 +05:30
cs = cs + ns
case ( 'resolvedstress_external' )
2012-02-23 22:13:17 +05:30
do s = 1_pInt , ns
2013-05-24 01:26:36 +05:30
sLattice = slipSystemLattice ( s , myInstance )
2013-01-22 04:41:16 +05:30
constitutive_nonlocal_postResults ( cs + s ) = math_mul6x6 ( Tstar_v , lattice_Sslip_v ( 1 : 6 , 1 , sLattice , myStructure ) )
2010-02-17 18:51:36 +05:30
enddo
cs = cs + ns
2009-08-24 13:46:01 +05:30
case ( 'resistance' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = sum ( rhoDotSgl , 2 ) + sum ( rhoDotDip , 2 )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_dot_sgl' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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' )
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoDotMultiplicationOutput ( 1 : ns , 1 , g , ip , el ) &
+ rhoDotMultiplicationOutput ( 1 : ns , 2 , g , ip , el )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_dot_gen_edge' )
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoDotMultiplicationOutput ( 1 : ns , 1 , g , ip , el )
2010-01-05 21:37:24 +05:30
cs = cs + ns
case ( 'rho_dot_gen_screw' )
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoDotMultiplicationOutput ( 1 : ns , 2 , 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
cs = cs + ns
case ( 'rho_dot_sgl2dip' )
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoDotSingle2DipoleGlideOutput ( 1 : ns , 1 , g , ip , el ) &
+ rhoDotSingle2DipoleGlideOutput ( 1 : ns , 2 , 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
cs = cs + ns
2012-08-27 21:27:31 +05:30
case ( 'rho_dot_sgl2dip_edge' )
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoDotSingle2DipoleGlideOutput ( 1 : ns , 1 , g , ip , el )
2012-08-27 21:27:31 +05:30
cs = cs + ns
case ( 'rho_dot_sgl2dip_screw' )
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoDotSingle2DipoleGlideOutput ( 1 : ns , 2 , g , ip , el )
2012-08-27 21:27:31 +05:30
cs = cs + 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
case ( 'rho_dot_ann_ath' )
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoDotAthermalAnnihilationOutput ( 1 : ns , 1 , g , ip , el ) &
+ rhoDotAthermalAnnihilationOutput ( 1 : ns , 2 , 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
cs = cs + ns
case ( 'rho_dot_ann_the' )
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoDotThermalAnnihilationOutput ( 1 : ns , 1 , g , ip , el ) &
+ rhoDotThermalAnnihilationOutput ( 1 : ns , 2 , g , ip , el )
2012-08-16 16:33:22 +05:30
cs = cs + ns
case ( 'rho_dot_ann_the_edge' )
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoDotThermalAnnihilationOutput ( 1 : ns , 1 , g , ip , el )
2012-08-16 16:33:22 +05:30
cs = cs + ns
case ( 'rho_dot_ann_the_screw' )
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoDotThermalAnnihilationOutput ( 1 : ns , 2 , g , ip , el )
2012-08-16 16:33:22 +05:30
cs = cs + ns
2012-11-28 17:39:48 +05:30
case ( 'rho_dot_edgejogs' )
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoDotEdgeJogsOutput ( 1 : ns , g , ip , el )
2012-11-28 17:39:48 +05:30
cs = cs + ns
2010-03-10 15:19:40 +05:30
case ( 'rho_dot_flux' )
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = sum ( rhoDotFluxOutput ( 1 : ns , 1 : 4 , g , ip , el ) , 2 ) &
+ sum ( abs ( rhoDotFluxOutput ( 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' )
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = sum ( rhoDotFluxOutput ( 1 : ns , 1 : 2 , g , ip , el ) , 2 ) &
+ sum ( abs ( rhoDotFluxOutput ( 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' )
2013-05-24 01:26:36 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = sum ( rhoDotFluxOutput ( 1 : ns , 3 : 4 , g , ip , el ) , 2 ) &
+ sum ( abs ( rhoDotFluxOutput ( 1 : ns , 7 : 8 , g , ip , el ) ) , 2 )
2010-05-21 14:21:15 +05:30
cs = cs + ns
2012-01-26 13:13:36 +05:30
case ( 'velocity_edge_pos' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = v ( 1 : ns , 1 )
2010-02-23 22:53:07 +05:30
cs = cs + ns
2012-01-26 13:13:36 +05:30
case ( 'velocity_edge_neg' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = v ( 1 : ns , 2 )
2012-01-26 13:13:36 +05:30
cs = cs + ns
case ( 'velocity_screw_pos' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = v ( 1 : ns , 3 )
2011-11-09 14:52:52 +05:30
cs = cs + ns
2012-01-26 13:13:36 +05:30
case ( 'velocity_screw_neg' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = v ( 1 : ns , 4 )
2012-01-26 13:13:36 +05:30
cs = cs + ns
2013-05-23 13:49:36 +05:30
case ( 'slipdirection.x' )
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = m_currentconf ( 1 , 1 : ns , 1 )
cs = cs + ns
case ( 'slipdirection.y' )
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = m_currentconf ( 2 , 1 : ns , 1 )
cs = cs + ns
case ( 'slipdirection.z' )
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = m_currentconf ( 3 , 1 : ns , 1 )
cs = cs + ns
case ( 'slipnormal.x' )
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = n_currentconf ( 1 , 1 : ns )
cs = cs + ns
case ( 'slipnormal.y' )
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = n_currentconf ( 2 , 1 : ns )
cs = cs + ns
case ( 'slipnormal.z' )
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = n_currentconf ( 3 , 1 : ns )
cs = cs + ns
case ( 'fluxdensity_edge_pos.x' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoSgl ( 1 : ns , 1 ) * v ( 1 : ns , 1 ) * m_currentconf ( 1 , 1 : ns , 1 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2013-05-23 13:49:36 +05:30
case ( 'fluxdensity_edge_pos.y' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoSgl ( 1 : ns , 1 ) * v ( 1 : ns , 1 ) * m_currentconf ( 2 , 1 : ns , 1 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2013-05-23 13:49:36 +05:30
case ( 'fluxdensity_edge_pos.z' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoSgl ( 1 : ns , 1 ) * v ( 1 : ns , 1 ) * m_currentconf ( 3 , 1 : ns , 1 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2013-05-23 13:49:36 +05:30
case ( 'fluxdensity_edge_neg.x' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = - rhoSgl ( 1 : ns , 2 ) * v ( 1 : ns , 2 ) * m_currentconf ( 1 , 1 : ns , 1 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2013-05-23 13:49:36 +05:30
case ( 'fluxdensity_edge_neg.y' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = - rhoSgl ( 1 : ns , 2 ) * v ( 1 : ns , 2 ) * m_currentconf ( 2 , 1 : ns , 1 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2013-05-23 13:49:36 +05:30
case ( 'fluxdensity_edge_neg.z' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = - rhoSgl ( 1 : ns , 2 ) * v ( 1 : ns , 2 ) * m_currentconf ( 3 , 1 : ns , 1 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2013-05-23 13:49:36 +05:30
case ( 'fluxdensity_screw_pos.x' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoSgl ( 1 : ns , 3 ) * v ( 1 : ns , 3 ) * m_currentconf ( 1 , 1 : ns , 2 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2013-05-23 13:49:36 +05:30
case ( 'fluxdensity_screw_pos.y' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoSgl ( 1 : ns , 3 ) * v ( 1 : ns , 3 ) * m_currentconf ( 2 , 1 : ns , 2 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2013-05-23 13:49:36 +05:30
case ( 'fluxdensity_screw_pos.z' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = rhoSgl ( 1 : ns , 3 ) * v ( 1 : ns , 3 ) * m_currentconf ( 3 , 1 : ns , 2 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2013-05-23 13:49:36 +05:30
case ( 'fluxdensity_screw_neg.x' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = - rhoSgl ( 1 : ns , 4 ) * v ( 1 : ns , 4 ) * m_currentconf ( 1 , 1 : ns , 2 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2013-05-23 13:49:36 +05:30
case ( 'fluxdensity_screw_neg.y' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = - rhoSgl ( 1 : ns , 4 ) * v ( 1 : ns , 4 ) * m_currentconf ( 2 , 1 : ns , 2 )
2009-12-15 13:50:31 +05:30
cs = cs + ns
2013-05-23 13:49:36 +05:30
case ( 'fluxdensity_screw_neg.z' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = - rhoSgl ( 1 : ns , 4 ) * v ( 1 : ns , 4 ) * 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
2012-01-25 22:34:37 +05:30
case ( 'maximumdipoleheight_edge' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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
2012-01-25 22:34:37 +05:30
case ( 'maximumdipoleheight_screw' )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : 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
2011-09-07 17:00:28 +05:30
2012-01-17 15:56:57 +05:30
case ( 'dislocationstress' )
sigma = constitutive_nonlocal_dislocationstress ( state , Fe , g , ip , el )
2012-02-23 22:13:17 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt ) = sigma ( 1 , 1 )
constitutive_nonlocal_postResults ( cs + 2_pInt ) = sigma ( 2 , 2 )
constitutive_nonlocal_postResults ( cs + 3_pInt ) = sigma ( 3 , 3 )
constitutive_nonlocal_postResults ( cs + 4_pInt ) = sigma ( 1 , 2 )
constitutive_nonlocal_postResults ( cs + 5_pInt ) = sigma ( 2 , 3 )
constitutive_nonlocal_postResults ( cs + 6_pInt ) = sigma ( 3 , 1 )
2011-09-07 17:00:28 +05:30
cs = cs + 6_pInt
2011-11-09 14:52:52 +05:30
case ( 'accumulatedshear' )
2013-04-04 19:07:14 +05:30
constitutive_nonlocal_postResults ( cs + 1_pInt : cs + ns ) = state ( g , ip , el ) % p ( 10 * ns + 1 : 11 * ns )
2011-11-09 14:52:52 +05:30
cs = cs + ns
2012-10-29 18:19:28 +05:30
case ( 'boundarylayer' )
do s = 1_pInt , ns
if ( sum ( abs ( rhoSgl ( s , 1 : 8 ) ) ) > 0.0_pReal ) then
constitutive_nonlocal_postResults ( cs + s ) = maxval ( abs ( rhoSgl ( s , 5 : 8 ) ) / ( rhoSgl ( s , 1 : 4 ) + abs ( rhoSgl ( s , 5 : 8 ) ) ) )
else
constitutive_nonlocal_postResults ( cs + s ) = 0.0_pReal
endif
enddo
cs = cs + ns
2011-11-09 14:52:52 +05:30
2009-08-11 22:01:57 +05:30
end select
enddo
endfunction
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
2009-08-28 19:20:47 +05:30
END MODULE