DAMASK_EICMD/src/homogenization_mechanical_i...

118 lines
4.8 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
2020-03-17 12:47:14 +05:30
enum, bind(c); enumerator :: &
parallel_ID, &
average_ID
2019-04-06 00:18:20 +05:30
end enum
type :: tParameters !< container type for internal constitutive parameters
2019-04-06 00:18:20 +05:30
integer :: &
2020-09-23 05:03:19 +05:30
N_constituents
2019-04-06 00:18:20 +05:30
integer(kind(average_ID)) :: &
mapping
end type
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstances)
contains
!--------------------------------------------------------------------------------------------------
!> @brief allocates all neccessary fields, reads information from material configuration file
!--------------------------------------------------------------------------------------------------
2021-02-09 03:51:53 +05:30
module subroutine mechanical_isostrain_init
2019-05-15 02:42:32 +05:30
2019-04-06 00:18:20 +05:30
integer :: &
Ninstances, &
2019-04-06 00:18:20 +05:30
h, &
Nmaterialpoints
2020-08-15 19:32:10 +05:30
class(tNode), pointer :: &
material_homogenization, &
homog, &
homogMech
2021-02-13 23:27:41 +05:30
print'(/,a)', ' <<<+- homogenization:mechanical:isostrain init -+>>>'
Ninstances = count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)
print'(a,i2)', ' # instances: ',Ninstances; flush(IO_STDOUT)
allocate(param(Ninstances)) ! one container of parameters per instance
2020-08-15 19:32:10 +05:30
material_homogenization => config_material%get('homogenization')
2019-04-06 00:18:20 +05:30
do h = 1, size(homogenization_type)
if (homogenization_type(h) /= HOMOGENIZATION_ISOSTRAIN_ID) cycle
2020-08-15 19:32:10 +05:30
homog => material_homogenization%get(h)
2020-11-18 01:54:40 +05:30
homogMech => homog%get('mechanics')
2020-08-15 19:32:10 +05:30
associate(prm => param(homogenization_typeInstance(h)))
prm%N_constituents = homogenization_Nconstituents(h)
2020-08-15 19:32:10 +05:30
select case(homogMech%get_asString('mapping',defaultVal = 'sum'))
2019-04-06 00:18:20 +05:30
case ('sum')
prm%mapping = parallel_ID
case ('avg')
prm%mapping = average_ID
case default
2021-02-09 03:51:53 +05:30
call IO_error(211,ext_msg='sum'//' (mechanical_isostrain)')
2019-04-06 00:18:20 +05:30
end select
Nmaterialpoints = count(material_homogenizationAt == h)
2019-04-06 00:18:20 +05:30
homogState(h)%sizeState = 0
allocate(homogState(h)%state0 (0,Nmaterialpoints))
allocate(homogState(h)%state (0,Nmaterialpoints))
2019-04-06 00:18:20 +05:30
end associate
2019-04-06 00:18:20 +05:30
enddo
2021-02-09 03:51:53 +05:30
end subroutine mechanical_isostrain_init
!--------------------------------------------------------------------------------------------------
!> @brief partitions the deformation gradient onto the constituents
!--------------------------------------------------------------------------------------------------
2021-02-09 03:51:53 +05:30
module subroutine mechanical_isostrain_partitionDeformation(F,avgF)
2019-04-06 00:18:20 +05:30
real(pReal), dimension (:,:,:), intent(out) :: F !< partitioned deformation gradient
2019-04-06 00:18:20 +05:30
real(pReal), dimension (3,3), intent(in) :: avgF !< average deformation gradient at material point
2019-04-06 00:18:20 +05:30
F = spread(avgF,3,size(F,3))
2021-02-09 03:51:53 +05:30
end subroutine mechanical_isostrain_partitionDeformation
!--------------------------------------------------------------------------------------------------
!> @brief derive average stress and stiffness from constituent quantities
!--------------------------------------------------------------------------------------------------
2021-02-09 03:51:53 +05:30
module subroutine mechanical_isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,instance)
2019-04-06 00:18:20 +05:30
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
2019-04-06 00:18:20 +05:30
real(pReal), dimension (:,:,:), intent(in) :: P !< partitioned stresses
real(pReal), dimension (:,:,:,:,:), intent(in) :: dPdF !< partitioned stiffnesses
integer, intent(in) :: instance
2019-04-06 00:18:20 +05:30
associate(prm => param(instance))
2019-04-06 00:18:20 +05:30
select case (prm%mapping)
case (parallel_ID)
avgP = sum(P,3)
dAvgPdAvgF = sum(dPdF,5)
case (average_ID)
2020-09-23 05:03:19 +05:30
avgP = sum(P,3) /real(prm%N_constituents,pReal)
dAvgPdAvgF = sum(dPdF,5)/real(prm%N_constituents,pReal)
2019-04-06 00:18:20 +05:30
end select
2019-04-06 00:18:20 +05:30
end associate
2021-02-09 03:51:53 +05:30
end subroutine mechanical_isostrain_averageStressAndItsTangent
2021-01-26 16:11:19 +05:30
end submodule isostrain