2013-07-12 12:27:15 +05:30
!--------------------------------------------------------------------------------------------------
! $Id$
!--------------------------------------------------------------------------------------------------
!> @author Alankar Alankar, Max-Planck-Institut für Eisenforschung GmbH
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @brief material subroutine for titanium
!--------------------------------------------------------------------------------------------------
2013-03-28 13:10:30 +05:30
module constitutive_titanmod
use prec , only : &
pReal , &
pInt
2010-07-13 13:49:25 +05:30
2013-07-12 12:27:15 +05:30
implicit none
private
2013-10-08 21:57:26 +05:30
character ( len = 18 ) , dimension ( 3 ) , parameter , private :: &
CONSTITUTIVE_TITANMOD_listBasicSlipStates = &
[ 'rho_edge ' , 'rho_screw ' , 'shear_system' ]
character ( len = 18 ) , dimension ( 1 ) , parameter , private :: &
2013-07-12 12:27:15 +05:30
CONSTITUTIVE_TITANMOD_listBasicTwinStates = [ 'gdot_twin' ]
2013-10-08 21:57:26 +05:30
character ( len = 19 ) , dimension ( 11 ) , parameter , private :: &
CONSTITUTIVE_TITANMOD_listDependentSlipStates = &
[ 'segment_edge ' , 'segment_screw ' , &
'resistance_edge ' , 'resistance_screw ' , &
'tau_slip ' , &
'velocity_edge ' , 'velocity_screw ' , &
'gdot_slip_edge ' , 'gdot_slip_screw ' , &
'stressratio_edge_p ' , 'stressratio_screw_p' ]
character ( len = 18 ) , dimension ( 2 ) , parameter , private :: &
constitutive_titanmod_listDependentTwinStates = &
[ 'twin_fraction' , 'tau_twin ' ]
real ( pReal ) , parameter , private :: &
2014-02-09 22:38:13 +05:30
kB = 1.38e-23_pReal !< Boltzmann constant in J/Kelvin
2013-07-12 12:27:15 +05:30
2010-07-13 13:49:25 +05:30
2013-07-12 12:27:15 +05:30
integer ( pInt ) , dimension ( : ) , allocatable , public , protected :: &
2014-02-09 22:38:13 +05:30
constitutive_titanmod_sizePostResults !< cumulative size of post results
2012-03-09 01:55:28 +05:30
2013-07-12 12:27:15 +05:30
integer ( pInt ) , dimension ( : , : ) , allocatable , target , public :: &
2014-02-09 22:38:13 +05:30
constitutive_titanmod_sizePostResult !< size of each post result output
2012-03-09 01:55:28 +05:30
2013-07-12 12:27:15 +05:30
character ( len = 64 ) , dimension ( : , : ) , allocatable , target , public :: &
2014-02-09 22:38:13 +05:30
constitutive_titanmod_output !< name of each post result output
2012-03-09 01:55:28 +05:30
2014-09-26 15:55:26 +05:30
integer ( pInt ) , dimension ( : ) , allocatable , target , public :: &
2014-03-09 02:20:31 +05:30
constitutive_titanmod_Noutput !< number of outputs per instance of this plasticity !< ID of the lattice structure
2012-03-09 01:55:28 +05:30
2013-10-08 21:57:26 +05:30
integer ( pInt ) , dimension ( : ) , allocatable , private :: &
2014-02-09 22:38:13 +05:30
constitutive_titanmod_totalNslip , & !< total number of active slip systems for each instance
constitutive_titanmod_totalNtwin !< total number of active twin systems for each instance
2012-03-09 01:55:28 +05:30
2013-10-08 21:57:26 +05:30
integer ( pInt ) , dimension ( : , : ) , allocatable , private :: &
2014-02-09 22:38:13 +05:30
constitutive_titanmod_Nslip , & !< number of active slip systems for each family and instance
constitutive_titanmod_Ntwin , & !< number of active twin systems for each family and instance
constitutive_titanmod_slipFamily , & !< lookup table relating active slip system to slip family for each instance
constitutive_titanmod_twinFamily , & !< lookup table relating active twin system to twin family for each instance
constitutive_titanmod_slipSystemLattice , & !< lookup table relating active slip system index to lattice slip system index for each instance
constitutive_titanmod_twinSystemLattice !< lookup table relating active twin system index to lattice twin system index for each instance
2012-03-09 01:55:28 +05:30
2013-10-08 21:57:26 +05:30
real ( pReal ) , dimension ( : ) , allocatable , private :: &
2014-02-09 22:38:13 +05:30
constitutive_titanmod_debyefrequency , & !< Debye frequency
constitutive_titanmod_kinkf0 , & !<
constitutive_titanmod_CAtomicVolume , & !< atomic volume in Bugers vector unit
constitutive_titanmod_dc , & !< prefactor for self-diffusion coefficient
constitutive_titanmod_twinhpconstant , & !< activation energy for dislocation climb
constitutive_titanmod_GrainSize , & !< grain size - Not being used
constitutive_titanmod_MaxTwinFraction , & !< maximum allowed total twin volume fraction
constitutive_titanmod_r , & !< r-exponent in twin nucleation rate
constitutive_titanmod_CEdgeDipMinDistance , & !< Not being used
constitutive_titanmod_Cmfptwin , & !< Not being used
constitutive_titanmod_Cthresholdtwin , & !< Not being used
constitutive_titanmod_aTolRho !< absolute tolerance for integration of dislocation density
2012-03-09 01:55:28 +05:30
2013-10-08 21:57:26 +05:30
real ( pReal ) , dimension ( : , : ) , allocatable , private :: &
2014-02-09 22:38:13 +05:30
constitutive_titanmod_rho_edge0 , & !< initial edge dislocation density per slip system for each family and instance
constitutive_titanmod_rho_screw0 , & !< initial screw dislocation density per slip system for each family and instance
constitutive_titanmod_shear_system0 , & !< accumulated shear on each system
constitutive_titanmod_burgersPerSlipFam , & !< absolute length of burgers vector [m] for each slip family and instance
constitutive_titanmod_burgersPerSlipSys , & !< absolute length of burgers vector [m] for each slip system and instance
constitutive_titanmod_burgersPerTwinFam , & !< absolute length of burgers vector [m] for each twin family and instance
constitutive_titanmod_burgersPerTwinSys , & !< absolute length of burgers vector [m] for each twin system and instance
constitutive_titanmod_f0_PerSlipFam , & !< activation energy for glide [J] for each slip family and instance
constitutive_titanmod_f0_PerSlipSys , & !< activation energy for glide [J] for each slip system and instance
constitutive_titanmod_twinf0_PerTwinFam , & !< activation energy for glide [J] for each twin family and instance
constitutive_titanmod_twinf0_PerTwinSys , & !< activation energy for glide [J] for each twin system and instance
constitutive_titanmod_twinshearconstant_PerTwinFam , & !< activation energy for glide [J] for each twin family and instance
constitutive_titanmod_twinshearconstant_PerTwinSys , & !< activation energy for glide [J] for each twin system and instance
constitutive_titanmod_tau0e_PerSlipFam , & !< Initial yield stress for edge dislocations per slip family
constitutive_titanmod_tau0e_PerSlipSys , & !< Initial yield stress for edge dislocations per slip system
constitutive_titanmod_tau0s_PerSlipFam , & !< Initial yield stress for screw dislocations per slip family
constitutive_titanmod_tau0s_PerSlipSys , & !< Initial yield stress for screw dislocations per slip system
constitutive_titanmod_twintau0_PerTwinFam , & !< Initial yield stress for edge dislocations per twin family
constitutive_titanmod_twintau0_PerTwinSys , & !< Initial yield stress for edge dislocations per twin system
constitutive_titanmod_capre_PerSlipFam , & !< Capture radii for edge dislocations per slip family
constitutive_titanmod_capre_PerSlipSys , & !< Capture radii for edge dislocations per slip system
constitutive_titanmod_caprs_PerSlipFam , & !< Capture radii for screw dislocations per slip family
constitutive_titanmod_caprs_PerSlipSys , & !< Capture radii for screw dislocations per slip system
constitutive_titanmod_pe_PerSlipFam , & !< p-exponent in glide velocity
constitutive_titanmod_ps_PerSlipFam , & !< p-exponent in glide velocity
constitutive_titanmod_qe_PerSlipFam , & !< q-exponent in glide velocity
constitutive_titanmod_qs_PerSlipFam , & !< q-exponent in glide velocity
constitutive_titanmod_pe_PerSlipSys , & !< p-exponent in glide velocity
constitutive_titanmod_ps_PerSlipSys , & !< p-exponent in glide velocity
constitutive_titanmod_qe_PerSlipSys , & !< q-exponent in glide velocity
constitutive_titanmod_qs_PerSlipSys , & !< q-exponent in glide velocity
constitutive_titanmod_twinp_PerTwinFam , & !< p-exponent in glide velocity
constitutive_titanmod_twinq_PerTwinFam , & !< q-exponent in glide velocity
constitutive_titanmod_twinp_PerTwinSys , & !< p-exponent in glide velocity
constitutive_titanmod_twinq_PerTwinSys , & !< p-exponent in glide velocity
constitutive_titanmod_v0e_PerSlipFam , & !< edge dislocation velocity prefactor [m/s] for each family and instance
constitutive_titanmod_v0e_PerSlipSys , & !< screw dislocation velocity prefactor [m/s] for each slip system and instance
constitutive_titanmod_v0s_PerSlipFam , & !< edge dislocation velocity prefactor [m/s] for each family and instance
constitutive_titanmod_v0s_PerSlipSys , & !< screw dislocation velocity prefactor [m/s] for each slip system and instance
constitutive_titanmod_twingamma0_PerTwinFam , & !< edge dislocation velocity prefactor [m/s] for each family and instance
constitutive_titanmod_twingamma0_PerTwinSys , & !< screw dislocation velocity prefactor [m/s] for each slip system and instance
constitutive_titanmod_kinkcriticallength_PerSlipFam , & !< screw dislocation mobility prefactor for kink-pairs per slip family
constitutive_titanmod_kinkcriticallength_PerSlipSys , & !< screw dislocation mobility prefactor for kink-pairs per slip system
constitutive_titanmod_twinsizePerTwinFam , & !< twin thickness [m] for each twin family and instance
constitutive_titanmod_twinsizePerTwinSys , & !< twin thickness [m] for each twin system and instance
constitutive_titanmod_CeLambdaSlipPerSlipFam , & !< Adj. parameter for distance between 2 forest dislocations for each slip family and instance
constitutive_titanmod_CeLambdaSlipPerSlipSys , & !< Adj. parameter for distance between 2 forest dislocations for each slip system and instance
constitutive_titanmod_CsLambdaSlipPerSlipFam , & !< Adj. parameter for distance between 2 forest dislocations for each slip family and instance
constitutive_titanmod_CsLambdaSlipPerSlipSys , & !< Adj. parameter for distance between 2 forest dislocations for each slip system and instance
constitutive_titanmod_twinLambdaSlipPerTwinFam , & !< Adj. parameter for distance between 2 forest dislocations for each slip family and instance
constitutive_titanmod_twinLambdaSlipPerTwinSys , & !< Adj. parameter for distance between 2 forest dislocations for each slip system and instance
constitutive_titanmod_interactionSlipSlip , & !< coefficients for slip-slip interaction for each interaction type and instance
constitutive_titanmod_interaction_ee , & !< coefficients for e-e interaction for each interaction type and instance
constitutive_titanmod_interaction_ss , & !< coefficients for s-s interaction for each interaction type and instance
constitutive_titanmod_interaction_es , & !< coefficients for e-s-twin interaction for each interaction type and instance
constitutive_titanmod_interactionSlipTwin , & !< coefficients for twin-slip interaction for each interaction type and instance
constitutive_titanmod_interactionTwinSlip , & !< coefficients for twin-slip interaction for each interaction type and instance
constitutive_titanmod_interactionTwinTwin !< coefficients for twin-twin interaction for each interaction type and instance
2013-07-12 12:27:15 +05:30
2013-10-08 21:57:26 +05:30
real ( pReal ) , dimension ( : , : , : ) , allocatable , private :: &
2014-02-09 22:38:13 +05:30
constitutive_titanmod_interactionMatrixSlipSlip , & !< interaction matrix of the different slip systems for each instance
constitutive_titanmod_interactionMatrix_ee , & !< interaction matrix of e-e for each instance
constitutive_titanmod_interactionMatrix_ss , & !< interaction matrix of s-s for each instance
constitutive_titanmod_interactionMatrix_es , & !< interaction matrix of e-s for each instance
constitutive_titanmod_interactionMatrixSlipTwin , & !< interaction matrix of slip systems with twin systems for each instance
constitutive_titanmod_interactionMatrixTwinSlip , & !< interaction matrix of twin systems with slip systems for each instance
constitutive_titanmod_interactionMatrixTwinTwin , & !< interaction matrix of the different twin systems for each instance
constitutive_titanmod_forestProjectionEdge , & !< matrix of forest projections of edge dislocations for each instance
constitutive_titanmod_forestProjectionScrew , & !< matrix of forest projections of screw dislocations for each instance
constitutive_titanmod_TwinforestProjectionEdge , & !< matrix of forest projections of edge dislocations in twin system for each instance
constitutive_titanmod_TwinforestProjectionScrew !< matrix of forest projections of screw dislocations in twin system for each instance
2013-07-12 12:27:15 +05:30
2013-10-08 21:57:26 +05:30
real ( pReal ) , dimension ( : , : , : , : ) , allocatable , private :: &
2014-03-09 02:20:31 +05:30
constitutive_titanmod_Ctwin66 !< twin elasticity matrix in Mandel notation for each instance
2013-07-12 12:27:15 +05:30
2013-10-08 21:57:26 +05:30
real ( pReal ) , dimension ( : , : , : , : , : , : ) , allocatable , private :: &
2014-03-09 02:20:31 +05:30
constitutive_titanmod_Ctwin3333 !< twin elasticity matrix for each instance
2014-02-09 22:38:13 +05:30
enum , bind ( c )
enumerator :: undefined_ID , &
rhoedge_ID , rhoscrew_ID , &
segment_edge_ID , segment_screw_ID , &
resistance_edge_ID , resistance_screw_ID , &
velocity_edge_ID , velocity_screw_ID , &
tau_slip_ID , &
gdot_slip_edge_ID , gdot_slip_screw_ID , &
gdot_slip_ID , &
stressratio_edge_p_ID , stressratio_screw_p_ID , &
shear_system_ID , &
twin_fraction_ID , &
shear_basal_ID , shear_prism_ID , shear_pyra_ID , shear_pyrca_ID , &
rhoedge_basal_ID , rhoedge_prism_ID , rhoedge_pyra_ID , rhoedge_pyrca_ID , &
rhoscrew_basal_ID , rhoscrew_prism_ID , rhoscrew_pyra_ID , rhoscrew_pyrca_ID , &
shear_total_ID
end enum
integer ( kind ( undefined_ID ) ) , dimension ( : , : ) , allocatable , private :: &
constitutive_titanmod_outputID !< ID of each post result output
2013-07-12 12:27:15 +05:30
public :: &
constitutive_titanmod_microstructure , &
constitutive_titanmod_stateInit , &
constitutive_titanmod_init , &
constitutive_titanmod_LpAndItsTangent , &
constitutive_titanmod_dotState , &
2014-10-10 22:04:51 +05:30
constitutive_titanmod_getAccumulatedSlip , &
2014-10-11 15:15:30 +05:30
constitutive_titanmod_getSlipRate , &
2013-07-12 12:27:15 +05:30
constitutive_titanmod_postResults , &
2014-07-02 17:57:39 +05:30
constitutive_titanmod_homogenizedC
2013-07-12 12:27:15 +05:30
contains
!--------------------------------------------------------------------------------------------------
!> @brief module initialization
!> @details reads in material parameters, allocates arrays, and does sanity checks
!--------------------------------------------------------------------------------------------------
2013-12-12 22:39:59 +05:30
subroutine constitutive_titanmod_init ( fileUnit )
2013-07-12 12:27:15 +05:30
use , intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
use debug , only : &
debug_level , &
debug_constitutive , &
debug_levelBasic
2013-12-19 14:19:47 +05:30
use math , only : &
math_Mandel3333to66 , &
math_Voigt66to3333 , &
math_mul3x3
use IO , only : &
IO_read , &
IO_lc , &
IO_getTag , &
IO_isBlank , &
IO_stringPos , &
IO_stringValue , &
IO_floatValue , &
IO_intValue , &
IO_warning , &
IO_error , &
IO_timeStamp , &
IO_EOF
use material , only : &
homogenization_maxNgrains , &
phase_plasticity , &
phase_plasticityInstance , &
phase_Noutput , &
PLASTICITY_TITANMOD_label , &
PLASTICITY_TITANMOD_ID , &
2014-06-11 17:57:41 +05:30
plasticState , &
2013-12-19 14:19:47 +05:30
MATERIAL_partPhase
2013-07-12 12:27:15 +05:30
use lattice
2014-06-11 17:57:41 +05:30
use numerics , only : &
2014-10-10 01:53:06 +05:30
worldrank , &
2014-06-11 17:57:41 +05:30
numerics_integrator
2013-01-09 03:41:59 +05:30
2013-07-12 12:27:15 +05:30
implicit none
2013-12-12 22:39:59 +05:30
integer ( pInt ) , intent ( in ) :: fileUnit
2013-07-12 12:27:15 +05:30
2013-10-09 11:42:16 +05:30
integer ( pInt ) , parameter :: MAXNCHUNKS = LATTICE_maxNinteraction + 1_pInt
2013-07-12 12:27:15 +05:30
integer ( pInt ) , dimension ( 1_pInt + 2_pInt * MAXNCHUNKS ) :: positions
2013-10-08 21:57:26 +05:30
integer ( pInt ) :: &
2014-03-09 02:20:31 +05:30
phase , &
2014-02-28 15:48:40 +05:30
instance , j , k , l , m , n , p , q , r , &
2013-10-08 21:57:26 +05:30
f , o , &
s , s1 , s2 , &
t , t1 , t2 , &
ns , nt , &
2013-10-09 11:42:16 +05:30
Nchunks_SlipSlip , Nchunks_SlipTwin , Nchunks_TwinSlip , Nchunks_TwinTwin , &
Nchunks_SlipFamilies , Nchunks_TwinFamilies , &
2014-03-09 02:20:31 +05:30
mySize , &
2013-10-08 21:57:26 +05:30
maxTotalNslip , maxTotalNtwin , maxNinstance
2014-06-11 17:57:41 +05:30
integer ( pInt ) :: sizeState , sizeDotState
integer ( pInt ) :: NofMyPhase
2013-07-12 12:27:15 +05:30
character ( len = 65536 ) :: &
tag = '' , &
2013-11-28 14:26:02 +05:30
line = ''
2013-07-12 12:27:15 +05:30
2014-10-10 22:15:14 +05:30
mainProcess : if ( worldrank == 0 ) then
write ( 6 , '(/,a)' ) ' <<<+- constitutive_' / / PLASTICITY_TITANMOD_label / / ' init -+>>>'
write ( 6 , '(a)' ) ' $Id$'
write ( 6 , '(a15,a)' ) ' Current time: ' , IO_timeStamp ( )
2012-02-01 00:48:55 +05:30
#include "compilation_info.f90"
2014-10-10 22:15:14 +05:30
endif mainProcess
2010-07-13 13:49:25 +05:30
2013-11-27 13:34:05 +05:30
maxNinstance = int ( count ( phase_plasticity == PLASTICITY_TITANMOD_ID ) , pInt )
2013-10-08 21:57:26 +05:30
if ( maxNinstance == 0_pInt ) return
2010-07-13 13:49:25 +05:30
2013-07-12 12:27:15 +05:30
if ( iand ( debug_level ( debug_constitutive ) , debug_levelBasic ) / = 0_pInt ) &
write ( 6 , '(a16,1x,i5,/)' ) '# instances:' , maxNinstance
2013-02-15 03:54:55 +05:30
2014-02-09 22:38:13 +05:30
allocate ( constitutive_titanmod_sizePostResults ( maxNinstance ) , source = 0_pInt )
allocate ( constitutive_titanmod_sizePostResult ( maxval ( phase_Noutput ) , maxNinstance ) , source = 0_pInt )
2013-07-12 12:27:15 +05:30
allocate ( constitutive_titanmod_output ( maxval ( phase_Noutput ) , maxNinstance ) )
constitutive_titanmod_output = ''
2014-02-09 22:38:13 +05:30
allocate ( constitutive_titanmod_outputID ( maxval ( phase_Noutput ) , maxNinstance ) , source = undefined_ID )
allocate ( constitutive_titanmod_Noutput ( maxNinstance ) , source = 0_pInt )
2013-07-12 12:27:15 +05:30
2014-02-09 22:38:13 +05:30
allocate ( constitutive_titanmod_Nslip ( lattice_maxNslipFamily , maxNinstance ) , source = 0_pInt )
allocate ( constitutive_titanmod_Ntwin ( lattice_maxNtwinFamily , maxNinstance ) , source = 0_pInt )
allocate ( constitutive_titanmod_slipFamily ( lattice_maxNslip , maxNinstance ) , source = 0_pInt )
allocate ( constitutive_titanmod_twinFamily ( lattice_maxNtwin , maxNinstance ) , source = 0_pInt )
allocate ( constitutive_titanmod_slipSystemLattice ( lattice_maxNslip , maxNinstance ) , source = 0_pInt )
allocate ( constitutive_titanmod_twinSystemLattice ( lattice_maxNtwin , maxNinstance ) , source = 0_pInt )
allocate ( constitutive_titanmod_totalNslip ( maxNinstance ) , source = 0_pInt )
allocate ( constitutive_titanmod_totalNtwin ( maxNinstance ) , source = 0_pInt )
allocate ( constitutive_titanmod_debyefrequency ( maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_kinkf0 ( maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_CAtomicVolume ( maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_dc ( maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_twinhpconstant ( maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_GrainSize ( maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_MaxTwinFraction ( maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_r ( maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_CEdgeDipMinDistance ( maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_Cmfptwin ( maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_Cthresholdtwin ( maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_aTolRho ( maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_rho_edge0 ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_rho_screw0 ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_shear_system0 ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_burgersPerSlipFam ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_burgersPerTwinFam ( lattice_maxNtwinFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_f0_PerSlipFam ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_tau0e_PerSlipFam ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_tau0s_PerSlipFam ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_capre_PerSlipFam ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_caprs_PerSlipFam ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_pe_PerSlipFam ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_ps_PerSlipFam ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_qe_PerSlipFam ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_qs_PerSlipFam ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_v0e_PerSlipFam ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_v0s_PerSlipFam ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_kinkcriticallength_PerSlipFam ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_twinsizePerTwinFam ( lattice_maxNtwinFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_CeLambdaSlipPerSlipFam ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_CsLambdaSlipPerSlipFam ( lattice_maxNslipFamily , maxNinstance ) , source = 0.0_pReal )
2013-06-27 00:49:00 +05:30
2014-02-09 22:38:13 +05:30
allocate ( constitutive_titanmod_twinf0_PerTwinFam ( lattice_maxNTwinFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_twinshearconstant_PerTwinFam ( lattice_maxNTwinFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_twintau0_PerTwinFam ( lattice_maxNTwinFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_twinp_PerTwinFam ( lattice_maxNTwinFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_twinq_PerTwinFam ( lattice_maxNTwinFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_twingamma0_PerTwinFam ( lattice_maxNTwinFamily , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_twinLambdaSlipPerTwinFam ( lattice_maxNTwinFamily , maxNinstance ) , source = 0.0_pReal )
2013-07-12 12:27:15 +05:30
2014-02-09 22:38:13 +05:30
allocate ( constitutive_titanmod_interactionSlipSlip ( lattice_maxNinteraction , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_interaction_ee ( lattice_maxNinteraction , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_interaction_ss ( lattice_maxNinteraction , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_interaction_es ( lattice_maxNinteraction , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_interactionSlipTwin ( lattice_maxNinteraction , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_interactionTwinSlip ( lattice_maxNinteraction , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_interactionTwinTwin ( lattice_maxNinteraction , maxNinstance ) , source = 0.0_pReal )
2013-07-12 12:27:15 +05:30
2013-12-12 22:39:59 +05:30
rewind ( fileUnit )
2014-03-09 02:20:31 +05:30
phase = 0_pInt
do while ( trim ( line ) / = IO_EOF . and . IO_lc ( IO_getTag ( line , '<' , '>' ) ) / = material_partPhase ) ! wind forward to <phase>
2013-12-12 22:39:59 +05:30
line = IO_read ( fileUnit )
2013-07-12 12:27:15 +05:30
enddo
2014-03-09 02:20:31 +05:30
parsingFile : do while ( trim ( line ) / = IO_EOF ) ! read through sections of phase part
2013-12-12 22:39:59 +05:30
line = IO_read ( fileUnit )
2013-07-12 12:27:15 +05:30
if ( IO_isBlank ( line ) ) cycle ! skip empty lines
2013-12-12 22:39:59 +05:30
if ( IO_getTag ( line , '<' , '>' ) / = '' ) then ! stop at next part
line = IO_read ( fileUnit , . true . ) ! reset IO_read
exit
endif
2013-07-12 12:27:15 +05:30
if ( IO_getTag ( line , '[' , ']' ) / = '' ) then ! next section
2014-03-09 02:20:31 +05:30
phase = phase + 1_pInt ! advance section counter
if ( phase_plasticity ( phase ) == PLASTICITY_TITANMOD_ID ) then
Nchunks_SlipFamilies = count ( lattice_NslipSystem ( : , phase ) > 0_pInt )
Nchunks_TwinFamilies = count ( lattice_NtwinSystem ( : , phase ) > 0_pInt )
Nchunks_SlipSlip = maxval ( lattice_interactionSlipSlip ( : , : , phase ) )
Nchunks_SlipTwin = maxval ( lattice_interactionSlipTwin ( : , : , phase ) )
Nchunks_TwinSlip = maxval ( lattice_interactionTwinSlip ( : , : , phase ) )
Nchunks_TwinTwin = maxval ( lattice_interactionTwinTwin ( : , : , phase ) )
2013-06-12 01:46:40 +05:30
endif
2014-03-09 02:20:31 +05:30
cycle ! skip to next line
2010-07-13 13:49:25 +05:30
endif
2014-03-09 02:20:31 +05:30
if ( phase > 0_pInt ) then ; if ( phase_plasticity ( phase ) == PLASTICITY_TITANMOD_ID ) then ! one of my sections. Do not short-circuit here (.and. between if-statements), it's not safe in Fortran
instance = phase_plasticityInstance ( phase ) ! which instance of my plasticity is present phase
positions = IO_stringPos ( line , MAXNCHUNKS )
tag = IO_lc ( IO_stringValue ( line , positions , 1_pInt ) ) ! extract key
select case ( tag )
case ( '(output)' )
select case ( IO_lc ( IO_stringValue ( line , positions , 2_pInt ) ) )
case ( 'rhoedge' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = rhoedge_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'rhoscrew' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = rhoscrew_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'segment_edge' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = segment_edge_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'segment_screw' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = segment_screw_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'resistance_edge' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = resistance_edge_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'resistance_screw' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = resistance_screw_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'velocity_edge' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = velocity_edge_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'velocity_screw' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = velocity_screw_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'tau_slip' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = tau_slip_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'gdot_slip_edge' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = gdot_slip_edge_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'gdot_slip_screw' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = gdot_slip_screw_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'gdot_slip' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = gdot_slip_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'stressratio_edge_p' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = stressratio_edge_p_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'stressratio_screw_p' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = stressratio_screw_p_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'shear_system' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = shear_system_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'twin_fraction' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = twin_fraction_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'shear_basal' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = shear_basal_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'shear_prism' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = shear_prism_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'shear_pyra' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = shear_pyra_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'shear_pyrca' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = shear_pyrca_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'rhoedge_basal' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = rhoedge_basal_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'rhoedge_prism' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = rhoedge_prism_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'rhoedge_pyra' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = rhoedge_pyra_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'rhoedge_pyrca' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = rhoedge_pyrca_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'rhoscrew_basal' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = rhoscrew_basal_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'rhoscrew_prism' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = rhoscrew_prism_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'rhoscrew_pyra' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = rhoscrew_pyra_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'rhoscrew_pyrca' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = rhoscrew_pyrca_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
case ( 'shear_total' )
2014-06-25 04:23:25 +05:30
constitutive_titanmod_Noutput ( instance ) = constitutive_titanmod_Noutput ( instance ) + 1_pInt
2014-06-26 19:23:12 +05:30
constitutive_titanmod_outputID ( constitutive_titanmod_Noutput ( instance ) , instance ) = shear_total_ID
2014-06-25 04:23:25 +05:30
constitutive_titanmod_output ( constitutive_titanmod_Noutput ( instance ) , instance ) = &
IO_lc ( IO_stringValue ( line , positions , 2_pInt ) )
2014-03-09 02:20:31 +05:30
end select
case ( 'debyefrequency' )
constitutive_titanmod_debyefrequency ( instance ) = IO_floatValue ( line , positions , 2_pInt )
case ( 'kinkf0' )
constitutive_titanmod_kinkf0 ( instance ) = IO_floatValue ( line , positions , 2_pInt )
case ( 'nslip' )
if ( positions ( 1 ) < 1_pInt + Nchunks_SlipFamilies ) &
call IO_warning ( 50_pInt , ext_msg = trim ( tag ) / / ' (' / / PLASTICITY_TITANMOD_label / / ')' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_Nslip ( j , instance ) = IO_intValue ( line , positions , 1_pInt + j )
enddo
case ( 'ntwin' )
if ( positions ( 1 ) < 1_pInt + Nchunks_TwinFamilies ) &
call IO_warning ( 51_pInt , ext_msg = trim ( tag ) / / ' (' / / PLASTICITY_TITANMOD_label / / ')' )
do j = 1_pInt , Nchunks_TwinFamilies
constitutive_titanmod_Ntwin ( j , instance ) = IO_intValue ( line , positions , 1_pInt + j )
enddo
case ( 'rho_edge0' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_rho_edge0 ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'rho_screw0' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_rho_screw0 ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'slipburgers' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_burgersPerSlipFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'twinburgers' )
do j = 1_pInt , Nchunks_TwinFamilies
constitutive_titanmod_burgersPerTwinFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'f0' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_f0_PerSlipFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'twinf0' )
do j = 1_pInt , Nchunks_TwinFamilies
constitutive_titanmod_twinf0_PerTwinFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'tau0e' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_tau0e_PerSlipFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'twintau0' )
do j = 1_pInt , Nchunks_TwinFamilies
constitutive_titanmod_twintau0_PerTwinFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'tau0s' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_tau0s_PerSlipFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'capre' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_capre_PerSlipFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'caprs' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_caprs_PerSlipFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'v0e' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_v0e_PerSlipFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'twingamma0' )
do j = 1_pInt , Nchunks_TwinFamilies
constitutive_titanmod_twingamma0_PerTwinFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'v0s' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_v0s_PerSlipFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'kinkcriticallength' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_kinkcriticallength_PerSlipFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'twinsize' )
do j = 1_pInt , Nchunks_TwinFamilies
constitutive_titanmod_twinsizePerTwinFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'celambdaslip' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_CeLambdaSlipPerSlipFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'twinlambdaslip' )
do j = 1_pInt , Nchunks_TwinFamilies
constitutive_titanmod_twinlambdaslipPerTwinFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'cslambdaslip' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_CsLambdaSlipPerSlipFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'grainsize' )
constitutive_titanmod_GrainSize ( instance ) = IO_floatValue ( line , positions , 2_pInt )
case ( 'maxtwinfraction' )
constitutive_titanmod_MaxTwinFraction ( instance ) = IO_floatValue ( line , positions , 2_pInt )
case ( 'pe' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_pe_PerSlipFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'twinp' )
do j = 1_pInt , Nchunks_TwinFamilies
constitutive_titanmod_twinp_PerTwinFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'ps' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_ps_PerSlipFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'qe' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_qe_PerSlipFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'twinq' )
do j = 1_pInt , Nchunks_TwinFamilies
constitutive_titanmod_twinq_PerTwinFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'qs' )
do j = 1_pInt , Nchunks_SlipFamilies
constitutive_titanmod_qs_PerSlipFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'twinshearconstant' )
do j = 1_pInt , Nchunks_TwinFamilies
constitutive_titanmod_twinshearconstant_PerTwinFam ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'dc' )
constitutive_titanmod_dc ( instance ) = IO_floatValue ( line , positions , 2_pInt )
case ( 'twinhpconstant' )
constitutive_titanmod_twinhpconstant ( instance ) = IO_floatValue ( line , positions , 2_pInt )
case ( 'atol_rho' )
constitutive_titanmod_aTolRho ( instance ) = IO_floatValue ( line , positions , 2_pInt )
case ( 'interactionee' )
do j = 1_pInt , lattice_maxNinteraction
constitutive_titanmod_interaction_ee ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'interactionss' )
do j = 1_pInt , lattice_maxNinteraction
constitutive_titanmod_interaction_ss ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'interactiones' )
do j = 1_pInt , lattice_maxNinteraction
constitutive_titanmod_interaction_es ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'interaction_slipslip' , 'interactionslipslip' )
if ( positions ( 1 ) < 1_pInt + Nchunks_SlipSlip ) &
call IO_warning ( 52_pInt , ext_msg = trim ( tag ) / / ' (' / / PLASTICITY_TITANMOD_label / / ')' )
do j = 1_pInt , Nchunks_SlipSlip
constitutive_titanmod_interactionSlipSlip ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'interaction_sliptwin' , 'interactionsliptwin' )
if ( positions ( 1 ) < 1_pInt + Nchunks_SlipTwin ) &
call IO_warning ( 52_pInt , ext_msg = trim ( tag ) / / ' (' / / PLASTICITY_TITANMOD_label / / ')' )
do j = 1_pInt , Nchunks_SlipTwin
constitutive_titanmod_interactionSlipTwin ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'interaction_twinslip' , 'interactiontwinslip' )
if ( positions ( 1 ) < 1_pInt + Nchunks_TwinSlip ) &
call IO_warning ( 52_pInt , ext_msg = trim ( tag ) / / ' (' / / PLASTICITY_TITANMOD_label / / ')' )
do j = 1_pInt , Nchunks_TwinSlip
constitutive_titanmod_interactionTwinSlip ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
case ( 'interaction_twintwin' , 'interactiontwintwin' )
if ( positions ( 1 ) < 1_pInt + Nchunks_TwinTwin ) &
call IO_warning ( 52_pInt , ext_msg = trim ( tag ) / / ' (' / / PLASTICITY_TITANMOD_label / / ')' )
do j = 1_pInt , Nchunks_TwinTwin
constitutive_titanmod_interactionTwinTwin ( j , instance ) = IO_floatValue ( line , positions , 1_pInt + j )
enddo
end select
endif ; endif
enddo parsingFile
sanityChecks : do phase = 1_pInt , size ( phase_plasticity )
myPhase : if ( phase_plasticity ( phase ) == PLASTICITY_TITANMOD_ID ) then
instance = phase_plasticityInstance ( phase )
2014-08-08 19:21:11 +05:30
if ( sum ( constitutive_titanmod_Nslip ( : , instance ) ) < 0_pInt ) &
2014-03-09 02:20:31 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'nslip (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( sum ( constitutive_titanmod_Ntwin ( : , instance ) ) < 0_pInt ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'ntwin (' / / PLASTICITY_TITANMOD_label / / ')' )
do f = 1_pInt , lattice_maxNslipFamily
if ( constitutive_titanmod_Nslip ( f , instance ) > 0_pInt ) then
if ( constitutive_titanmod_rho_edge0 ( f , instance ) < 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'rho_edge0 (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( constitutive_titanmod_rho_screw0 ( f , instance ) < 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'rho_screw0 (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( constitutive_titanmod_burgersPerSlipFam ( f , instance ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'slipburgers (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( constitutive_titanmod_f0_PerSlipFam ( f , instance ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'f0 (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( constitutive_titanmod_tau0e_PerSlipFam ( f , instance ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'tau0e (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( constitutive_titanmod_tau0s_PerSlipFam ( f , instance ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'tau0s (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( constitutive_titanmod_capre_PerSlipFam ( f , instance ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'capre (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( constitutive_titanmod_caprs_PerSlipFam ( f , instance ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'caprs (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( constitutive_titanmod_v0e_PerSlipFam ( f , instance ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'v0e (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( constitutive_titanmod_v0s_PerSlipFam ( f , instance ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'v0s (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( constitutive_titanmod_kinkcriticallength_PerSlipFam ( f , instance ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'kinkCriticalLength (' / / PLASTICITY_TITANMOD_label / / ')' )
endif
enddo
do f = 1_pInt , lattice_maxNtwinFamily
if ( constitutive_titanmod_Ntwin ( f , instance ) > 0_pInt ) then
if ( constitutive_titanmod_burgersPerTwinFam ( f , instance ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'twinburgers (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( constitutive_titanmod_twinf0_PerTwinFam ( f , instance ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'twinf0 (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( constitutive_titanmod_twinshearconstant_PerTwinFam ( f , instance ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'twinshearconstant (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( constitutive_titanmod_twintau0_PerTwinFam ( f , instance ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'twintau0 (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( constitutive_titanmod_twingamma0_PerTwinFam ( f , instance ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'twingamma0 (' / / PLASTICITY_TITANMOD_label / / ')' )
endif
enddo
if ( constitutive_titanmod_dc ( instance ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'dc (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( constitutive_titanmod_twinhpconstant ( instance ) < = 0.0_pReal ) &
call IO_error ( 211_pInt , el = instance , ext_msg = 'twinhpconstant (' / / PLASTICITY_TITANMOD_label / / ')' )
if ( constitutive_titanmod_aTolRho ( instance ) < = 0.0_pReal ) &
2014-08-08 19:21:11 +05:30
call IO_error ( 211_pInt , el = instance , ext_msg = 'aTol_rho (' / / PLASTICITY_TITANMOD_label / / ')' )
2014-03-09 02:20:31 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! determine total number of active slip or twin systems
2014-03-09 02:20:31 +05:30
constitutive_titanmod_Nslip ( : , instance ) = min ( lattice_NslipSystem ( : , phase ) , constitutive_titanmod_Nslip ( : , instance ) )
constitutive_titanmod_Ntwin ( : , instance ) = min ( lattice_NtwinSystem ( : , phase ) , constitutive_titanmod_Ntwin ( : , instance ) )
constitutive_titanmod_totalNslip ( instance ) = sum ( constitutive_titanmod_Nslip ( : , instance ) )
constitutive_titanmod_totalNtwin ( instance ) = sum ( constitutive_titanmod_Ntwin ( : , instance ) )
endif myPhase
2013-07-12 12:27:15 +05:30
enddo sanityChecks
!--------------------------------------------------------------------------------------------------
! allocation of variables whose size depends on the total number of active slip systems
maxTotalNslip = maxval ( constitutive_titanmod_totalNslip )
maxTotalNtwin = maxval ( constitutive_titanmod_totalNtwin )
2014-02-09 22:38:13 +05:30
allocate ( constitutive_titanmod_burgersPerSlipSys ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
2013-07-12 12:27:15 +05:30
2014-02-09 22:38:13 +05:30
allocate ( constitutive_titanmod_f0_PerSlipSys ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_tau0e_PerSlipSys ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_tau0s_PerSlipSys ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_capre_PerSlipSys ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_caprs_PerSlipSys ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_pe_PerSlipSys ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_ps_PerSlipSys ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_qe_PerSlipSys ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_qs_PerSlipSys ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_v0e_PerSlipSys ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_v0s_PerSlipSys ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_kinkcriticallength_PerSlipSys ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_CeLambdaSlipPerSlipSys ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_CsLambdaSlipPerSlipSys ( maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
2013-07-12 12:27:15 +05:30
2014-02-09 22:38:13 +05:30
allocate ( constitutive_titanmod_burgersPerTwinSys ( maxTotalNtwin , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_twinf0_PerTwinSys ( maxTotalNTwin , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_twinshearconstant_PerTwinSys ( maxTotalNTwin , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_twintau0_PerTwinSys ( maxTotalNTwin , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_twinp_PerTwinSys ( maxTotalNTwin , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_twinq_PerTwinSys ( maxTotalNTwin , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_twingamma0_PerTwinSys ( maxTotalNTwin , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_twinsizePerTwinSys ( maxTotalNtwin , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_twinLambdaSlipPerTwinSys ( maxTotalNtwin , maxNinstance ) , source = 0.0_pReal )
2014-03-09 02:20:31 +05:30
allocate ( constitutive_titanmod_Ctwin66 ( 6 , 6 , maxTotalNtwin , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_Ctwin3333 ( 3 , 3 , 3 , 3 , maxTotalNtwin , maxNinstance ) , source = 0.0_pReal )
2014-02-09 22:38:13 +05:30
allocate ( constitutive_titanmod_interactionMatrixSlipSlip ( maxTotalNslip , maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_interactionMatrix_ee ( maxTotalNslip , maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_interactionMatrix_ss ( maxTotalNslip , maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_interactionMatrix_es ( maxTotalNslip , maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_interactionMatrixSlipTwin ( maxTotalNslip , maxTotalNtwin , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_interactionMatrixTwinSlip ( maxTotalNtwin , maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_interactionMatrixTwinTwin ( maxTotalNtwin , maxTotalNtwin , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_forestProjectionEdge ( maxTotalNslip , maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_forestProjectionScrew ( maxTotalNslip , maxTotalNslip , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_TwinforestProjectionEdge ( maxTotalNtwin , maxTotalNtwin , maxNinstance ) , source = 0.0_pReal )
allocate ( constitutive_titanmod_TwinforestProjectionScrew ( maxTotalNtwin , maxTotalNtwin , maxNinstance ) , source = 0.0_pReal )
2013-07-12 12:27:15 +05:30
2014-03-09 02:20:31 +05:30
initializeInstances : do phase = 1_pInt , size ( phase_plasticity )
if ( phase_plasticity ( phase ) == PLASTICITY_TITANMOD_ID ) then
instance = phase_plasticityInstance ( phase )
2010-07-13 13:49:25 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! inverse lookup of slip system family
2014-03-09 02:20:31 +05:30
l = 0_pInt
do f = 1_pInt , lattice_maxNslipFamily
do s = 1_pInt , constitutive_titanmod_Nslip ( f , instance )
l = l + 1_pInt
constitutive_titanmod_slipFamily ( l , instance ) = f
constitutive_titanmod_slipSystemLattice ( l , instance ) = sum ( lattice_NslipSystem ( 1 : f - 1_pInt , phase ) ) + s
enddo ; enddo
2010-09-22 14:30:40 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! inverse lookup of twin system family
2014-03-09 02:20:31 +05:30
l = 0_pInt
do f = 1_pInt , lattice_maxNtwinFamily
do t = 1_pInt , constitutive_titanmod_Ntwin ( f , instance )
l = l + 1_pInt
constitutive_titanmod_twinFamily ( l , instance ) = f
constitutive_titanmod_twinSystemLattice ( l , instance ) = sum ( lattice_NtwinSystem ( 1 : f - 1_pInt , phase ) ) + t
enddo ; enddo
2010-07-13 13:49:25 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
2014-07-02 17:57:39 +05:30
! determine size of state array
2014-03-09 02:20:31 +05:30
ns = constitutive_titanmod_totalNslip ( instance )
nt = constitutive_titanmod_totalNtwin ( instance )
2014-06-11 17:57:41 +05:30
sizeDotState = &
size ( constitutive_titanmod_listBasicSlipStates ) * ns + &
size ( constitutive_titanmod_listBasicTwinStates ) * nt
2014-07-02 17:57:39 +05:30
sizeState = sizeDotState + &
2014-06-11 17:57:41 +05:30
size ( constitutive_titanmod_listDependentSlipStates ) * ns + &
size ( constitutive_titanmod_listDependentTwinStates ) * nt
2013-02-15 03:54:55 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! determine size of postResults array
2014-03-09 02:20:31 +05:30
outputsLoop : do o = 1_pInt , constitutive_titanmod_Noutput ( instance )
mySize = 0_pInt
select case ( constitutive_titanmod_outputID ( o , instance ) )
case ( rhoedge_ID , rhoscrew_ID , &
segment_edge_ID , segment_screw_ID , &
resistance_edge_ID , resistance_screw_ID , &
velocity_edge_ID , velocity_screw_ID , &
tau_slip_ID , &
gdot_slip_edge_ID , gdot_slip_screw_ID , &
gdot_slip_ID , &
stressratio_edge_p_ID , stressratio_screw_p_ID , &
shear_system_ID )
mySize = constitutive_titanmod_totalNslip ( instance )
case ( twin_fraction_ID )
mySize = constitutive_titanmod_totalNtwin ( instance )
case ( shear_basal_ID , shear_prism_ID , shear_pyra_ID , shear_pyrca_ID , & ! use only if all 4 slip families in hex are considered
rhoedge_basal_ID , rhoedge_prism_ID , rhoedge_pyra_ID , rhoedge_pyrca_ID , &
rhoscrew_basal_ID , rhoscrew_prism_ID , rhoscrew_pyra_ID , rhoscrew_pyrca_ID , &
shear_total_ID )
mySize = 1_pInt
case default
call IO_error ( 105_pInt , ext_msg = constitutive_titanmod_output ( o , instance ) / / &
' (' / / PLASTICITY_TITANMOD_label / / ')' )
end select
outputFound : if ( mySize > 0_pInt ) then
constitutive_titanmod_sizePostResult ( o , instance ) = mySize
constitutive_titanmod_sizePostResults ( instance ) = constitutive_titanmod_sizePostResults ( instance ) + mySize
endif outputFound
enddo outputsLoop
2014-06-11 17:57:41 +05:30
! Determine size of state array
plasticState ( phase ) % sizeState = sizeState
plasticState ( phase ) % sizeDotState = sizeDotState
2014-06-30 20:17:30 +05:30
plasticState ( phase ) % sizePostResults = constitutive_titanmod_sizePostResults ( instance )
2014-07-02 17:57:39 +05:30
allocate ( plasticState ( phase ) % aTolState ( sizeState ) , source = constitutive_titanmod_aTolRho ( instance ) )
2014-06-11 17:57:41 +05:30
allocate ( plasticState ( phase ) % state0 ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % partionedState0 ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % subState0 ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % state ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % state_backup ( sizeState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % dotState ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % deltaState ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % dotState_backup ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
if ( any ( numerics_integrator == 1_pInt ) ) then
allocate ( plasticState ( phase ) % previousDotState ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
allocate ( plasticState ( phase ) % previousDotState2 ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
endif
if ( any ( numerics_integrator == 4_pInt ) ) &
allocate ( plasticState ( phase ) % RK4dotState ( sizeDotState , NofMyPhase ) , source = 0.0_pReal )
if ( any ( numerics_integrator == 5_pInt ) ) &
allocate ( plasticState ( phase ) % RKCK45dotState ( 6 , sizeDotState , NofMyPhase ) , source = 0.0_pReal )
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! construction of the twin elasticity matrices
2014-03-09 02:20:31 +05:30
do j = 1_pInt , lattice_maxNtwinFamily
do k = 1_pInt , constitutive_titanmod_Ntwin ( j , instance )
do l = 1_pInt , 3_pInt ; do m = 1_pInt , 3_pInt ; do n = 1_pInt , 3_pInt ; do o = 1_pInt , 3_pInt
do p = 1_pInt , 3_pInt ; do q = 1_pInt , 3_pInt ; do r = 1_pInt , 3_pInt ; do s = 1_pInt , 3_pInt
constitutive_titanmod_Ctwin3333 ( l , m , n , o , sum ( constitutive_titanmod_Nslip ( 1 : j - 1_pInt , instance ) ) + k , instance ) = &
constitutive_titanmod_Ctwin3333 ( l , m , n , o , sum ( constitutive_titanmod_Nslip ( 1 : j - 1_pInt , instance ) ) + k , instance ) + &
lattice_C3333 ( p , q , r , s , phase ) * &
lattice_Qtwin ( l , p , sum ( lattice_NslipSystem ( 1 : j - 1_pInt , phase ) ) + k , phase ) * &
lattice_Qtwin ( m , q , sum ( lattice_NslipSystem ( 1 : j - 1_pInt , phase ) ) + k , phase ) * &
lattice_Qtwin ( n , r , sum ( lattice_NslipSystem ( 1 : j - 1_pInt , phase ) ) + k , phase ) * &
lattice_Qtwin ( o , s , sum ( lattice_NslipSystem ( 1 : j - 1_pInt , phase ) ) + k , phase )
enddo ; enddo ; enddo ; enddo
enddo ; enddo ; enddo ; enddo
constitutive_titanmod_Ctwin66 ( 1 : 6 , 1 : 6 , k , instance ) = &
math_Mandel3333to66 ( constitutive_titanmod_Ctwin3333 ( 1 : 3 , 1 : 3 , 1 : 3 , 1 : 3 , k , instance ) )
enddo ; enddo
2010-07-13 13:49:25 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! Burgers vector, dislocation velocity prefactor for each slip system
2014-03-09 02:20:31 +05:30
do s = 1_pInt , constitutive_titanmod_totalNslip ( instance )
f = constitutive_titanmod_slipFamily ( s , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_burgersPerSlipSys ( s , instance ) = &
constitutive_titanmod_burgersPerSlipFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_f0_PerSlipSys ( s , instance ) = &
constitutive_titanmod_f0_PerSlipFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_tau0e_PerSlipSys ( s , instance ) = &
constitutive_titanmod_tau0e_PerSlipFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_tau0s_PerSlipSys ( s , instance ) = &
constitutive_titanmod_tau0s_PerSlipFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_capre_PerSlipSys ( s , instance ) = &
constitutive_titanmod_capre_PerSlipFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_caprs_PerSlipSys ( s , instance ) = &
constitutive_titanmod_caprs_PerSlipFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_v0e_PerSlipSys ( s , instance ) = &
constitutive_titanmod_v0e_PerSlipFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_v0s_PerSlipSys ( s , instance ) = &
constitutive_titanmod_v0s_PerSlipFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_kinkcriticallength_PerSlipSys ( s , instance ) = &
constitutive_titanmod_kinkcriticallength_PerSlipFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_pe_PerSlipSys ( s , instance ) = &
constitutive_titanmod_pe_PerSlipFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_ps_PerSlipSys ( s , instance ) = &
constitutive_titanmod_ps_PerSlipFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_qe_PerSlipSys ( s , instance ) = &
constitutive_titanmod_qe_PerSlipFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_qs_PerSlipSys ( s , instance ) = &
constitutive_titanmod_qs_PerSlipFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_CeLambdaSlipPerSlipSys ( s , instance ) = &
constitutive_titanmod_CeLambdaSlipPerSlipFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_CsLambdaSlipPerSlipSys ( s , instance ) = &
constitutive_titanmod_CsLambdaSlipPerSlipFam ( f , instance )
enddo
2010-07-13 13:49:25 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! Burgers vector, nucleation rate prefactor and twin size for each twin system
2014-03-09 02:20:31 +05:30
do t = 1_pInt , constitutive_titanmod_totalNtwin ( instance )
f = constitutive_titanmod_twinFamily ( t , instance )
constitutive_titanmod_burgersPerTwinSys ( t , instance ) = &
constitutive_titanmod_burgersPerTwinFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_twinsizePerTwinSys ( t , instance ) = &
constitutive_titanmod_twinsizePerTwinFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_twinf0_PerTwinSys ( t , instance ) = &
constitutive_titanmod_twinf0_PerTwinFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_twinshearconstant_PerTwinSys ( t , instance ) = &
constitutive_titanmod_twinshearconstant_PerTwinFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_twintau0_PerTwinSys ( t , instance ) = &
constitutive_titanmod_twintau0_PerTwinFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_twingamma0_PerTwinSys ( t , instance ) = &
constitutive_titanmod_twingamma0_PerTwinFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_twinp_PerTwinSys ( t , instance ) = &
constitutive_titanmod_twinp_PerTwinFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_twinq_PerTwinSys ( t , instance ) = &
constitutive_titanmod_twinq_PerTwinFam ( f , instance )
2014-02-28 15:48:40 +05:30
2014-03-09 02:20:31 +05:30
constitutive_titanmod_twinLambdaSlipPerTwinSys ( t , instance ) = &
constitutive_titanmod_twinLambdaSlipPerTwinFam ( f , instance )
enddo
2010-07-13 13:49:25 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! Construction of interaction matrices
2014-03-09 02:20:31 +05:30
do s1 = 1_pInt , constitutive_titanmod_totalNslip ( instance )
do s2 = 1_pInt , constitutive_titanmod_totalNslip ( instance )
constitutive_titanmod_interactionMatrixSlipSlip ( s1 , s2 , instance ) = &
constitutive_titanmod_interactionSlipSlip ( lattice_interactionSlipSlip ( &
constitutive_titanmod_slipSystemLattice ( s1 , instance ) , &
constitutive_titanmod_slipSystemLattice ( s2 , instance ) , phase ) , instance )
constitutive_titanmod_interactionMatrix_ee ( s1 , s2 , instance ) = &
constitutive_titanmod_interaction_ee ( lattice_interactionSlipSlip ( &
constitutive_titanmod_slipSystemLattice ( s1 , instance ) , &
constitutive_titanmod_slipSystemLattice ( s2 , instance ) , phase ) , instance )
constitutive_titanmod_interactionMatrix_ss ( s1 , s2 , instance ) = &
constitutive_titanmod_interaction_ss ( lattice_interactionSlipSlip ( &
constitutive_titanmod_slipSystemLattice ( s1 , instance ) , &
constitutive_titanmod_slipSystemLattice ( s2 , instance ) , phase ) , instance )
constitutive_titanmod_interactionMatrix_es ( s1 , s2 , instance ) = &
constitutive_titanmod_interaction_es ( lattice_interactionSlipSlip ( &
constitutive_titanmod_slipSystemLattice ( s1 , instance ) , &
constitutive_titanmod_slipSystemLattice ( s2 , instance ) , phase ) , instance )
enddo ; enddo
do s1 = 1_pInt , constitutive_titanmod_totalNslip ( instance )
do t2 = 1_pInt , constitutive_titanmod_totalNtwin ( instance )
constitutive_titanmod_interactionMatrixSlipTwin ( s1 , t2 , instance ) = &
constitutive_titanmod_interactionSlipTwin ( lattice_interactionSlipTwin ( &
constitutive_titanmod_slipSystemLattice ( s1 , instance ) , &
constitutive_titanmod_twinSystemLattice ( t2 , instance ) , phase ) , instance )
enddo ; enddo
do t1 = 1_pInt , constitutive_titanmod_totalNtwin ( instance )
do s2 = 1_pInt , constitutive_titanmod_totalNslip ( instance )
constitutive_titanmod_interactionMatrixTwinSlip ( t1 , s2 , instance ) = &
constitutive_titanmod_interactionTwinSlip ( lattice_interactionTwinSlip ( &
constitutive_titanmod_twinSystemLattice ( t1 , instance ) , &
constitutive_titanmod_slipSystemLattice ( s2 , instance ) , phase ) , instance )
enddo ; enddo
do t1 = 1_pInt , constitutive_titanmod_totalNtwin ( instance )
do t2 = 1_pInt , constitutive_titanmod_totalNtwin ( instance )
constitutive_titanmod_interactionMatrixTwinTwin ( t1 , t2 , instance ) = &
constitutive_titanmod_interactionTwinTwin ( lattice_interactionTwinTwin ( &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_twinSystemLattice ( t1 , instance ) , &
2014-03-09 02:20:31 +05:30
constitutive_titanmod_twinSystemLattice ( t2 , instance ) , phase ) , instance )
enddo ; enddo
do s1 = 1_pInt , constitutive_titanmod_totalNslip ( instance )
do s2 = 1_pInt , constitutive_titanmod_totalNslip ( instance )
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! calculation of forest projections for edge dislocations
2014-03-09 02:20:31 +05:30
constitutive_titanmod_forestProjectionEdge ( s1 , s2 , instance ) = &
abs ( math_mul3x3 ( lattice_sn ( : , constitutive_titanmod_slipSystemLattice ( s1 , instance ) , phase ) , &
lattice_st ( : , constitutive_titanmod_slipSystemLattice ( s2 , instance ) , phase ) ) )
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! calculation of forest projections for screw dislocations
2014-03-09 02:20:31 +05:30
constitutive_titanmod_forestProjectionScrew ( s1 , s2 , instance ) = &
abs ( math_mul3x3 ( lattice_sn ( : , constitutive_titanmod_slipSystemLattice ( s1 , instance ) , phase ) , &
lattice_sd ( : , constitutive_titanmod_slipSystemLattice ( s2 , instance ) , phase ) ) )
enddo ; enddo
2010-07-13 13:49:25 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! calculation of forest projections for edge dislocations in twin system
2014-03-09 02:20:31 +05:30
do t1 = 1_pInt , constitutive_titanmod_totalNtwin ( instance )
do t2 = 1_pInt , constitutive_titanmod_totalNtwin ( instance )
constitutive_titanmod_TwinforestProjectionEdge ( t1 , t2 , instance ) = &
abs ( math_mul3x3 ( lattice_tn ( : , constitutive_titanmod_twinSystemLattice ( t1 , instance ) , phase ) , &
lattice_tt ( : , constitutive_titanmod_twinSystemLattice ( t2 , instance ) , phase ) ) )
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! calculation of forest projections for screw dislocations in twin system
2014-03-09 02:20:31 +05:30
constitutive_titanmod_TwinforestProjectionScrew ( t1 , t2 , instance ) = &
abs ( math_mul3x3 ( lattice_tn ( : , constitutive_titanmod_twinSystemLattice ( t1 , instance ) , phase ) , &
lattice_td ( : , constitutive_titanmod_twinSystemLattice ( t2 , instance ) , phase ) ) )
enddo ; enddo
2014-07-02 17:57:39 +05:30
call constitutive_titanmod_stateInit ( phase , instance )
2014-03-09 02:20:31 +05:30
endif
enddo initializeInstances
2013-07-12 12:27:15 +05:30
end subroutine constitutive_titanmod_init
!--------------------------------------------------------------------------------------------------
2013-10-08 21:57:26 +05:30
!> @brief sets the initial microstructural state for a given instance of this plasticity
2013-07-12 12:27:15 +05:30
!--------------------------------------------------------------------------------------------------
2014-07-02 17:57:39 +05:30
subroutine constitutive_titanmod_stateInit ( ph , instance )
2014-06-11 17:57:41 +05:30
use lattice , only : &
lattice_maxNslipFamily , &
lattice_maxNtwinFamily , &
lattice_mu
use material , only : &
2014-07-02 17:57:39 +05:30
plasticState , &
mappingConstitutive
2014-06-11 17:57:41 +05:30
implicit none
integer ( pInt ) , intent ( in ) :: instance !< number specifying the instance of the plasticity
2014-07-02 17:57:39 +05:30
integer ( pInt ) , intent ( in ) :: ph !< number specifying the phase of the plasticity
2014-06-11 17:57:41 +05:30
integer ( pInt ) :: &
s , s0 , s1 , &
t , t0 , t1 , &
ns , nt , f
real ( pReal ) , dimension ( constitutive_titanmod_totalNslip ( instance ) ) :: &
rho_edge0 , &
rho_screw0 , &
shear_system0 , &
segment_edge0 , &
segment_screw0 , &
resistance_edge0 , &
resistance_screw0
real ( pReal ) , dimension ( constitutive_titanmod_totalNtwin ( instance ) ) :: &
twingamma_dot0 , &
resistance_twin0
2014-07-02 17:57:39 +05:30
real ( pReal ) , dimension ( plasticState ( ph ) % sizeState ) :: tempState !!!!!!!!!????????? check
2014-06-11 17:57:41 +05:30
ns = constitutive_titanmod_totalNslip ( instance )
nt = constitutive_titanmod_totalNtwin ( instance )
tempState = 0.0_pReal
!--------------------------------------------------------------------------------------------------
! initialize basic slip state variables for slip
s1 = 0_pInt
do f = 1_pInt , lattice_maxNslipFamily
s0 = s1 + 1_pInt
s1 = s0 + constitutive_titanmod_Nslip ( f , instance ) - 1_pInt
do s = s0 , s1
rho_edge0 ( s ) = constitutive_titanmod_rho_edge0 ( f , instance )
rho_screw0 ( s ) = constitutive_titanmod_rho_screw0 ( f , instance )
shear_system0 ( s ) = 0.0_pReal
enddo
enddo
!--------------------------------------------------------------------------------------------------
! initialize basic slip state variables for twin
t1 = 0_pInt
do f = 1_pInt , lattice_maxNtwinFamily
t0 = t1 + 1_pInt
t1 = t0 + constitutive_titanmod_Ntwin ( f , instance ) - 1_pInt
do t = t0 , t1
twingamma_dot0 ( t ) = 0.0_pReal
enddo
enddo
!--------------------------------------------------------------------------------------------------
! initialize dependent slip microstructural variables
forall ( s = 1_pInt : ns )
segment_edge0 ( s ) = constitutive_titanmod_CeLambdaSlipPerSlipSys ( s , instance ) / &
sqrt ( dot_product ( ( rho_edge0 ) , constitutive_titanmod_forestProjectionEdge ( 1 : ns , s , instance ) ) + &
dot_product ( ( rho_screw0 ) , constitutive_titanmod_forestProjectionScrew ( 1 : ns , s , instance ) ) )
segment_screw0 ( s ) = constitutive_titanmod_CsLambdaSlipPerSlipSys ( s , instance ) / &
sqrt ( dot_product ( ( rho_edge0 ) , constitutive_titanmod_forestProjectionEdge ( 1 : ns , s , instance ) ) + &
dot_product ( ( rho_screw0 ) , constitutive_titanmod_forestProjectionScrew ( 1 : ns , s , instance ) ) )
resistance_edge0 ( s ) = &
2014-07-02 17:57:39 +05:30
lattice_mu ( ph ) * constitutive_titanmod_burgersPerSlipSys ( s , instance ) * &
2014-06-11 17:57:41 +05:30
sqrt ( dot_product ( ( rho_edge0 ) , constitutive_titanmod_interactionMatrix_ee ( 1 : ns , s , instance ) ) + &
dot_product ( ( rho_screw0 ) , constitutive_titanmod_interactionMatrix_es ( 1 : ns , s , instance ) ) )
resistance_screw0 ( s ) = &
2014-07-02 17:57:39 +05:30
lattice_mu ( ph ) * constitutive_titanmod_burgersPerSlipSys ( s , instance ) * &
2014-06-11 17:57:41 +05:30
sqrt ( dot_product ( ( rho_edge0 ) , constitutive_titanmod_interactionMatrix_es ( 1 : ns , s , instance ) ) + &
dot_product ( ( rho_screw0 ) , constitutive_titanmod_interactionMatrix_ss ( 1 : ns , s , instance ) ) )
end forall
forall ( t = 1_pInt : nt ) &
resistance_twin0 ( t ) = 0.0_pReal
tempState = 0.0_pReal
tempState ( 1 : ns ) = rho_edge0
tempState ( 1_pInt * ns + 1_pInt : 2_pInt * ns ) = rho_screw0
tempState ( 2_pInt * ns + 1_pInt : 3_pInt * ns ) = shear_system0
tempState ( 3_pInt * ns + 1_pInt : 3_pInt * ns + nt ) = twingamma_dot0
tempState ( 3_pInt * ns + nt + 1_pInt : 4_pInt * ns + nt ) = segment_edge0
tempState ( 4_pInt * ns + nt + 1_pInt : 5_pInt * ns + nt ) = segment_screw0
tempState ( 5_pInt * ns + nt + 1_pInt : 6_pInt * ns + nt ) = resistance_edge0
tempState ( 6_pInt * ns + nt + 1_pInt : 7_pInt * ns + nt ) = resistance_screw0
tempState ( 7_pInt * ns + nt + 1_pInt : 7_pInt * ns + 2_pInt * nt ) = resistance_twin0
2014-07-02 17:57:39 +05:30
plasticState ( ph ) % state0 = spread ( tempState , 2 , size ( plasticState ( ph ) % state ( 1 , : ) ) )
end subroutine constitutive_titanmod_stateInit
2010-07-13 13:49:25 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief returns the homogenized elasticity matrix
!--------------------------------------------------------------------------------------------------
2014-07-02 17:57:39 +05:30
function constitutive_titanmod_homogenizedC ( ipc , ip , el )
2013-10-08 21:57:26 +05:30
use mesh , only : &
mesh_NcpElems , &
mesh_maxNips
use material , only : &
homogenization_maxNgrains , &
material_phase , &
2014-07-02 17:57:39 +05:30
phase_plasticityInstance , &
plasticState , &
mappingConstitutive
2014-03-09 02:20:31 +05:30
use lattice , only : &
lattice_C66
2010-07-13 13:49:25 +05:30
2012-03-09 01:55:28 +05:30
implicit none
2013-10-08 21:57:26 +05:30
real ( pReal ) , dimension ( 6 , 6 ) :: &
constitutive_titanmod_homogenizedC
integer ( pInt ) , intent ( in ) :: &
ipc , & !< component-ID of integration point
ip , & !< integration point
el !< element
2013-07-12 12:27:15 +05:30
real ( pReal ) , dimension ( constitutive_titanmod_totalNtwin ( phase_plasticityInstance ( material_phase ( ipc , ip , el ) ) ) ) :: &
volumefraction_PerTwinSys
2013-10-08 21:57:26 +05:30
integer ( pInt ) :: &
2014-07-02 17:57:39 +05:30
ph , &
of , &
2014-02-28 15:48:40 +05:30
instance , &
2013-10-08 21:57:26 +05:30
ns , nt , &
i
real ( pReal ) :: &
sumf
2014-06-11 17:57:41 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! shortened notation
2014-07-02 17:57:39 +05:30
! ph = material_phase(ipc,ip,el)
of = mappingConstitutive ( 1 , ipc , ip , el )
ph = mappingConstitutive ( 2 , ipc , ip , el )
instance = phase_plasticityInstance ( ph )
2014-02-28 15:48:40 +05:30
ns = constitutive_titanmod_totalNslip ( instance )
nt = constitutive_titanmod_totalNtwin ( instance )
2010-07-13 13:49:25 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! total twin volume fraction
2013-07-12 12:27:15 +05:30
do i = 1_pInt , nt
2014-07-02 17:57:39 +05:30
volumefraction_PerTwinSys ( i ) = plasticState ( ph ) % state ( 3_pInt * ns + i , of ) / &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_twinshearconstant_PerTwinSys ( i , instance )
2013-07-12 12:27:15 +05:30
enddo
sumf = sum ( abs ( volumefraction_PerTwinSys ( 1 : nt ) ) ) ! safe for nt == 0
2010-07-13 13:49:25 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! homogenized elasticity matrix
2014-07-02 17:57:39 +05:30
constitutive_titanmod_homogenizedC = ( 1.0_pReal - sumf ) * lattice_C66 ( 1 : 6 , 1 : 6 , ph )
2013-07-12 12:27:15 +05:30
do i = 1_pInt , nt
2013-10-16 18:34:59 +05:30
constitutive_titanmod_homogenizedC = constitutive_titanmod_homogenizedC &
+ volumefraction_PerTwinSys ( i ) * &
2014-03-09 02:20:31 +05:30
constitutive_titanmod_Ctwin66 ( 1 : 6 , 1 : 6 , i , instance )
2013-07-12 12:27:15 +05:30
enddo
end function constitutive_titanmod_homogenizedC
2010-09-07 20:14:37 +05:30
2010-07-13 13:49:25 +05:30
2013-07-12 12:27:15 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief calculates derived quantities from state
!--------------------------------------------------------------------------------------------------
2014-07-02 17:57:39 +05:30
subroutine constitutive_titanmod_microstructure ( temperature , ipc , ip , el )
2013-07-12 12:27:15 +05:30
use mesh , only : &
mesh_NcpElems , &
mesh_maxNips
use material , only : &
homogenization_maxNgrains , &
material_phase , &
2014-07-02 17:57:39 +05:30
phase_plasticityInstance , &
plasticState , &
mappingConstitutive
2014-03-09 02:20:31 +05:30
use lattice , only : &
lattice_mu
2013-07-12 12:27:15 +05:30
implicit none
2013-10-08 21:57:26 +05:30
integer ( pInt ) , intent ( in ) :: &
ipc , & !< component-ID of integration point
ip , & !< integration point
el !< element
real ( pReal ) , intent ( in ) :: &
temperature !< temperature at IP
integer ( pInt ) :: &
2014-03-09 02:20:31 +05:30
instance , &
2013-10-08 21:57:26 +05:30
ns , nt , s , t , &
2014-07-02 17:57:39 +05:30
i , &
ph , &
of
2013-10-08 21:57:26 +05:30
real ( pReal ) :: &
sumf , &
sfe ! stacking fault energy
2013-07-12 12:27:15 +05:30
real ( pReal ) , dimension ( constitutive_titanmod_totalNtwin ( phase_plasticityInstance ( material_phase ( ipc , ip , el ) ) ) ) :: &
volumefraction_PerTwinSys
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
2014-06-11 17:57:41 +05:30
2013-10-08 21:57:26 +05:30
!Shortened notation
2014-07-02 17:57:39 +05:30
of = mappingConstitutive ( 1 , ipc , ip , el )
ph = mappingConstitutive ( 2 , ipc , ip , el )
instance = phase_plasticityInstance ( ph )
2014-02-28 15:48:40 +05:30
ns = constitutive_titanmod_totalNslip ( instance )
nt = constitutive_titanmod_totalNtwin ( instance )
2013-07-12 12:27:15 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! total twin volume fraction
2014-03-13 12:13:49 +05:30
forall ( i = 1_pInt : nt ) &
2014-07-02 17:57:39 +05:30
volumefraction_PerTwinSys ( i ) = plasticState ( ph ) % state ( 3_pInt * ns + i , of ) / &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_twinshearconstant_PerTwinSys ( i , instance )
2013-07-12 12:27:15 +05:30
sumf = sum ( abs ( volumefraction_PerTwinSys ( 1 : nt ) ) ) ! safe for nt == 0
sfe = 0.0002_pReal * Temperature - 0.0396_pReal
2010-07-13 13:49:25 +05:30
2013-07-12 12:27:15 +05:30
!--------------------------------------------------------------------------------------------------
2010-09-01 15:37:52 +05:30
! average segment length for edge dislocations in matrix
2013-07-12 12:27:15 +05:30
forall ( s = 1_pInt : ns ) &
2014-07-02 17:57:39 +05:30
plasticState ( ph ) % state ( 3_pInt * ns + nt + s , of ) = constitutive_titanmod_CeLambdaSlipPerSlipSys ( s , instance ) / &
sqrt ( dot_product ( plasticState ( ph ) % state ( 1 : ns , of ) , &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_forestProjectionEdge ( 1 : ns , s , instance ) ) + &
2014-07-02 17:57:39 +05:30
dot_product ( plasticState ( ph ) % state ( ns + 1_pInt : 2_pInt * ns , of ) , &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_forestProjectionScrew ( 1 : ns , s , instance ) ) )
2013-07-12 12:27:15 +05:30
!--------------------------------------------------------------------------------------------------
2010-09-22 14:30:40 +05:30
! average segment length for screw dislocations in matrix
2013-07-12 12:27:15 +05:30
forall ( s = 1_pInt : ns ) &
2014-07-02 17:57:39 +05:30
plasticState ( ph ) % state ( 4_pInt * ns + nt + s , of ) = constitutive_titanmod_CsLambdaSlipPerSlipSys ( s , instance ) / &
sqrt ( dot_product ( plasticState ( ph ) % state ( 1 : ns , of ) , &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_forestProjectionEdge ( 1 : ns , s , instance ) ) + &
2014-07-02 17:57:39 +05:30
dot_product ( plasticState ( ph ) % state ( ns + 1_pInt : 2_pInt * ns , of ) , &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_forestProjectionScrew ( 1 : ns , s , instance ) ) )
2013-07-12 12:27:15 +05:30
!--------------------------------------------------------------------------------------------------
! threshold stress or slip resistance for edge dislocation motion
forall ( s = 1_pInt : ns ) &
2014-07-02 17:57:39 +05:30
plasticState ( ph ) % state ( 5_pInt * ns + nt + s , of ) = &
lattice_mu ( ph ) * constitutive_titanmod_burgersPerSlipSys ( s , instance ) * &
sqrt ( dot_product ( ( plasticState ( ph ) % state ( 1 : ns , of ) ) , &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_interactionMatrix_ee ( 1 : ns , s , instance ) ) + &
2014-07-02 17:57:39 +05:30
dot_product ( ( plasticState ( ph ) % state ( ns + 1_pInt : 2_pInt * ns , of ) ) , &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_interactionMatrix_es ( 1 : ns , s , instance ) ) )
2013-07-12 12:27:15 +05:30
!--------------------------------------------------------------------------------------------------
! threshold stress or slip resistance for screw dislocation motion
forall ( s = 1_pInt : ns ) &
2014-07-02 17:57:39 +05:30
plasticState ( ph ) % state ( 6_pInt * ns + nt + s , of ) = &
lattice_mu ( ph ) * constitutive_titanmod_burgersPerSlipSys ( s , instance ) * &
sqrt ( dot_product ( ( plasticState ( ph ) % state ( 1 : ns , of ) ) , &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_interactionMatrix_es ( 1 : ns , s , instance ) ) + &
2014-07-02 17:57:39 +05:30
dot_product ( ( plasticState ( ph ) % state ( ns + 1_pInt : 2_pInt * ns , of ) ) , &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_interactionMatrix_ss ( 1 : ns , s , instance ) ) )
2013-07-12 12:27:15 +05:30
!--------------------------------------------------------------------------------------------------
! threshold stress or slip resistance for dislocation motion in twin
forall ( t = 1_pInt : nt ) &
2014-07-02 17:57:39 +05:30
plasticState ( ph ) % state ( 7_pInt * ns + nt + t , of ) = &
lattice_mu ( ph ) * constitutive_titanmod_burgersPerTwinSys ( t , instance ) * &
( dot_product ( ( abs ( plasticState ( ph ) % state ( 2_pInt * ns + 1_pInt : 2_pInt * ns + nt , of ) ) ) , &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_interactionMatrixTwinTwin ( 1 : nt , t , instance ) ) )
2014-06-11 17:57:41 +05:30
2014-07-02 17:57:39 +05:30
! state=tempState
2013-07-12 12:27:15 +05:30
end subroutine constitutive_titanmod_microstructure
2010-07-13 13:49:25 +05:30
2013-07-12 12:27:15 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief calculates plastic velocity gradient and its tangent
!--------------------------------------------------------------------------------------------------
2014-07-02 17:57:39 +05:30
subroutine constitutive_titanmod_LpAndItsTangent ( Lp , dLp_dTstar99 , Tstar_v , temperature , ipc , ip , el )
2013-07-12 12:27:15 +05:30
use math , only : &
math_Plain3333to99 , &
math_Mandel6to33
use lattice , only : &
lattice_Sslip , &
lattice_Sslip_v , &
lattice_Stwin , &
lattice_Stwin_v , &
lattice_maxNslipFamily , &
lattice_maxNtwinFamily , &
lattice_NslipSystem , &
2014-03-09 02:20:31 +05:30
lattice_NtwinSystem , &
lattice_structure , &
LATTICE_hex_ID
2013-07-12 12:27:15 +05:30
use mesh , only : &
mesh_NcpElems , &
mesh_maxNips
use material , only : &
homogenization_maxNgrains , &
material_phase , &
2014-07-02 17:57:39 +05:30
phase_plasticityInstance , &
plasticState , &
mappingConstitutive
2013-07-12 12:27:15 +05:30
implicit none
2014-03-13 12:13:49 +05:30
real ( pReal ) , dimension ( 3 , 3 ) , intent ( out ) :: &
2013-07-12 12:27:15 +05:30
Lp !< plastic velocity gradient
2014-03-13 12:13:49 +05:30
real ( pReal ) , dimension ( 9 , 9 ) , intent ( out ) :: &
2013-07-12 12:27:15 +05:30
dLp_dTstar99 !< derivative of Lp with respect to 2nd Piola Kirchhoff stress
2014-03-13 12:13:49 +05:30
real ( pReal ) , dimension ( 6 ) , intent ( in ) :: &
2013-07-12 12:27:15 +05:30
Tstar_v !< 2nd Piola Kirchhoff stress tensor in Mandel notation
2014-03-13 12:13:49 +05:30
real ( pReal ) , intent ( in ) :: &
2013-07-12 12:27:15 +05:30
temperature !< temperature at IP
2014-03-13 12:13:49 +05:30
integer ( pInt ) , intent ( in ) :: &
2013-07-12 12:27:15 +05:30
ipc , & !< component-ID of integration point
ip , & !< integration point
el !< element
2013-10-08 21:57:26 +05:30
integer ( pInt ) :: &
2014-07-02 17:57:39 +05:30
index_myFamily , instance , &
2013-10-08 21:57:26 +05:30
ns , nt , &
2014-07-02 17:57:39 +05:30
f , i , j , k , l , m , n , &
ph , &
of
2013-10-08 21:57:26 +05:30
real ( pReal ) :: sumf , &
StressRatio_edge_p , minusStressRatio_edge_p , StressRatio_edge_pminus1 , BoltzmannRatioedge , &
StressRatio_screw_p , minusStressRatio_screw_p , StressRatio_screw_pminus1 , BoltzmannRatioscrew , &
twinStressRatio_p , twinminusStressRatio_p , twinStressRatio_pminus1 , BoltzmannRatiotwin , &
twinDotGamma0 , bottomstress_edge , bottomstress_screw , screwvelocity_prefactor
2013-07-12 12:27:15 +05:30
real ( pReal ) , dimension ( 3 , 3 , 3 , 3 ) :: dLp_dTstar3333
real ( pReal ) , dimension ( constitutive_titanmod_totalNslip ( phase_plasticityInstance ( material_phase ( ipc , ip , el ) ) ) ) :: &
2013-10-08 21:57:26 +05:30
gdot_slip , dgdot_dtauslip , tau_slip , &
edge_velocity , screw_velocity , &
gdot_slip_edge , gdot_slip_screw
2013-07-12 12:27:15 +05:30
real ( pReal ) , dimension ( constitutive_titanmod_totalNtwin ( phase_plasticityInstance ( material_phase ( ipc , ip , el ) ) ) ) :: &
gdot_twin , dgdot_dtautwin , tau_twin , volumefraction_PerTwinSys
2014-06-11 17:57:41 +05:30
2014-07-02 17:57:39 +05:30
! tempState=state
2014-06-11 17:57:41 +05:30
2013-07-12 12:27:15 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! shortened notation
2014-07-02 17:57:39 +05:30
of = mappingConstitutive ( 1 , ipc , ip , el )
ph = mappingConstitutive ( 2 , ipc , ip , el )
instance = phase_plasticityInstance ( ph )
2014-02-28 15:48:40 +05:30
ns = constitutive_titanmod_totalNslip ( instance )
nt = constitutive_titanmod_totalNtwin ( instance )
2013-07-12 12:27:15 +05:30
do i = 1_pInt , nt
2014-07-02 17:57:39 +05:30
volumefraction_PerTwinSys ( i ) = plasticState ( ph ) % state ( 3_pInt * ns + i , of ) / &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_twinshearconstant_PerTwinSys ( i , instance )
2013-07-12 12:27:15 +05:30
enddo
sumf = sum ( abs ( volumefraction_PerTwinSys ( 1 : nt ) ) ) ! safe for nt == 0
Lp = 0.0_pReal
dLp_dTstar3333 = 0.0_pReal
dLp_dTstar99 = 0.0_pReal
!* Dislocation glide part
gdot_slip = 0.0_pReal
gdot_slip_edge = 0.0_pReal
gdot_slip_screw = 0.0_pReal
dgdot_dtauslip = 0.0_pReal
j = 0_pInt
2013-10-08 21:57:26 +05:30
slipFamiliesLoop : do f = 1_pInt , lattice_maxNslipFamily
2014-07-02 17:57:39 +05:30
index_myFamily = sum ( lattice_NslipSystem ( 1 : f - 1_pInt , ph ) ) ! at which index starts my family
2014-02-28 15:48:40 +05:30
do i = 1_pInt , constitutive_titanmod_Nslip ( f , instance ) ! process each (active) slip system in family
2010-07-13 13:49:25 +05:30
j = j + 1_pInt
!* Calculation of Lp
!* Resolved shear stress on slip system
2014-07-02 17:57:39 +05:30
tau_slip ( j ) = dot_product ( Tstar_v , lattice_Sslip_v ( : , 1 , index_myFamily + i , ph ) )
if ( lattice_structure ( ph ) == LATTICE_hex_ID ) then ! only for prismatic and pyr <a> systems in hex
2014-02-28 15:48:40 +05:30
screwvelocity_prefactor = constitutive_titanmod_debyefrequency ( instance ) * &
2014-07-02 17:57:39 +05:30
plasticState ( ph ) % state ( 4_pInt * ns + nt + j , of ) * ( constitutive_titanmod_burgersPerSlipSys ( j , instance ) / &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_kinkcriticallength_PerSlipSys ( j , instance ) ) ** 2
2010-09-22 14:30:40 +05:30
2010-09-29 12:05:08 +05:30
!* Stress ratio for screw ! No slip resistance for screw dislocations, only Peierls stress
2014-02-28 15:48:40 +05:30
bottomstress_screw = constitutive_titanmod_tau0s_PerSlipSys ( j , instance )
2010-08-23 17:06:51 +05:30
StressRatio_screw_p = ( ( abs ( tau_slip ( j ) ) ) / &
2011-03-31 14:51:43 +05:30
( bottomstress_screw ) &
2014-02-28 15:48:40 +05:30
) ** constitutive_titanmod_ps_PerSlipSys ( j , instance )
2011-03-31 14:51:43 +05:30
2010-09-01 15:37:52 +05:30
if ( ( 1.0_pReal - StressRatio_screw_p ) > 0.001_pReal ) then
2010-08-23 17:06:51 +05:30
minusStressRatio_screw_p = 1.0_pReal - StressRatio_screw_p
else
2010-09-01 15:37:52 +05:30
minusStressRatio_screw_p = 0.001_pReal
2010-08-23 17:06:51 +05:30
endif
2014-02-28 15:48:40 +05:30
bottomstress_screw = constitutive_titanmod_tau0s_PerSlipSys ( j , instance )
2010-08-06 21:23:45 +05:30
StressRatio_screw_pminus1 = ( ( abs ( tau_slip ( j ) ) ) / &
2011-03-31 14:51:43 +05:30
( bottomstress_screw ) &
2014-02-28 15:48:40 +05:30
) ** ( constitutive_titanmod_ps_PerSlipSys ( j , instance ) - 1.0_pReal )
2010-07-13 13:49:25 +05:30
2010-09-29 12:05:08 +05:30
!* Boltzmann ratio for screw
2014-02-28 15:48:40 +05:30
BoltzmannRatioscrew = constitutive_titanmod_kinkf0 ( instance ) / ( kB * Temperature )
2010-07-13 13:49:25 +05:30
2011-03-31 14:51:43 +05:30
else ! if the structure is not hex or the slip family is basal
2014-02-28 15:48:40 +05:30
screwvelocity_prefactor = constitutive_titanmod_v0s_PerSlipSys ( j , instance )
2014-07-02 17:57:39 +05:30
bottomstress_screw = constitutive_titanmod_tau0s_PerSlipSys ( j , instance ) + &
plasticState ( ph ) % state ( 6 * ns + nt + j , of )
2014-02-28 15:48:40 +05:30
StressRatio_screw_p = ( ( abs ( tau_slip ( j ) ) ) / ( bottomstress_screw ) ) ** constitutive_titanmod_ps_PerSlipSys ( j , instance )
2011-03-31 14:51:43 +05:30
if ( ( 1.0_pReal - StressRatio_screw_p ) > 0.001_pReal ) then
minusStressRatio_screw_p = 1.0_pReal - StressRatio_screw_p
else
minusStressRatio_screw_p = 0.001_pReal
endif
StressRatio_screw_pminus1 = ( ( abs ( tau_slip ( j ) ) ) / ( bottomstress_screw ) ) ** &
2014-02-28 15:48:40 +05:30
( constitutive_titanmod_ps_PerSlipSys ( j , instance ) - 1.0_pReal )
2011-03-31 14:51:43 +05:30
!* Boltzmann ratio for screw
2014-02-28 15:48:40 +05:30
BoltzmannRatioscrew = constitutive_titanmod_f0_PerSlipSys ( j , instance ) / ( kB * Temperature )
2011-03-31 14:51:43 +05:30
endif
!* Stress ratio for edge
2014-07-02 17:57:39 +05:30
bottomstress_edge = constitutive_titanmod_tau0e_PerSlipSys ( j , instance ) + &
plasticState ( ph ) % state ( 5 * ns + nt + j , of )
2011-03-31 14:51:43 +05:30
StressRatio_edge_p = ( ( abs ( tau_slip ( j ) ) ) / &
( bottomstress_edge ) &
2014-02-28 15:48:40 +05:30
) ** constitutive_titanmod_pe_PerSlipSys ( j , instance )
2011-03-31 14:51:43 +05:30
if ( ( 1.0_pReal - StressRatio_edge_p ) > 0.001_pReal ) then
minusStressRatio_edge_p = 1.0_pReal - StressRatio_edge_p
else
minusStressRatio_edge_p = 0.001_pReal
endif
StressRatio_edge_pminus1 = ( ( abs ( tau_slip ( j ) ) ) / ( bottomstress_edge ) ) ** &
2014-02-28 15:48:40 +05:30
( constitutive_titanmod_pe_PerSlipSys ( j , instance ) - 1.0_pReal )
2011-03-31 14:51:43 +05:30
!* Boltzmann ratio for edge. For screws it is defined above
2014-02-28 15:48:40 +05:30
BoltzmannRatioedge = constitutive_titanmod_f0_PerSlipSys ( j , instance ) / ( kB * Temperature )
2011-03-31 14:51:43 +05:30
2010-09-22 14:30:40 +05:30
screw_velocity ( j ) = screwvelocity_prefactor * & ! there is no v0 for screw now because it is included in the prefactor
2010-09-29 12:05:08 +05:30
exp ( - BoltzmannRatioscrew * ( minusStressRatio_screw_p ) ** &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_qs_PerSlipSys ( j , instance ) )
2010-08-06 21:23:45 +05:30
2014-02-28 15:48:40 +05:30
edge_velocity ( j ) = constitutive_titanmod_v0e_PerSlipSys ( j , instance ) * exp ( - BoltzmannRatioedge * &
2011-03-31 14:51:43 +05:30
( minusStressRatio_edge_p ) ** &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_qe_PerSlipSys ( j , instance ) )
2011-03-31 14:51:43 +05:30
2010-09-29 12:05:08 +05:30
!* Shear rates due to edge slip
2014-07-02 17:57:39 +05:30
gdot_slip_edge ( j ) = constitutive_titanmod_burgersPerSlipSys ( j , instance ) * ( plasticState ( ph ) % state ( j , of ) * &
2010-09-29 12:05:08 +05:30
edge_velocity ( j ) ) * sign ( 1.0_pReal , tau_slip ( j ) )
!* Shear rates due to screw slip
2014-07-02 17:57:39 +05:30
gdot_slip_screw ( j ) = constitutive_titanmod_burgersPerSlipSys ( j , instance ) * ( plasticState ( ph ) % state ( ns + j , of ) * &
2010-09-29 12:05:08 +05:30
screw_velocity ( j ) ) * sign ( 1.0_pReal , tau_slip ( j ) )
!Total shear rate
gdot_slip ( j ) = gdot_slip_edge ( j ) + gdot_slip_screw ( j )
2010-08-23 17:06:51 +05:30
2014-07-02 17:57:39 +05:30
plasticState ( ph ) % state ( 7 * ns + 2 * nt + j , of ) = edge_velocity ( j )
plasticState ( ph ) % state ( 8 * ns + 2 * nt + j , of ) = screw_velocity ( j )
plasticState ( ph ) % state ( 9 * ns + 2 * nt + j , of ) = tau_slip ( j )
plasticState ( ph ) % state ( 10 * ns + 2 * nt + j , of ) = gdot_slip_edge ( j )
plasticState ( ph ) % state ( 11 * ns + 2 * nt + j , of ) = gdot_slip_screw ( j )
plasticState ( ph ) % state ( 12 * ns + 2 * nt + j , of ) = StressRatio_edge_p
plasticState ( ph ) % state ( 13 * ns + 2 * nt + j , of ) = StressRatio_screw_p
2010-09-22 14:30:40 +05:30
2010-07-13 13:49:25 +05:30
!* Derivatives of shear rates
2014-02-28 15:48:40 +05:30
dgdot_dtauslip ( j ) = constitutive_titanmod_burgersPerSlipSys ( j , instance ) * ( ( &
2010-08-23 17:06:51 +05:30
( &
( &
( &
2014-07-02 17:57:39 +05:30
( edge_velocity ( j ) * plasticState ( ph ) % state ( j , of ) ) ) * &
2011-03-31 14:51:43 +05:30
BoltzmannRatioedge * &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_pe_PerSlipSys ( j , instance ) * &
constitutive_titanmod_qe_PerSlipSys ( j , instance ) &
2010-08-23 17:06:51 +05:30
) / &
2011-03-31 14:51:43 +05:30
bottomstress_edge &
2010-08-23 17:06:51 +05:30
) * &
2010-08-06 21:23:45 +05:30
StressRatio_edge_pminus1 * ( minusStressRatio_edge_p ) ** &
2014-02-28 15:48:40 +05:30
( constitutive_titanmod_qe_PerSlipSys ( j , instance ) - 1.0_pReal ) &
2010-08-23 17:06:51 +05:30
) + &
( &
( &
( &
2014-07-02 17:57:39 +05:30
( plasticState ( ph ) % state ( ns + j , of ) * screw_velocity ( j ) ) * &
2011-03-31 14:51:43 +05:30
BoltzmannRatioscrew * &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_ps_PerSlipSys ( j , instance ) * &
constitutive_titanmod_qs_PerSlipSys ( j , instance ) &
2010-08-23 17:06:51 +05:30
) / &
2011-03-31 14:51:43 +05:30
bottomstress_screw &
2010-08-23 17:06:51 +05:30
) * &
2014-02-28 15:48:40 +05:30
StressRatio_screw_pminus1 * ( minusStressRatio_screw_p ) ** ( constitutive_titanmod_qs_PerSlipSys ( j , instance ) - 1.0_pReal ) &
2010-08-23 17:06:51 +05:30
) &
) !* sign(1.0_pReal,tau_slip(j))
2011-03-31 14:51:43 +05:30
2010-08-23 17:06:51 +05:30
!*************************************************
2010-09-07 20:14:37 +05:30
!sumf=0.0_pReal
2010-07-13 13:49:25 +05:30
!* Plastic velocity gradient for dislocation glide
2014-07-02 17:57:39 +05:30
Lp = Lp + ( 1.0_pReal - sumf ) * gdot_slip ( j ) * lattice_Sslip ( 1 : 3 , 1 : 3 , 1 , index_myFamily + i , ph )
2010-07-13 13:49:25 +05:30
!* Calculation of the tangent of Lp
2012-02-21 21:30:00 +05:30
forall ( k = 1_pInt : 3_pInt , l = 1_pInt : 3_pInt , m = 1_pInt : 3_pInt , n = 1_pInt : 3_pInt ) &
2010-07-13 13:49:25 +05:30
dLp_dTstar3333 ( k , l , m , n ) = &
dLp_dTstar3333 ( k , l , m , n ) + dgdot_dtauslip ( j ) * &
2014-07-02 17:57:39 +05:30
lattice_Sslip ( k , l , 1 , index_myFamily + i , ph ) * &
lattice_Sslip ( m , n , 1 , index_myFamily + i , ph )
2010-07-13 13:49:25 +05:30
enddo
2013-10-08 21:57:26 +05:30
enddo slipFamiliesLoop
2010-07-13 13:49:25 +05:30
!* Mechanical twinning part
2014-02-09 22:38:13 +05:30
gdot_twin = 0.0_pReal
dgdot_dtautwin = 0.0_pReal
j = 0_pInt
twinFamiliesLoop : do f = 1_pInt , lattice_maxNtwinFamily
2014-07-02 17:57:39 +05:30
index_myFamily = sum ( lattice_NtwinSystem ( 1 : f - 1_pInt , ph ) ) ! at which index starts my family
2014-02-28 15:48:40 +05:30
do i = 1_pInt , constitutive_titanmod_Ntwin ( f , instance ) ! process each (active) slip system in family
2014-02-09 22:38:13 +05:30
j = j + 1_pInt
2010-07-13 13:49:25 +05:30
!* Calculation of Lp
!* Resolved shear stress on twin system
2014-07-02 17:57:39 +05:30
tau_twin ( j ) = dot_product ( Tstar_v , lattice_Stwin_v ( : , index_myFamily + i , ph ) )
2010-07-13 13:49:25 +05:30
2010-09-01 15:37:52 +05:30
!**************************************************************************************
!* Stress ratios
2014-07-02 17:57:39 +05:30
! StressRatio_r = (plasticState(ph)%state6*ns+3*nt+j, of)/tau_twin(j))**constitutive_titanmod_r(instance)
2010-07-13 13:49:25 +05:30
2010-08-23 17:06:51 +05:30
!* Shear rates and their derivatives due to twin
2010-08-06 21:23:45 +05:30
! if ( tau_twin(j) > 0.0_pReal ) !then
2010-09-01 15:37:52 +05:30
! gdot_twin(j) = 0.0_pReal!&
2014-07-02 17:57:39 +05:30
! (constitutive_titanmod_MaxTwinFraction(instance)-sumf)*lattice_shearTwin(index_myFamily+i,ph)*&
! plasticState(ph)%state(6*ns+4*nt+j, of)*constitutive_titanmod_Ndot0PerTwinSys(f,instance)*exp(-StressRatio_r)
2014-02-28 15:48:40 +05:30
! dgdot_dtautwin(j) = ((gdot_twin(j)*constitutive_titanmod_r(instance))/tau_twin(j))*StressRatio_r
2010-08-06 21:23:45 +05:30
! endif
2010-09-01 15:37:52 +05:30
!**************************************************************************************
!* Stress ratio for edge
2010-09-22 14:30:40 +05:30
twinStressRatio_p = ( ( abs ( tau_twin ( j ) ) ) / &
2014-07-02 17:57:39 +05:30
( constitutive_titanmod_twintau0_PerTwinSys ( j , instance ) + plasticState ( ph ) % state ( 7 * ns + nt + j , of ) ) &
2014-02-28 15:48:40 +05:30
) ** constitutive_titanmod_twinp_PerTwinSys ( j , instance )
2011-03-31 14:51:43 +05:30
2010-09-22 14:30:40 +05:30
if ( ( 1.0_pReal - twinStressRatio_p ) > 0.001_pReal ) then
twinminusStressRatio_p = 1.0_pReal - twinStressRatio_p
2010-09-01 15:37:52 +05:30
else
2010-09-22 14:30:40 +05:30
twinminusStressRatio_p = 0.001_pReal
2010-09-01 15:37:52 +05:30
endif
2011-03-31 14:51:43 +05:30
2010-09-22 14:30:40 +05:30
twinStressRatio_pminus1 = ( ( abs ( tau_twin ( j ) ) ) / &
2014-07-02 17:57:39 +05:30
( constitutive_titanmod_twintau0_PerTwinSys ( j , instance ) + plasticState ( ph ) % state ( 7 * ns + nt + j , of ) ) &
2014-02-28 15:48:40 +05:30
) ** ( constitutive_titanmod_twinp_PerTwinSys ( j , instance ) - 1.0_pReal )
2010-09-01 15:37:52 +05:30
!* Boltzmann ratio
2014-02-28 15:48:40 +05:30
BoltzmannRatiotwin = constitutive_titanmod_twinf0_PerTwinSys ( j , instance ) / ( kB * Temperature )
2010-09-01 15:37:52 +05:30
2010-09-22 14:30:40 +05:30
!* Initial twin shear rates
2010-09-01 15:37:52 +05:30
TwinDotGamma0 = &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_twingamma0_PerTwinSys ( j , instance )
2010-09-22 14:30:40 +05:30
!* Shear rates due to twin
2014-02-28 15:48:40 +05:30
gdot_twin ( j ) = sign ( 1.0_pReal , tau_twin ( j ) ) * constitutive_titanmod_twingamma0_PerTwinSys ( j , instance ) * &
exp ( - BoltzmannRatiotwin * ( twinminusStressRatio_p ) ** constitutive_titanmod_twinq_PerTwinSys ( j , instance ) )
2010-09-22 14:30:40 +05:30
2011-03-31 14:51:43 +05:30
2010-09-01 15:37:52 +05:30
!* Derivatives of shear rates in twin
dgdot_dtautwin ( j ) = ( &
( &
( &
( abs ( gdot_twin ( j ) ) ) * &
2011-03-31 14:51:43 +05:30
BoltzmannRatiotwin * &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_twinp_PerTwinSys ( j , instance ) * &
constitutive_titanmod_twinq_PerTwinSys ( j , instance ) &
2010-09-01 15:37:52 +05:30
) / &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_twintau0_PerTwinSys ( j , instance ) &
2010-09-01 15:37:52 +05:30
) * &
2010-09-22 14:30:40 +05:30
twinStressRatio_pminus1 * ( twinminusStressRatio_p ) ** &
2014-02-28 15:48:40 +05:30
( constitutive_titanmod_twinq_PerTwinSys ( j , instance ) - 1.0_pReal ) &
2010-09-01 15:37:52 +05:30
) !* sign(1.0_pReal,tau_slip(j))
2010-08-23 17:06:51 +05:30
!* Plastic velocity gradient for mechanical twinning
2014-07-02 17:57:39 +05:30
! Lp = Lp + sumf*gdot_twin(j)*lattice_Stwin(:,:,index_myFamily+i,ph)
Lp = Lp + gdot_twin ( j ) * lattice_Stwin ( : , : , index_myFamily + i , ph )
2010-07-13 13:49:25 +05:30
!* Calculation of the tangent of Lp
2012-02-21 21:30:00 +05:30
forall ( k = 1_pInt : 3_pInt , l = 1_pInt : 3_pInt , m = 1_pInt : 3_pInt , n = 1_pInt : 3_pInt ) &
2010-07-13 13:49:25 +05:30
dLp_dTstar3333 ( k , l , m , n ) = &
dLp_dTstar3333 ( k , l , m , n ) + dgdot_dtautwin ( j ) * &
2014-07-02 17:57:39 +05:30
lattice_Stwin ( k , l , index_myFamily + i , ph ) * &
lattice_Stwin ( m , n , index_myFamily + i , ph )
2010-07-13 13:49:25 +05:30
enddo
2013-10-08 21:57:26 +05:30
enddo twinFamiliesLoop
2010-07-13 13:49:25 +05:30
2013-07-12 12:27:15 +05:30
dLp_dTstar99 = math_Plain3333to99 ( dLp_dTstar3333 )
2014-07-02 17:57:39 +05:30
! tempState=state
2010-07-13 13:49:25 +05:30
2013-07-12 12:27:15 +05:30
end subroutine constitutive_titanmod_LpAndItsTangent
!--------------------------------------------------------------------------------------------------
!> @brief calculates the rate of change of microstructure
!--------------------------------------------------------------------------------------------------
2014-07-02 17:57:39 +05:30
subroutine constitutive_titanmod_dotState ( Tstar_v , temperature , ipc , ip , el )
2013-10-08 21:57:26 +05:30
use lattice , only : &
lattice_Stwin_v , &
lattice_maxNslipFamily , &
lattice_maxNtwinFamily , &
lattice_NslipSystem , &
lattice_NtwinSystem
2013-07-12 12:27:15 +05:30
use mesh , only : &
mesh_NcpElems , &
mesh_maxNips
use material , only : &
homogenization_maxNgrains , &
material_phase , &
2014-07-02 17:57:39 +05:30
phase_plasticityInstance , &
plasticState , &
mappingConstitutive
2010-07-13 13:49:25 +05:30
2012-03-09 01:55:28 +05:30
implicit none
2014-03-13 12:13:49 +05:30
real ( pReal ) , dimension ( 6 ) , intent ( in ) :: &
2013-07-12 12:27:15 +05:30
Tstar_v !< 2nd Piola Kirchhoff stress tensor in Mandel notation
2014-03-13 12:13:49 +05:30
real ( pReal ) , intent ( in ) :: &
2013-07-12 12:27:15 +05:30
temperature !< temperature at integration point
2014-03-13 12:13:49 +05:30
integer ( pInt ) , intent ( in ) :: &
2013-07-12 12:27:15 +05:30
ipc , & !< component-ID of integration point
ip , & !< integration point
el !< element
2013-10-08 21:57:26 +05:30
integer ( pInt ) :: &
2014-07-02 17:57:39 +05:30
index_myFamily , instance , &
2013-10-08 21:57:26 +05:30
ns , nt , &
2014-07-02 17:57:39 +05:30
f , i , j , &
ph , &
of
2013-10-08 21:57:26 +05:30
real ( pReal ) :: &
2014-02-09 22:38:13 +05:30
sumf , BoltzmannRatio , &
twinStressRatio_p , twinminusStressRatio_p
real ( pReal ) , dimension ( constitutive_titanmod_totalNslip ( phase_plasticityInstance ( material_phase ( ipc , ip , el ) ) ) ) :: &
2013-10-08 21:57:26 +05:30
DotRhoEdgeGeneration , &
DotRhoEdgeAnnihilation , &
DotRhoScrewGeneration , &
DotRhoScrewAnnihilation
real ( pReal ) , dimension ( constitutive_titanmod_totalNtwin ( phase_plasticityInstance ( material_phase ( ipc , ip , el ) ) ) ) :: &
gdot_twin , &
2014-02-09 22:38:13 +05:30
tau_twin , &
volumefraction_PerTwinSys
2010-07-13 13:49:25 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! shortened notation
2014-07-02 17:57:39 +05:30
of = mappingConstitutive ( 1 , ipc , ip , el )
ph = mappingConstitutive ( 2 , ipc , ip , el )
instance = phase_plasticityInstance ( ph )
2014-02-28 15:48:40 +05:30
ns = constitutive_titanmod_totalNslip ( instance )
nt = constitutive_titanmod_totalNtwin ( instance )
2014-02-09 22:38:13 +05:30
do i = 1_pInt , nt
2014-07-02 17:57:39 +05:30
volumefraction_PerTwinSys ( i ) = plasticState ( ph ) % state ( 3_pInt * ns + i , of ) / &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_twinshearconstant_PerTwinSys ( i , instance )
2010-09-07 20:14:37 +05:30
2014-02-09 22:38:13 +05:30
enddo
2010-09-07 20:14:37 +05:30
2014-02-09 22:38:13 +05:30
sumf = sum ( abs ( volumefraction_PerTwinSys ( 1_pInt : nt ) ) ) ! safe for nt == 0
2010-07-13 13:49:25 +05:30
2014-07-02 17:57:39 +05:30
plasticState ( ph ) % dotState ( : , of ) = 0.0_pReal
2014-02-09 22:38:13 +05:30
j = 0_pInt
2013-10-08 21:57:26 +05:30
slipFamiliesLoop : do f = 1_pInt , lattice_maxNslipFamily
2014-07-02 17:57:39 +05:30
index_myFamily = sum ( lattice_NslipSystem ( 1 : f - 1_pInt , ph ) ) ! at which index starts my family
2014-02-28 15:48:40 +05:30
do i = 1_pInt , constitutive_titanmod_Nslip ( f , instance ) ! process each (active) slip system in family
2010-07-13 13:49:25 +05:30
j = j + 1_pInt
2013-10-08 21:57:26 +05:30
DotRhoEdgeGeneration ( j ) = & ! multiplication of edge dislocations
2014-07-02 17:57:39 +05:30
plasticState ( ph ) % state ( ns + j , of ) * plasticState ( ph ) % state ( 8 * ns + 2 * nt + j , of ) / plasticState ( ph ) % state ( 4 * ns + nt + j , of )
2013-10-08 21:57:26 +05:30
DotRhoScrewGeneration ( j ) = & ! multiplication of screw dislocations
2014-07-02 17:57:39 +05:30
plasticState ( ph ) % state ( j , of ) * plasticState ( ph ) % state ( 7 * ns + 2 * nt + j , of ) / plasticState ( ph ) % state ( 3 * ns + nt + j , of )
DotRhoEdgeAnnihilation ( j ) = - ( ( plasticState ( ph ) % state ( j , of ) ) ** 2 ) * & ! annihilation of edge dislocations
constitutive_titanmod_capre_PerSlipSys ( j , instance ) * plasticState ( ph ) % state ( 7 * ns + 2 * nt + j , of ) * 0.5_pReal
DotRhoScrewAnnihilation ( j ) = - ( ( plasticState ( ph ) % state ( ns + j , of ) ) ** 2 ) * & ! annihilation of screw dislocations
constitutive_titanmod_caprs_PerSlipSys ( j , instance ) * plasticState ( ph ) % state ( 8 * ns + 2 * nt + j , of ) * 0.5_pReal
plasticState ( ph ) % dotState ( j , of ) = & ! edge dislocation density rate of change
2010-07-13 13:49:25 +05:30
DotRhoEdgeGeneration ( j ) + DotRhoEdgeAnnihilation ( j )
2014-07-02 17:57:39 +05:30
plasticState ( ph ) % dotState ( ns + j , of ) = & ! screw dislocation density rate of change
2010-07-13 13:49:25 +05:30
DotRhoScrewGeneration ( j ) + DotRhoScrewAnnihilation ( j )
2010-07-15 12:46:15 +05:30
2014-07-02 17:57:39 +05:30
plasticState ( ph ) % dotState ( 2 * ns + j , of ) = & ! sum of shear due to edge and screw
plasticState ( ph ) % state ( 10 * ns + 2 * nt + j , of ) + plasticState ( ph ) % state ( 11 * ns + 2 * nt + j , of )
2010-07-13 13:49:25 +05:30
enddo
2013-10-08 21:57:26 +05:30
enddo slipFamiliesLoop
2010-08-06 21:23:45 +05:30
2010-09-01 15:37:52 +05:30
!* Twin fraction evolution
2014-02-09 22:38:13 +05:30
j = 0_pInt
2013-10-08 21:57:26 +05:30
twinFamiliesLoop : do f = 1_pInt , lattice_maxNtwinFamily
2014-07-02 17:57:39 +05:30
index_myFamily = sum ( lattice_NtwinSystem ( 1 : f - 1_pInt , ph ) ) ! at which index starts my family
2014-02-28 15:48:40 +05:30
do i = 1_pInt , constitutive_titanmod_Ntwin ( f , instance ) ! process each (active) twin system in family
2010-07-13 13:49:25 +05:30
j = j + 1_pInt
!* Resolved shear stress on twin system
2014-07-02 17:57:39 +05:30
tau_twin ( j ) = dot_product ( Tstar_v , lattice_Stwin_v ( : , index_myFamily + i , ph ) )
2010-09-01 15:37:52 +05:30
!* Stress ratio for edge
2010-09-22 14:30:40 +05:30
twinStressRatio_p = ( ( abs ( tau_twin ( j ) ) ) / &
2014-07-02 17:57:39 +05:30
( constitutive_titanmod_twintau0_PerTwinSys ( j , instance ) + plasticState ( ph ) % state ( 7 * ns + nt + j , of ) ) &
2014-02-28 15:48:40 +05:30
) ** ( constitutive_titanmod_twinp_PerTwinSys ( j , instance ) )
2010-09-01 15:37:52 +05:30
2010-09-22 14:30:40 +05:30
if ( ( 1.0_pReal - twinStressRatio_p ) > 0.001_pReal ) then
twinminusStressRatio_p = 1.0_pReal - twinStressRatio_p
2010-09-01 15:37:52 +05:30
else
2010-09-22 14:30:40 +05:30
twinminusStressRatio_p = 0.001_pReal
2010-09-01 15:37:52 +05:30
endif
2014-02-28 15:48:40 +05:30
BoltzmannRatio = constitutive_titanmod_twinf0_PerTwinSys ( j , instance ) / ( kB * Temperature )
2010-09-29 12:05:08 +05:30
2014-02-28 15:48:40 +05:30
gdot_twin ( j ) = constitutive_titanmod_twingamma0_PerTwinSys ( j , instance ) * exp ( - BoltzmannRatio * &
2010-09-22 14:30:40 +05:30
( twinminusStressRatio_p ) ** &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_twinq_PerTwinSys ( j , instance ) ) * sign ( 1.0_pReal , tau_twin ( j ) )
2010-09-22 14:30:40 +05:30
2014-07-02 17:57:39 +05:30
plasticState ( ph ) % dotState ( 3 * ns + j , of ) = gdot_twin ( j )
2010-09-07 20:14:37 +05:30
enddo
2013-10-08 21:57:26 +05:30
enddo twinFamiliesLoop
2010-09-29 12:05:08 +05:30
2014-07-02 17:57:39 +05:30
end subroutine constitutive_titanmod_dotState
2014-10-10 22:04:51 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief returns accumulated slip
!--------------------------------------------------------------------------------------------------
subroutine constitutive_titanmod_getAccumulatedSlip ( nSlip , accumulatedSlip , ipc , ip , el )
use lattice , only : &
lattice_maxNslipFamily
use material , only : &
mappingConstitutive , &
plasticState , &
phase_plasticityInstance
implicit none
real ( pReal ) , dimension ( : ) , allocatable :: &
accumulatedSlip
integer ( pInt ) :: &
nSlip
integer ( pInt ) , intent ( in ) :: &
ipc , & !< grain number
ip , & !< integration point number
el !< element number
integer ( pInt ) :: &
offset , &
phase , &
instance , &
offset_accshear_slip , &
f , j , i
offset = mappingConstitutive ( 1 , ipc , ip , el )
phase = mappingConstitutive ( 2 , ipc , ip , el )
instance = phase_plasticityInstance ( phase )
nSlip = constitutive_titanmod_totalNslip ( instance )
allocate ( accumulatedSlip ( nSlip ) )
offset_accshear_slip = 2_pInt * nSlip
j = 0_pInt
do f = 1_pInt , lattice_maxNslipFamily ! loop over all slip families
do i = 1_pInt , constitutive_titanmod_Nslip ( f , instance ) ! process each (active) slip system in family
j = j + 1_pInt
accumulatedSlip ( j ) = plasticState ( phase ) % state ( offset_accshear_slip + j , offset )
enddo
enddo
end subroutine constitutive_titanmod_getAccumulatedSlip
2014-10-11 15:15:30 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief returns accumulated slip
!--------------------------------------------------------------------------------------------------
subroutine constitutive_titanmod_getSlipRate ( nSlip , slipRate , ipc , ip , el )
use lattice , only : &
lattice_maxNslipFamily
use material , only : &
mappingConstitutive , &
plasticState , &
phase_plasticityInstance
implicit none
real ( pReal ) , dimension ( : ) , allocatable :: &
slipRate
integer ( pInt ) :: &
nSlip
integer ( pInt ) , intent ( in ) :: &
ipc , & !< grain number
ip , & !< integration point number
el !< element number
integer ( pInt ) :: &
offset , &
phase , &
instance , &
offset_accshear_slip , &
f , j , i
offset = mappingConstitutive ( 1 , ipc , ip , el )
phase = mappingConstitutive ( 2 , ipc , ip , el )
instance = phase_plasticityInstance ( phase )
nSlip = constitutive_titanmod_totalNslip ( instance )
allocate ( slipRate ( nSlip ) )
offset_accshear_slip = 2_pInt * nSlip
j = 0_pInt
do f = 1_pInt , lattice_maxNslipFamily ! loop over all slip families
do i = 1_pInt , constitutive_titanmod_Nslip ( f , instance ) ! process each (active) slip system in family
j = j + 1_pInt
slipRate ( j ) = plasticState ( phase ) % dotState ( offset_accshear_slip + j , offset )
enddo
enddo
end subroutine constitutive_titanmod_getSlipRate
2010-07-13 13:49:25 +05:30
2013-07-12 12:27:15 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief return array of constitutive results
!--------------------------------------------------------------------------------------------------
2014-07-02 17:57:39 +05:30
function constitutive_titanmod_postResults ( ipc , ip , el )
2013-10-08 21:57:26 +05:30
use mesh , only : &
mesh_NcpElems , &
mesh_maxNips
use material , only : &
homogenization_maxNgrains , &
material_phase , &
phase_plasticityInstance , &
2014-07-02 17:57:39 +05:30
phase_Noutput , &
plasticState , &
mappingConstitutive
2013-07-12 12:27:15 +05:30
implicit none
2014-03-13 12:13:49 +05:30
integer ( pInt ) , intent ( in ) :: &
2013-10-08 21:57:26 +05:30
ipc , & !< component-ID of integration point
ip , & !< integration point
el !< element
2013-10-16 18:34:59 +05:30
real ( pReal ) , dimension ( constitutive_titanmod_sizePostResults ( phase_plasticityInstance ( material_phase ( ipc , ip , el ) ) ) ) :: &
constitutive_titanmod_postResults
2013-10-08 21:57:26 +05:30
integer ( pInt ) :: &
2014-07-02 17:57:39 +05:30
instance , &
2013-10-08 21:57:26 +05:30
ns , nt , &
2014-07-02 17:57:39 +05:30
o , i , c , &
ph , &
of
2013-10-08 21:57:26 +05:30
real ( pReal ) :: sumf
2013-10-16 18:34:59 +05:30
2013-07-12 12:27:15 +05:30
real ( pReal ) , dimension ( constitutive_titanmod_totalNtwin ( phase_plasticityInstance ( material_phase ( ipc , ip , el ) ) ) ) :: &
volumefraction_PerTwinSys
2014-07-02 17:57:39 +05:30
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! shortened notation
2014-07-02 17:57:39 +05:30
of = mappingConstitutive ( 1 , ipc , ip , el )
ph = mappingConstitutive ( 2 , ipc , ip , el )
instance = phase_plasticityInstance ( ph )
2014-02-28 15:48:40 +05:30
ns = constitutive_titanmod_totalNslip ( instance )
nt = constitutive_titanmod_totalNtwin ( instance )
2013-07-12 12:27:15 +05:30
do i = 1_pInt , nt
2014-07-02 17:57:39 +05:30
volumefraction_PerTwinSys ( i ) = plasticState ( ph ) % state ( 3_pInt * ns + i , of ) / &
2014-02-28 15:48:40 +05:30
constitutive_titanmod_twinshearconstant_PerTwinSys ( i , instance )
2013-07-12 12:27:15 +05:30
enddo
sumf = sum ( abs ( volumefraction_PerTwinSys ( 1 : nt ) ) ) ! safe for nt == 0
2013-10-08 21:57:26 +05:30
!--------------------------------------------------------------------------------------------------
! required output
2013-07-12 12:27:15 +05:30
c = 0_pInt
constitutive_titanmod_postResults = 0.0_pReal
2010-07-13 13:49:25 +05:30
2014-06-25 04:23:25 +05:30
do o = 1_pInt , constitutive_titanmod_Noutput ( instance )
2014-02-28 15:48:40 +05:30
select case ( constitutive_titanmod_outputID ( o , instance ) )
2014-02-09 22:38:13 +05:30
case ( rhoedge_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + ns ) = plasticState ( ph ) % state ( 1_pInt : ns , of )
2010-07-13 13:49:25 +05:30
c = c + ns
2014-02-09 22:38:13 +05:30
case ( rhoscrew_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + ns ) = plasticState ( ph ) % state ( ns + 1_pInt : 2_pInt * ns , of )
2010-07-13 13:49:25 +05:30
c = c + ns
2014-02-09 22:38:13 +05:30
case ( segment_edge_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + ns ) = plasticState ( ph ) % state ( 3_pInt * ns + nt + 1_pInt : 4_pInt * ns + nt , of )
2010-08-06 21:23:45 +05:30
c = c + ns
2014-02-09 22:38:13 +05:30
case ( segment_screw_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + ns ) = plasticState ( ph ) % state ( 4_pInt * ns + nt + 1_pInt : 5_pInt * ns + nt , of )
2010-08-06 21:23:45 +05:30
c = c + ns
2014-02-09 22:38:13 +05:30
case ( resistance_edge_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + ns ) = plasticState ( ph ) % state ( 5_pInt * ns + nt + 1_pInt : 6_pInt * ns + nt , of )
2010-08-06 21:23:45 +05:30
c = c + ns
2014-02-09 22:38:13 +05:30
case ( resistance_screw_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + ns ) = plasticState ( ph ) % state ( 6_pInt * ns + nt + 1_pInt : 7_pInt * ns + nt , of )
2010-09-29 12:05:08 +05:30
c = c + ns
2014-02-09 22:38:13 +05:30
case ( velocity_edge_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + ns ) = plasticState ( ph ) % state ( 7 * ns + 2 * nt + 1 : 8 * ns + 2 * nt , of )
2010-09-29 12:05:08 +05:30
c = c + ns
2014-02-09 22:38:13 +05:30
case ( velocity_screw_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + ns ) = plasticState ( ph ) % state ( 8 * ns + 2 * nt + 1 : 9 * ns + 2 * nt , of )
2011-03-31 14:51:43 +05:30
c = c + ns
2014-02-09 22:38:13 +05:30
case ( tau_slip_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + ns ) = abs ( plasticState ( ph ) % state ( 9 * ns + 2 * nt + 1 : 10 * ns + 2 * nt , of ) )
2010-09-29 12:05:08 +05:30
c = c + ns
2014-02-09 22:38:13 +05:30
case ( gdot_slip_edge_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + ns ) = abs ( plasticState ( ph ) % state ( 10 * ns + 2 * nt + 1 : 11 * ns + 2 * nt , of ) )
2010-09-29 12:05:08 +05:30
c = c + ns
2014-02-09 22:38:13 +05:30
case ( gdot_slip_screw_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + ns ) = abs ( plasticState ( ph ) % state ( 11 * ns + 2 * nt + 1 : 12 * ns + 2 * nt , of ) )
2011-03-31 14:51:43 +05:30
c = c + ns
2014-02-09 22:38:13 +05:30
case ( gdot_slip_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + ns ) = abs ( plasticState ( ph ) % state ( 10 * ns + 2 * nt + 1 : 11 * ns + 2 * nt , of ) ) + &
abs ( plasticState ( ph ) % state ( 11 * ns + 2 * nt + 1 : 12 * ns + 2 * nt , of ) )
2010-09-29 12:05:08 +05:30
c = c + ns
2014-02-09 22:38:13 +05:30
case ( stressratio_edge_p_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + ns ) = abs ( plasticState ( ph ) % state ( 12 * ns + 2 * nt + 1 : 13 * ns + 2 * nt , of ) )
2010-09-29 12:05:08 +05:30
c = c + ns
2014-02-09 22:38:13 +05:30
case ( stressratio_screw_p_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + ns ) = abs ( plasticState ( ph ) % state ( 13 * ns + 2 * nt + 1 : 14 * ns + 2 * nt , of ) )
2010-09-29 12:05:08 +05:30
c = c + ns
2014-02-09 22:38:13 +05:30
case ( shear_system_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + ns ) = abs ( plasticState ( ph ) % state ( 2 * ns + 1 : 3 * ns , of ) )
2011-03-31 14:51:43 +05:30
c = c + ns
2014-02-09 22:38:13 +05:30
case ( shear_basal_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + 1_pInt ) = sum ( abs ( plasticState ( ph ) % state ( 2 * ns + 1 : 2 * ns + 3 , of ) ) )
2012-02-21 21:30:00 +05:30
c = c + 1_pInt
2014-02-09 22:38:13 +05:30
case ( shear_prism_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + 1_pInt ) = sum ( abs ( plasticState ( ph ) % state ( 2 * ns + 4 : 2 * ns + 6 , of ) ) )
2012-02-21 21:30:00 +05:30
c = c + 1_pInt
2014-02-09 22:38:13 +05:30
case ( shear_pyra_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + 1_pInt ) = sum ( abs ( plasticState ( ph ) % state ( 2 * ns + 7 : 2 * ns + 12 , of ) ) )
2012-02-21 21:30:00 +05:30
c = c + 1_pInt
2014-02-09 22:38:13 +05:30
case ( shear_pyrca_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + 1_pInt ) = sum ( abs ( plasticState ( ph ) % state ( 2 * ns + 13 : 2 * ns + 24 , of ) ) )
2012-02-21 21:30:00 +05:30
c = c + 1_pInt
2011-03-31 14:51:43 +05:30
2014-02-09 22:38:13 +05:30
case ( rhoedge_basal_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + 1_pInt ) = sum ( plasticState ( ph ) % state ( 1 : 3 , of ) )
2012-02-21 21:30:00 +05:30
c = c + 1_pInt
2014-02-09 22:38:13 +05:30
case ( rhoedge_prism_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + 1_pInt ) = sum ( plasticState ( ph ) % state ( 4 : 6 , of ) )
2012-02-21 21:30:00 +05:30
c = c + 1_pInt
2014-02-09 22:38:13 +05:30
case ( rhoedge_pyra_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + 1_pInt ) = sum ( plasticState ( ph ) % state ( 7 : 12 , of ) )
2012-02-21 21:30:00 +05:30
c = c + 1_pInt
2014-02-09 22:38:13 +05:30
case ( rhoedge_pyrca_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + 1_pInt ) = sum ( plasticState ( ph ) % state ( 13 : 24 , of ) )
2012-02-21 21:30:00 +05:30
c = c + 1_pInt
2011-03-31 14:51:43 +05:30
2014-02-09 22:38:13 +05:30
case ( rhoscrew_basal_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + 1_pInt ) = sum ( plasticState ( ph ) % state ( ns + 1 : ns + 3 , of ) )
2012-02-21 21:30:00 +05:30
c = c + 1_pInt
2014-02-09 22:38:13 +05:30
case ( rhoscrew_prism_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + 1_pInt ) = sum ( plasticState ( ph ) % state ( ns + 4 : ns + 6 , of ) )
2012-02-21 21:30:00 +05:30
c = c + 1_pInt
2014-02-09 22:38:13 +05:30
case ( rhoscrew_pyra_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + 1_pInt ) = sum ( plasticState ( ph ) % state ( ns + 7 : ns + 12 , of ) )
2012-02-21 21:30:00 +05:30
c = c + 1_pInt
2014-02-09 22:38:13 +05:30
case ( rhoscrew_pyrca_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + 1_pInt ) = sum ( plasticState ( ph ) % state ( ns + 13 : ns + 24 , of ) )
2012-02-21 21:30:00 +05:30
c = c + 1_pInt
2014-02-09 22:38:13 +05:30
case ( shear_total_ID )
2014-07-02 17:57:39 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + 1_pInt ) = sum ( abs ( plasticState ( ph ) % state ( 2 * ns + 1 : 3 * ns , of ) ) )
2012-02-21 21:30:00 +05:30
c = c + 1_pInt
2014-02-09 22:38:13 +05:30
case ( twin_fraction_ID )
2013-07-12 12:27:15 +05:30
constitutive_titanmod_postResults ( c + 1_pInt : c + nt ) = abs ( volumefraction_PerTwinSys ( 1 : nt ) )
2010-07-13 13:49:25 +05:30
c = c + nt
end select
2013-07-12 12:27:15 +05:30
enddo
2010-07-13 13:49:25 +05:30
2013-07-12 12:27:15 +05:30
end function constitutive_titanmod_postResults
2010-07-13 13:49:25 +05:30
2013-07-12 12:27:15 +05:30
end module constitutive_titanmod