updated to read in TRIP parameters
This commit is contained in:
parent
cd9adf78ca
commit
1707f7d367
|
@ -1731,6 +1731,8 @@ subroutine IO_warning(warning_ID,el,ip,g,ext_msg)
|
||||||
msg = 'not all available twin system families are defined'
|
msg = 'not all available twin system families are defined'
|
||||||
case (52_pInt)
|
case (52_pInt)
|
||||||
msg = 'not all available parameters are defined'
|
msg = 'not all available parameters are defined'
|
||||||
|
case (53_pInt)
|
||||||
|
msg = 'not all available transformation system families are defined'
|
||||||
case (101_pInt)
|
case (101_pInt)
|
||||||
msg = 'crystallite debugging off'
|
msg = 'crystallite debugging off'
|
||||||
case (201_pInt)
|
case (201_pInt)
|
||||||
|
|
|
@ -46,11 +46,13 @@ module constitutive_dislotwin
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, private :: &
|
integer(pInt), dimension(:), allocatable, private :: &
|
||||||
constitutive_dislotwin_totalNslip, & !< total number of active slip systems for each instance
|
constitutive_dislotwin_totalNslip, & !< total number of active slip systems for each instance
|
||||||
constitutive_dislotwin_totalNtwin !< total number of active twin systems for each instance
|
constitutive_dislotwin_totalNtwin, & !< total number of active twin systems for each instance
|
||||||
|
constitutive_dislotwin_totalNtrans !< number of active transformation systems
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, private :: &
|
integer(pInt), dimension(:,:), allocatable, private :: &
|
||||||
constitutive_dislotwin_Nslip, & !< number of active slip systems for each family and instance
|
constitutive_dislotwin_Nslip, & !< number of active slip systems for each family and instance
|
||||||
constitutive_dislotwin_Ntwin !< number of active twin systems for each family and instance
|
constitutive_dislotwin_Ntwin, & !< number of active twin systems for each family and instance
|
||||||
|
constitutive_dislotwin_Ntrans !< number of active transformation systems for each family and instance
|
||||||
|
|
||||||
real(pReal), dimension(:), allocatable, private :: &
|
real(pReal), dimension(:), allocatable, private :: &
|
||||||
constitutive_dislotwin_CAtomicVolume, & !< atomic volume in Bugers vector unit
|
constitutive_dislotwin_CAtomicVolume, & !< atomic volume in Bugers vector unit
|
||||||
|
@ -74,7 +76,12 @@ module constitutive_dislotwin
|
||||||
constitutive_dislotwin_dSFE_dT, & !< temperature dependance of stacking fault energy
|
constitutive_dislotwin_dSFE_dT, & !< temperature dependance of stacking fault energy
|
||||||
constitutive_dislotwin_dipoleFormationFactor, & !< scaling factor for dipole formation: 0: off, 1: on. other values not useful
|
constitutive_dislotwin_dipoleFormationFactor, & !< scaling factor for dipole formation: 0: off, 1: on. other values not useful
|
||||||
constitutive_dislotwin_aTolRho, & !< absolute tolerance for integration of dislocation density
|
constitutive_dislotwin_aTolRho, & !< absolute tolerance for integration of dislocation density
|
||||||
constitutive_dislotwin_aTolTwinFrac !< absolute tolerance for integration of twin volume fraction
|
constitutive_dislotwin_aTolTwinFrac, & !< absolute tolerance for integration of twin volume fraction
|
||||||
|
constitutive_dislotwin_c1, & !< strain induced martensite nucleation coefficient
|
||||||
|
constitutive_dislotwin_c2, & !< phase boundary energy
|
||||||
|
constitutive_dislotwin_c3, & !< Lagrange multiplier
|
||||||
|
constitutive_dislotwin_c5, & !< phase transformation rate coefficient
|
||||||
|
constitutive_dislotwin_deltaG !< free energy difference between austensite and martensite [MPa]
|
||||||
|
|
||||||
real(pReal), dimension(:,:,:,:), allocatable, private :: &
|
real(pReal), dimension(:,:,:,:), allocatable, private :: &
|
||||||
constitutive_dislotwin_Ctwin66 !< twin elasticity matrix in Mandel notation for each instance
|
constitutive_dislotwin_Ctwin66 !< twin elasticity matrix in Mandel notation for each instance
|
||||||
|
@ -207,14 +214,14 @@ subroutine constitutive_dislotwin_init(fileUnit)
|
||||||
integer(pInt) :: maxNinstance,mySize=0_pInt,phase,maxTotalNslip,maxTotalNtwin,&
|
integer(pInt) :: maxNinstance,mySize=0_pInt,phase,maxTotalNslip,maxTotalNtwin,&
|
||||||
f,instance,j,k,l,m,n,o,p,q,r,s,ns,nt, &
|
f,instance,j,k,l,m,n,o,p,q,r,s,ns,nt, &
|
||||||
Nchunks_SlipSlip, Nchunks_SlipTwin, Nchunks_TwinSlip, Nchunks_TwinTwin, &
|
Nchunks_SlipSlip, Nchunks_SlipTwin, Nchunks_TwinSlip, Nchunks_TwinTwin, &
|
||||||
Nchunks_SlipFamilies, Nchunks_TwinFamilies, &
|
Nchunks_SlipFamilies, Nchunks_TwinFamilies, Nchunks_TransFamilies, &
|
||||||
index_myFamily, index_otherFamily
|
index_myFamily, index_otherFamily
|
||||||
integer(pInt) :: sizeState, sizeDotState
|
integer(pInt) :: sizeState, sizeDotState
|
||||||
integer(pInt) :: NofMyPhase
|
integer(pInt) :: NofMyPhase
|
||||||
character(len=65536) :: &
|
character(len=65536) :: &
|
||||||
tag = '', &
|
tag = '', &
|
||||||
line = ''
|
line = ''
|
||||||
real(pReal), dimension(:), allocatable :: tempPerSlip, tempPerTwin
|
real(pReal), dimension(:), allocatable :: tempPerSlip, tempPerTwin, tempPerTrans
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- constitutive_'//PLASTICITY_DISLOTWIN_label//' init -+>>>'
|
write(6,'(/,a)') ' <<<+- constitutive_'//PLASTICITY_DISLOTWIN_label//' init -+>>>'
|
||||||
write(6,'(a)') ' $Id$'
|
write(6,'(a)') ' $Id$'
|
||||||
|
@ -235,8 +242,10 @@ subroutine constitutive_dislotwin_init(fileUnit)
|
||||||
allocate(constitutive_dislotwin_Noutput(maxNinstance), source=0_pInt)
|
allocate(constitutive_dislotwin_Noutput(maxNinstance), source=0_pInt)
|
||||||
allocate(constitutive_dislotwin_Nslip(lattice_maxNslipFamily,maxNinstance), source=0_pInt)
|
allocate(constitutive_dislotwin_Nslip(lattice_maxNslipFamily,maxNinstance), source=0_pInt)
|
||||||
allocate(constitutive_dislotwin_Ntwin(lattice_maxNtwinFamily,maxNinstance), source=0_pInt)
|
allocate(constitutive_dislotwin_Ntwin(lattice_maxNtwinFamily,maxNinstance), source=0_pInt)
|
||||||
|
allocate(constitutive_dislotwin_Ntrans(lattice_maxNtransFamily,maxNinstance), source=0_pInt)
|
||||||
allocate(constitutive_dislotwin_totalNslip(maxNinstance), source=0_pInt)
|
allocate(constitutive_dislotwin_totalNslip(maxNinstance), source=0_pInt)
|
||||||
allocate(constitutive_dislotwin_totalNtwin(maxNinstance), source=0_pInt)
|
allocate(constitutive_dislotwin_totalNtwin(maxNinstance), source=0_pInt)
|
||||||
|
allocate(constitutive_dislotwin_totalNtrans(maxNinstance), source=0_pInt)
|
||||||
allocate(constitutive_dislotwin_CAtomicVolume(maxNinstance), source=0.0_pReal)
|
allocate(constitutive_dislotwin_CAtomicVolume(maxNinstance), source=0.0_pReal)
|
||||||
allocate(constitutive_dislotwin_D0(maxNinstance), source=0.0_pReal)
|
allocate(constitutive_dislotwin_D0(maxNinstance), source=0.0_pReal)
|
||||||
allocate(constitutive_dislotwin_Qsd(maxNinstance), source=0.0_pReal)
|
allocate(constitutive_dislotwin_Qsd(maxNinstance), source=0.0_pReal)
|
||||||
|
@ -259,6 +268,11 @@ subroutine constitutive_dislotwin_init(fileUnit)
|
||||||
allocate(constitutive_dislotwin_SFE_0K(maxNinstance), source=0.0_pReal)
|
allocate(constitutive_dislotwin_SFE_0K(maxNinstance), source=0.0_pReal)
|
||||||
allocate(constitutive_dislotwin_dSFE_dT(maxNinstance), source=0.0_pReal)
|
allocate(constitutive_dislotwin_dSFE_dT(maxNinstance), source=0.0_pReal)
|
||||||
allocate(constitutive_dislotwin_dipoleFormationFactor(maxNinstance), source=1.0_pReal) !should be on by default
|
allocate(constitutive_dislotwin_dipoleFormationFactor(maxNinstance), source=1.0_pReal) !should be on by default
|
||||||
|
allocate(constitutive_dislotwin_c1(maxNinstance), source=0.0_pReal)
|
||||||
|
allocate(constitutive_dislotwin_c2(maxNinstance), source=0.0_pReal)
|
||||||
|
allocate(constitutive_dislotwin_c3(maxNinstance), source=0.0_pReal)
|
||||||
|
allocate(constitutive_dislotwin_c5(maxNinstance), source=0.0_pReal)
|
||||||
|
allocate(constitutive_dislotwin_deltaG(maxNinstance), source=0.0_pReal)
|
||||||
allocate(constitutive_dislotwin_rhoEdge0(lattice_maxNslipFamily,maxNinstance), source=0.0_pReal)
|
allocate(constitutive_dislotwin_rhoEdge0(lattice_maxNslipFamily,maxNinstance), source=0.0_pReal)
|
||||||
allocate(constitutive_dislotwin_rhoEdgeDip0(lattice_maxNslipFamily,maxNinstance), source=0.0_pReal)
|
allocate(constitutive_dislotwin_rhoEdgeDip0(lattice_maxNslipFamily,maxNinstance), source=0.0_pReal)
|
||||||
allocate(constitutive_dislotwin_burgersPerSlipFamily(lattice_maxNslipFamily,maxNinstance), &
|
allocate(constitutive_dislotwin_burgersPerSlipFamily(lattice_maxNslipFamily,maxNinstance), &
|
||||||
|
@ -310,14 +324,17 @@ subroutine constitutive_dislotwin_init(fileUnit)
|
||||||
if (phase_plasticity(phase) == PLASTICITY_DISLOTWIN_ID) then
|
if (phase_plasticity(phase) == PLASTICITY_DISLOTWIN_ID) then
|
||||||
Nchunks_SlipFamilies = count(lattice_NslipSystem(:,phase) > 0_pInt)
|
Nchunks_SlipFamilies = count(lattice_NslipSystem(:,phase) > 0_pInt)
|
||||||
Nchunks_TwinFamilies = count(lattice_NtwinSystem(:,phase) > 0_pInt)
|
Nchunks_TwinFamilies = count(lattice_NtwinSystem(:,phase) > 0_pInt)
|
||||||
|
Nchunks_TransFamilies =count(lattice_NtransSystem(:,phase)> 0_pInt)
|
||||||
Nchunks_SlipSlip = maxval(lattice_interactionSlipSlip(:,:,phase))
|
Nchunks_SlipSlip = maxval(lattice_interactionSlipSlip(:,:,phase))
|
||||||
Nchunks_SlipTwin = maxval(lattice_interactionSlipTwin(:,:,phase))
|
Nchunks_SlipTwin = maxval(lattice_interactionSlipTwin(:,:,phase))
|
||||||
Nchunks_TwinSlip = maxval(lattice_interactionTwinSlip(:,:,phase))
|
Nchunks_TwinSlip = maxval(lattice_interactionTwinSlip(:,:,phase))
|
||||||
Nchunks_TwinTwin = maxval(lattice_interactionTwinTwin(:,:,phase))
|
Nchunks_TwinTwin = maxval(lattice_interactionTwinTwin(:,:,phase))
|
||||||
if(allocated(tempPerSlip)) deallocate(tempPerSlip)
|
if(allocated(tempPerSlip)) deallocate(tempPerSlip)
|
||||||
if(allocated(tempPerTwin)) deallocate(tempPerTwin)
|
if(allocated(tempPerTwin)) deallocate(tempPerTwin)
|
||||||
|
if(allocated(tempPerTrans)) deallocate(tempPerTrans)
|
||||||
allocate(tempPerSlip(Nchunks_SlipFamilies))
|
allocate(tempPerSlip(Nchunks_SlipFamilies))
|
||||||
allocate(tempPerTwin(Nchunks_TwinFamilies))
|
allocate(tempPerTwin(Nchunks_TwinFamilies))
|
||||||
|
allocate(tempPerTrans(Nchunks_TransFamilies))
|
||||||
endif
|
endif
|
||||||
cycle ! skip to next line
|
cycle ! skip to next line
|
||||||
endif
|
endif
|
||||||
|
@ -485,6 +502,17 @@ subroutine constitutive_dislotwin_init(fileUnit)
|
||||||
constitutive_dislotwin_rPerTwinFamily(1:Nchunks_TwinFamilies,instance) = tempPerTwin(1:Nchunks_TwinFamilies)
|
constitutive_dislotwin_rPerTwinFamily(1:Nchunks_TwinFamilies,instance) = tempPerTwin(1:Nchunks_TwinFamilies)
|
||||||
end select
|
end select
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
! parameters depending on number of transformation system families
|
||||||
|
case ('ntrans')
|
||||||
|
if (positions(1) < Nchunks_TransFamilies + 1_pInt) &
|
||||||
|
call IO_warning(53_pInt,ext_msg=trim(tag)//' ('//PLASTICITY_DISLOTWIN_label//')')
|
||||||
|
if (positions(1) > Nchunks_TransFamilies + 1_pInt) &
|
||||||
|
call IO_error(150_pInt,ext_msg=trim(tag)//' ('//PLASTICITY_DISLOTWIN_label//')')
|
||||||
|
Nchunks_TransFamilies = positions(1) - 1_pInt
|
||||||
|
do j = 1_pInt, Nchunks_TransFamilies
|
||||||
|
constitutive_dislotwin_Ntrans(j,instance) = IO_intValue(line,positions,1_pInt+j)
|
||||||
|
enddo
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
! parameters depending on number of interactions
|
! parameters depending on number of interactions
|
||||||
case ('interaction_slipslip','interactionslipslip')
|
case ('interaction_slipslip','interactionslipslip')
|
||||||
if (positions(1) < 1_pInt + Nchunks_SlipSlip) &
|
if (positions(1) < 1_pInt + Nchunks_SlipSlip) &
|
||||||
|
@ -556,6 +584,16 @@ subroutine constitutive_dislotwin_init(fileUnit)
|
||||||
constitutive_dislotwin_sbVelocity(instance) = IO_floatValue(line,positions,2_pInt)
|
constitutive_dislotwin_sbVelocity(instance) = IO_floatValue(line,positions,2_pInt)
|
||||||
case ('qedgepersbsystem')
|
case ('qedgepersbsystem')
|
||||||
constitutive_dislotwin_sbQedge(instance) = IO_floatValue(line,positions,2_pInt)
|
constitutive_dislotwin_sbQedge(instance) = IO_floatValue(line,positions,2_pInt)
|
||||||
|
case ('c1')
|
||||||
|
constitutive_dislotwin_c1(instance) = IO_floatValue(line,positions,2_pInt)
|
||||||
|
case ('c2')
|
||||||
|
constitutive_dislotwin_c2(instance) = IO_floatValue(line,positions,2_pInt)
|
||||||
|
case ('c3')
|
||||||
|
constitutive_dislotwin_c3(instance) = IO_floatValue(line,positions,2_pInt)
|
||||||
|
case ('c5')
|
||||||
|
constitutive_dislotwin_c5(instance) = IO_floatValue(line,positions,2_pInt)
|
||||||
|
case ('deltag')
|
||||||
|
constitutive_dislotwin_deltaG(instance) = IO_floatValue(line,positions,2_pInt)
|
||||||
end select
|
end select
|
||||||
endif; endif
|
endif; endif
|
||||||
enddo parsingFile
|
enddo parsingFile
|
||||||
|
@ -623,8 +661,10 @@ subroutine constitutive_dislotwin_init(fileUnit)
|
||||||
! Determine total number of active slip or twin systems
|
! Determine total number of active slip or twin systems
|
||||||
constitutive_dislotwin_Nslip(:,instance) = min(lattice_NslipSystem(:,phase),constitutive_dislotwin_Nslip(:,instance))
|
constitutive_dislotwin_Nslip(:,instance) = min(lattice_NslipSystem(:,phase),constitutive_dislotwin_Nslip(:,instance))
|
||||||
constitutive_dislotwin_Ntwin(:,instance) = min(lattice_NtwinSystem(:,phase),constitutive_dislotwin_Ntwin(:,instance))
|
constitutive_dislotwin_Ntwin(:,instance) = min(lattice_NtwinSystem(:,phase),constitutive_dislotwin_Ntwin(:,instance))
|
||||||
|
constitutive_dislotwin_Ntrans(:,instance)= min(lattice_NtransSystem(:,phase),constitutive_dislotwin_Ntrans(:,instance))
|
||||||
constitutive_dislotwin_totalNslip(instance) = sum(constitutive_dislotwin_Nslip(:,instance))
|
constitutive_dislotwin_totalNslip(instance) = sum(constitutive_dislotwin_Nslip(:,instance))
|
||||||
constitutive_dislotwin_totalNtwin(instance) = sum(constitutive_dislotwin_Ntwin(:,instance))
|
constitutive_dislotwin_totalNtwin(instance) = sum(constitutive_dislotwin_Ntwin(:,instance))
|
||||||
|
constitutive_dislotwin_totalNtrans(instance) = sum(constitutive_dislotwin_Ntrans(:,instance))
|
||||||
endif myPhase
|
endif myPhase
|
||||||
enddo sanityChecks
|
enddo sanityChecks
|
||||||
|
|
||||||
|
@ -872,7 +912,6 @@ subroutine constitutive_dislotwin_stateInit(ph,instance)
|
||||||
instance, & !< number specifying the instance of the plasticity
|
instance, & !< number specifying the instance of the plasticity
|
||||||
ph
|
ph
|
||||||
|
|
||||||
|
|
||||||
real(pReal), dimension(plasticState(ph)%sizeState) :: tempState
|
real(pReal), dimension(plasticState(ph)%sizeState) :: tempState
|
||||||
|
|
||||||
integer(pInt) :: i,j,f,ns,nt, index_myFamily
|
integer(pInt) :: i,j,f,ns,nt, index_myFamily
|
||||||
|
@ -973,6 +1012,8 @@ subroutine constitutive_dislotwin_aTolState(ph,instance)
|
||||||
2_pInt*constitutive_dislotwin_totalNtwin(instance)) = 1e6_pReal
|
2_pInt*constitutive_dislotwin_totalNtwin(instance)) = 1e6_pReal
|
||||||
|
|
||||||
end subroutine constitutive_dislotwin_aTolState
|
end subroutine constitutive_dislotwin_aTolState
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief returns the homogenized elasticity matrix
|
!> @brief returns the homogenized elasticity matrix
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
|
236
code/lattice.f90
236
code/lattice.f90
|
@ -18,14 +18,17 @@ module lattice
|
||||||
integer(pInt), parameter, public :: &
|
integer(pInt), parameter, public :: &
|
||||||
LATTICE_maxNslipFamily = 6_pInt, & !< max # of slip system families over lattice structures
|
LATTICE_maxNslipFamily = 6_pInt, & !< max # of slip system families over lattice structures
|
||||||
LATTICE_maxNtwinFamily = 4_pInt, & !< max # of twin system families over lattice structures
|
LATTICE_maxNtwinFamily = 4_pInt, & !< max # of twin system families over lattice structures
|
||||||
|
LATTICE_maxNtransFamily = 2_pInt, & !< max # of transformation system families over lattice structures
|
||||||
LATTICE_maxNslip = 33_pInt, & !< max # of slip systems over lattice structures
|
LATTICE_maxNslip = 33_pInt, & !< max # of slip systems over lattice structures
|
||||||
LATTICE_maxNtwin = 24_pInt, & !< max # of twin systems over lattice structures
|
LATTICE_maxNtwin = 24_pInt, & !< max # of twin systems over lattice structures
|
||||||
LATTICE_maxNinteraction = 42_pInt, & !< max # of interaction types (in hardening matrix part)
|
LATTICE_maxNinteraction = 42_pInt, & !< max # of interaction types (in hardening matrix part)
|
||||||
LATTICE_maxNnonSchmid = 6_pInt !< max # of non schmid contributions over lattice structures
|
LATTICE_maxNnonSchmid = 6_pInt, & !< max # of non schmid contributions over lattice structures
|
||||||
|
LATTICE_maxNtrans = 36_pInt !< max # of transformations over lattice structures
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:,:), protected, public :: &
|
integer(pInt), allocatable, dimension(:,:), protected, public :: &
|
||||||
lattice_NslipSystem, & !< total # of slip systems in each family
|
lattice_NslipSystem, & !< total # of slip systems in each family
|
||||||
lattice_NtwinSystem !< total # of twin systems in each family
|
lattice_NtwinSystem, & !< total # of twin systems in each family
|
||||||
|
lattice_NtransSystem !< total # of transformation systems in each family
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:,:,:), protected, public :: &
|
integer(pInt), allocatable, dimension(:,:,:), protected, public :: &
|
||||||
lattice_interactionSlipSlip, & !< Slip--slip interaction type
|
lattice_interactionSlipSlip, & !< Slip--slip interaction type
|
||||||
|
@ -33,7 +36,6 @@ module lattice
|
||||||
lattice_interactionTwinSlip, & !< Twin--slip interaction type
|
lattice_interactionTwinSlip, & !< Twin--slip interaction type
|
||||||
lattice_interactionTwinTwin !< Twin--twin interaction type
|
lattice_interactionTwinTwin !< Twin--twin interaction type
|
||||||
|
|
||||||
|
|
||||||
real(pReal), allocatable, dimension(:,:,:,:,:), protected, public :: &
|
real(pReal), allocatable, dimension(:,:,:,:,:), protected, public :: &
|
||||||
lattice_Sslip !< Schmid and non-Schmid matrices
|
lattice_Sslip !< Schmid and non-Schmid matrices
|
||||||
|
|
||||||
|
@ -64,19 +66,23 @@ module lattice
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! fcc
|
! fcc
|
||||||
integer(pInt), dimension(lattice_maxNslipFamily), parameter, public :: &
|
integer(pInt), dimension(LATTICE_maxNslipFamily), parameter, public :: &
|
||||||
LATTICE_fcc_NslipSystem = int([12, 0, 0, 0, 0, 0],pInt) !< total # of slip systems per family for fcc
|
LATTICE_fcc_NslipSystem = int([12, 0, 0, 0, 0, 0],pInt) !< total # of slip systems per family for fcc
|
||||||
|
|
||||||
integer(pInt), dimension(lattice_maxNtwinFamily), parameter, public :: &
|
integer(pInt), dimension(LATTICE_maxNtwinFamily), parameter, public :: &
|
||||||
lattice_fcc_NtwinSystem = int([12, 0, 0, 0],pInt) !< total # of twin systems per family for fcc
|
LATTICE_fcc_NtwinSystem = int([12, 0, 0, 0],pInt) !< total # of twin systems per family for fcc
|
||||||
|
|
||||||
|
integer(pInt), dimension(LATTICE_maxNtransFamily), parameter, public :: &
|
||||||
|
LATTICE_fcc_NtransSystem = int([12, 24],pInt) !< total # of transformation systems per family for fcc
|
||||||
|
|
||||||
integer(pInt), parameter, private :: &
|
integer(pInt), parameter, private :: &
|
||||||
lattice_fcc_Nslip = 12_pInt, & ! sum(lattice_fcc_NslipSystem), & !< total # of slip systems for fcc
|
LATTICE_fcc_Nslip = 12_pInt, & ! sum(lattice_fcc_NslipSystem), & !< total # of slip systems for fcc
|
||||||
lattice_fcc_Ntwin = 12_pInt, & ! sum(lattice_fcc_NtwinSystem) !< total # of twin systems for fcc
|
LATTICE_fcc_Ntwin = 12_pInt, & ! sum(lattice_fcc_NtwinSystem) !< total # of twin systems for fcc
|
||||||
lattice_fcc_NnonSchmid = 0_pInt !< total # of non-Schmid contributions for fcc
|
LATTICE_fcc_NnonSchmid = 0_pInt, & !< total # of non-Schmid contributions for fcc
|
||||||
|
LATTICE_fcc_Ntrans = 36_pInt !< total # of transformations for fcc
|
||||||
|
|
||||||
real(pReal), dimension(3+3,lattice_fcc_Nslip), parameter, private :: &
|
real(pReal), dimension(3+3,LATTICE_fcc_Nslip), parameter, private :: &
|
||||||
lattice_fcc_systemSlip = reshape(real([&
|
LATTICE_fcc_systemSlip = reshape(real([&
|
||||||
! Slip direction Plane normal
|
! Slip direction Plane normal
|
||||||
0, 1,-1, 1, 1, 1, &
|
0, 1,-1, 1, 1, 1, &
|
||||||
-1, 0, 1, 1, 1, 1, &
|
-1, 0, 1, 1, 1, 1, &
|
||||||
|
@ -90,10 +96,10 @@ module lattice
|
||||||
0, 1, 1, -1, 1,-1, &
|
0, 1, 1, -1, 1,-1, &
|
||||||
1, 0,-1, -1, 1,-1, &
|
1, 0,-1, -1, 1,-1, &
|
||||||
-1,-1, 0, -1, 1,-1 &
|
-1,-1, 0, -1, 1,-1 &
|
||||||
],pReal),[ 3_pInt + 3_pInt,lattice_fcc_Nslip]) !< Slip system <110>{111} directions. Sorted according to Eisenlohr & Hantcherli
|
],pReal),[ 3_pInt + 3_pInt,LATTICE_fcc_Nslip]) !< Slip system <110>{111} directions. Sorted according to Eisenlohr & Hantcherli
|
||||||
|
|
||||||
real(pReal), dimension(3+3,lattice_fcc_Ntwin), parameter, private :: &
|
real(pReal), dimension(3+3,LATTICE_fcc_Ntwin), parameter, private :: &
|
||||||
lattice_fcc_systemTwin = reshape(real( [&
|
LATTICE_fcc_systemTwin = reshape(real( [&
|
||||||
-2, 1, 1, 1, 1, 1, &
|
-2, 1, 1, 1, 1, 1, &
|
||||||
1,-2, 1, 1, 1, 1, &
|
1,-2, 1, 1, 1, 1, &
|
||||||
1, 1,-2, 1, 1, 1, &
|
1, 1,-2, 1, 1, 1, &
|
||||||
|
@ -106,13 +112,13 @@ module lattice
|
||||||
2, 1,-1, -1, 1,-1, &
|
2, 1,-1, -1, 1,-1, &
|
||||||
-1,-2,-1, -1, 1,-1, &
|
-1,-2,-1, -1, 1,-1, &
|
||||||
-1, 1, 2, -1, 1,-1 &
|
-1, 1, 2, -1, 1,-1 &
|
||||||
],pReal),[ 3_pInt + 3_pInt ,lattice_fcc_Ntwin]) !< Twin system <112>{111} directions. Sorted according to Eisenlohr & Hantcherli
|
],pReal),[ 3_pInt + 3_pInt,LATTICE_fcc_Ntwin]) !< Twin system <112>{111} directions. Sorted according to Eisenlohr & Hantcherli
|
||||||
|
|
||||||
real(pReal), dimension(lattice_fcc_Ntwin), parameter, private :: &
|
real(pReal), dimension(LATTICE_fcc_Ntwin), parameter, private :: &
|
||||||
lattice_fcc_shearTwin = 0.5_pReal*sqrt(2.0_pReal) !< Twin system <112>{111} ??? Sorted according to Eisenlohr & Hantcherli
|
LATTICE_fcc_shearTwin = 0.5_pReal*sqrt(2.0_pReal) !< Twin system <112>{111} ??? Sorted according to Eisenlohr & Hantcherli
|
||||||
|
|
||||||
integer(pInt), dimension(2_pInt,lattice_fcc_Ntwin), parameter, public :: &
|
integer(pInt), dimension(2_pInt,LATTICE_fcc_Ntwin), parameter, public :: &
|
||||||
lattice_fcc_twinNucleationSlipPair = reshape(int( [&
|
LATTICE_fcc_twinNucleationSlipPair = reshape(int( [&
|
||||||
2,3, &
|
2,3, &
|
||||||
1,3, &
|
1,3, &
|
||||||
1,2, &
|
1,2, &
|
||||||
|
@ -125,10 +131,10 @@ module lattice
|
||||||
11,12, &
|
11,12, &
|
||||||
10,12, &
|
10,12, &
|
||||||
10,11 &
|
10,11 &
|
||||||
],pInt),[2_pInt,lattice_fcc_Ntwin])
|
],pInt),[2_pInt,LATTICE_fcc_Ntwin])
|
||||||
|
|
||||||
integer(pInt), dimension(lattice_fcc_Nslip,lattice_fcc_Nslip), parameter, public :: &
|
integer(pInt), dimension(LATTICE_fcc_Nslip,lattice_fcc_Nslip), parameter, public :: &
|
||||||
lattice_fcc_interactionSlipSlip = reshape(int( [&
|
LATTICE_fcc_interactionSlipSlip = reshape(int( [&
|
||||||
1,2,2,4,6,5,3,5,5,4,5,6, & ! ---> slip
|
1,2,2,4,6,5,3,5,5,4,5,6, & ! ---> slip
|
||||||
2,1,2,6,4,5,5,4,6,5,3,5, & ! |
|
2,1,2,6,4,5,5,4,6,5,3,5, & ! |
|
||||||
2,2,1,5,5,3,5,6,4,6,5,4, & ! |
|
2,2,1,5,5,3,5,6,4,6,5,4, & ! |
|
||||||
|
@ -141,15 +147,15 @@ module lattice
|
||||||
4,5,6,3,5,5,4,6,5,1,2,2, &
|
4,5,6,3,5,5,4,6,5,1,2,2, &
|
||||||
5,3,5,5,4,6,6,4,5,2,1,2, &
|
5,3,5,5,4,6,6,4,5,2,1,2, &
|
||||||
6,5,4,5,6,4,5,5,3,2,2,1 &
|
6,5,4,5,6,4,5,5,3,2,2,1 &
|
||||||
],pInt),[lattice_fcc_Nslip,lattice_fcc_Nslip],order=[2,1]) !< Slip--slip interaction types for fcc
|
],pInt),[LATTICE_fcc_Nslip,LATTICE_fcc_Nslip],order=[2,1]) !< Slip--slip interaction types for fcc
|
||||||
!< 1: self interaction
|
!< 1: self interaction
|
||||||
!< 2: coplanar interaction
|
!< 2: coplanar interaction
|
||||||
!< 3: collinear interaction
|
!< 3: collinear interaction
|
||||||
!< 4: Hirth locks
|
!< 4: Hirth locks
|
||||||
!< 5: glissile junctions
|
!< 5: glissile junctions
|
||||||
!< 6: Lomer locks
|
!< 6: Lomer locks
|
||||||
integer(pInt), dimension(lattice_fcc_Nslip,lattice_fcc_Ntwin), parameter, public :: &
|
integer(pInt), dimension(LATTICE_fcc_Nslip,LATTICE_fcc_Ntwin), parameter, public :: &
|
||||||
lattice_fcc_interactionSlipTwin = reshape(int( [&
|
LATTICE_fcc_interactionSlipTwin = reshape(int( [&
|
||||||
1,1,1,3,3,3,2,2,2,3,3,3, & ! ---> twin
|
1,1,1,3,3,3,2,2,2,3,3,3, & ! ---> twin
|
||||||
1,1,1,3,3,3,3,3,3,2,2,2, & ! |
|
1,1,1,3,3,3,3,3,3,2,2,2, & ! |
|
||||||
1,1,1,2,2,2,3,3,3,3,3,3, & ! |
|
1,1,1,2,2,2,3,3,3,3,3,3, & ! |
|
||||||
|
@ -162,15 +168,15 @@ module lattice
|
||||||
3,3,3,2,2,2,3,3,3,1,1,1, &
|
3,3,3,2,2,2,3,3,3,1,1,1, &
|
||||||
2,2,2,3,3,3,3,3,3,1,1,1, &
|
2,2,2,3,3,3,3,3,3,1,1,1, &
|
||||||
3,3,3,3,3,3,2,2,2,1,1,1 &
|
3,3,3,3,3,3,2,2,2,1,1,1 &
|
||||||
],pInt),[lattice_fcc_Nslip,lattice_fcc_Ntwin],order=[2,1]) !< Slip--twin interaction types for fcc
|
],pInt),[LATTICE_fcc_Nslip,LATTICE_fcc_Ntwin],order=[2,1]) !< Slip--twin interaction types for fcc
|
||||||
!< 1: coplanar interaction
|
!< 1: coplanar interaction
|
||||||
!< 2: screw trace between slip system and twin habit plane (easy cross slip)
|
!< 2: screw trace between slip system and twin habit plane (easy cross slip)
|
||||||
!< 3: other interaction
|
!< 3: other interaction
|
||||||
integer(pInt), dimension(lattice_fcc_Ntwin,lattice_fcc_Nslip), parameter, public :: &
|
integer(pInt), dimension(LATTICE_fcc_Ntwin,LATTICE_fcc_Nslip), parameter, public :: &
|
||||||
lattice_fcc_interactionTwinSlip = 1_pInt !< Twin--Slip interaction types for fcc
|
LATTICE_fcc_interactionTwinSlip = 1_pInt !< Twin--Slip interaction types for fcc
|
||||||
|
|
||||||
integer(pInt), dimension(lattice_fcc_Ntwin,lattice_fcc_Ntwin), parameter,public :: &
|
integer(pInt), dimension(LATTICE_fcc_Ntwin,LATTICE_fcc_Ntwin), parameter,public :: &
|
||||||
lattice_fcc_interactionTwinTwin = reshape(int( [&
|
LATTICE_fcc_interactionTwinTwin = reshape(int( [&
|
||||||
1,1,1,2,2,2,2,2,2,2,2,2, & ! ---> twin
|
1,1,1,2,2,2,2,2,2,2,2,2, & ! ---> twin
|
||||||
1,1,1,2,2,2,2,2,2,2,2,2, & ! |
|
1,1,1,2,2,2,2,2,2,2,2,2, & ! |
|
||||||
1,1,1,2,2,2,2,2,2,2,2,2, & ! |
|
1,1,1,2,2,2,2,2,2,2,2,2, & ! |
|
||||||
|
@ -189,19 +195,23 @@ module lattice
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! bcc
|
! bcc
|
||||||
integer(pInt), dimension(lattice_maxNslipFamily), parameter, public :: &
|
integer(pInt), dimension(LATTICE_maxNslipFamily), parameter, public :: &
|
||||||
lattice_bcc_NslipSystem = int([ 12, 12, 0, 0, 0, 0], pInt) !< total # of slip systems per family for bcc
|
LATTICE_bcc_NslipSystem = int([ 12, 12, 0, 0, 0, 0], pInt) !< total # of slip systems per family for bcc
|
||||||
|
|
||||||
integer(pInt), dimension(lattice_maxNtwinFamily), parameter, public :: &
|
integer(pInt), dimension(LATTICE_maxNtwinFamily), parameter, public :: &
|
||||||
lattice_bcc_NtwinSystem = int([ 12, 0, 0, 0], pInt) !< total # of twin systems per family for bcc
|
LATTICE_bcc_NtwinSystem = int([ 12, 0, 0, 0], pInt) !< total # of twin systems per family for bcc
|
||||||
|
|
||||||
|
integer(pInt), dimension(LATTICE_maxNtransFamily), parameter, public :: &
|
||||||
|
LATTICE_bcc_NtransSystem = int([0,0],pInt) !< total # of transformation systems per family for bcc
|
||||||
|
|
||||||
integer(pInt), parameter, private :: &
|
integer(pInt), parameter, private :: &
|
||||||
lattice_bcc_Nslip = 24_pInt, & ! sum(lattice_bcc_NslipSystem), & !< total # of slip systems for bcc
|
LATTICE_bcc_Nslip = 24_pInt, & ! sum(lattice_bcc_NslipSystem), & !< total # of slip systems for bcc
|
||||||
lattice_bcc_Ntwin = 12_pInt, & ! sum(lattice_bcc_NtwinSystem) !< total # of twin systems for bcc
|
LATTICE_bcc_Ntwin = 12_pInt, & ! sum(lattice_bcc_NtwinSystem) !< total # of twin systems for bcc
|
||||||
lattice_bcc_NnonSchmid = 6_pInt !< # of non-Schmid contributions for bcc. 6 known non schmid contributions for BCC (A. Koester, A. Ma, A. Hartmaier 2012)
|
LATTICE_bcc_NnonSchmid = 6_pInt, & !< # of non-Schmid contributions for bcc. 6 known non schmid contributions for BCC (A. Koester, A. Ma, A. Hartmaier 2012)
|
||||||
|
LATTICE_bcc_Ntrans = 0_pInt !< total # of transformations for bcc
|
||||||
|
|
||||||
real(pReal), dimension(3+3,lattice_bcc_Nslip), parameter, private :: &
|
real(pReal), dimension(3+3,LATTICE_bcc_Nslip), parameter, private :: &
|
||||||
lattice_bcc_systemSlip = reshape(real([&
|
LATTICE_bcc_systemSlip = reshape(real([&
|
||||||
! Slip direction Plane normal
|
! Slip direction Plane normal
|
||||||
! Slip system <111>{110}
|
! Slip system <111>{110}
|
||||||
1,-1, 1, 0, 1, 1, &
|
1,-1, 1, 0, 1, 1, &
|
||||||
|
@ -254,10 +264,10 @@ module lattice
|
||||||
! 1, 1, 1, -3, 2, 1, &
|
! 1, 1, 1, -3, 2, 1, &
|
||||||
! 1, 1,-1, 3,-2, 1, &
|
! 1, 1,-1, 3,-2, 1, &
|
||||||
! 1,-1, 1, 3, 2,-1 &
|
! 1,-1, 1, 3, 2,-1 &
|
||||||
],pReal),[ 3_pInt + 3_pInt ,lattice_bcc_Nslip])
|
],pReal),[ 3_pInt + 3_pInt ,LATTICE_bcc_Nslip])
|
||||||
|
|
||||||
real(pReal), dimension(3+3,lattice_bcc_Ntwin), parameter, private :: &
|
real(pReal), dimension(3+3,LATTICE_bcc_Ntwin), parameter, private :: &
|
||||||
lattice_bcc_systemTwin = reshape(real([&
|
LATTICE_bcc_systemTwin = reshape(real([&
|
||||||
! Twin system <111>{112}
|
! Twin system <111>{112}
|
||||||
-1, 1, 1, 2, 1, 1, &
|
-1, 1, 1, 2, 1, 1, &
|
||||||
1, 1, 1, -2, 1, 1, &
|
1, 1, 1, -2, 1, 1, &
|
||||||
|
@ -271,13 +281,13 @@ module lattice
|
||||||
1,-1, 1, -1, 1, 2, &
|
1,-1, 1, -1, 1, 2, &
|
||||||
-1, 1, 1, 1,-1, 2, &
|
-1, 1, 1, 1,-1, 2, &
|
||||||
1, 1, 1, 1, 1,-2 &
|
1, 1, 1, 1, 1,-2 &
|
||||||
],pReal),[ 3_pInt + 3_pInt,lattice_bcc_Ntwin])
|
],pReal),[ 3_pInt + 3_pInt,LATTICE_bcc_Ntwin])
|
||||||
|
|
||||||
real(pReal), dimension(lattice_bcc_Ntwin), parameter, private :: &
|
real(pReal), dimension(LATTICE_bcc_Ntwin), parameter, private :: &
|
||||||
lattice_bcc_shearTwin = 0.5_pReal*sqrt(2.0_pReal)
|
LATTICE_bcc_shearTwin = 0.5_pReal*sqrt(2.0_pReal)
|
||||||
|
|
||||||
integer(pInt), dimension(lattice_bcc_Nslip,lattice_bcc_Nslip), parameter, public :: &
|
integer(pInt), dimension(LATTICE_bcc_Nslip,LATTICE_bcc_Nslip), parameter, public :: &
|
||||||
lattice_bcc_interactionSlipSlip = reshape(int( [&
|
LATTICE_bcc_interactionSlipSlip = reshape(int( [&
|
||||||
1,2,6,6,5,4,4,3,4,3,5,4, 6,6,4,3,3,4,6,6,4,3,6,6, & ! ---> slip
|
1,2,6,6,5,4,4,3,4,3,5,4, 6,6,4,3,3,4,6,6,4,3,6,6, & ! ---> slip
|
||||||
2,1,6,6,4,3,5,4,5,4,4,3, 6,6,3,4,4,3,6,6,3,4,6,6, & ! |
|
2,1,6,6,4,3,5,4,5,4,4,3, 6,6,3,4,4,3,6,6,3,4,6,6, & ! |
|
||||||
6,6,1,2,4,5,3,4,4,5,3,4, 4,3,6,6,6,6,3,4,6,6,4,3, & ! |
|
6,6,1,2,4,5,3,4,4,5,3,4, 4,3,6,6,6,6,3,4,6,6,4,3, & ! |
|
||||||
|
@ -310,8 +320,8 @@ module lattice
|
||||||
!< 4: mixed-asymmetrical junction
|
!< 4: mixed-asymmetrical junction
|
||||||
!< 5: mixed-symmetrical junction
|
!< 5: mixed-symmetrical junction
|
||||||
!< 6: edge junction
|
!< 6: edge junction
|
||||||
integer(pInt), dimension(lattice_bcc_Nslip,lattice_bcc_Ntwin), parameter, public :: &
|
integer(pInt), dimension(LATTICE_bcc_Nslip,LATTICE_bcc_Ntwin), parameter, public :: &
|
||||||
lattice_bcc_interactionSlipTwin = reshape(int( [&
|
LATTICE_bcc_interactionSlipTwin = reshape(int( [&
|
||||||
3,3,3,2,2,3,3,3,3,2,3,3, & ! ---> twin
|
3,3,3,2,2,3,3,3,3,2,3,3, & ! ---> twin
|
||||||
3,3,2,3,3,2,3,3,2,3,3,3, & ! |
|
3,3,2,3,3,2,3,3,2,3,3,3, & ! |
|
||||||
3,2,3,3,3,3,2,3,3,3,3,2, & ! |
|
3,2,3,3,3,3,2,3,3,3,3,2, & ! |
|
||||||
|
@ -337,15 +347,15 @@ module lattice
|
||||||
3,3,3,2,2,3,3,3,3,1,3,3, &
|
3,3,3,2,2,3,3,3,3,1,3,3, &
|
||||||
2,3,3,3,3,3,3,2,3,3,1,3, &
|
2,3,3,3,3,3,3,2,3,3,1,3, &
|
||||||
3,2,3,3,3,3,2,3,3,3,3,1 &
|
3,2,3,3,3,3,2,3,3,3,3,1 &
|
||||||
],pInt),[lattice_bcc_Nslip,lattice_bcc_Ntwin],order=[2,1]) !< Slip--twin interaction types for bcc
|
],pInt),[LATTICE_bcc_Nslip,LATTICE_bcc_Ntwin],order=[2,1]) !< Slip--twin interaction types for bcc
|
||||||
!< 1: coplanar interaction
|
!< 1: coplanar interaction
|
||||||
!< 2: screw trace between slip system and twin habit plane (easy cross slip)
|
!< 2: screw trace between slip system and twin habit plane (easy cross slip)
|
||||||
!< 3: other interaction
|
!< 3: other interaction
|
||||||
integer(pInt), dimension(lattice_bcc_Ntwin,lattice_bcc_Nslip), parameter, public :: &
|
integer(pInt), dimension(LATTICE_bcc_Ntwin,LATTICE_bcc_Nslip), parameter, public :: &
|
||||||
lattice_bcc_interactionTwinSlip = 1_pInt !< Twin--slip interaction types for bcc @todo not implemented yet
|
LATTICE_bcc_interactionTwinSlip = 1_pInt !< Twin--slip interaction types for bcc @todo not implemented yet
|
||||||
|
|
||||||
integer(pInt), dimension(lattice_bcc_Ntwin,lattice_bcc_Ntwin), parameter, public :: &
|
integer(pInt), dimension(LATTICE_bcc_Ntwin,LATTICE_bcc_Ntwin), parameter, public :: &
|
||||||
lattice_bcc_interactionTwinTwin = reshape(int( [&
|
LATTICE_bcc_interactionTwinTwin = reshape(int( [&
|
||||||
1,3,3,3,3,3,3,2,3,3,2,3, & ! ---> twin
|
1,3,3,3,3,3,3,2,3,3,2,3, & ! ---> twin
|
||||||
3,1,3,3,3,3,2,3,3,3,3,2, & ! |
|
3,1,3,3,3,3,2,3,3,3,3,2, & ! |
|
||||||
3,3,1,3,3,2,3,3,2,3,3,3, & ! |
|
3,3,1,3,3,2,3,3,2,3,3,3, & ! |
|
||||||
|
@ -358,7 +368,7 @@ module lattice
|
||||||
3,3,3,2,2,3,3,3,3,1,3,3, &
|
3,3,3,2,2,3,3,3,3,1,3,3, &
|
||||||
2,3,3,3,3,3,3,2,3,3,1,3, &
|
2,3,3,3,3,3,3,2,3,3,1,3, &
|
||||||
3,2,3,3,3,3,2,3,3,3,3,1 &
|
3,2,3,3,3,3,2,3,3,3,3,1 &
|
||||||
],pInt),[lattice_bcc_Ntwin,lattice_bcc_Ntwin],order=[2,1]) !< Twin--twin interaction types for bcc
|
],pInt),[LATTICE_bcc_Ntwin,LATTICE_bcc_Ntwin],order=[2,1]) !< Twin--twin interaction types for bcc
|
||||||
!< 1: self interaction
|
!< 1: self interaction
|
||||||
!< 2: collinear interaction
|
!< 2: collinear interaction
|
||||||
!< 3: other interaction
|
!< 3: other interaction
|
||||||
|
@ -366,19 +376,23 @@ module lattice
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! hex
|
! hex
|
||||||
integer(pInt), dimension(lattice_maxNslipFamily), parameter, public :: &
|
integer(pInt), dimension(LATTICE_maxNslipFamily), parameter, public :: &
|
||||||
lattice_hex_NslipSystem = int([ 3, 3, 3, 6, 12, 6],pInt) !< # of slip systems per family for hex
|
lattice_hex_NslipSystem = int([ 3, 3, 3, 6, 12, 6],pInt) !< # of slip systems per family for hex
|
||||||
|
|
||||||
integer(pInt), dimension(lattice_maxNtwinFamily), parameter, public :: &
|
integer(pInt), dimension(LATTICE_maxNtwinFamily), parameter, public :: &
|
||||||
lattice_hex_NtwinSystem = int([ 6, 6, 6, 6],pInt) !< # of slip systems per family for hex
|
lattice_hex_NtwinSystem = int([ 6, 6, 6, 6],pInt) !< # of slip systems per family for hex
|
||||||
|
|
||||||
integer(pInt), parameter , private :: &
|
integer(pInt), dimension(LATTICE_maxNtransFamily), parameter, public :: &
|
||||||
lattice_hex_Nslip = 33_pInt, & ! sum(lattice_hex_NslipSystem), !< total # of slip systems for hex
|
LATTICE_hex_NtransSystem = int([0,0],pInt) !< total # of transformation systems per family for hex
|
||||||
lattice_hex_Ntwin = 24_pInt, & ! sum(lattice_hex_NtwinSystem) !< total # of twin systems for hex
|
|
||||||
lattice_hex_NnonSchmid = 0_pInt !< # of non-Schmid contributions for hex
|
|
||||||
|
|
||||||
real(pReal), dimension(4+4,lattice_hex_Nslip), parameter, private :: &
|
integer(pInt), parameter , private :: &
|
||||||
lattice_hex_systemSlip = reshape(real([&
|
LATTICE_hex_Nslip = 33_pInt, & ! sum(lattice_hex_NslipSystem), !< total # of slip systems for hex
|
||||||
|
LATTICE_hex_Ntwin = 24_pInt, & ! sum(lattice_hex_NtwinSystem) !< total # of twin systems for hex
|
||||||
|
LATTICE_hex_NnonSchmid = 0_pInt, & !< # of non-Schmid contributions for hex
|
||||||
|
LATTICE_hex_Ntrans = 0_pInt !< total # of transformations for hex
|
||||||
|
|
||||||
|
real(pReal), dimension(4+4,LATTICE_hex_Nslip), parameter, private :: &
|
||||||
|
LATTICE_hex_systemSlip = reshape(real([&
|
||||||
! Slip direction Plane normal
|
! Slip direction Plane normal
|
||||||
! Basal systems <11.0>{00.1} (independent of c/a-ratio, Bravais notation (4 coordinate base))
|
! Basal systems <11.0>{00.1} (independent of c/a-ratio, Bravais notation (4 coordinate base))
|
||||||
2, -1, -1, 0, 0, 0, 0, 1, &
|
2, -1, -1, 0, 0, 0, 0, 1, &
|
||||||
|
@ -419,10 +433,10 @@ module lattice
|
||||||
-2, 1, 1, 3, 2, -1, -1, 2, &
|
-2, 1, 1, 3, 2, -1, -1, 2, &
|
||||||
1, -2, 1, 3, -1, 2, -1, 2, &
|
1, -2, 1, 3, -1, 2, -1, 2, &
|
||||||
1, 1, -2, 3, -1, -1, 2, 2 &
|
1, 1, -2, 3, -1, -1, 2, 2 &
|
||||||
],pReal),[ 4_pInt + 4_pInt,lattice_hex_Nslip]) !< slip systems for hex sorted by A. Alankar & P. Eisenlohr
|
],pReal),[ 4_pInt + 4_pInt,LATTICE_hex_Nslip]) !< slip systems for hex sorted by A. Alankar & P. Eisenlohr
|
||||||
|
|
||||||
real(pReal), dimension(4+4,lattice_hex_Ntwin), parameter, private :: &
|
real(pReal), dimension(4+4,LATTICE_hex_Ntwin), parameter, private :: &
|
||||||
lattice_hex_systemTwin = reshape(real([&
|
LATTICE_hex_systemTwin = reshape(real([&
|
||||||
! Compression or Tension =f(twinning shear=f(c/a)) for each metal ! (according to Yoo 1981)
|
! Compression or Tension =f(twinning shear=f(c/a)) for each metal ! (according to Yoo 1981)
|
||||||
1, -1, 0, 1, -1, 1, 0, 2, & ! <-10.1>{10.2} shear = (3-(c/a)^2)/(sqrt(3) c/a)
|
1, -1, 0, 1, -1, 1, 0, 2, & ! <-10.1>{10.2} shear = (3-(c/a)^2)/(sqrt(3) c/a)
|
||||||
-1, 0, 1, 1, 1, 0, -1, 2, &
|
-1, 0, 1, 1, 1, 0, -1, 2, &
|
||||||
|
@ -451,10 +465,10 @@ module lattice
|
||||||
-2, 1, 1, -3, -2, 1, 1, 2, &
|
-2, 1, 1, -3, -2, 1, 1, 2, &
|
||||||
1, -2, 1, -3, 1, -2, 1, 2, &
|
1, -2, 1, -3, 1, -2, 1, 2, &
|
||||||
1, 1, -2, -3, 1, 1, -2, 2 &
|
1, 1, -2, -3, 1, 1, -2, 2 &
|
||||||
],pReal),[ 4_pInt + 4_pInt ,lattice_hex_Ntwin]) !< twin systems for hex, order follows Prof. Tom Bieler's scheme; but numbering in data was restarted from 1
|
],pReal),[ 4_pInt + 4_pInt ,LATTICE_hex_Ntwin]) !< twin systems for hex, order follows Prof. Tom Bieler's scheme; but numbering in data was restarted from 1
|
||||||
|
|
||||||
integer(pInt), dimension(lattice_hex_Ntwin), parameter, private :: &
|
integer(pInt), dimension(LATTICE_hex_Ntwin), parameter, private :: &
|
||||||
lattice_hex_shearTwin = reshape(int( [& ! indicator to formula further below
|
LATTICE_hex_shearTwin = reshape(int( [& ! indicator to formula further below
|
||||||
1, & ! <-10.1>{10.2}
|
1, & ! <-10.1>{10.2}
|
||||||
1, &
|
1, &
|
||||||
1, &
|
1, &
|
||||||
|
@ -479,10 +493,10 @@ module lattice
|
||||||
4, &
|
4, &
|
||||||
4, &
|
4, &
|
||||||
4 &
|
4 &
|
||||||
],pInt),[lattice_hex_Ntwin])
|
],pInt),[LATTICE_hex_Ntwin])
|
||||||
|
|
||||||
integer(pInt), dimension(lattice_hex_Nslip,lattice_hex_Nslip), parameter, public :: &
|
integer(pInt), dimension(LATTICE_hex_Nslip,LATTICE_hex_Nslip), parameter, public :: &
|
||||||
lattice_hex_interactionSlipSlip = reshape(int( [&
|
LATTICE_hex_interactionSlipSlip = reshape(int( [&
|
||||||
1, 2, 2, 3, 3, 3, 7, 7, 7, 13,13,13,13,13,13, 21,21,21,21,21,21,21,21,21,21,21,21, 31,31,31,31,31,31, & ! ---> slip
|
1, 2, 2, 3, 3, 3, 7, 7, 7, 13,13,13,13,13,13, 21,21,21,21,21,21,21,21,21,21,21,21, 31,31,31,31,31,31, & ! ---> slip
|
||||||
2, 1, 2, 3, 3, 3, 7, 7, 7, 13,13,13,13,13,13, 21,21,21,21,21,21,21,21,21,21,21,21, 31,31,31,31,31,31, & ! |
|
2, 1, 2, 3, 3, 3, 7, 7, 7, 13,13,13,13,13,13, 21,21,21,21,21,21,21,21,21,21,21,21, 31,31,31,31,31,31, & ! |
|
||||||
2, 2, 1, 3, 3, 3, 7, 7, 7, 13,13,13,13,13,13, 21,21,21,21,21,21,21,21,21,21,21,21, 31,31,31,31,31,31, & ! |
|
2, 2, 1, 3, 3, 3, 7, 7, 7, 13,13,13,13,13,13, 21,21,21,21,21,21,21,21,21,21,21,21, 31,31,31,31,31,31, & ! |
|
||||||
|
@ -522,10 +536,10 @@ module lattice
|
||||||
42,42,42, 41,41,41, 40,40,40, 39,39,39,39,39,39, 38,38,38,38,38,38,38,38,38,38,38,38, 37,37,37,37,36,37, &
|
42,42,42, 41,41,41, 40,40,40, 39,39,39,39,39,39, 38,38,38,38,38,38,38,38,38,38,38,38, 37,37,37,37,36,37, &
|
||||||
42,42,42, 41,41,41, 40,40,40, 39,39,39,39,39,39, 38,38,38,38,38,38,38,38,38,38,38,38, 37,37,37,37,37,36 &
|
42,42,42, 41,41,41, 40,40,40, 39,39,39,39,39,39, 38,38,38,38,38,38,38,38,38,38,38,38, 37,37,37,37,37,36 &
|
||||||
!
|
!
|
||||||
],pInt),[lattice_hex_Nslip,lattice_hex_Nslip],order=[2,1]) !< Slip--slip interaction types for hex (32? in total)
|
],pInt),[LATTICE_hex_Nslip,LATTICE_hex_Nslip],order=[2,1]) !< Slip--slip interaction types for hex (32? in total)
|
||||||
|
|
||||||
integer(pInt), dimension(lattice_hex_Nslip,lattice_hex_Ntwin), parameter, public :: &
|
integer(pInt), dimension(LATTICE_hex_Nslip,LATTICE_hex_Ntwin), parameter, public :: &
|
||||||
lattice_hex_interactionSlipTwin = reshape(int( [&
|
LATTICE_hex_interactionSlipTwin = reshape(int( [&
|
||||||
1, 1, 1, 1, 1, 1, 2, 2, 2, 2, 2, 2, 3, 3, 3, 3, 3, 3, 4, 4, 4, 4, 4, 4, & ! --> twin
|
1, 1, 1, 1, 1, 1, 2, 2, 2, 2, 2, 2, 3, 3, 3, 3, 3, 3, 4, 4, 4, 4, 4, 4, & ! --> twin
|
||||||
1, 1, 1, 1, 1, 1, 2, 2, 2, 2, 2, 2, 3, 3, 3, 3, 3, 3, 4, 4, 4, 4, 4, 4, & ! |
|
1, 1, 1, 1, 1, 1, 2, 2, 2, 2, 2, 2, 3, 3, 3, 3, 3, 3, 4, 4, 4, 4, 4, 4, & ! |
|
||||||
1, 1, 1, 1, 1, 1, 2, 2, 2, 2, 2, 2, 3, 3, 3, 3, 3, 3, 4, 4, 4, 4, 4, 4, & ! |
|
1, 1, 1, 1, 1, 1, 2, 2, 2, 2, 2, 2, 3, 3, 3, 3, 3, 3, 4, 4, 4, 4, 4, 4, & ! |
|
||||||
|
@ -565,10 +579,10 @@ module lattice
|
||||||
21,21,21,21,21,21, 22,22,22,22,22,22, 23,23,23,23,23,23, 24,24,24,24,24,24, &
|
21,21,21,21,21,21, 22,22,22,22,22,22, 23,23,23,23,23,23, 24,24,24,24,24,24, &
|
||||||
21,21,21,21,21,21, 22,22,22,22,22,22, 23,23,23,23,23,23, 24,24,24,24,24,24 &
|
21,21,21,21,21,21, 22,22,22,22,22,22, 23,23,23,23,23,23, 24,24,24,24,24,24 &
|
||||||
!
|
!
|
||||||
],pInt),[lattice_hex_Nslip,lattice_hex_Ntwin],order=[2,1]) !< Slip--twin interaction types for hex (isotropic, 24 in total)
|
],pInt),[LATTICE_hex_Nslip,LATTICE_hex_Ntwin],order=[2,1]) !< Slip--twin interaction types for hex (isotropic, 24 in total)
|
||||||
|
|
||||||
integer(pInt), dimension(lattice_hex_Ntwin,lattice_hex_Nslip), parameter, public :: &
|
integer(pInt), dimension(LATTICE_hex_Ntwin,LATTICE_hex_Nslip), parameter, public :: &
|
||||||
lattice_hex_interactionTwinSlip = reshape(int( [&
|
LATTICE_hex_interactionTwinSlip = reshape(int( [&
|
||||||
1, 1, 1, 5, 5, 5, 9, 9, 9, 13,13,13,13,13,13, 17,17,17,17,17,17,17,17,17,17,17,17, 21,21,21,21,21,21, & ! --> slip
|
1, 1, 1, 5, 5, 5, 9, 9, 9, 13,13,13,13,13,13, 17,17,17,17,17,17,17,17,17,17,17,17, 21,21,21,21,21,21, & ! --> slip
|
||||||
1, 1, 1, 5, 5, 5, 9, 9, 9, 13,13,13,13,13,13, 17,17,17,17,17,17,17,17,17,17,17,17, 21,21,21,21,21,21, & ! |
|
1, 1, 1, 5, 5, 5, 9, 9, 9, 13,13,13,13,13,13, 17,17,17,17,17,17,17,17,17,17,17,17, 21,21,21,21,21,21, & ! |
|
||||||
1, 1, 1, 5, 5, 5, 9, 9, 9, 13,13,13,13,13,13, 17,17,17,17,17,17,17,17,17,17,17,17, 21,21,21,21,21,21, & ! |
|
1, 1, 1, 5, 5, 5, 9, 9, 9, 13,13,13,13,13,13, 17,17,17,17,17,17,17,17,17,17,17,17, 21,21,21,21,21,21, & ! |
|
||||||
|
@ -596,10 +610,10 @@ module lattice
|
||||||
4, 4, 4, 8, 8, 8, 12,12,12, 16,16,16,16,16,16, 20,20,20,20,20,20,20,20,20,20,20,20, 24,24,24,24,24,24, &
|
4, 4, 4, 8, 8, 8, 12,12,12, 16,16,16,16,16,16, 20,20,20,20,20,20,20,20,20,20,20,20, 24,24,24,24,24,24, &
|
||||||
4, 4, 4, 8, 8, 8, 12,12,12, 16,16,16,16,16,16, 20,20,20,20,20,20,20,20,20,20,20,20, 24,24,24,24,24,24, &
|
4, 4, 4, 8, 8, 8, 12,12,12, 16,16,16,16,16,16, 20,20,20,20,20,20,20,20,20,20,20,20, 24,24,24,24,24,24, &
|
||||||
4, 4, 4, 8, 8, 8, 12,12,12, 16,16,16,16,16,16, 20,20,20,20,20,20,20,20,20,20,20,20, 24,24,24,24,24,24 &
|
4, 4, 4, 8, 8, 8, 12,12,12, 16,16,16,16,16,16, 20,20,20,20,20,20,20,20,20,20,20,20, 24,24,24,24,24,24 &
|
||||||
],pInt),[lattice_hex_Ntwin,lattice_hex_Nslip],order=[2,1]) !< Twin--twin interaction types for hex (isotropic, 20 in total)
|
],pInt),[LATTICE_hex_Ntwin,LATTICE_hex_Nslip],order=[2,1]) !< Twin--twin interaction types for hex (isotropic, 20 in total)
|
||||||
|
|
||||||
integer(pInt), dimension(lattice_hex_Ntwin,lattice_hex_Ntwin), parameter, public :: &
|
integer(pInt), dimension(LATTICE_hex_Ntwin,LATTICE_hex_Ntwin), parameter, public :: &
|
||||||
lattice_hex_interactionTwinTwin = reshape(int( [&
|
LATTICE_hex_interactionTwinTwin = reshape(int( [&
|
||||||
1, 2, 2, 2, 2, 2, 3, 3, 3, 3, 3, 3, 7, 7, 7, 7, 7, 7, 13,13,13,13,13,13, & ! ---> twin
|
1, 2, 2, 2, 2, 2, 3, 3, 3, 3, 3, 3, 7, 7, 7, 7, 7, 7, 13,13,13,13,13,13, & ! ---> twin
|
||||||
2, 1, 2, 2, 2, 2, 3, 3, 3, 3, 3, 3, 7, 7, 7, 7, 7, 7, 13,13,13,13,13,13, & ! |
|
2, 1, 2, 2, 2, 2, 3, 3, 3, 3, 3, 3, 7, 7, 7, 7, 7, 7, 13,13,13,13,13,13, & ! |
|
||||||
2, 2, 1, 2, 2, 2, 3, 3, 3, 3, 3, 3, 7, 7, 7, 7, 7, 7, 13,13,13,13,13,13, & ! |
|
2, 2, 1, 2, 2, 2, 3, 3, 3, 3, 3, 3, 7, 7, 7, 7, 7, 7, 13,13,13,13,13,13, & ! |
|
||||||
|
@ -813,7 +827,11 @@ subroutine lattice_init
|
||||||
integer(pInt), parameter :: MAXNCHUNKS = 2_pInt
|
integer(pInt), parameter :: MAXNCHUNKS = 2_pInt
|
||||||
integer(pInt), dimension(1+2*MAXNCHUNKS) :: positions
|
integer(pInt), dimension(1+2*MAXNCHUNKS) :: positions
|
||||||
integer(pInt) :: section = 0_pInt,i
|
integer(pInt) :: section = 0_pInt,i
|
||||||
real(pReal), dimension(:), allocatable :: CoverA !< c/a ratio for hex type lattice
|
real(pReal), dimension(:), allocatable :: &
|
||||||
|
CoverA, & !< c/a ratio for hex type lattice
|
||||||
|
aA, & !< lattice parameter a for fcc austenite
|
||||||
|
aM, & !< lattice paramater a for bcc martensite
|
||||||
|
cM !< lattice parameter c for bcc martensite
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- lattice init -+>>>'
|
write(6,'(/,a)') ' <<<+- lattice init -+>>>'
|
||||||
write(6,'(a)') ' $Id$'
|
write(6,'(a)') ' $Id$'
|
||||||
|
@ -822,12 +840,36 @@ subroutine lattice_init
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! consistency checks
|
! consistency checks
|
||||||
if (LATTICE_maxNslip /= maxval([lattice_fcc_Nslip,lattice_bcc_Nslip,lattice_hex_Nslip])) &
|
if (LATTICE_maxNslip /= maxval([LATTICE_fcc_Nslip,LATTICE_bcc_Nslip,LATTICE_hex_Nslip])) &
|
||||||
call IO_error(0_pInt,ext_msg = 'LATTICE_maxNslip')
|
call IO_error(0_pInt,ext_msg = 'LATTICE_maxNslip')
|
||||||
if (LATTICE_maxNtwin /= maxval([lattice_fcc_Ntwin,lattice_bcc_Ntwin,lattice_hex_Ntwin])) &
|
if (LATTICE_maxNtwin /= maxval([LATTICE_fcc_Ntwin,LATTICE_bcc_Ntwin,LATTICE_hex_Ntwin])) &
|
||||||
call IO_error(0_pInt,ext_msg = 'LATTICE_maxNtwin')
|
call IO_error(0_pInt,ext_msg = 'LATTICE_maxNtwin')
|
||||||
|
if (LATTICE_maxNtrans /= maxval([LATTICE_fcc_Ntrans,LATTICE_bcc_Ntrans,LATTICE_hex_Ntrans])) &
|
||||||
|
call IO_error(0_pInt,ext_msg = 'LATTICE_maxNtrans')
|
||||||
if (LATTICE_maxNnonSchmid /= maxval([lattice_fcc_NnonSchmid,lattice_bcc_NnonSchmid,&
|
if (LATTICE_maxNnonSchmid /= maxval([lattice_fcc_NnonSchmid,lattice_bcc_NnonSchmid,&
|
||||||
lattice_hex_NnonSchmid])) call IO_error(0_pInt,ext_msg = 'LATTICE_maxNnonSchmid')
|
lattice_hex_NnonSchmid])) call IO_error(0_pInt,ext_msg = 'LATTICE_maxNnonSchmid')
|
||||||
|
|
||||||
|
if (LATTICE_fcc_Nslip /= sum(lattice_fcc_NslipSystem)) &
|
||||||
|
call IO_error(0_pInt,ext_msg = 'LATTICE_fcc_Nslip')
|
||||||
|
if (LATTICE_bcc_Nslip /= sum(lattice_bcc_NslipSystem)) &
|
||||||
|
call IO_error(0_pInt,ext_msg = 'LATTICE_bcc_Nslip')
|
||||||
|
if (LATTICE_hex_Nslip /= sum(lattice_hex_NslipSystem)) &
|
||||||
|
call IO_error(0_pInt,ext_msg = 'LATTICE_hex_Nslip')
|
||||||
|
|
||||||
|
if (LATTICE_fcc_Ntwin /= sum(lattice_fcc_NtwinSystem)) &
|
||||||
|
call IO_error(0_pInt,ext_msg = 'LATTICE_fcc_Ntwin')
|
||||||
|
if (LATTICE_bcc_Ntwin /= sum(lattice_bcc_NtwinSystem)) &
|
||||||
|
call IO_error(0_pInt,ext_msg = 'LATTICE_bcc_Ntwin')
|
||||||
|
if (LATTICE_hex_Ntwin /= sum(lattice_hex_NtwinSystem)) &
|
||||||
|
call IO_error(0_pInt,ext_msg = 'LATTICE_hex_Ntwin')
|
||||||
|
|
||||||
|
if (LATTICE_fcc_Ntrans /= sum(lattice_fcc_NtransSystem)) &
|
||||||
|
call IO_error(0_pInt,ext_msg = 'LATTICE_fcc_Ntrans')
|
||||||
|
if (LATTICE_bcc_Ntrans /= sum(lattice_bcc_NtransSystem)) &
|
||||||
|
call IO_error(0_pInt,ext_msg = 'LATTICE_bcc_Ntrans')
|
||||||
|
if (LATTICE_hex_Ntrans /= sum(lattice_hex_NtransSystem)) &
|
||||||
|
call IO_error(0_pInt,ext_msg = 'LATTICE_hex_Ntrans')
|
||||||
|
|
||||||
if (LATTICE_maxNinteraction /= max(&
|
if (LATTICE_maxNinteraction /= max(&
|
||||||
maxval(lattice_fcc_interactionSlipSlip), &
|
maxval(lattice_fcc_interactionSlipSlip), &
|
||||||
maxval(lattice_bcc_interactionSlipSlip), &
|
maxval(lattice_bcc_interactionSlipSlip), &
|
||||||
|
@ -888,6 +930,7 @@ subroutine lattice_init
|
||||||
|
|
||||||
allocate(lattice_NslipSystem(lattice_maxNslipFamily,Nphases),source=0_pInt)
|
allocate(lattice_NslipSystem(lattice_maxNslipFamily,Nphases),source=0_pInt)
|
||||||
allocate(lattice_NtwinSystem(lattice_maxNtwinFamily,Nphases),source=0_pInt)
|
allocate(lattice_NtwinSystem(lattice_maxNtwinFamily,Nphases),source=0_pInt)
|
||||||
|
allocate(lattice_NtransSystem(lattice_maxNtransFamily,Nphases),source=0_pInt)
|
||||||
|
|
||||||
allocate(lattice_interactionSlipSlip(lattice_maxNslip,lattice_maxNslip,Nphases),source=0_pInt) ! other:me
|
allocate(lattice_interactionSlipSlip(lattice_maxNslip,lattice_maxNslip,Nphases),source=0_pInt) ! other:me
|
||||||
allocate(lattice_interactionSlipTwin(lattice_maxNslip,lattice_maxNtwin,Nphases),source=0_pInt) ! other:me
|
allocate(lattice_interactionSlipTwin(lattice_maxNslip,lattice_maxNtwin,Nphases),source=0_pInt) ! other:me
|
||||||
|
@ -895,6 +938,10 @@ subroutine lattice_init
|
||||||
allocate(lattice_interactionTwinTwin(lattice_maxNtwin,lattice_maxNtwin,Nphases),source=0_pInt) ! other:me
|
allocate(lattice_interactionTwinTwin(lattice_maxNtwin,lattice_maxNtwin,Nphases),source=0_pInt) ! other:me
|
||||||
|
|
||||||
allocate(CoverA(Nphases),source=0.0_pReal)
|
allocate(CoverA(Nphases),source=0.0_pReal)
|
||||||
|
allocate(aA(Nphases),source=0.0_pReal)
|
||||||
|
allocate(aM(Nphases),source=0.0_pReal)
|
||||||
|
allocate(cM(Nphases),source=0.0_pReal)
|
||||||
|
|
||||||
rewind(fileUnit)
|
rewind(fileUnit)
|
||||||
line = '' ! to have it initialized
|
line = '' ! to have it initialized
|
||||||
section = 0_pInt ! - " -
|
section = 0_pInt ! - " -
|
||||||
|
@ -951,6 +998,12 @@ subroutine lattice_init
|
||||||
lattice_C66(6,6,section) = IO_floatValue(line,positions,2_pInt)
|
lattice_C66(6,6,section) = IO_floatValue(line,positions,2_pInt)
|
||||||
case ('covera_ratio','c/a_ratio','c/a')
|
case ('covera_ratio','c/a_ratio','c/a')
|
||||||
CoverA(section) = IO_floatValue(line,positions,2_pInt)
|
CoverA(section) = IO_floatValue(line,positions,2_pInt)
|
||||||
|
case ('aa', 'a_a', 'a_austenite')
|
||||||
|
aA(section) = IO_floatValue(line,positions,2_pInt)
|
||||||
|
case ('am', 'a_m', 'a_martensite')
|
||||||
|
aM(section) = IO_floatValue(line,positions,2_pInt)
|
||||||
|
case ('cm', 'c_m', 'c_martensite')
|
||||||
|
cM(section) = IO_floatValue(line,positions,2_pInt)
|
||||||
case ('k11')
|
case ('k11')
|
||||||
lattice_thermalConductivity33(1,1,section) = IO_floatValue(line,positions,2_pInt)
|
lattice_thermalConductivity33(1,1,section) = IO_floatValue(line,positions,2_pInt)
|
||||||
case ('k22')
|
case ('k22')
|
||||||
|
@ -978,10 +1031,10 @@ subroutine lattice_init
|
||||||
do i = 1_pInt,Nphases
|
do i = 1_pInt,Nphases
|
||||||
if ((CoverA(i) < 1.0_pReal .or. CoverA(i) > 2.0_pReal) &
|
if ((CoverA(i) < 1.0_pReal .or. CoverA(i) > 2.0_pReal) &
|
||||||
.and. lattice_structure(i) == LATTICE_hex_ID) call IO_error(206_pInt) ! checking physical significance of c/a
|
.and. lattice_structure(i) == LATTICE_hex_ID) call IO_error(206_pInt) ! checking physical significance of c/a
|
||||||
call lattice_initializeStructure(i, CoverA(i))
|
call lattice_initializeStructure(i, CoverA(i), aA(i), aM(i), cM(i))
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
deallocate(CoverA)
|
deallocate(CoverA,aA,aM,cM)
|
||||||
|
|
||||||
end subroutine lattice_init
|
end subroutine lattice_init
|
||||||
|
|
||||||
|
@ -989,7 +1042,7 @@ end subroutine lattice_init
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Calculation of Schmid matrices, etc.
|
!> @brief Calculation of Schmid matrices, etc.
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine lattice_initializeStructure(myPhase,CoverA)
|
subroutine lattice_initializeStructure(myPhase,CoverA,aA,aM,cM)
|
||||||
use prec, only: &
|
use prec, only: &
|
||||||
tol_math_check
|
tol_math_check
|
||||||
use math, only: &
|
use math, only: &
|
||||||
|
@ -1009,7 +1062,11 @@ subroutine lattice_initializeStructure(myPhase,CoverA)
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt), intent(in) :: myPhase
|
integer(pInt), intent(in) :: myPhase
|
||||||
real(pReal), intent(in) :: CoverA
|
real(pReal), intent(in) :: &
|
||||||
|
CoverA, &
|
||||||
|
aA, &
|
||||||
|
aM, &
|
||||||
|
cM
|
||||||
|
|
||||||
real(pReal), dimension(3) :: &
|
real(pReal), dimension(3) :: &
|
||||||
sdU, snU, &
|
sdU, snU, &
|
||||||
|
@ -1066,6 +1123,7 @@ subroutine lattice_initializeStructure(myPhase,CoverA)
|
||||||
enddo
|
enddo
|
||||||
lattice_NslipSystem(1:lattice_maxNslipFamily,myPhase) = lattice_fcc_NslipSystem
|
lattice_NslipSystem(1:lattice_maxNslipFamily,myPhase) = lattice_fcc_NslipSystem
|
||||||
lattice_NtwinSystem(1:lattice_maxNtwinFamily,myPhase) = lattice_fcc_NtwinSystem
|
lattice_NtwinSystem(1:lattice_maxNtwinFamily,myPhase) = lattice_fcc_NtwinSystem
|
||||||
|
lattice_NtransSystem(1:lattice_maxNtransFamily,myPhase) = lattice_fcc_NtransSystem
|
||||||
lattice_NnonSchmid(myPhase) = lattice_fcc_NnonSchmid
|
lattice_NnonSchmid(myPhase) = lattice_fcc_NnonSchmid
|
||||||
lattice_interactionSlipSlip(1:myNslip,1:myNslip,myPhase) = lattice_fcc_interactionSlipSlip
|
lattice_interactionSlipSlip(1:myNslip,1:myNslip,myPhase) = lattice_fcc_interactionSlipSlip
|
||||||
lattice_interactionSlipTwin(1:myNslip,1:myNtwin,myPhase) = lattice_fcc_interactionSlipTwin
|
lattice_interactionSlipTwin(1:myNslip,1:myNtwin,myPhase) = lattice_fcc_interactionSlipTwin
|
||||||
|
@ -1106,6 +1164,7 @@ subroutine lattice_initializeStructure(myPhase,CoverA)
|
||||||
enddo
|
enddo
|
||||||
lattice_NslipSystem(1:lattice_maxNslipFamily,myPhase) = lattice_bcc_NslipSystem
|
lattice_NslipSystem(1:lattice_maxNslipFamily,myPhase) = lattice_bcc_NslipSystem
|
||||||
lattice_NtwinSystem(1:lattice_maxNtwinFamily,myPhase) = lattice_bcc_NtwinSystem
|
lattice_NtwinSystem(1:lattice_maxNtwinFamily,myPhase) = lattice_bcc_NtwinSystem
|
||||||
|
lattice_NtransSystem(1:lattice_maxNtransFamily,myPhase) = lattice_bcc_NtransSystem
|
||||||
lattice_NnonSchmid(myPhase) = lattice_bcc_NnonSchmid
|
lattice_NnonSchmid(myPhase) = lattice_bcc_NnonSchmid
|
||||||
lattice_interactionSlipSlip(1:myNslip,1:myNslip,myPhase) = lattice_bcc_interactionSlipSlip
|
lattice_interactionSlipSlip(1:myNslip,1:myNslip,myPhase) = lattice_bcc_interactionSlipSlip
|
||||||
lattice_interactionSlipTwin(1:myNslip,1:myNtwin,myPhase) = lattice_bcc_interactionSlipTwin
|
lattice_interactionSlipTwin(1:myNslip,1:myNtwin,myPhase) = lattice_bcc_interactionSlipTwin
|
||||||
|
@ -1147,6 +1206,7 @@ subroutine lattice_initializeStructure(myPhase,CoverA)
|
||||||
enddo
|
enddo
|
||||||
lattice_NslipSystem(1:lattice_maxNslipFamily,myPhase) = lattice_hex_NslipSystem
|
lattice_NslipSystem(1:lattice_maxNslipFamily,myPhase) = lattice_hex_NslipSystem
|
||||||
lattice_NtwinSystem(1:lattice_maxNtwinFamily,myPhase) = lattice_hex_NtwinSystem
|
lattice_NtwinSystem(1:lattice_maxNtwinFamily,myPhase) = lattice_hex_NtwinSystem
|
||||||
|
lattice_NtransSystem(1:lattice_maxNtransFamily,myPhase) = lattice_hex_NtransSystem
|
||||||
lattice_NnonSchmid(myPhase) = lattice_hex_NnonSchmid
|
lattice_NnonSchmid(myPhase) = lattice_hex_NnonSchmid
|
||||||
lattice_interactionSlipSlip(1:myNslip,1:myNslip,myPhase) = lattice_hex_interactionSlipSlip
|
lattice_interactionSlipSlip(1:myNslip,1:myNslip,myPhase) = lattice_hex_interactionSlipSlip
|
||||||
lattice_interactionSlipTwin(1:myNslip,1:myNtwin,myPhase) = lattice_hex_interactionSlipTwin
|
lattice_interactionSlipTwin(1:myNslip,1:myNtwin,myPhase) = lattice_hex_interactionSlipTwin
|
||||||
|
|
Loading…
Reference in New Issue