2021-03-16 21:50:24 +05:30
submodule ( phase : mechanical ) elastic
2021-05-24 20:49:38 +05:30
type :: tParameters
2022-01-31 19:35:15 +05:30
type ( tPolynomial ) :: &
C_11 , &
C_12 , &
C_13 , &
C_33 , &
C_44 , &
C_66
2021-05-24 20:49:38 +05:30
end type tParameters
2021-06-01 02:32:51 +05:30
2021-05-24 20:49:38 +05:30
type ( tParameters ) , allocatable , dimension ( : ) :: param
2021-03-16 21:50:24 +05:30
contains
2021-11-17 23:40:01 +05:30
!--------------------------------------------------------------------------------------------------
2021-11-22 02:19:04 +05:30
!> @brief initialize elasticity
2021-11-17 23:40:01 +05:30
!--------------------------------------------------------------------------------------------------
2021-03-16 21:50:24 +05:30
module subroutine elastic_init ( phases )
class ( tNode ) , pointer :: &
phases
integer :: &
2021-05-20 02:07:36 +05:30
ph
2021-03-16 21:50:24 +05:30
class ( tNode ) , pointer :: &
phase , &
mech , &
2021-05-20 02:07:36 +05:30
elastic
2022-01-10 22:33:32 +05:30
2021-05-24 20:49:38 +05:30
2021-11-15 23:05:44 +05:30
print '(/,1x,a)' , '<<<+- phase:mechanical:elastic init -+>>>'
print '(/,1x,a)' , '<<<+- phase:mechanical:elastic:Hooke init -+>>>'
2021-05-27 11:55:48 +05:30
2021-11-15 23:05:44 +05:30
print '(/,a,i0)' , ' # phases: ' , phases % length ; flush ( IO_STDOUT )
2021-03-16 21:50:24 +05:30
2021-05-24 20:49:38 +05:30
allocate ( param ( phases % length ) )
2021-06-01 02:32:51 +05:30
2021-03-16 21:50:24 +05:30
do ph = 1 , phases % length
phase = > phases % get ( ph )
mech = > phase % get ( 'mechanical' )
elastic = > mech % get ( 'elastic' )
2021-05-24 20:49:38 +05:30
if ( elastic % get_asString ( 'type' ) / = 'Hooke' ) call IO_error ( 200 , ext_msg = elastic % get_asString ( 'type' ) )
2021-06-01 02:32:51 +05:30
2021-05-24 20:49:38 +05:30
associate ( prm = > param ( ph ) )
2021-07-21 19:53:21 +05:30
2022-01-31 19:35:15 +05:30
prm % C_11 = polynomial ( elastic % asDict ( ) , 'C_11' , 'T' )
prm % C_12 = polynomial ( elastic % asDict ( ) , 'C_12' , 'T' )
prm % C_44 = polynomial ( elastic % asDict ( ) , 'C_44' , 'T' )
2022-02-03 13:31:33 +05:30
2021-06-01 14:39:02 +05:30
if ( any ( phase_lattice ( ph ) == [ 'hP' , 'tI' ] ) ) then
2022-01-31 19:35:15 +05:30
prm % C_13 = polynomial ( elastic % asDict ( ) , 'C_13' , 'T' )
prm % C_33 = polynomial ( elastic % asDict ( ) , 'C_33' , 'T' )
2021-11-25 03:21:14 +05:30
end if
2022-01-31 19:35:15 +05:30
if ( phase_lattice ( ph ) == 'tI' ) &
prm % C_66 = polynomial ( elastic % asDict ( ) , 'C_66' , 'T' )
2021-07-21 19:53:21 +05:30
2021-05-24 20:49:38 +05:30
end associate
2021-11-17 23:40:01 +05:30
end do
2021-03-16 21:50:24 +05:30
end subroutine elastic_init
2021-11-18 17:16:37 +05:30
2021-11-17 23:40:01 +05:30
!--------------------------------------------------------------------------------------------------
2021-11-22 02:19:04 +05:30
!> @brief return 6x6 elasticity tensor
2021-11-17 23:40:01 +05:30
!--------------------------------------------------------------------------------------------------
2021-12-31 02:25:49 +05:30
pure module function elastic_C66 ( ph , en ) result ( C66 )
2021-11-17 23:40:01 +05:30
integer , intent ( in ) :: &
ph , &
en
2021-11-26 21:53:42 +05:30
2021-11-18 22:03:08 +05:30
real ( pReal ) , dimension ( 6 , 6 ) :: C66
2021-11-25 03:21:14 +05:30
real ( pReal ) :: T
2021-11-17 23:40:01 +05:30
2021-11-18 17:16:37 +05:30
2021-11-17 23:40:01 +05:30
associate ( prm = > param ( ph ) )
2022-02-02 22:15:13 +05:30
2021-11-18 22:03:08 +05:30
C66 = 0.0_pReal
2021-11-25 03:21:14 +05:30
T = thermal_T ( ph , en )
2021-11-25 19:21:31 +05:30
2022-01-31 19:35:15 +05:30
C66 ( 1 , 1 ) = prm % C_11 % at ( T )
C66 ( 1 , 2 ) = prm % C_12 % at ( T )
C66 ( 4 , 4 ) = prm % C_44 % at ( T )
2021-11-17 23:40:01 +05:30
if ( any ( phase_lattice ( ph ) == [ 'hP' , 'tI' ] ) ) then
2022-01-31 19:35:15 +05:30
C66 ( 1 , 3 ) = prm % C_13 % at ( T )
C66 ( 3 , 3 ) = prm % C_33 % at ( T )
2021-11-17 23:40:01 +05:30
end if
2021-11-18 17:16:37 +05:30
2022-01-31 19:35:15 +05:30
if ( phase_lattice ( ph ) == 'tI' ) C66 ( 6 , 6 ) = prm % C_66 % at ( T )
2021-11-18 17:16:37 +05:30
2021-11-18 22:03:08 +05:30
C66 = lattice_symmetrize_C66 ( C66 , phase_lattice ( ph ) )
2021-11-17 23:40:01 +05:30
end associate
end function elastic_C66
2021-11-18 17:16:37 +05:30
2021-11-17 23:40:01 +05:30
!--------------------------------------------------------------------------------------------------
2021-11-22 02:19:04 +05:30
!> @brief return shear modulus
2021-11-17 23:40:01 +05:30
!--------------------------------------------------------------------------------------------------
2021-12-31 02:25:49 +05:30
pure module function elastic_mu ( ph , en ) result ( mu )
2021-11-17 23:40:01 +05:30
integer , intent ( in ) :: &
ph , &
en
real ( pReal ) :: &
mu
2021-11-18 17:16:37 +05:30
2021-11-18 22:03:08 +05:30
mu = lattice_equivalent_mu ( elastic_C66 ( ph , en ) , 'voigt' )
2021-11-17 23:40:01 +05:30
end function elastic_mu
2021-11-18 22:03:08 +05:30
2021-11-17 23:40:01 +05:30
!--------------------------------------------------------------------------------------------------
2021-11-22 02:19:04 +05:30
!> @brief return Poisson ratio
2021-11-17 23:40:01 +05:30
!--------------------------------------------------------------------------------------------------
2021-12-31 02:25:49 +05:30
pure module function elastic_nu ( ph , en ) result ( nu )
2021-11-17 23:40:01 +05:30
integer , intent ( in ) :: &
ph , &
en
real ( pReal ) :: &
nu
2021-11-18 17:16:37 +05:30
2021-11-18 22:03:08 +05:30
nu = lattice_equivalent_nu ( elastic_C66 ( ph , en ) , 'voigt' )
2021-11-17 23:40:01 +05:30
end function elastic_nu
2021-03-16 21:50:24 +05:30
!--------------------------------------------------------------------------------------------------
2021-11-22 02:19:04 +05:30
!> @brief return the 2nd Piola-Kirchhoff stress tensor and its tangent with respect to
2021-03-16 21:50:24 +05:30
!> the elastic and intermediate deformation gradients using Hooke's law
2021-11-19 11:59:40 +05:30
! ToDo: Use Voigt matrix directly
2021-03-16 21:50:24 +05:30
!--------------------------------------------------------------------------------------------------
module subroutine phase_hooke_SandItsTangents ( S , dS_dFe , dS_dFi , &
2021-04-29 02:59:57 +05:30
Fe , Fi , ph , en )
2021-03-16 21:50:24 +05:30
integer , intent ( in ) :: &
ph , &
2021-04-29 02:59:57 +05:30
en
2021-03-16 21:50:24 +05:30
real ( pReal ) , intent ( in ) , dimension ( 3 , 3 ) :: &
Fe , & !< elastic deformation gradient
Fi !< intermediate deformation gradient
real ( pReal ) , intent ( out ) , dimension ( 3 , 3 ) :: &
S !< 2nd Piola-Kirchhoff stress tensor in lattice configuration
real ( pReal ) , intent ( out ) , dimension ( 3 , 3 , 3 , 3 ) :: &
dS_dFe , & !< derivative of 2nd P-K stress with respect to elastic deformation gradient
dS_dFi !< derivative of 2nd P-K stress with respect to intermediate deformation gradient
real ( pReal ) , dimension ( 3 , 3 ) :: E
2021-11-21 03:06:01 +05:30
real ( pReal ) , dimension ( 6 , 6 ) :: C66
2021-03-16 21:50:24 +05:30
real ( pReal ) , dimension ( 3 , 3 , 3 , 3 ) :: C
integer :: &
i , j
2021-05-24 20:49:38 +05:30
2021-11-21 03:06:01 +05:30
C66 = phase_damage_C66 ( phase_homogenizedC66 ( ph , en ) , ph , en )
2022-01-30 10:54:50 +05:30
C = math_Voigt66to3333_stiffness ( C66 )
2021-03-16 21:50:24 +05:30
E = 0.5_pReal * ( matmul ( transpose ( Fe ) , Fe ) - math_I3 ) !< Green-Lagrange strain in unloaded configuration
2021-11-21 03:06:01 +05:30
S = math_Voigt6to33_stress ( matmul ( C66 , math_33toVoigt6_strain ( matmul ( matmul ( transpose ( Fi ) , E ) , Fi ) ) ) ) !< 2PK stress in lattice configuration in work conjugate with GL strain pulled back to lattice configuration
2021-03-16 21:50:24 +05:30
2021-11-19 02:29:09 +05:30
do i = 1 , 3 ; do j = 1 , 3
2021-03-16 21:50:24 +05:30
dS_dFe ( i , j , 1 : 3 , 1 : 3 ) = matmul ( Fe , matmul ( matmul ( Fi , C ( i , j , 1 : 3 , 1 : 3 ) ) , transpose ( Fi ) ) ) !< dS_ij/dFe_kl = C_ijmn * Fi_lm * Fi_on * Fe_ko
dS_dFi ( i , j , 1 : 3 , 1 : 3 ) = 2.0_pReal * matmul ( matmul ( E , Fi ) , C ( i , j , 1 : 3 , 1 : 3 ) ) !< dS_ij/dFi_kl = C_ijln * E_km * Fe_mn
2021-11-17 23:40:01 +05:30
end do ; end do
2021-03-16 21:50:24 +05:30
end subroutine phase_hooke_SandItsTangents
2021-04-29 19:46:51 +05:30
!--------------------------------------------------------------------------------------------------
2021-11-19 11:59:40 +05:30
!> @brief Return the homogenized elasticity matrix.
2021-04-29 19:46:51 +05:30
!--------------------------------------------------------------------------------------------------
2021-11-18 21:07:34 +05:30
module function phase_homogenizedC66 ( ph , en ) result ( C )
2021-04-29 19:46:51 +05:30
real ( pReal ) , dimension ( 6 , 6 ) :: C
integer , intent ( in ) :: ph , en
2021-11-18 17:16:37 +05:30
2021-04-29 19:46:51 +05:30
plasticType : select case ( phase_plasticity ( ph ) )
2021-12-11 14:24:46 +05:30
case ( PLASTIC_DISLOTWIN_ID ) plasticType
2021-11-19 11:59:40 +05:30
C = plastic_dislotwin_homogenizedC ( ph , en )
2021-04-29 19:46:51 +05:30
case default plasticType
2021-11-19 02:29:09 +05:30
C = elastic_C66 ( ph , en )
2021-04-29 19:46:51 +05:30
end select plasticType
2021-11-18 21:07:34 +05:30
end function phase_homogenizedC66
2021-04-29 19:46:51 +05:30
2021-03-16 21:50:24 +05:30
end submodule elastic