DAMASK_EICMD/src/homogenization_mechanical.f90

261 lines
10 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
!--------------------------------------------------------------------------------------------------
2021-02-13 23:27:41 +05:30
submodule(homogenization) mechanical
2020-12-16 15:51:24 +05:30
2020-12-23 18:33:15 +05:30
2020-12-16 15:51:24 +05:30
interface
module subroutine pass_init()
end subroutine pass_init
2020-12-16 15:51:24 +05:30
module subroutine isostrain_init()
end subroutine isostrain_init
2020-12-16 15:51:24 +05:30
module subroutine RGC_init()
end subroutine RGC_init
2020-12-16 15:51:24 +05:30
module subroutine 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 isostrain_partitionDeformation
2020-12-16 15:51:24 +05:30
module subroutine RGC_partitionDeformation(F,avgF,ce)
real(pREAL), dimension (:,:,:), intent(out) :: F !< partitioned deformation gradient
real(pREAL), dimension (3,3), intent(in) :: avgF !< average deformation gradient at material point
2020-12-16 15:51:24 +05:30
integer, intent(in) :: &
2021-02-15 23:13:51 +05:30
ce
end subroutine RGC_partitionDeformation
2020-12-16 15:51:24 +05:30
module function RGC_updateState(P,F,avgF,dt,dPdF,ce) result(doneAndHappy)
2020-12-28 14:25:54 +05:30
logical, dimension(2) :: doneAndHappy
real(pREAL), dimension(:,:,:), intent(in) :: &
2020-12-28 14:25:54 +05:30
P,& !< partitioned stresses
F !< partitioned deformation gradients
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
2020-12-28 14:25:54 +05:30
integer, intent(in) :: &
2021-02-22 20:47:32 +05:30
ce !< cell
end function RGC_updateState
2020-12-28 14:25:54 +05:30
2023-01-19 22:07:45 +05:30
module subroutine RGC_result(ho,group)
integer, intent(in) :: ho !< homogenization type
2020-12-16 15:51:24 +05:30
character(len=*), intent(in) :: group !< group name in HDF5 file
2023-01-19 22:07:45 +05:30
end subroutine RGC_result
2020-12-16 15:51:24 +05:30
end interface
type :: tOutput !< requested output (per phase)
2023-06-04 10:47:38 +05:30
character(len=pSTRLEN), allocatable, dimension(:) :: &
label
end type tOutput
type(tOutput), allocatable, dimension(:) :: output_mechanical
2022-02-24 16:39:47 +05:30
enum, bind(c); enumerator :: &
MECHANICAL_UNDEFINED_ID, &
MECHANICAL_PASS_ID, &
MECHANICAL_ISOSTRAIN_ID, &
MECHANICAL_RGC_ID
end enum
integer(kind(MECHANICAL_UNDEFINED_ID)), dimension(:), allocatable :: &
2023-06-04 10:47:38 +05:30
mechanical_type !< type of each homogenization
2021-04-08 00:09:11 +05:30
2020-12-16 15:51:24 +05:30
contains
!--------------------------------------------------------------------------------------------------
!> @brief Allocate variables and set parameters.
!--------------------------------------------------------------------------------------------------
module subroutine mechanical_init()
2020-12-16 15:51:24 +05:30
print'(/,1x,a)', '<<<+- homogenization:mechanical init -+>>>'
2020-12-16 15:51:24 +05:30
call parseMechanical()
2021-04-07 15:18:04 +05:30
allocate(homogenization_dPdF(3,3,3,3,discretization_Ncells), source=0.0_pREAL)
2023-12-24 03:09:23 +05:30
homogenization_F = spread(math_I3,3,discretization_Ncells)
allocate(homogenization_P(3,3,discretization_Ncells),source=0.0_pREAL)
2020-12-16 15:51:24 +05:30
2022-02-24 16:39:47 +05:30
if (any(mechanical_type == MECHANICAL_PASS_ID)) call pass_init()
if (any(mechanical_type == MECHANICAL_ISOSTRAIN_ID)) call isostrain_init()
if (any(mechanical_type == MECHANICAL_RGC_ID)) call RGC_init()
2020-12-16 15:51:24 +05:30
2021-02-09 03:51:53 +05:30
end subroutine mechanical_init
2020-12-16 15:51:24 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Partition F onto the individual constituents.
!--------------------------------------------------------------------------------------------------
2021-02-15 23:13:51 +05:30
module subroutine mechanical_partition(subF,ce)
2020-12-16 15:51:24 +05:30
real(pREAL), intent(in), dimension(3,3) :: &
2020-12-16 15:51:24 +05:30
subF
integer, intent(in) :: &
2021-02-15 23:13:51 +05:30
ce
2020-12-30 15:33:13 +05:30
2020-12-29 16:55:03 +05:30
integer :: co
real(pREAL), dimension (3,3,homogenization_Nconstituents(material_ID_homogenization(ce))) :: Fs
2020-12-29 16:55:03 +05:30
2020-12-16 15:51:24 +05:30
2023-01-23 13:01:59 +05:30
chosenHomogenization: select case(mechanical_type(material_ID_homogenization(ce)))
2020-12-16 15:51:24 +05:30
2022-02-24 16:39:47 +05:30
case (MECHANICAL_PASS_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
2022-02-24 16:39:47 +05:30
case (MECHANICAL_ISOSTRAIN_ID) chosenHomogenization
call isostrain_partitionDeformation(Fs,subF)
2020-12-16 15:51:24 +05:30
2022-02-24 16:39:47 +05:30
case (MECHANICAL_RGC_ID) chosenHomogenization
call RGC_partitionDeformation(Fs,subF,ce)
2020-12-16 15:51:24 +05:30
end select chosenHomogenization
2023-01-23 13:01:59 +05:30
do co = 1,homogenization_Nconstituents(material_ID_homogenization(ce))
2021-04-08 00:36:29 +05:30
call phase_set_F(Fs(1:3,1:3,co),co,ce)
end do
2020-12-29 16:55:03 +05:30
2021-02-09 03:51:53 +05:30
end subroutine mechanical_partition
2020-12-16 15:51:24 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Average P and dPdF from the individual constituents.
!--------------------------------------------------------------------------------------------------
2021-07-17 15:20:21 +05:30
module subroutine mechanical_homogenize(Delta_t,ce)
2020-12-16 15:51:24 +05:30
real(pREAL), intent(in) :: Delta_t
2021-02-26 02:12:40 +05:30
integer, intent(in) :: ce
2021-02-26 02:12:40 +05:30
integer :: co
2020-12-16 15:51:24 +05:30
homogenization_P(1:3,1:3,ce) = phase_P(1,ce)*material_v(1,ce)
homogenization_dPdF(1:3,1:3,1:3,1:3,ce) = phase_mechanical_dPdF(Delta_t,1,ce)*material_v(1,ce)
2023-01-23 13:01:59 +05:30
do co = 2, homogenization_Nconstituents(material_ID_homogenization(ce))
2021-04-11 15:48:26 +05:30
homogenization_P(1:3,1:3,ce) = homogenization_P(1:3,1:3,ce) &
+ phase_P(co,ce)*material_v(co,ce)
2021-04-11 15:48:26 +05:30
homogenization_dPdF(1:3,1:3,1:3,1:3,ce) = homogenization_dPdF(1:3,1:3,1:3,1:3,ce) &
+ phase_mechanical_dPdF(Delta_t,co,ce)*material_v(co,ce)
end do
2020-12-16 15:51:24 +05:30
2021-02-09 03:51:53 +05:30
end subroutine mechanical_homogenize
2020-12-16 15:51:24 +05:30
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 mechanical_updateState(subdt,subF,ce) result(doneAndHappy)
2020-12-28 14:25:54 +05:30
real(pREAL), intent(in) :: &
2020-12-28 14:25:54 +05:30
subdt !< current time step
real(pREAL), intent(in), dimension(3,3) :: &
2020-12-28 14:25:54 +05:30
subF
integer, intent(in) :: &
ce
2020-12-28 14:25:54 +05:30
logical, dimension(2) :: doneAndHappy
integer :: co
real(pREAL) :: dPdFs(3,3,3,3,homogenization_Nconstituents(material_ID_homogenization(ce)))
real(pREAL) :: Fs(3,3,homogenization_Nconstituents(material_ID_homogenization(ce)))
real(pREAL) :: Ps(3,3,homogenization_Nconstituents(material_ID_homogenization(ce)))
2020-12-28 14:25:54 +05:30
2023-01-23 13:01:59 +05:30
if (mechanical_type(material_ID_homogenization(ce)) == MECHANICAL_RGC_ID) then
do co = 1, homogenization_Nconstituents(material_ID_homogenization(ce))
dPdFs(:,:,:,:,co) = phase_mechanical_dPdF(subdt,co,ce)
2021-04-08 00:36:29 +05:30
Fs(:,:,co) = phase_F(co,ce)
Ps(:,:,co) = phase_P(co,ce)
end do
doneAndHappy = RGC_updateState(Ps,Fs,subF,subdt,dPdFs,ce)
2020-12-28 14:25:54 +05:30
else
doneAndHappy = .true.
end if
2020-12-28 14:25:54 +05:30
2021-02-09 03:51:53 +05:30
end function mechanical_updateState
2020-12-28 14:25:54 +05:30
2020-12-16 15:51:24 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Write results to file.
!--------------------------------------------------------------------------------------------------
2023-01-19 22:07:45 +05:30
module subroutine mechanical_result(group_base,ho)
2020-12-16 15:51:24 +05:30
character(len=*), intent(in) :: group_base
integer, intent(in) :: ho
2020-12-16 15:51:24 +05:30
integer :: ou
2020-12-16 15:51:24 +05:30
character(len=:), allocatable :: group
2021-03-25 23:52:59 +05:30
group = trim(group_base)//'/mechanical'
2023-01-19 22:07:45 +05:30
call result_closeGroup(result_addGroup(group))
2020-12-16 15:51:24 +05:30
2022-02-24 16:39:47 +05:30
select case(mechanical_type(ho))
2020-12-16 15:51:24 +05:30
2022-02-24 16:39:47 +05:30
case(MECHANICAL_RGC_ID)
2023-01-19 22:07:45 +05:30
call RGC_result(ho,group)
2020-12-16 15:51:24 +05:30
end select
do ou = 1, size(output_mechanical(1)%label)
select case (output_mechanical(ho)%label(ou))
case('F')
2023-01-19 22:07:45 +05:30
call result_writeDataset(reshape(homogenization_F,[3,3,discretization_nCells]),group,'F', &
'deformation gradient','1')
case('P')
2023-01-19 22:07:45 +05:30
call result_writeDataset(reshape(homogenization_P,[3,3,discretization_nCells]),group,'P', &
'first Piola-Kirchhoff stress','Pa')
end select
end do
2020-12-16 15:51:24 +05:30
2023-01-19 22:07:45 +05:30
end subroutine mechanical_result
2020-12-16 15:51:24 +05:30
2021-04-07 15:18:04 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief parses the homogenization part from the material configuration
!--------------------------------------------------------------------------------------------------
subroutine parseMechanical()
2021-04-07 15:18:04 +05:30
type(tDict), pointer :: &
2021-04-07 15:18:04 +05:30
material_homogenization, &
homog, &
mechanical
integer :: ho
2021-04-07 15:18:04 +05:30
material_homogenization => config_material%get_dict('homogenization')
2021-04-07 15:18:04 +05:30
2022-02-24 16:39:47 +05:30
allocate(mechanical_type(size(material_name_homogenization)), source=MECHANICAL_UNDEFINED_ID)
allocate(output_mechanical(size(material_name_homogenization)))
do ho=1, size(material_name_homogenization)
homog => material_homogenization%get_dict(ho)
mechanical => homog%get_dict('mechanical')
#if defined(__GFORTRAN__)
2023-06-04 10:47:38 +05:30
output_mechanical(ho)%label = output_as1dStr(mechanical)
#else
2023-06-04 10:47:38 +05:30
output_mechanical(ho)%label = mechanical%get_as1dStr('output',defaultVal=emptyStrArray)
#endif
2023-06-04 10:47:38 +05:30
select case (mechanical%get_asStr('type'))
2021-04-07 15:18:04 +05:30
case('pass')
2022-02-24 16:39:47 +05:30
mechanical_type(ho) = MECHANICAL_PASS_ID
2021-04-07 15:18:04 +05:30
case('isostrain')
2022-02-24 16:39:47 +05:30
mechanical_type(ho) = MECHANICAL_ISOSTRAIN_ID
2021-04-07 15:18:04 +05:30
case('RGC')
2022-02-24 16:39:47 +05:30
mechanical_type(ho) = MECHANICAL_RGC_ID
2021-04-07 15:18:04 +05:30
case default
2023-06-04 10:47:38 +05:30
call IO_error(500,ext_msg=mechanical%get_asStr('type'))
2021-04-07 15:18:04 +05:30
end select
end do
2021-04-07 15:18:04 +05:30
end subroutine parseMechanical
2021-04-07 15:18:04 +05:30
2021-02-13 23:27:41 +05:30
end submodule mechanical