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
|
|
|
|
|
2022-02-19 18:26:24 +05:30
|
|
|
module subroutine pass_init()
|
2021-04-06 15:35:47 +05:30
|
|
|
end subroutine pass_init
|
2020-12-16 15:51:24 +05:30
|
|
|
|
2022-02-19 18:26:24 +05:30
|
|
|
module subroutine isostrain_init()
|
2021-04-06 15:35:47 +05:30
|
|
|
end subroutine isostrain_init
|
2020-12-16 15:51:24 +05:30
|
|
|
|
2022-02-19 18:26:24 +05:30
|
|
|
module subroutine RGC_init()
|
2021-04-06 15:35:47 +05:30
|
|
|
end subroutine RGC_init
|
2020-12-16 15:51:24 +05:30
|
|
|
|
|
|
|
|
2021-04-06 15:35:47 +05:30
|
|
|
module subroutine isostrain_partitionDeformation(F,avgF)
|
2020-12-16 15:51:24 +05:30
|
|
|
real(pReal), dimension (:,:,:), intent(out) :: F !< partitioned deformation gradient
|
|
|
|
real(pReal), dimension (3,3), intent(in) :: avgF !< average deformation gradient at material point
|
2021-04-06 15:35:47 +05:30
|
|
|
end subroutine isostrain_partitionDeformation
|
2020-12-16 15:51:24 +05:30
|
|
|
|
2021-04-06 15:35:47 +05:30
|
|
|
module subroutine RGC_partitionDeformation(F,avgF,ce)
|
2020-12-16 15:51:24 +05:30
|
|
|
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) :: &
|
2021-02-15 23:13:51 +05:30
|
|
|
ce
|
2021-04-06 15:35:47 +05:30
|
|
|
end subroutine RGC_partitionDeformation
|
2020-12-16 15:51:24 +05:30
|
|
|
|
|
|
|
|
2021-04-06 15:35:47 +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) :: &
|
|
|
|
P,& !< partitioned stresses
|
2020-12-29 19:24:58 +05:30
|
|
|
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) :: &
|
2021-02-22 20:47:32 +05:30
|
|
|
ce !< cell
|
2021-04-06 15:35:47 +05:30
|
|
|
end function RGC_updateState
|
2020-12-28 14:25:54 +05:30
|
|
|
|
|
|
|
|
2021-04-06 15:35:47 +05:30
|
|
|
module subroutine RGC_results(ho,group)
|
2021-02-23 17:47:51 +05:30
|
|
|
integer, intent(in) :: ho !< homogenization type
|
2020-12-16 15:51:24 +05:30
|
|
|
character(len=*), intent(in) :: group !< group name in HDF5 file
|
2021-04-06 15:35:47 +05:30
|
|
|
end subroutine RGC_results
|
2020-12-16 15:51:24 +05:30
|
|
|
|
|
|
|
end interface
|
|
|
|
|
2022-02-19 18:49:11 +05:30
|
|
|
type :: tOutput !< requested output (per phase)
|
|
|
|
character(len=pStringLen), allocatable, dimension(:) :: &
|
|
|
|
label
|
|
|
|
end type tOutput
|
|
|
|
type(tOutput), allocatable, dimension(:) :: output_mechanical
|
|
|
|
|
2021-04-08 00:09:11 +05:30
|
|
|
integer(kind(HOMOGENIZATION_undefined_ID)), dimension(:), allocatable :: &
|
|
|
|
homogenization_type !< type of each homogenization
|
|
|
|
|
2020-12-16 15:51:24 +05:30
|
|
|
contains
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Allocate variables and set parameters.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2022-02-19 18:26:24 +05:30
|
|
|
module subroutine mechanical_init()
|
2020-12-16 15:51:24 +05:30
|
|
|
|
2021-11-15 23:05:44 +05:30
|
|
|
print'(/,1x,a)', '<<<+- homogenization:mechanical init -+>>>'
|
2020-12-16 15:51:24 +05:30
|
|
|
|
2022-02-19 18:26:24 +05:30
|
|
|
call parseMechanical()
|
2021-04-07 15:18:04 +05:30
|
|
|
|
2022-02-19 18:26:24 +05:30
|
|
|
allocate(homogenization_dPdF(3,3,3,3,discretization_Ncells), source=0.0_pReal)
|
|
|
|
homogenization_F0 = spread(math_I3,3,discretization_Ncells)
|
|
|
|
homogenization_F = homogenization_F0
|
|
|
|
allocate(homogenization_P(3,3,discretization_Ncells),source=0.0_pReal)
|
2020-12-16 15:51:24 +05:30
|
|
|
|
2022-02-19 18:26:24 +05:30
|
|
|
if (any(homogenization_type == HOMOGENIZATION_NONE_ID)) call pass_init()
|
|
|
|
if (any(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)) call isostrain_init()
|
|
|
|
if (any(homogenization_type == HOMOGENIZATION_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) :: &
|
|
|
|
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
|
2021-04-06 15:08:44 +05:30
|
|
|
real(pReal), dimension (3,3,homogenization_Nconstituents(material_homogenizationID(ce))) :: Fs
|
2020-12-29 16:55:03 +05:30
|
|
|
|
2020-12-16 15:51:24 +05:30
|
|
|
|
2021-04-06 15:08:44 +05:30
|
|
|
chosenHomogenization: select case(homogenization_type(material_homogenizationID(ce)))
|
2020-12-16 15:51:24 +05:30
|
|
|
|
|
|
|
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
|
2021-04-06 15:35:47 +05:30
|
|
|
call isostrain_partitionDeformation(Fs,subF)
|
2020-12-16 15:51:24 +05:30
|
|
|
|
|
|
|
case (HOMOGENIZATION_RGC_ID) chosenHomogenization
|
2021-04-06 15:35:47 +05:30
|
|
|
call RGC_partitionDeformation(Fs,subF,ce)
|
2020-12-16 15:51:24 +05:30
|
|
|
|
|
|
|
end select chosenHomogenization
|
|
|
|
|
2021-04-06 15:08:44 +05:30
|
|
|
do co = 1,homogenization_Nconstituents(material_homogenizationID(ce))
|
2021-04-08 00:36:29 +05:30
|
|
|
call phase_set_F(Fs(1:3,1:3,co),co,ce)
|
2021-11-15 23:05:44 +05:30
|
|
|
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
|
|
|
|
2021-07-17 15:20:21 +05:30
|
|
|
real(pReal), intent(in) :: Delta_t
|
2021-02-26 02:12:40 +05:30
|
|
|
integer, intent(in) :: ce
|
2020-12-29 05:09:23 +05:30
|
|
|
|
2021-02-26 02:12:40 +05:30
|
|
|
integer :: co
|
2020-12-16 15:51:24 +05:30
|
|
|
|
|
|
|
|
2022-02-07 19:13:32 +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)
|
2021-04-11 15:48:26 +05:30
|
|
|
do co = 2, homogenization_Nconstituents(material_homogenizationID(ce))
|
|
|
|
homogenization_P(1:3,1:3,ce) = homogenization_P(1:3,1:3,ce) &
|
2022-02-07 19:13:32 +05:30
|
|
|
+ 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) &
|
2022-02-07 19:13:32 +05:30
|
|
|
+ phase_mechanical_dPdF(Delta_t,co,ce)*material_v(co,ce)
|
2021-11-15 23:05:44 +05:30
|
|
|
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
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2021-02-23 16:14:39 +05:30
|
|
|
module function mechanical_updateState(subdt,subF,ce) result(doneAndHappy)
|
2020-12-28 14:25:54 +05:30
|
|
|
|
|
|
|
real(pReal), intent(in) :: &
|
|
|
|
subdt !< current time step
|
|
|
|
real(pReal), intent(in), dimension(3,3) :: &
|
|
|
|
subF
|
|
|
|
integer, intent(in) :: &
|
2021-02-23 16:14:39 +05:30
|
|
|
ce
|
2020-12-28 14:25:54 +05:30
|
|
|
logical, dimension(2) :: doneAndHappy
|
|
|
|
|
|
|
|
integer :: co
|
2021-04-06 15:08:44 +05:30
|
|
|
real(pReal) :: dPdFs(3,3,3,3,homogenization_Nconstituents(material_homogenizationID(ce)))
|
|
|
|
real(pReal) :: Fs(3,3,homogenization_Nconstituents(material_homogenizationID(ce)))
|
|
|
|
real(pReal) :: Ps(3,3,homogenization_Nconstituents(material_homogenizationID(ce)))
|
2020-12-28 14:25:54 +05:30
|
|
|
|
|
|
|
|
2021-04-06 15:08:44 +05:30
|
|
|
if (homogenization_type(material_homogenizationID(ce)) == HOMOGENIZATION_RGC_ID) then
|
|
|
|
do co = 1, homogenization_Nconstituents(material_homogenizationID(ce))
|
2021-02-23 16:14:39 +05:30
|
|
|
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)
|
2021-11-15 23:05:44 +05:30
|
|
|
end do
|
2021-04-06 15:35:47 +05:30
|
|
|
doneAndHappy = RGC_updateState(Ps,Fs,subF,subdt,dPdFs,ce)
|
2020-12-28 14:25:54 +05:30
|
|
|
else
|
|
|
|
doneAndHappy = .true.
|
2021-11-15 23:05:44 +05:30
|
|
|
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.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2021-02-23 17:47:51 +05:30
|
|
|
module subroutine mechanical_results(group_base,ho)
|
2020-12-16 15:51:24 +05:30
|
|
|
|
|
|
|
character(len=*), intent(in) :: group_base
|
2021-02-23 17:47:51 +05:30
|
|
|
integer, intent(in) :: ho
|
2020-12-16 15:51:24 +05:30
|
|
|
|
2022-02-19 20:05:38 +05:30
|
|
|
integer :: ou
|
2020-12-16 15:51:24 +05:30
|
|
|
character(len=:), allocatable :: group
|
|
|
|
|
2022-02-19 20:05:38 +05:30
|
|
|
|
2021-03-25 23:52:59 +05:30
|
|
|
group = trim(group_base)//'/mechanical'
|
2020-12-16 15:51:24 +05:30
|
|
|
call results_closeGroup(results_addGroup(group))
|
|
|
|
|
2021-02-23 17:47:51 +05:30
|
|
|
select case(homogenization_type(ho))
|
2020-12-16 15:51:24 +05:30
|
|
|
|
|
|
|
case(HOMOGENIZATION_rgc_ID)
|
2021-04-06 15:35:47 +05:30
|
|
|
call RGC_results(ho,group)
|
2020-12-16 15:51:24 +05:30
|
|
|
|
|
|
|
end select
|
|
|
|
|
2022-02-19 20:05:38 +05:30
|
|
|
do ou = 1, size(output_mechanical(1)%label)
|
|
|
|
|
|
|
|
select case (output_mechanical(ho)%label(ou))
|
|
|
|
case('F')
|
|
|
|
call results_writeDataset(reshape(homogenization_F,[3,3,discretization_nCells]),group,'F', &
|
|
|
|
'deformation gradient','1')
|
|
|
|
case('P')
|
|
|
|
call results_writeDataset(reshape(homogenization_P,[3,3,discretization_nCells]),group,'P', &
|
2022-02-23 03:46:14 +05:30
|
|
|
'first Piola-Kirchhoff stress','Pa')
|
2022-02-19 20:05:38 +05:30
|
|
|
end select
|
|
|
|
end do
|
2020-12-16 15:51:24 +05:30
|
|
|
|
2021-02-09 03:51:53 +05:30
|
|
|
end subroutine mechanical_results
|
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
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2022-02-19 18:26:24 +05:30
|
|
|
subroutine parseMechanical()
|
2021-04-07 15:18:04 +05:30
|
|
|
|
|
|
|
class(tNode), pointer :: &
|
|
|
|
material_homogenization, &
|
|
|
|
homog, &
|
2022-02-19 18:49:11 +05:30
|
|
|
mechanical
|
|
|
|
|
|
|
|
integer :: ho
|
2021-04-07 15:18:04 +05:30
|
|
|
|
|
|
|
|
|
|
|
material_homogenization => config_material%get('homogenization')
|
|
|
|
|
|
|
|
allocate(homogenization_type(size(material_name_homogenization)), source=HOMOGENIZATION_undefined_ID)
|
2022-02-19 18:49:11 +05:30
|
|
|
allocate(output_mechanical(size(material_name_homogenization)))
|
|
|
|
|
|
|
|
do ho=1, size(material_name_homogenization)
|
|
|
|
homog => material_homogenization%get(ho)
|
|
|
|
mechanical => homog%get('mechanical')
|
|
|
|
#if defined(__GFORTRAN__)
|
|
|
|
output_mechanical(ho)%label = output_as1dString(mechanical)
|
|
|
|
#else
|
|
|
|
output_mechanical(ho)%label = mechanical%get_as1dString('output',defaultVal=emptyStringArray)
|
|
|
|
#endif
|
|
|
|
select case (mechanical%get_asString('type'))
|
2021-04-07 15:18:04 +05:30
|
|
|
case('pass')
|
2022-02-19 18:49:11 +05:30
|
|
|
homogenization_type(ho) = HOMOGENIZATION_NONE_ID
|
2021-04-07 15:18:04 +05:30
|
|
|
case('isostrain')
|
2022-02-19 18:49:11 +05:30
|
|
|
homogenization_type(ho) = HOMOGENIZATION_ISOSTRAIN_ID
|
2021-04-07 15:18:04 +05:30
|
|
|
case('RGC')
|
2022-02-19 18:49:11 +05:30
|
|
|
homogenization_type(ho) = HOMOGENIZATION_RGC_ID
|
2021-04-07 15:18:04 +05:30
|
|
|
case default
|
2022-02-19 18:49:11 +05:30
|
|
|
call IO_error(500,ext_msg=mechanical%get_asString('type'))
|
2021-04-07 15:18:04 +05:30
|
|
|
end select
|
2021-11-15 23:05:44 +05:30
|
|
|
end do
|
2021-04-07 15:18:04 +05:30
|
|
|
|
2022-02-19 18:26:24 +05:30
|
|
|
end subroutine parseMechanical
|
2021-04-07 15:18:04 +05:30
|
|
|
|
|
|
|
|
2021-02-13 23:27:41 +05:30
|
|
|
end submodule mechanical
|