DAMASK_EICMD/src/homogenization_mech.f90

257 lines
12 KiB
Fortran
Raw Normal View History

2020-12-16 15:51:24 +05:30
!--------------------------------------------------------------------------------------------------
!> @author Martin Diehl, KU Leuven
!> @brief Partition F and homogenize P/dPdF
!--------------------------------------------------------------------------------------------------
submodule(homogenization) homogenization_mech
2020-12-23 18:33:15 +05:30
2020-12-16 15:51:24 +05:30
interface
module subroutine mech_none_init
end subroutine mech_none_init
module subroutine mech_isostrain_init
end subroutine mech_isostrain_init
module subroutine mech_RGC_init(num_homogMech)
class(tNode), pointer, intent(in) :: &
num_homogMech !< pointer to mechanical homogenization numerics data
end subroutine mech_RGC_init
module subroutine mech_isostrain_partitionDeformation(F,avgF)
real(pReal), dimension (:,:,:), intent(out) :: F !< partitioned deformation gradient
real(pReal), dimension (3,3), intent(in) :: avgF !< average deformation gradient at material point
end subroutine mech_isostrain_partitionDeformation
module subroutine mech_RGC_partitionDeformation(F,avgF,instance,of)
real(pReal), dimension (:,:,:), intent(out) :: F !< partitioned deformation gradient
real(pReal), dimension (3,3), intent(in) :: avgF !< average deformation gradient at material point
integer, intent(in) :: &
instance, &
of
end subroutine mech_RGC_partitionDeformation
module subroutine mech_isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,instance)
real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point
real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF !< average stiffness at material point
real(pReal), dimension (:,:,:), intent(in) :: P !< partitioned stresses
real(pReal), dimension (:,:,:,:,:), intent(in) :: dPdF !< partitioned stiffnesses
integer, intent(in) :: instance
end subroutine mech_isostrain_averageStressAndItsTangent
module subroutine mech_RGC_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,instance)
real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point
real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF !< average stiffness at material point
real(pReal), dimension (:,:,:), intent(in) :: P !< partitioned stresses
real(pReal), dimension (:,:,:,:,:), intent(in) :: dPdF !< partitioned stiffnesses
integer, intent(in) :: instance
end subroutine mech_RGC_averageStressAndItsTangent
module function mech_RGC_updateState(P,F,avgF,dt,dPdF,ip,el) result(doneAndHappy)
2020-12-28 14:25:54 +05:30
logical, dimension(2) :: doneAndHappy
real(pReal), dimension(:,:,:), intent(in) :: &
P,& !< partitioned stresses
F !< partitioned deformation gradients
2020-12-28 14:25:54 +05:30
real(pReal), dimension(:,:,:,:,:), intent(in) :: dPdF !< partitioned stiffnesses
real(pReal), dimension(3,3), intent(in) :: avgF !< average F
real(pReal), intent(in) :: dt !< time increment
integer, intent(in) :: &
ip, & !< integration point number
el !< element number
end function mech_RGC_updateState
2020-12-16 15:51:24 +05:30
module subroutine mech_RGC_results(instance,group)
integer, intent(in) :: instance !< homogenization instance
character(len=*), intent(in) :: group !< group name in HDF5 file
end subroutine mech_RGC_results
end interface
contains
!--------------------------------------------------------------------------------------------------
!> @brief Allocate variables and set parameters.
!--------------------------------------------------------------------------------------------------
module subroutine mech_init(num_homog)
class(tNode), pointer, intent(in) :: &
num_homog
class(tNode), pointer :: &
num_homogMech
print'(/,a)', ' <<<+- homogenization_mech init -+>>>'
allocate(homogenization_dPdF(3,3,3,3,discretization_nIPs*discretization_Nelems), source=0.0_pReal)
homogenization_F0 = spread(math_I3,3,discretization_nIPs*discretization_Nelems) ! initialize to identity
homogenization_F = homogenization_F0 ! initialize to identity
allocate(homogenization_P(3,3,discretization_nIPs*discretization_Nelems), source=0.0_pReal)
2020-12-16 15:51:24 +05:30
num_homogMech => num_homog%get('mech',defaultVal=emptyDict)
if (any(homogenization_type == HOMOGENIZATION_NONE_ID)) call mech_none_init
if (any(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)) call mech_isostrain_init
if (any(homogenization_type == HOMOGENIZATION_RGC_ID)) call mech_RGC_init(num_homogMech)
end subroutine mech_init
!--------------------------------------------------------------------------------------------------
!> @brief Partition F onto the individual constituents.
!--------------------------------------------------------------------------------------------------
module subroutine mech_partition(subF,ip,el)
real(pReal), intent(in), dimension(3,3) :: &
subF
integer, intent(in) :: &
ip, & !< integration point
el !< element number
2020-12-30 15:33:13 +05:30
2020-12-29 16:55:03 +05:30
integer :: co
2020-12-31 12:16:26 +05:30
real(pReal), dimension (3,3,homogenization_Nconstituents(material_homogenizationAt(el))) :: Fs
2020-12-29 16:55:03 +05:30
2020-12-16 15:51:24 +05:30
chosenHomogenization: select case(homogenization_type(material_homogenizationAt(el)))
case (HOMOGENIZATION_NONE_ID) chosenHomogenization
2020-12-31 12:16:26 +05:30
Fs(1:3,1:3,1) = subF
2020-12-16 15:51:24 +05:30
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
2020-12-31 12:16:26 +05:30
call mech_isostrain_partitionDeformation(Fs,subF)
2020-12-16 15:51:24 +05:30
case (HOMOGENIZATION_RGC_ID) chosenHomogenization
2020-12-31 12:16:26 +05:30
call mech_RGC_partitionDeformation(Fs,subF,ip,el)
2020-12-16 15:51:24 +05:30
end select chosenHomogenization
2020-12-29 16:55:03 +05:30
do co = 1,homogenization_Nconstituents(material_homogenizationAt(el))
2020-12-31 12:16:26 +05:30
call constitutive_mech_setF(Fs(1:3,1:3,co),co,ip,el)
2020-12-29 16:55:03 +05:30
enddo
2020-12-16 15:51:24 +05:30
end subroutine mech_partition
!--------------------------------------------------------------------------------------------------
!> @brief Average P and dPdF from the individual constituents.
!--------------------------------------------------------------------------------------------------
module subroutine mech_homogenize(dt,ip,el)
2020-12-16 15:51:24 +05:30
real(pReal), intent(in) :: dt
2020-12-16 15:51:24 +05:30
integer, intent(in) :: &
ip, & !< integration point
el !< element number
2020-12-27 14:17:20 +05:30
integer :: co,ce
2020-12-16 15:51:24 +05:30
real(pReal) :: dPdFs(3,3,3,3,homogenization_Nconstituents(material_homogenizationAt(el)))
2020-12-30 15:33:13 +05:30
real(pReal) :: Ps(3,3,homogenization_Nconstituents(material_homogenizationAt(el)))
2020-12-16 15:51:24 +05:30
2020-12-27 14:17:20 +05:30
ce = (el-1)* discretization_nIPs + ip
2020-12-16 15:51:24 +05:30
chosenHomogenization: select case(homogenization_type(material_homogenizationAt(el)))
case (HOMOGENIZATION_NONE_ID) chosenHomogenization
2020-12-30 15:33:13 +05:30
homogenization_P(1:3,1:3,ce) = constitutive_mech_getP(1,ip,el)
2020-12-30 02:01:22 +05:30
homogenization_dPdF(1:3,1:3,1:3,1:3,ce) = constitutive_mech_dPdF(dt,1,ip,el)
2020-12-16 15:51:24 +05:30
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
2020-12-27 14:17:20 +05:30
do co = 1, homogenization_Nconstituents(material_homogenizationAt(el))
2020-12-30 02:01:22 +05:30
dPdFs(:,:,:,:,co) = constitutive_mech_dPdF(dt,co,ip,el)
2020-12-30 15:33:13 +05:30
Ps(:,:,co) = constitutive_mech_getP(co,ip,el)
2020-12-16 15:51:24 +05:30
enddo
call mech_isostrain_averageStressAndItsTangent(&
2020-12-27 14:17:20 +05:30
homogenization_P(1:3,1:3,ce), &
homogenization_dPdF(1:3,1:3,1:3,1:3,ce),&
2020-12-30 15:33:13 +05:30
Ps,dPdFs, &
2020-12-16 15:51:24 +05:30
homogenization_typeInstance(material_homogenizationAt(el)))
case (HOMOGENIZATION_RGC_ID) chosenHomogenization
2020-12-27 14:17:20 +05:30
do co = 1, homogenization_Nconstituents(material_homogenizationAt(el))
2020-12-30 02:01:22 +05:30
dPdFs(:,:,:,:,co) = constitutive_mech_dPdF(dt,co,ip,el)
2020-12-30 15:33:13 +05:30
Ps(:,:,co) = constitutive_mech_getP(co,ip,el)
2020-12-16 15:51:24 +05:30
enddo
call mech_RGC_averageStressAndItsTangent(&
2020-12-27 14:17:20 +05:30
homogenization_P(1:3,1:3,ce), &
homogenization_dPdF(1:3,1:3,1:3,1:3,ce),&
2020-12-30 15:33:13 +05:30
Ps,dPdFs, &
2020-12-16 15:51:24 +05:30
homogenization_typeInstance(material_homogenizationAt(el)))
end select chosenHomogenization
end subroutine mech_homogenize
2020-12-28 14:25:54 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief update the internal state of the homogenization scheme and tell whether "done" and
!> "happy" with result
!--------------------------------------------------------------------------------------------------
module function mech_updateState(subdt,subF,ip,el) result(doneAndHappy)
real(pReal), intent(in) :: &
subdt !< current time step
real(pReal), intent(in), dimension(3,3) :: &
subF
integer, intent(in) :: &
ip, & !< integration point
el !< element number
logical, dimension(2) :: doneAndHappy
integer :: co
real(pReal) :: dPdFs(3,3,3,3,homogenization_Nconstituents(material_homogenizationAt(el)))
2020-12-29 22:57:24 +05:30
real(pReal) :: Fs(3,3,homogenization_Nconstituents(material_homogenizationAt(el)))
2020-12-30 15:33:13 +05:30
real(pReal) :: Ps(3,3,homogenization_Nconstituents(material_homogenizationAt(el)))
2020-12-28 14:25:54 +05:30
if (homogenization_type(material_homogenizationAt(el)) == HOMOGENIZATION_RGC_ID) then
do co = 1, homogenization_Nconstituents(material_homogenizationAt(el))
2020-12-30 02:01:22 +05:30
dPdFs(:,:,:,:,co) = constitutive_mech_dPdF(subdt,co,ip,el)
2020-12-29 22:57:24 +05:30
Fs(:,:,co) = constitutive_mech_getF(co,ip,el)
2020-12-30 15:33:13 +05:30
Ps(:,:,co) = constitutive_mech_getP(co,ip,el)
2020-12-28 14:25:54 +05:30
enddo
2020-12-30 15:33:13 +05:30
doneAndHappy = mech_RGC_updateState(Ps,Fs,subF,subdt,dPdFs,ip,el)
2020-12-28 14:25:54 +05:30
else
doneAndHappy = .true.
endif
end function mech_updateState
2020-12-16 15:51:24 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Write results to file.
!--------------------------------------------------------------------------------------------------
module subroutine mech_results(group_base,h)
use material, only: &
material_homogenization_type => homogenization_type
character(len=*), intent(in) :: group_base
integer, intent(in) :: h
character(len=:), allocatable :: group
group = trim(group_base)//'/mech'
call results_closeGroup(results_addGroup(group))
select case(material_homogenization_type(h))
case(HOMOGENIZATION_rgc_ID)
call mech_RGC_results(homogenization_typeInstance(h),group)
end select
!temp = reshape(homogenization_F,[3,3,discretization_nIPs*discretization_Nelems])
!call results_writeDataset(group,temp,'F',&
! 'deformation gradient','1')
!temp = reshape(homogenization_P,[3,3,discretization_nIPs*discretization_Nelems])
!call results_writeDataset(group,temp,'P',&
! '1st Piola-Kirchhoff stress','Pa')
end subroutine mech_results
end submodule homogenization_mech