change latticeName to latticeID
This commit is contained in:
parent
6c2ab1f1f8
commit
0bc99a9622
|
@ -28,6 +28,8 @@ module constitutive_dislotwin
|
|||
use prec, only: &
|
||||
pReal, &
|
||||
pInt
|
||||
use lattice, only: &
|
||||
LATTICE_iso_ID
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
@ -36,8 +38,8 @@ module constitutive_dislotwin
|
|||
constitutive_dislotwin_sizeState, & !< total number of microstructural state variables
|
||||
constitutive_dislotwin_sizePostResults !< cumulative size of post results
|
||||
|
||||
character(len=32), dimension(:), allocatable, public, protected :: &
|
||||
constitutive_dislotwin_structureName !< name of the lattice structure
|
||||
integer(kind(LATTICE_iso_ID)), dimension(:), allocatable, public :: &
|
||||
constitutive_dislotwin_structureID !< ID of the lattice structure !< name of the lattice structure
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
constitutive_dislotwin_sizePostResult !< size of each post result output
|
||||
|
@ -227,8 +229,8 @@ subroutine constitutive_dislotwin_init(file)
|
|||
allocate(constitutive_dislotwin_Noutput(maxNinstance))
|
||||
constitutive_dislotwin_Noutput = 0_pInt
|
||||
|
||||
allocate(constitutive_dislotwin_structureName(maxNinstance))
|
||||
constitutive_dislotwin_structureName = ''
|
||||
allocate(constitutive_dislotwin_structureID(maxNinstance))
|
||||
constitutive_dislotwin_structureID = -1
|
||||
allocate(constitutive_dislotwin_structure(maxNinstance))
|
||||
constitutive_dislotwin_structure = 0_pInt
|
||||
allocate(constitutive_dislotwin_Nslip(lattice_maxNslipFamily,maxNinstance))
|
||||
|
@ -348,8 +350,19 @@ subroutine constitutive_dislotwin_init(file)
|
|||
constitutive_dislotwin_Noutput(i) = constitutive_dislotwin_Noutput(i) + 1_pInt
|
||||
constitutive_dislotwin_output(constitutive_dislotwin_Noutput(i),i) = IO_lc(IO_stringValue(line,positions,2_pInt))
|
||||
case ('lattice_structure')
|
||||
constitutive_dislotwin_structureName(i) = IO_lc(IO_stringValue(line,positions,2_pInt))
|
||||
configNchunks = lattice_configNchunks(constitutive_dislotwin_structureName(i))
|
||||
select case(IO_lc(IO_stringValue(line,positions,2_pInt)))
|
||||
case(LATTICE_iso_label)
|
||||
constitutive_dislotwin_structureID(i) = LATTICE_iso_ID
|
||||
case(LATTICE_fcc_label)
|
||||
constitutive_dislotwin_structureID(i) = LATTICE_fcc_ID
|
||||
case(LATTICE_bcc_label)
|
||||
constitutive_dislotwin_structureID(i) = LATTICE_bcc_ID
|
||||
case(LATTICE_hex_label)
|
||||
constitutive_dislotwin_structureID(i) = LATTICE_hex_ID
|
||||
case(LATTICE_ort_label)
|
||||
constitutive_dislotwin_structureID(i) = LATTICE_ort_ID
|
||||
end select
|
||||
configNchunks = lattice_configNchunks(constitutive_dislotwin_structureID(i))
|
||||
Nchunks_SlipFamilies = configNchunks(1)
|
||||
Nchunks_TwinFamilies = configNchunks(2)
|
||||
Nchunks_SlipSlip = configNchunks(3)
|
||||
|
@ -503,7 +516,7 @@ subroutine constitutive_dislotwin_init(file)
|
|||
|
||||
sanityChecks: do i = 1_pInt,maxNinstance
|
||||
constitutive_dislotwin_structure(i) = &
|
||||
lattice_initializeStructure(constitutive_dislotwin_structureName(i),constitutive_dislotwin_CoverA(i))
|
||||
lattice_initializeStructure(constitutive_dislotwin_structureID(i),constitutive_dislotwin_CoverA(i))
|
||||
structID = constitutive_dislotwin_structure(i)
|
||||
|
||||
if (structID < 1_pInt) call IO_error(205_pInt,el=i)
|
||||
|
@ -652,7 +665,7 @@ subroutine constitutive_dislotwin_init(file)
|
|||
|
||||
|
||||
!* Elasticity matrix and shear modulus according to material.config
|
||||
constitutive_dislotwin_Cslip_66(1:6,1:6,i) = lattice_symmetrizeC66(constitutive_dislotwin_structureName(i),&
|
||||
constitutive_dislotwin_Cslip_66(1:6,1:6,i) = lattice_symmetrizeC66(constitutive_dislotwin_structureID(i),&
|
||||
constitutive_dislotwin_Cslip_66(:,:,i))
|
||||
constitutive_dislotwin_Gmod(i) = &
|
||||
0.2_pReal*(constitutive_dislotwin_Cslip_66(1,1,i)-constitutive_dislotwin_Cslip_66(1,2,i)) &
|
||||
|
@ -1097,7 +1110,8 @@ subroutine constitutive_dislotwin_LpAndItsTangent(Lp,dLp_dTstar,Tstar_v,Temperat
|
|||
lattice_NslipSystem, &
|
||||
lattice_NtwinSystem, &
|
||||
lattice_shearTwin, &
|
||||
lattice_fcc_corellationTwinSlip
|
||||
lattice_fcc_corellationTwinSlip, &
|
||||
LATTICE_fcc_ID
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: ipc,ip,el
|
||||
|
@ -1261,8 +1275,8 @@ subroutine constitutive_dislotwin_LpAndItsTangent(Lp,dLp_dTstar,Tstar_v,Temperat
|
|||
|
||||
!* Shear rates and their derivatives due to twin
|
||||
if ( tau_twin(j) > 0.0_pReal ) then
|
||||
select case(constitutive_dislotwin_structureName(matID))
|
||||
case ('fcc')
|
||||
select case(constitutive_dislotwin_structureID(matID))
|
||||
case (LATTICE_fcc_ID)
|
||||
s1=lattice_fcc_corellationTwinSlip(1,index_myFamily+i)
|
||||
s2=lattice_fcc_corellationTwinSlip(2,index_myFamily+i)
|
||||
if (tau_twin(j) < constitutive_dislotwin_tau_r(j,matID)) then
|
||||
|
@ -1304,14 +1318,27 @@ end subroutine constitutive_dislotwin_LpAndItsTangent
|
|||
!> @brief calculates the rate of change of microstructure
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
pure function constitutive_dislotwin_dotState(Tstar_v,Temperature,state,ipc,ip,el)
|
||||
use prec, only: p_vec
|
||||
|
||||
use math, only: pi
|
||||
use mesh, only: mesh_NcpElems, mesh_maxNips
|
||||
use material, only: homogenization_maxNgrains, material_phase, phase_plasticityInstance
|
||||
use lattice, only: lattice_Sslip_v, lattice_Stwin_v, &
|
||||
lattice_maxNslipFamily,lattice_maxNtwinFamily, &
|
||||
lattice_NslipSystem, lattice_NtwinSystem, lattice_sheartwin, lattice_fcc_corellationTwinSlip
|
||||
use prec, only: &
|
||||
p_vec
|
||||
use math, only: &
|
||||
pi
|
||||
use mesh, only: &
|
||||
mesh_NcpElems, &
|
||||
mesh_maxNips
|
||||
use material, only: &
|
||||
homogenization_maxNgrains, &
|
||||
material_phase, &
|
||||
phase_plasticityInstance
|
||||
use lattice, only: &
|
||||
lattice_Sslip_v, &
|
||||
lattice_Stwin_v, &
|
||||
lattice_maxNslipFamily, &
|
||||
lattice_maxNtwinFamily, &
|
||||
lattice_NslipSystem, &
|
||||
lattice_NtwinSystem, &
|
||||
lattice_sheartwin, &
|
||||
lattice_fcc_corellationTwinSlip, &
|
||||
LATTICE_fcc_ID
|
||||
|
||||
implicit none
|
||||
real(pReal), dimension(6), intent(in):: &
|
||||
|
@ -1447,8 +1474,8 @@ pure function constitutive_dislotwin_dotState(Tstar_v,Temperature,state,ipc,ip,e
|
|||
|
||||
!* Shear rates and their derivatives due to twin
|
||||
if ( tau_twin(j) > 0.0_pReal ) then
|
||||
select case(constitutive_dislotwin_structureName(matID))
|
||||
case ('fcc')
|
||||
select case(constitutive_dislotwin_structureID(matID))
|
||||
case (LATTICE_fcc_ID)
|
||||
s1=lattice_fcc_corellationTwinSlip(1,index_myFamily+i)
|
||||
s2=lattice_fcc_corellationTwinSlip(2,index_myFamily+i)
|
||||
if (tau_twin(j) < constitutive_dislotwin_tau_r(j,matID)) then
|
||||
|
@ -1505,7 +1532,8 @@ function constitutive_dislotwin_postResults(Tstar_v,Temperature,state,ipc,ip,el)
|
|||
lattice_NslipSystem, &
|
||||
lattice_NtwinSystem, &
|
||||
lattice_shearTwin, &
|
||||
lattice_fcc_corellationTwinSlip
|
||||
lattice_fcc_corellationTwinSlip, &
|
||||
LATTICE_fcc_ID
|
||||
|
||||
implicit none
|
||||
real(pReal), dimension(6), intent(in) :: &
|
||||
|
@ -1688,8 +1716,8 @@ function constitutive_dislotwin_postResults(Tstar_v,Temperature,state,ipc,ip,el)
|
|||
|
||||
!* Shear rates due to twin
|
||||
if ( tau > 0.0_pReal ) then
|
||||
select case(constitutive_dislotwin_structureName(matID))
|
||||
case ('fcc')
|
||||
select case(constitutive_dislotwin_structureID(matID))
|
||||
case (LATTICE_fcc_ID)
|
||||
s1=lattice_fcc_corellationTwinSlip(1,index_myFamily+i)
|
||||
s2=lattice_fcc_corellationTwinSlip(2,index_myFamily+i)
|
||||
if (tau < constitutive_dislotwin_tau_r(j,matID)) then
|
||||
|
|
|
@ -30,6 +30,8 @@ module constitutive_j2
|
|||
use prec, only: &
|
||||
pReal,&
|
||||
pInt
|
||||
use lattice, only: &
|
||||
LATTICE_iso_ID
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
@ -44,8 +46,8 @@ module constitutive_j2
|
|||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
constitutive_j2_output !< name of each post result output
|
||||
|
||||
character(len=32), dimension(:), allocatable, private :: &
|
||||
constitutive_j2_structureName !< name of the lattice structure
|
||||
integer(kind(LATTICE_iso_ID)), dimension(:), allocatable, public :: &
|
||||
constitutive_j2_structureID !< ID of the lattice structure
|
||||
|
||||
integer(pInt), dimension(:), allocatable, private :: &
|
||||
constitutive_j2_Noutput !< number of outputs per instance
|
||||
|
@ -108,8 +110,7 @@ subroutine constitutive_j2_init(myFile)
|
|||
debug_level, &
|
||||
debug_constitutive, &
|
||||
debug_levelBasic
|
||||
use lattice, only: &
|
||||
lattice_symmetrizeC66
|
||||
use lattice
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: myFile
|
||||
|
@ -145,8 +146,8 @@ subroutine constitutive_j2_init(myFile)
|
|||
constitutive_j2_output = ''
|
||||
allocate(constitutive_j2_Noutput(maxNinstance))
|
||||
constitutive_j2_Noutput = 0_pInt
|
||||
allocate(constitutive_j2_structureName(maxNinstance))
|
||||
constitutive_j2_structureName = ''
|
||||
allocate(constitutive_j2_structureID(maxNinstance))
|
||||
constitutive_j2_structureID = -1
|
||||
allocate(constitutive_j2_Cslip_66(6,6,maxNinstance))
|
||||
constitutive_j2_Cslip_66 = 0.0_pReal
|
||||
allocate(constitutive_j2_fTaylor(maxNinstance))
|
||||
|
@ -202,7 +203,18 @@ subroutine constitutive_j2_init(myFile)
|
|||
constitutive_j2_output(constitutive_j2_Noutput(i),i) = &
|
||||
IO_lc(IO_stringValue(line,positions,2_pInt))
|
||||
case ('lattice_structure')
|
||||
constitutive_j2_structureName(i) = IO_lc(IO_stringValue(line,positions,2_pInt))
|
||||
select case(IO_lc(IO_stringValue(line,positions,2_pInt)))
|
||||
case(LATTICE_iso_label)
|
||||
constitutive_j2_structureID(i) = LATTICE_iso_ID
|
||||
case(LATTICE_fcc_label)
|
||||
constitutive_j2_structureID(i) = LATTICE_fcc_ID
|
||||
case(LATTICE_bcc_label)
|
||||
constitutive_j2_structureID(i) = LATTICE_bcc_ID
|
||||
case(LATTICE_hex_label)
|
||||
constitutive_j2_structureID(i) = LATTICE_hex_ID
|
||||
case(LATTICE_ort_label)
|
||||
constitutive_j2_structureID(i) = LATTICE_ort_ID
|
||||
end select
|
||||
case ('c11')
|
||||
constitutive_j2_Cslip_66(1,1,i) = IO_floatValue(line,positions,2_pInt)
|
||||
case ('c12')
|
||||
|
@ -255,7 +267,6 @@ subroutine constitutive_j2_init(myFile)
|
|||
enddo
|
||||
|
||||
sanityChecks: do i = 1_pInt,maxNinstance
|
||||
if (constitutive_j2_structureName(i) == '') call IO_error(205_pInt,el=i)
|
||||
if (constitutive_j2_tau0(i) < 0.0_pReal) call IO_error(211_pInt,ext_msg='tau0 (' &
|
||||
//PLASTICITY_J2_label//')')
|
||||
if (constitutive_j2_gdot0(i) <= 0.0_pReal) call IO_error(211_pInt,ext_msg='gdot0 (' &
|
||||
|
@ -293,7 +304,7 @@ subroutine constitutive_j2_init(myFile)
|
|||
constitutive_j2_sizeDotState(i) = 1_pInt
|
||||
constitutive_j2_sizeState(i) = 1_pInt
|
||||
|
||||
constitutive_j2_Cslip_66(1:6,1:6,i) = lattice_symmetrizeC66(constitutive_j2_structureName(i),&
|
||||
constitutive_j2_Cslip_66(1:6,1:6,i) = lattice_symmetrizeC66(constitutive_j2_structureID(i),&
|
||||
constitutive_j2_Cslip_66(1:6,1:6,i))
|
||||
constitutive_j2_Cslip_66(1:6,1:6,i) = &
|
||||
math_Mandel3333to66(math_Voigt66to3333(constitutive_j2_Cslip_66(1:6,1:6,i))) ! Literature data is Voigt, DAMASK uses Mandel
|
||||
|
|
|
@ -27,6 +27,8 @@ module constitutive_none
|
|||
use prec, only: &
|
||||
pReal, &
|
||||
pInt
|
||||
use lattice, only: &
|
||||
LATTICE_iso_ID
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
@ -38,8 +40,8 @@ module constitutive_none
|
|||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
constitutive_none_sizePostResult !< size of each post result output
|
||||
|
||||
character(len=32), dimension(:), allocatable, private :: &
|
||||
constitutive_none_structureName
|
||||
integer(kind(LATTICE_iso_ID)), dimension(:), allocatable, public :: &
|
||||
constitutive_none_structureID !< ID of the lattice structure
|
||||
|
||||
real(pReal), dimension(:,:,:), allocatable, private :: &
|
||||
constitutive_none_Cslip_66
|
||||
|
@ -75,8 +77,7 @@ subroutine constitutive_none_init(myFile)
|
|||
debug_level, &
|
||||
debug_constitutive, &
|
||||
debug_levelBasic
|
||||
use lattice, only: &
|
||||
lattice_symmetrizeC66
|
||||
use lattice
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: myFile
|
||||
|
@ -106,8 +107,8 @@ subroutine constitutive_none_init(myFile)
|
|||
constitutive_none_sizeState = 0_pInt
|
||||
allocate(constitutive_none_sizePostResults(maxNinstance))
|
||||
constitutive_none_sizePostResults = 0_pInt
|
||||
allocate(constitutive_none_structureName(maxNinstance))
|
||||
constitutive_none_structureName = ''
|
||||
allocate(constitutive_none_structureID(maxNinstance))
|
||||
constitutive_none_structureID = -1
|
||||
allocate(constitutive_none_Cslip_66(6,6,maxNinstance))
|
||||
constitutive_none_Cslip_66 = 0.0_pReal
|
||||
|
||||
|
@ -134,7 +135,18 @@ subroutine constitutive_none_init(myFile)
|
|||
case ('plasticity','elasticity')
|
||||
cycle
|
||||
case ('lattice_structure')
|
||||
constitutive_none_structureName(i) = IO_lc(IO_stringValue(line,positions,2_pInt))
|
||||
select case(IO_lc(IO_stringValue(line,positions,2_pInt)))
|
||||
case(LATTICE_iso_label)
|
||||
constitutive_none_structureID(i) = LATTICE_iso_ID
|
||||
case(LATTICE_fcc_label)
|
||||
constitutive_none_structureID(i) = LATTICE_fcc_ID
|
||||
case(LATTICE_bcc_label)
|
||||
constitutive_none_structureID(i) = LATTICE_bcc_ID
|
||||
case(LATTICE_hex_label)
|
||||
constitutive_none_structureID(i) = LATTICE_hex_ID
|
||||
case(LATTICE_ort_label)
|
||||
constitutive_none_structureID(i) = LATTICE_ort_ID
|
||||
end select
|
||||
case ('c11')
|
||||
constitutive_none_Cslip_66(1,1,i) = IO_floatValue(line,positions,2_pInt)
|
||||
case ('c12')
|
||||
|
@ -160,18 +172,14 @@ subroutine constitutive_none_init(myFile)
|
|||
endif
|
||||
enddo
|
||||
|
||||
do i = 1_pInt,maxNinstance
|
||||
if (constitutive_none_structureName(i) == '') call IO_error(205_pInt,el=i)
|
||||
enddo
|
||||
|
||||
instancesLoop: do i = 1_pInt,maxNinstance
|
||||
constitutive_none_sizeDotState(i) = 1_pInt
|
||||
constitutive_none_sizeState(i) = 1_pInt
|
||||
|
||||
constitutive_none_Cslip_66(:,:,i) = lattice_symmetrizeC66(constitutive_none_structureName(i),&
|
||||
constitutive_none_Cslip_66(:,:,i))
|
||||
constitutive_none_Cslip_66(:,:,i) = &
|
||||
math_Mandel3333to66(math_Voigt66to3333(constitutive_none_Cslip_66(:,:,i)))
|
||||
constitutive_none_Cslip_66(1:6,1:6,i) = lattice_symmetrizeC66(constitutive_none_structureID(i),&
|
||||
constitutive_none_Cslip_66(1:6,1:6,i))
|
||||
constitutive_none_Cslip_66(1:6,1:6,i) = &
|
||||
math_Mandel3333to66(math_Voigt66to3333(constitutive_none_Cslip_66(1:6,1:6,i)))
|
||||
|
||||
enddo instancesLoop
|
||||
|
||||
|
|
|
@ -29,6 +29,8 @@ use prec, only: &
|
|||
pReal, &
|
||||
pInt, &
|
||||
p_vec
|
||||
use lattice, only: &
|
||||
LATTICE_iso_ID
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
@ -92,8 +94,8 @@ iV, & !< state in
|
|||
iD !< state indices for stable dipole height
|
||||
|
||||
|
||||
character(len=32), dimension(:), allocatable, public :: &
|
||||
constitutive_nonlocal_structureName !< name of the lattice structure
|
||||
integer(kind(LATTICE_iso_ID)), dimension(:), allocatable, public :: &
|
||||
constitutive_nonlocal_structureID !< ID of the lattice structure
|
||||
|
||||
integer(pInt), dimension(:), allocatable, public :: &
|
||||
constitutive_nonlocal_structure !< number representing the kind of lattice structure
|
||||
|
@ -238,7 +240,6 @@ use material, only: homogenization_maxNgrains, &
|
|||
PLASTICITY_NONLOCAL_ID
|
||||
use lattice
|
||||
|
||||
!*** input variables
|
||||
integer(pInt), intent(in) :: myFile
|
||||
|
||||
!*** local variables
|
||||
|
@ -296,13 +297,13 @@ constitutive_nonlocal_sizePostResult = 0_pInt
|
|||
constitutive_nonlocal_output = ''
|
||||
Noutput = 0_pInt
|
||||
|
||||
allocate(constitutive_nonlocal_structureName(maxNmatIDs))
|
||||
allocate(constitutive_nonlocal_structureID(maxNmatIDs))
|
||||
allocate(constitutive_nonlocal_structure(maxNmatIDs))
|
||||
allocate(Nslip(lattice_maxNslipFamily, maxNmatIDs))
|
||||
allocate(slipFamily(lattice_maxNslip, maxNmatIDs))
|
||||
allocate(slipSystemLattice(lattice_maxNslip, maxNmatIDs))
|
||||
allocate(totalNslip(maxNmatIDs))
|
||||
constitutive_nonlocal_structureName = ''
|
||||
constitutive_nonlocal_structureID = -1
|
||||
constitutive_nonlocal_structure = 0_pInt
|
||||
Nslip = 0_pInt
|
||||
slipFamily = 0_pInt
|
||||
|
@ -428,8 +429,19 @@ do while (trim(line) /= '#EOF#')
|
|||
Noutput(i) = Noutput(i) + 1_pInt
|
||||
constitutive_nonlocal_output(Noutput(i),i) = IO_lc(IO_stringValue(line,positions,2_pInt))
|
||||
case ('lattice_structure')
|
||||
constitutive_nonlocal_structureName(i) = IO_lc(IO_stringValue(line,positions,2_pInt))
|
||||
configNchunks = lattice_configNchunks(constitutive_nonlocal_structureName(i))
|
||||
select case(IO_lc(IO_stringValue(line,positions,2_pInt)))
|
||||
case(LATTICE_iso_label)
|
||||
constitutive_nonlocal_structureID(i) = LATTICE_iso_ID
|
||||
case(LATTICE_fcc_label)
|
||||
constitutive_nonlocal_structureID(i) = LATTICE_fcc_ID
|
||||
case(LATTICE_bcc_label)
|
||||
constitutive_nonlocal_structureID(i) = LATTICE_bcc_ID
|
||||
case(LATTICE_hex_label)
|
||||
constitutive_nonlocal_structureID(i) = LATTICE_hex_ID
|
||||
case(LATTICE_ort_label)
|
||||
constitutive_nonlocal_structureID(i) = LATTICE_ort_ID
|
||||
end select
|
||||
configNchunks = lattice_configNchunks(constitutive_nonlocal_structureID(i))
|
||||
Nchunks_SlipFamilies = configNchunks(1)
|
||||
Nchunks_SlipSlip = configNchunks(3)
|
||||
Nchunks_nonSchmid = configNchunks(7)
|
||||
|
@ -585,7 +597,7 @@ enddo
|
|||
do i = 1_pInt,maxNmatIDs
|
||||
|
||||
constitutive_nonlocal_structure(i) = &
|
||||
lattice_initializeStructure(constitutive_nonlocal_structureName(i), CoverA(i)) ! our lattice structure is defined in the material.config file by the structureName (and the c/a ratio)
|
||||
lattice_initializeStructure(constitutive_nonlocal_structureID(i), CoverA(i)) ! our lattice structure is defined in the material.config file by the structureName (and the c/a ratio)
|
||||
structID = constitutive_nonlocal_structure(i)
|
||||
|
||||
|
||||
|
@ -944,7 +956,7 @@ do i = 1,maxNmatIDs
|
|||
|
||||
!*** elasticity matrix and shear modulus according to material.config
|
||||
|
||||
Cslip66(:,:,i) = lattice_symmetrizeC66(constitutive_nonlocal_structureName(i), Cslip66(:,:,i))
|
||||
Cslip66(:,:,i) = lattice_symmetrizeC66(constitutive_nonlocal_structureID(i), Cslip66(:,:,i))
|
||||
mu(i) = 0.2_pReal * ( Cslip66(1,1,i) - Cslip66(1,2,i) + 3.0_pReal*Cslip66(4,4,i)) ! (C11iso-C12iso)/2 with C11iso=(3*C11+2*C12+4*C44)/5 and C12iso=(C11+4*C12-2*C44)/5
|
||||
nu(i) = (Cslip66(1,1,i) + 4.0_pReal*Cslip66(1,2,i) - 2.0_pReal*Cslip66(4,4,i)) &
|
||||
/ (4.0_pReal*Cslip66(1,1,i) + 6.0_pReal*Cslip66(1,2,i) + 2.0_pReal*Cslip66(4,4,i)) ! C12iso/(C11iso+C12iso) with C11iso=(3*C11+2*C12+4*C44)/5 and C12iso=(C11+4*C12-2*C44)/5
|
||||
|
|
|
@ -28,6 +28,8 @@ module constitutive_phenopowerlaw
|
|||
use prec, only: &
|
||||
pReal,&
|
||||
pInt
|
||||
use lattice, only: &
|
||||
LATTICE_iso_ID
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
@ -43,8 +45,8 @@ module constitutive_phenopowerlaw
|
|||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
constitutive_phenopowerlaw_output !< name of each post result output
|
||||
|
||||
character(len=32), dimension(:), allocatable, public :: &
|
||||
constitutive_phenopowerlaw_structureName
|
||||
integer(kind(LATTICE_iso_ID)), dimension(:), allocatable, public :: &
|
||||
constitutive_phenopowerlaw_structureID !< ID of the lattice structure
|
||||
|
||||
integer(pInt), dimension(:), allocatable, private :: &
|
||||
constitutive_phenopowerlaw_Noutput, & !< number of outputs per instance of this constitution
|
||||
|
@ -189,8 +191,8 @@ subroutine constitutive_phenopowerlaw_init(myFile)
|
|||
constitutive_phenopowerlaw_outputID = -1
|
||||
allocate(constitutive_phenopowerlaw_Noutput(maxNinstance))
|
||||
constitutive_phenopowerlaw_Noutput = 0_pInt
|
||||
allocate(constitutive_phenopowerlaw_structureName(maxNinstance))
|
||||
constitutive_phenopowerlaw_structureName = ''
|
||||
allocate(constitutive_phenopowerlaw_structureID(maxNinstance))
|
||||
constitutive_phenopowerlaw_structureID = -1
|
||||
allocate(constitutive_phenopowerlaw_structure(maxNinstance))
|
||||
constitutive_phenopowerlaw_structure = 0_pInt
|
||||
allocate(constitutive_phenopowerlaw_Nslip(lattice_maxNslipFamily,maxNinstance))
|
||||
|
@ -303,8 +305,19 @@ subroutine constitutive_phenopowerlaw_init(myFile)
|
|||
constitutive_phenopowerlaw_outputID(constitutive_phenopowerlaw_Noutput(i),i) = totalvolfrac_ID
|
||||
end select
|
||||
case ('lattice_structure')
|
||||
constitutive_phenopowerlaw_structureName(i) = IO_lc(IO_stringValue(line,positions,2_pInt))
|
||||
configNchunks = lattice_configNchunks(constitutive_phenopowerlaw_structureName(i))
|
||||
select case(IO_lc(IO_stringValue(line,positions,2_pInt)))
|
||||
case(LATTICE_iso_label)
|
||||
constitutive_phenopowerlaw_structureID(i) = LATTICE_iso_ID
|
||||
case(LATTICE_fcc_label)
|
||||
constitutive_phenopowerlaw_structureID(i) = LATTICE_fcc_ID
|
||||
case(LATTICE_bcc_label)
|
||||
constitutive_phenopowerlaw_structureID(i) = LATTICE_bcc_ID
|
||||
case(LATTICE_hex_label)
|
||||
constitutive_phenopowerlaw_structureID(i) = LATTICE_hex_ID
|
||||
case(LATTICE_ort_label)
|
||||
constitutive_phenopowerlaw_structureID(i) = LATTICE_ort_ID
|
||||
end select
|
||||
configNchunks = lattice_configNchunks(constitutive_phenopowerlaw_structureID(i))
|
||||
Nchunks_SlipFamilies = configNchunks(1)
|
||||
Nchunks_TwinFamilies = configNchunks(2)
|
||||
Nchunks_SlipSlip = configNchunks(3)
|
||||
|
@ -450,7 +463,7 @@ subroutine constitutive_phenopowerlaw_init(myFile)
|
|||
|
||||
sanityChecks: do i = 1_pInt,maxNinstance
|
||||
constitutive_phenopowerlaw_structure(i) = &
|
||||
lattice_initializeStructure(constitutive_phenopowerlaw_structureName(i), constitutive_phenopowerlaw_CoverA(i)) ! get structure
|
||||
lattice_initializeStructure(constitutive_phenopowerlaw_structureID(i), constitutive_phenopowerlaw_CoverA(i)) ! get structure
|
||||
|
||||
constitutive_phenopowerlaw_Nslip(1:lattice_maxNslipFamily,i) = &
|
||||
min(lattice_NslipSystem(1:lattice_maxNslipFamily,constitutive_phenopowerlaw_structure(i)),& ! limit active slip systems per family to min of available and requested
|
||||
|
@ -550,11 +563,11 @@ subroutine constitutive_phenopowerlaw_init(myFile)
|
|||
|
||||
structID = constitutive_phenopowerlaw_structure(i)
|
||||
|
||||
constitutive_phenopowerlaw_Cslip_66(:,:,i) = &
|
||||
lattice_symmetrizeC66(constitutive_phenopowerlaw_structureName(i),&
|
||||
constitutive_phenopowerlaw_Cslip_66(1:6,1:6,i) = &
|
||||
lattice_symmetrizeC66(constitutive_phenopowerlaw_structureID(i),&
|
||||
constitutive_phenopowerlaw_Cslip_66(:,:,i)) ! assign elasticity tensor
|
||||
|
||||
constitutive_phenopowerlaw_Cslip_66(:,:,i) = &
|
||||
constitutive_phenopowerlaw_Cslip_66(1:6,1:6,i) = &
|
||||
math_Mandel3333to66(math_Voigt66to3333(constitutive_phenopowerlaw_Cslip_66(:,:,i)))
|
||||
|
||||
do f = 1_pInt,lattice_maxNslipFamily ! >>> interaction slip -- X
|
||||
|
|
|
@ -28,6 +28,8 @@ module constitutive_titanmod
|
|||
use prec, only: &
|
||||
pReal, &
|
||||
pInt
|
||||
use lattice, only: &
|
||||
LATTICE_iso_ID
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
@ -65,8 +67,8 @@ module constitutive_titanmod
|
|||
integer(pInt), dimension(:), allocatable, private :: &
|
||||
constitutive_titanmod_Noutput !< number of outputs per instance of this plasticity
|
||||
|
||||
character(len=32), dimension(:), allocatable, public, protected :: &
|
||||
constitutive_titanmod_structureName !< name of the lattice structure
|
||||
integer(kind(LATTICE_iso_ID)), dimension(:), allocatable, public :: &
|
||||
constitutive_titanmod_structureID !< ID of the lattice structure
|
||||
|
||||
integer(pInt), dimension(:), allocatable, private :: &
|
||||
constitutive_titanmod_structure, & !< number representing the kind of lattice structure
|
||||
|
@ -265,8 +267,8 @@ subroutine constitutive_titanmod_init(myFile)
|
|||
allocate(constitutive_titanmod_Noutput(maxNinstance))
|
||||
constitutive_titanmod_Noutput = 0_pInt
|
||||
|
||||
allocate(constitutive_titanmod_structureName(maxNinstance))
|
||||
constitutive_titanmod_structureName = ''
|
||||
allocate(constitutive_titanmod_structureID(maxNinstance))
|
||||
constitutive_titanmod_structureID= -1
|
||||
allocate(constitutive_titanmod_structure(maxNinstance))
|
||||
constitutive_titanmod_structure = 0_pInt
|
||||
allocate(constitutive_titanmod_Nslip(lattice_maxNslipFamily,maxNinstance))
|
||||
|
@ -413,8 +415,19 @@ subroutine constitutive_titanmod_init(myFile)
|
|||
constitutive_titanmod_Noutput(i) = constitutive_titanmod_Noutput(i) + 1_pInt
|
||||
constitutive_titanmod_output(constitutive_titanmod_Noutput(i),i) = IO_lc(IO_stringValue(line,positions,2_pInt))
|
||||
case ('lattice_structure')
|
||||
constitutive_titanmod_structureName(i) = IO_lc(IO_stringValue(line,positions,2_pInt))
|
||||
configNchunks = lattice_configNchunks(constitutive_titanmod_structureName(i))
|
||||
select case(IO_lc(IO_stringValue(line,positions,2_pInt)))
|
||||
case(LATTICE_iso_label)
|
||||
constitutive_titanmod_structureID(i) = LATTICE_iso_ID
|
||||
case(LATTICE_fcc_label)
|
||||
constitutive_titanmod_structureID(i) = LATTICE_fcc_ID
|
||||
case(LATTICE_bcc_label)
|
||||
constitutive_titanmod_structureID(i) = LATTICE_bcc_ID
|
||||
case(LATTICE_hex_label)
|
||||
constitutive_titanmod_structureID(i) = LATTICE_hex_ID
|
||||
case(LATTICE_ort_label)
|
||||
constitutive_titanmod_structureID(i) = LATTICE_ort_ID
|
||||
end select
|
||||
configNchunks = lattice_configNchunks(constitutive_titanmod_structureID(i))
|
||||
Nchunks_SlipFamilies = configNchunks(1)
|
||||
Nchunks_TwinFamilies = configNchunks(2)
|
||||
Nchunks_SlipSlip = configNchunks(3)
|
||||
|
@ -616,7 +629,7 @@ subroutine constitutive_titanmod_init(myFile)
|
|||
|
||||
sanityChecks: do i = 1_pInt,maxNinstance
|
||||
constitutive_titanmod_structure(i) = &
|
||||
lattice_initializeStructure(constitutive_titanmod_structureName(i),constitutive_titanmod_CoverA(i))
|
||||
lattice_initializeStructure(constitutive_titanmod_structureID(i),constitutive_titanmod_CoverA(i))
|
||||
structID = constitutive_titanmod_structure(i)
|
||||
|
||||
if (structID < 1_pInt) call IO_error(205_pInt,el=i)
|
||||
|
@ -838,7 +851,7 @@ subroutine constitutive_titanmod_init(myFile)
|
|||
enddo outputsLoop
|
||||
|
||||
constitutive_titanmod_Cslip_66(1:6,1:6,i) = &
|
||||
lattice_symmetrizeC66(constitutive_titanmod_structureName(i),&
|
||||
lattice_symmetrizeC66(constitutive_titanmod_structureID(i),&
|
||||
constitutive_titanmod_Cslip_66(1:6,1:6,i)) ! assign elasticity tensor
|
||||
constitutive_titanmod_Gmod(i) = &
|
||||
0.2_pReal*(constitutive_titanmod_Cslip_66(1,1,i)-constitutive_titanmod_Cslip_66(1,2,i))&
|
||||
|
|
|
@ -165,13 +165,13 @@ subroutine crystallite_init(temperature)
|
|||
use constitutive, only: &
|
||||
constitutive_microstructure
|
||||
use constitutive_phenopowerlaw, only: &
|
||||
constitutive_phenopowerlaw_structureName
|
||||
constitutive_phenopowerlaw_structureID
|
||||
use constitutive_dislotwin, only: &
|
||||
constitutive_dislotwin_structureName
|
||||
constitutive_dislotwin_structureID
|
||||
use constitutive_titanmod, only: &
|
||||
constitutive_titanmod_structureName
|
||||
constitutive_titanmod_structureID
|
||||
use constitutive_nonlocal, only: &
|
||||
constitutive_nonlocal_structureName
|
||||
constitutive_nonlocal_structureID
|
||||
|
||||
implicit none
|
||||
real(pReal), intent(in) :: temperature
|
||||
|
@ -368,16 +368,16 @@ subroutine crystallite_init(temperature)
|
|||
select case (phase_plasticity(myPhase))
|
||||
case (PLASTICITY_PHENOPOWERLAW_ID)
|
||||
crystallite_symmetryID(g,i,e) = &
|
||||
lattice_symmetryType(constitutive_phenopowerlaw_structureName(myMat))
|
||||
lattice_symmetryType(constitutive_phenopowerlaw_structureID(myMat))
|
||||
case (PLASTICITY_TITANMOD_ID)
|
||||
crystallite_symmetryID(g,i,e) = &
|
||||
lattice_symmetryType(constitutive_titanmod_structureName(myMat))
|
||||
lattice_symmetryType(constitutive_titanmod_structureID(myMat))
|
||||
case (PLASTICITY_DISLOTWIN_ID)
|
||||
crystallite_symmetryID(g,i,e) = &
|
||||
lattice_symmetryType(constitutive_dislotwin_structureName(myMat))
|
||||
lattice_symmetryType(constitutive_dislotwin_structureID(myMat))
|
||||
case (PLASTICITY_NONLOCAL_ID)
|
||||
crystallite_symmetryID(g,i,e) = &
|
||||
lattice_symmetryType(constitutive_nonlocal_structureName(myMat))
|
||||
lattice_symmetryType(constitutive_nonlocal_structureID(myMat))
|
||||
case default
|
||||
crystallite_symmetryID(g,i,e) = 0_pInt !< @ToDo: does this happen for j2 material?
|
||||
end select
|
||||
|
|
|
@ -500,7 +500,7 @@ module lattice
|
|||
1, -2, 1, 6, -1, 2, -1, 1, &
|
||||
1, 1, -2, 6, -1, -1, 2, 1, &
|
||||
!
|
||||
-1, 1, 0, -2, -1, 1, 0, 1, & !! <10.-2>{10.1} shear = (4(c/a)^2-9)/(4 sqrt(3) c/a)
|
||||
-1, 1, 0, -2, -1, 1, 0, 1, & !! <10.-2>{10.1} shear = (4(c/a)^2-9)/(4 sqrt(3) c/a)
|
||||
1, 0, -1, -2, 1, 0, -1, 1, &
|
||||
0, -1, 1, -2, 0, -1, 1, 1, &
|
||||
1, -1, 0, -2, 1, -1, 0, 1, &
|
||||
|
@ -690,15 +690,31 @@ module lattice
|
|||
20,20,20,20,20,20, 19,19,19,19,19,19, 18,18,18,18,18,18, 17,17,17,17,16,17, &
|
||||
20,20,20,20,20,20, 19,19,19,19,19,19, 18,18,18,18,18,18, 17,17,17,17,17,16 &
|
||||
],pInt),[lattice_hex_Ntwin,lattice_hex_Ntwin],order=[2,1]) !< Twin--slip interaction types for hex (isotropic, 16 in total)
|
||||
|
||||
|
||||
enum, bind(c)
|
||||
enumerator :: LATTICE_iso_ID, &
|
||||
LATTICE_fcc_ID, &
|
||||
LATTICE_bcc_ID, &
|
||||
LATTICE_hex_ID, &
|
||||
LATTICE_ort_ID
|
||||
end enum
|
||||
character(len=*), parameter, public :: &
|
||||
LATTICE_iso_label = 'iso', &
|
||||
LATTICE_fcc_label = 'fcc', &
|
||||
LATTICE_bcc_label = 'bcc', &
|
||||
LATTICE_hex_label = 'hex', &
|
||||
LATTICE_ort_label = 'ort'
|
||||
|
||||
public :: &
|
||||
lattice_init, &
|
||||
lattice_initializeStructure, &
|
||||
lattice_symmetryType, &
|
||||
lattice_symmetrizeC66, &
|
||||
lattice_configNchunks
|
||||
lattice_configNchunks, &
|
||||
LATTICE_iso_ID, &
|
||||
LATTICE_fcc_ID, &
|
||||
LATTICE_bcc_ID, &
|
||||
LATTICE_hex_ID, &
|
||||
LATTICE_ort_ID
|
||||
|
||||
contains
|
||||
|
||||
|
@ -732,9 +748,8 @@ subroutine lattice_init
|
|||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||
#include "compilation_info.f90"
|
||||
|
||||
if (.not. IO_open_jobFile_stat(fileunit,material_localFileExt)) then ! no local material configuration present...
|
||||
if (.not. IO_open_jobFile_stat(fileunit,material_localFileExt)) & ! no local material configuration present...
|
||||
call IO_open_file(fileunit,material_configFile) ! ... open material.config file
|
||||
endif
|
||||
Nsections = IO_countSections(fileunit,material_partPhase)
|
||||
lattice_Nstructure = 2_pInt + sum(IO_countTagInPart(fileunit,material_partPhase,'covera_ratio',Nsections)) ! fcc + bcc + all hex
|
||||
close(fileunit)
|
||||
|
@ -778,7 +793,7 @@ end subroutine lattice_init
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief Calculation of Schmid matrices, etc.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
integer(pInt) function lattice_initializeStructure(struct,CoverA)
|
||||
integer(pInt) function lattice_initializeStructure(struct_ID,CoverA)
|
||||
use math, only: &
|
||||
math_vectorproduct, &
|
||||
math_tensorproduct, &
|
||||
|
@ -793,8 +808,8 @@ integer(pInt) function lattice_initializeStructure(struct,CoverA)
|
|||
IO_error
|
||||
|
||||
implicit none
|
||||
character(len=*) struct
|
||||
real(pReal) CoverA
|
||||
integer(kind(LATTICE_fcc_ID)), intent(in) :: struct_ID
|
||||
real(pReal) :: CoverA
|
||||
real(pReal), dimension(3) :: sdU = 0.0_pReal, &
|
||||
snU = 0.0_pReal, &
|
||||
np = 0.0_pReal, &
|
||||
|
@ -812,8 +827,8 @@ integer(pInt) function lattice_initializeStructure(struct,CoverA)
|
|||
|
||||
processMe = .false.
|
||||
|
||||
select case(struct(1:3)) ! check first three chars of structure name
|
||||
case ('fcc')
|
||||
select case(struct_ID)
|
||||
case (LATTICE_fcc_ID)
|
||||
myStructure = 1_pInt
|
||||
myNslipSystem = lattice_fcc_NslipSystem ! size of slip system families
|
||||
myNtwinSystem = lattice_fcc_NtwinSystem ! size of twin system families
|
||||
|
@ -842,7 +857,7 @@ integer(pInt) function lattice_initializeStructure(struct,CoverA)
|
|||
interactionTwinTwin => lattice_fcc_interactionTwinTwin
|
||||
endif
|
||||
|
||||
case ('bcc')
|
||||
case (LATTICE_bcc_ID)
|
||||
myStructure = 2_pInt
|
||||
myNslipSystem = lattice_bcc_NslipSystem ! size of slip system families
|
||||
myNtwinSystem = lattice_bcc_NtwinSystem ! size of twin system families
|
||||
|
@ -883,7 +898,7 @@ integer(pInt) function lattice_initializeStructure(struct,CoverA)
|
|||
interactionTwinTwin => lattice_bcc_interactionTwinTwin
|
||||
endif
|
||||
|
||||
case ('hex')
|
||||
case (LATTICE_hex_ID)
|
||||
if (CoverA < 1.0_pReal .or. CoverA > 2.0_pReal) call IO_error(206_pInt) ! checking physical significance of c/a
|
||||
|
||||
lattice_hex_Nstructure = lattice_hex_Nstructure + 1_pInt ! count instances of hex structures
|
||||
|
@ -984,15 +999,15 @@ end function lattice_initializeStructure
|
|||
!> @brief Maps structure to symmetry type
|
||||
!> @details fcc(1) and bcc(2) are cubic(1) hex(3+) is hexagonal(2)
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
integer(pInt) pure function lattice_symmetryType(structName)
|
||||
integer(pInt) pure function lattice_symmetryType(struct_ID)
|
||||
|
||||
implicit none
|
||||
character(len=32), intent(in) :: structName
|
||||
integer(kind(LATTICE_fcc_ID)), intent(in) :: struct_ID
|
||||
|
||||
select case(structName(1:3))
|
||||
case ('fcc','bcc')
|
||||
select case(struct_ID)
|
||||
case (LATTICE_fcc_ID,LATTICE_bcc_ID)
|
||||
lattice_symmetryType = 1_pInt
|
||||
case ('hex')
|
||||
case (LATTICE_hex_ID)
|
||||
lattice_symmetryType = 2_pInt
|
||||
case default
|
||||
lattice_symmetryType = 0_pInt
|
||||
|
@ -1006,30 +1021,30 @@ end function lattice_symmetryType
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief Symmetrizes stiffness matrix according to lattice type
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
pure function lattice_symmetrizeC66(structName,C66)
|
||||
pure function lattice_symmetrizeC66(struct_ID,C66)
|
||||
|
||||
implicit none
|
||||
character(len=32), intent(in) :: structName
|
||||
integer(kind(LATTICE_fcc_ID)), intent(in) :: struct_ID
|
||||
real(pReal), dimension(6,6), intent(in) :: C66
|
||||
real(pReal), dimension(6,6) :: lattice_symmetrizeC66
|
||||
integer(pInt) :: j,k
|
||||
|
||||
lattice_symmetrizeC66 = 0.0_pReal
|
||||
|
||||
select case(structName(1:3))
|
||||
case ('iso')
|
||||
select case(struct_ID)
|
||||
case (LATTICE_iso_ID)
|
||||
forall(k=1_pInt:3_pInt)
|
||||
forall(j=1_pInt:3_pInt) lattice_symmetrizeC66(k,j) = C66(1,2)
|
||||
lattice_symmetrizeC66(k,k) = C66(1,1)
|
||||
lattice_symmetrizeC66(k+3,k+3) = 0.5_pReal*(C66(1,1)-C66(1,2))
|
||||
end forall
|
||||
case ('fcc','bcc')
|
||||
case (LATTICE_fcc_ID,LATTICE_bcc_ID)
|
||||
forall(k=1_pInt:3_pInt)
|
||||
forall(j=1_pInt:3_pInt) lattice_symmetrizeC66(k,j) = C66(1,2)
|
||||
lattice_symmetrizeC66(k,k) = C66(1,1)
|
||||
lattice_symmetrizeC66(k+3_pInt,k+3_pInt) = C66(4,4)
|
||||
end forall
|
||||
case ('hex')
|
||||
case (LATTICE_hex_ID)
|
||||
lattice_symmetrizeC66(1,1) = C66(1,1)
|
||||
lattice_symmetrizeC66(2,2) = C66(1,1)
|
||||
lattice_symmetrizeC66(3,3) = C66(3,3)
|
||||
|
@ -1042,7 +1057,7 @@ pure function lattice_symmetrizeC66(structName,C66)
|
|||
lattice_symmetrizeC66(4,4) = C66(4,4)
|
||||
lattice_symmetrizeC66(5,5) = C66(4,4)
|
||||
lattice_symmetrizeC66(6,6) = 0.5_pReal*(C66(1,1)-C66(1,2))
|
||||
case ('ort')
|
||||
case (LATTICE_ort_ID)
|
||||
lattice_symmetrizeC66(1,1) = C66(1,1)
|
||||
lattice_symmetrizeC66(2,2) = C66(2,2)
|
||||
lattice_symmetrizeC66(3,3) = C66(3,3)
|
||||
|
@ -1070,16 +1085,16 @@ pure function lattice_symmetrizeC66(structName,C66)
|
|||
! TwinTwinInteraction
|
||||
! NnonSchmid
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function lattice_configNchunks(struct)
|
||||
function lattice_configNchunks(struct_ID)
|
||||
use prec, only: &
|
||||
pInt
|
||||
|
||||
implicit none
|
||||
integer(pInt), dimension(7) :: lattice_configNchunks
|
||||
character(len=*), intent(in) :: struct
|
||||
integer(kind(LATTICE_fcc_ID)) :: struct_ID
|
||||
|
||||
select case(struct(1:3)) ! check first three chars of structure name
|
||||
case ('fcc')
|
||||
select case(struct_ID)
|
||||
case (LATTICE_fcc_ID)
|
||||
lattice_configNchunks(1) = count(lattice_fcc_NslipSystem > 0_pInt)
|
||||
lattice_configNchunks(2) = count(lattice_fcc_NtwinSystem > 0_pInt)
|
||||
lattice_configNchunks(3) = maxval(lattice_fcc_interactionSlipSlip)
|
||||
|
@ -1087,7 +1102,7 @@ function lattice_configNchunks(struct)
|
|||
lattice_configNchunks(5) = maxval(lattice_fcc_interactionTwinSlip)
|
||||
lattice_configNchunks(6) = maxval(lattice_fcc_interactionTwinTwin)
|
||||
lattice_configNchunks(7) = lattice_fcc_NnonSchmid
|
||||
case ('bcc')
|
||||
case (LATTICE_bcc_ID)
|
||||
lattice_configNchunks(1) = count(lattice_bcc_NslipSystem > 0_pInt)
|
||||
lattice_configNchunks(2) = count(lattice_bcc_NtwinSystem > 0_pInt)
|
||||
lattice_configNchunks(3) = maxval(lattice_bcc_interactionSlipSlip)
|
||||
|
@ -1095,7 +1110,7 @@ function lattice_configNchunks(struct)
|
|||
lattice_configNchunks(5) = maxval(lattice_bcc_interactionTwinSlip)
|
||||
lattice_configNchunks(6) = maxval(lattice_bcc_interactionTwinTwin)
|
||||
lattice_configNchunks(7) = lattice_bcc_NnonSchmid
|
||||
case ('hex')
|
||||
case (LATTICE_hex_ID)
|
||||
lattice_configNchunks(1) = count(lattice_hex_NslipSystem > 0_pInt)
|
||||
lattice_configNchunks(2) = count(lattice_hex_NtwinSystem > 0_pInt)
|
||||
lattice_configNchunks(3) = maxval(lattice_hex_interactionSlipSlip)
|
||||
|
|
Loading…
Reference in New Issue