DAMASK_EICMD/src/homogenization_mechanical_i...

53 lines
2.1 KiB
Fortran
Raw Normal View History

!--------------------------------------------------------------------------------------------------
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @brief Isostrain (full constraint Taylor assuption) homogenization scheme
!--------------------------------------------------------------------------------------------------
2021-02-13 23:27:41 +05:30
submodule(homogenization:mechanical) isostrain
contains
!--------------------------------------------------------------------------------------------------
!> @brief allocates all neccessary fields, reads information from material configuration file
!--------------------------------------------------------------------------------------------------
module subroutine isostrain_init
2019-05-15 02:42:32 +05:30
2019-04-06 00:18:20 +05:30
integer :: &
2021-04-11 15:48:26 +05:30
ho, &
2021-05-23 13:40:25 +05:30
Nmembers
print'(/,1x,a)', '<<<+- homogenization:mechanical:isostrain init -+>>>'
2022-02-24 16:39:47 +05:30
print'(/,a,i0)', ' # homogenizations: ',count(mechanical_type == MECHANICAL_ISOSTRAIN_ID)
2021-04-11 15:48:26 +05:30
flush(IO_STDOUT)
2022-02-24 16:39:47 +05:30
do ho = 1, size(mechanical_type)
if (mechanical_type(ho) /= MECHANICAL_ISOSTRAIN_ID) cycle
2023-01-23 13:01:59 +05:30
Nmembers = count(material_ID_homogenization == ho)
2021-04-11 15:48:26 +05:30
homogState(ho)%sizeState = 0
2021-05-23 13:40:25 +05:30
allocate(homogState(ho)%state0(0,Nmembers))
allocate(homogState(ho)%state (0,Nmembers))
end do
end subroutine isostrain_init
!--------------------------------------------------------------------------------------------------
!> @brief partitions the deformation gradient onto the constituents
!--------------------------------------------------------------------------------------------------
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
2021-04-11 15:48:26 +05:30
2019-04-06 00:18:20 +05:30
F = spread(avgF,3,size(F,3))
end subroutine isostrain_partitionDeformation
2021-01-26 16:11:19 +05:30
end submodule isostrain