cleaning
This commit is contained in:
parent
95826d094c
commit
0f106e77d9
|
@ -50,16 +50,11 @@ module lattice
|
||||||
lattice_Strans_v !< Eigendeformation tensor in vector form
|
lattice_Strans_v !< Eigendeformation tensor in vector form
|
||||||
|
|
||||||
real(pReal), allocatable, dimension(:,:), protected, public :: &
|
real(pReal), allocatable, dimension(:,:), protected, public :: &
|
||||||
lattice_shearTwin, & !< characteristic twin shear
|
|
||||||
lattice_shearTrans !< characteristic transformation shear
|
lattice_shearTrans !< characteristic transformation shear
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:), protected, public :: &
|
integer(pInt), allocatable, dimension(:), protected, public :: &
|
||||||
lattice_NnonSchmid !< total # of non-Schmid contributions for each structure
|
lattice_NnonSchmid !< total # of non-Schmid contributions for each structure
|
||||||
|
|
||||||
real(pReal), allocatable, dimension(:,:,:), private :: &
|
|
||||||
lattice_tn, &
|
|
||||||
lattice_td, &
|
|
||||||
lattice_tt
|
|
||||||
! END DEPRECATED
|
! END DEPRECATED
|
||||||
|
|
||||||
|
|
||||||
|
@ -1340,7 +1335,6 @@ subroutine lattice_init
|
||||||
|
|
||||||
allocate(lattice_Qtwin(3,3,lattice_maxNtwin,Nphases),source=0.0_pReal)
|
allocate(lattice_Qtwin(3,3,lattice_maxNtwin,Nphases),source=0.0_pReal)
|
||||||
|
|
||||||
allocate(lattice_shearTwin(lattice_maxNtwin,Nphases),source=0.0_pReal)
|
|
||||||
allocate(lattice_shearTrans(lattice_maxNtrans,Nphases),source=0.0_pReal)
|
allocate(lattice_shearTrans(lattice_maxNtrans,Nphases),source=0.0_pReal)
|
||||||
|
|
||||||
allocate(lattice_Qtrans(3,3,lattice_maxNtrans,Nphases),source=0.0_pReal)
|
allocate(lattice_Qtrans(3,3,lattice_maxNtrans,Nphases),source=0.0_pReal)
|
||||||
|
@ -1361,9 +1355,6 @@ subroutine lattice_init
|
||||||
allocate(a_fcc(Nphases),source=0.0_pReal)
|
allocate(a_fcc(Nphases),source=0.0_pReal)
|
||||||
allocate(a_bcc(Nphases),source=0.0_pReal)
|
allocate(a_bcc(Nphases),source=0.0_pReal)
|
||||||
|
|
||||||
allocate(lattice_td(3,lattice_maxNtwin,Nphases),source=0.0_pReal)
|
|
||||||
allocate(lattice_tt(3,lattice_maxNtwin,Nphases),source=0.0_pReal)
|
|
||||||
allocate(lattice_tn(3,lattice_maxNtwin,Nphases),source=0.0_pReal)
|
|
||||||
allocate(lattice_sd(3,lattice_maxNslip,Nphases),source=0.0_pReal)
|
allocate(lattice_sd(3,lattice_maxNslip,Nphases),source=0.0_pReal)
|
||||||
allocate(lattice_st(3,lattice_maxNslip,Nphases),source=0.0_pReal)
|
allocate(lattice_st(3,lattice_maxNslip,Nphases),source=0.0_pReal)
|
||||||
allocate(lattice_sn(3,lattice_maxNslip,Nphases),source=0.0_pReal)
|
allocate(lattice_sn(3,lattice_maxNslip,Nphases),source=0.0_pReal)
|
||||||
|
@ -1518,8 +1509,6 @@ subroutine lattice_initializeStructure(myPhase,CoverA,CoverA_trans,a_fcc,a_bcc)
|
||||||
sns
|
sns
|
||||||
real(pReal), dimension(3,lattice_maxNtwin) :: &
|
real(pReal), dimension(3,lattice_maxNtwin) :: &
|
||||||
td, tn
|
td, tn
|
||||||
real(pReal), dimension(lattice_maxNtwin) :: &
|
|
||||||
ts
|
|
||||||
real(pReal), dimension(lattice_maxNtrans) :: &
|
real(pReal), dimension(lattice_maxNtrans) :: &
|
||||||
trs
|
trs
|
||||||
real(pReal), dimension(3,lattice_maxNtrans) :: &
|
real(pReal), dimension(3,lattice_maxNtrans) :: &
|
||||||
|
@ -1622,9 +1611,7 @@ subroutine lattice_initializeStructure(myPhase,CoverA,CoverA_trans,a_fcc,a_bcc)
|
||||||
sn(1:3,i) = lattice_fcc_systemSlip(4:6,i)
|
sn(1:3,i) = lattice_fcc_systemSlip(4:6,i)
|
||||||
enddo
|
enddo
|
||||||
do i = 1_pInt,myNtwin ! assign twin system vectors and shears
|
do i = 1_pInt,myNtwin ! assign twin system vectors and shears
|
||||||
td(1:3,i) = lattice_fcc_systemTwin(1:3,i)
|
|
||||||
tn(1:3,i) = lattice_fcc_systemTwin(4:6,i)
|
tn(1:3,i) = lattice_fcc_systemTwin(4:6,i)
|
||||||
ts(i) = lattice_fcc_shearTwin(i)
|
|
||||||
enddo
|
enddo
|
||||||
do i = 1_pInt, myNcleavage ! assign cleavage system vectors
|
do i = 1_pInt, myNcleavage ! assign cleavage system vectors
|
||||||
cd(1:3,i) = lattice_fcc_systemCleavage(1:3,i)/norm2(lattice_fcc_systemCleavage(1:3,i))
|
cd(1:3,i) = lattice_fcc_systemCleavage(1:3,i)/norm2(lattice_fcc_systemCleavage(1:3,i))
|
||||||
|
@ -1716,9 +1703,7 @@ subroutine lattice_initializeStructure(myPhase,CoverA,CoverA_trans,a_fcc,a_bcc)
|
||||||
sns(1:3,1:3,2,6,i) = math_tensorproduct33(-sdU, -sdU)
|
sns(1:3,1:3,2,6,i) = math_tensorproduct33(-sdU, -sdU)
|
||||||
enddo
|
enddo
|
||||||
do i = 1_pInt,myNtwin ! assign twin system vectors and shears
|
do i = 1_pInt,myNtwin ! assign twin system vectors and shears
|
||||||
td(1:3,i) = lattice_bcc_systemTwin(1:3,i)
|
|
||||||
tn(1:3,i) = lattice_bcc_systemTwin(4:6,i)
|
tn(1:3,i) = lattice_bcc_systemTwin(4:6,i)
|
||||||
ts(i) = lattice_bcc_shearTwin(i)
|
|
||||||
enddo
|
enddo
|
||||||
do i = 1_pInt, myNcleavage ! assign cleavage system vectors
|
do i = 1_pInt, myNcleavage ! assign cleavage system vectors
|
||||||
cd(1:3,i) = lattice_bcc_systemCleavage(1:3,i)/norm2(lattice_bcc_systemCleavage(1:3,i))
|
cd(1:3,i) = lattice_bcc_systemCleavage(1:3,i)/norm2(lattice_bcc_systemCleavage(1:3,i))
|
||||||
|
@ -1749,23 +1734,9 @@ subroutine lattice_initializeStructure(myPhase,CoverA,CoverA_trans,a_fcc,a_bcc)
|
||||||
sn(3,i) = lattice_hex_systemSlip(8,i)/CoverA
|
sn(3,i) = lattice_hex_systemSlip(8,i)/CoverA
|
||||||
enddo
|
enddo
|
||||||
do i = 1_pInt,myNtwin ! assign twin system vectors and shears
|
do i = 1_pInt,myNtwin ! assign twin system vectors and shears
|
||||||
td(1,i) = lattice_hex_systemTwin(1,i)*1.5_pReal
|
|
||||||
td(2,i) = (lattice_hex_systemTwin(1,i)+2.0_pReal*lattice_hex_systemTwin(2,i))*&
|
|
||||||
0.5_pReal*sqrt(3.0_pReal)
|
|
||||||
td(3,i) = lattice_hex_systemTwin(4,i)*CoverA
|
|
||||||
tn(1,i) = lattice_hex_systemTwin(5,i)
|
tn(1,i) = lattice_hex_systemTwin(5,i)
|
||||||
tn(2,i) = (lattice_hex_systemTwin(5,i)+2.0_pReal*lattice_hex_systemTwin(6,i))/sqrt(3.0_pReal)
|
tn(2,i) = (lattice_hex_systemTwin(5,i)+2.0_pReal*lattice_hex_systemTwin(6,i))/sqrt(3.0_pReal)
|
||||||
tn(3,i) = lattice_hex_systemTwin(8,i)/CoverA
|
tn(3,i) = lattice_hex_systemTwin(8,i)/CoverA
|
||||||
select case(lattice_hex_shearTwin(i)) ! from Christian & Mahajan 1995 p.29
|
|
||||||
case (1_pInt) ! <-10.1>{10.2}
|
|
||||||
ts(i) = (3.0_pReal-CoverA*CoverA)/sqrt(3.0_pReal)/CoverA
|
|
||||||
case (2_pInt) ! <11.6>{-1-1.1}
|
|
||||||
ts(i) = 1.0_pReal/CoverA
|
|
||||||
case (3_pInt) ! <10.-2>{10.1}
|
|
||||||
ts(i) = (4.0_pReal*CoverA*CoverA-9.0_pReal)/4.0_pReal/sqrt(3.0_pReal)/CoverA
|
|
||||||
case (4_pInt) ! <11.-3>{11.2}
|
|
||||||
ts(i) = 2.0_pReal*(CoverA*CoverA-2.0_pReal)/3.0_pReal/CoverA
|
|
||||||
end select
|
|
||||||
enddo
|
enddo
|
||||||
do i = 1_pInt, myNcleavage ! cleavage system vectors
|
do i = 1_pInt, myNcleavage ! cleavage system vectors
|
||||||
cd(1,i) = lattice_hex_systemCleavage(1,i)*1.5_pReal ! direction [uvtw]->[3u/2 (u+2v)*sqrt(3)/2 w*(c/a)]
|
cd(1,i) = lattice_hex_systemCleavage(1,i)*1.5_pReal ! direction [uvtw]->[3u/2 (u+2v)*sqrt(3)/2 w*(c/a)]
|
||||||
|
@ -1861,9 +1832,7 @@ subroutine lattice_initializeStructure(myPhase,CoverA,CoverA_trans,a_fcc,a_bcc)
|
||||||
call IO_error(0_pInt,myPhase,i,0_pInt,ext_msg = 'dilatational slip Schmid matrix')
|
call IO_error(0_pInt,myPhase,i,0_pInt,ext_msg = 'dilatational slip Schmid matrix')
|
||||||
enddo
|
enddo
|
||||||
do i = 1_pInt,myNtwin ! store twin system vectors and Schmid plus rotation matrix for my structure
|
do i = 1_pInt,myNtwin ! store twin system vectors and Schmid plus rotation matrix for my structure
|
||||||
lattice_tn(1:3,i,myPhase) = tn(1:3,i)/norm2(tn(1:3,i)) ! make unit vector
|
|
||||||
lattice_Qtwin(1:3,1:3,i,myPhase) = math_axisAngleToR(tn(1:3,i),180.0_pReal*INRAD)
|
lattice_Qtwin(1:3,1:3,i,myPhase) = math_axisAngleToR(tn(1:3,i),180.0_pReal*INRAD)
|
||||||
lattice_shearTwin(i,myPhase) = ts(i)
|
|
||||||
enddo
|
enddo
|
||||||
do i = 1_pInt,myNtrans
|
do i = 1_pInt,myNtrans
|
||||||
lattice_Qtrans(1:3,1:3,i,myPhase) = Qtr(1:3,1:3,i)
|
lattice_Qtrans(1:3,1:3,i,myPhase) = Qtr(1:3,1:3,i)
|
||||||
|
@ -2181,7 +2150,7 @@ function lattice_C66_twin(Ntwin,C66,structure,CoverA)
|
||||||
lattice_C66_twin(1:6,1:6,i) = math_Mandel3333to66(math_rotate_forward3333(math_Mandel66to3333(C66),R))
|
lattice_C66_twin(1:6,1:6,i) = math_Mandel3333to66(math_rotate_forward3333(math_Mandel66to3333(C66),R))
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end function
|
end function lattice_C66_twin
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -2716,11 +2685,11 @@ function lattice_SchmidMatrix_cleavage(Ncleavage,structure,cOverA) result(Schmid
|
||||||
|
|
||||||
coordinateSystem = buildCoordinateSystem(Ncleavage,NcleavageMax,cleavageSystems,structure,cOverA)
|
coordinateSystem = buildCoordinateSystem(Ncleavage,NcleavageMax,cleavageSystems,structure,cOverA)
|
||||||
|
|
||||||
do i = 1, sum(Ncleavage)
|
do i = 1, sum(Ncleavage)
|
||||||
SchmidMatrix(1:3,1:3,1,i) = math_tensorproduct33(coordinateSystem(1:3,1,i),coordinateSystem(1:3,2,i))
|
SchmidMatrix(1:3,1:3,1,i) = math_tensorproduct33(coordinateSystem(1:3,1,i),coordinateSystem(1:3,2,i))
|
||||||
SchmidMatrix(1:3,1:3,2,i) = math_tensorproduct33(coordinateSystem(1:3,3,i),coordinateSystem(1:3,2,i))
|
SchmidMatrix(1:3,1:3,2,i) = math_tensorproduct33(coordinateSystem(1:3,3,i),coordinateSystem(1:3,2,i))
|
||||||
SchmidMatrix(1:3,1:3,3,i) = math_tensorproduct33(coordinateSystem(1:3,2,i),coordinateSystem(1:3,2,i))
|
SchmidMatrix(1:3,1:3,3,i) = math_tensorproduct33(coordinateSystem(1:3,2,i),coordinateSystem(1:3,2,i))
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end function lattice_SchmidMatrix_cleavage
|
end function lattice_SchmidMatrix_cleavage
|
||||||
|
|
||||||
|
|
|
@ -239,7 +239,7 @@ subroutine plastic_dislotwin_init(fileUnit)
|
||||||
integer(pInt) :: sizeState, sizeDotState
|
integer(pInt) :: sizeState, sizeDotState
|
||||||
integer(pInt) :: NipcMyPhase
|
integer(pInt) :: NipcMyPhase
|
||||||
|
|
||||||
real(pReal), allocatable, dimension(:,:) :: temp1,temp2
|
real(pReal), allocatable, dimension(:,:) :: temp1
|
||||||
|
|
||||||
integer(pInt), dimension(0), parameter :: emptyIntArray = [integer(pInt)::]
|
integer(pInt), dimension(0), parameter :: emptyIntArray = [integer(pInt)::]
|
||||||
real(pReal), dimension(0), parameter :: emptyRealArray = [real(pReal)::]
|
real(pReal), dimension(0), parameter :: emptyRealArray = [real(pReal)::]
|
||||||
|
@ -371,6 +371,9 @@ subroutine plastic_dislotwin_init(fileUnit)
|
||||||
prm%Cthresholdtwin = config_phase(p)%getFloat('cthresholdtwin', defaultVal=0.0_pReal)
|
prm%Cthresholdtwin = config_phase(p)%getFloat('cthresholdtwin', defaultVal=0.0_pReal)
|
||||||
prm%Cmfptwin = config_phase(p)%getFloat('cmfptwin', defaultVal=0.0_pReal) ! ToDo: How to handle that???
|
prm%Cmfptwin = config_phase(p)%getFloat('cmfptwin', defaultVal=0.0_pReal) ! ToDo: How to handle that???
|
||||||
|
|
||||||
|
prm%shear_twin = lattice_characteristicShear_Twin(prm%Ntwin,structure(1:3),&
|
||||||
|
config_phase(p)%getFloat('c/a',defaultVal=0.0_pReal))
|
||||||
|
|
||||||
|
|
||||||
if (.not. prm%isFCC) then
|
if (.not. prm%isFCC) then
|
||||||
prm%Ndot0_twin = config_phase(p)%getFloats('ndot0_twin')
|
prm%Ndot0_twin = config_phase(p)%getFloats('ndot0_twin')
|
||||||
|
@ -627,13 +630,11 @@ subroutine plastic_dislotwin_init(fileUnit)
|
||||||
allocate(prm%C66_twin(6,6,prm%totalNtwin), source=0.0_pReal)
|
allocate(prm%C66_twin(6,6,prm%totalNtwin), source=0.0_pReal)
|
||||||
if (lattice_structure(p) == LATTICE_fcc_ID) &
|
if (lattice_structure(p) == LATTICE_fcc_ID) &
|
||||||
allocate(prm%fcc_twinNucleationSlipPair(2,prm%totalNtwin),source = 0_pInt)
|
allocate(prm%fcc_twinNucleationSlipPair(2,prm%totalNtwin),source = 0_pInt)
|
||||||
allocate(prm%shear_twin(prm%totalNtwin),source = 0.0_pReal)
|
|
||||||
i = 0_pInt
|
i = 0_pInt
|
||||||
twinFamiliesLoop: do f = 1_pInt, size(prm%Ntwin,1)
|
twinFamiliesLoop: do f = 1_pInt, size(prm%Ntwin,1)
|
||||||
index_myFamily = sum(prm%Ntwin(1:f-1_pInt)) ! index in truncated twin system list
|
index_myFamily = sum(prm%Ntwin(1:f-1_pInt)) ! index in truncated twin system list
|
||||||
twinSystemsLoop: do j = 1_pInt,prm%Ntwin(f)
|
twinSystemsLoop: do j = 1_pInt,prm%Ntwin(f)
|
||||||
i = i + 1_pInt
|
i = i + 1_pInt
|
||||||
prm%shear_twin(i) = lattice_shearTwin(sum(lattice_Ntwinsystem(1:f-1,p))+j,p)
|
|
||||||
if (lattice_structure(p) == LATTICE_fcc_ID) prm%fcc_twinNucleationSlipPair(1:2,i) = &
|
if (lattice_structure(p) == LATTICE_fcc_ID) prm%fcc_twinNucleationSlipPair(1:2,i) = &
|
||||||
lattice_fcc_twinNucleationSlipPair(1:2,sum(lattice_Ntwinsystem(1:f-1,p))+j)
|
lattice_fcc_twinNucleationSlipPair(1:2,sum(lattice_Ntwinsystem(1:f-1,p))+j)
|
||||||
!* Rotate twin elasticity matrices
|
!* Rotate twin elasticity matrices
|
||||||
|
@ -644,7 +645,7 @@ subroutine plastic_dislotwin_init(fileUnit)
|
||||||
enddo twinSystemsLoop
|
enddo twinSystemsLoop
|
||||||
enddo twinFamiliesLoop
|
enddo twinFamiliesLoop
|
||||||
|
|
||||||
|
|
||||||
allocate(temp1(prm%totalNtrans,prm%totalNslip), source =0.0_pReal)
|
allocate(temp1(prm%totalNtrans,prm%totalNslip), source =0.0_pReal)
|
||||||
allocate(prm%C66_trans(6,6,prm%totalNtrans) ,source=0.0_pReal)
|
allocate(prm%C66_trans(6,6,prm%totalNtrans) ,source=0.0_pReal)
|
||||||
allocate(prm%Schmid_trans(3,3,prm%totalNtrans),source = 0.0_pReal)
|
allocate(prm%Schmid_trans(3,3,prm%totalNtrans),source = 0.0_pReal)
|
||||||
|
|
Loading…
Reference in New Issue