avoid repetition
This commit is contained in:
parent
8b7f777186
commit
071c1a5ad4
|
@ -32,25 +32,6 @@ submodule(homogenization) mechanical
|
||||||
end subroutine RGC_partitionDeformation
|
end subroutine RGC_partitionDeformation
|
||||||
|
|
||||||
|
|
||||||
module subroutine isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,ho)
|
|
||||||
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) :: ho
|
|
||||||
end subroutine isostrain_averageStressAndItsTangent
|
|
||||||
|
|
||||||
module subroutine RGC_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,ho)
|
|
||||||
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) :: ho
|
|
||||||
end subroutine RGC_averageStressAndItsTangent
|
|
||||||
|
|
||||||
|
|
||||||
module function RGC_updateState(P,F,avgF,dt,dPdF,ce) result(doneAndHappy)
|
module function RGC_updateState(P,F,avgF,dt,dPdF,ce) result(doneAndHappy)
|
||||||
logical, dimension(2) :: doneAndHappy
|
logical, dimension(2) :: doneAndHappy
|
||||||
real(pReal), dimension(:,:,:), intent(in) :: &
|
real(pReal), dimension(:,:,:), intent(in) :: &
|
||||||
|
@ -148,39 +129,21 @@ module subroutine mechanical_homogenize(dt,ce)
|
||||||
integer, intent(in) :: ce
|
integer, intent(in) :: ce
|
||||||
|
|
||||||
integer :: co
|
integer :: co
|
||||||
real(pReal) :: dPdFs(3,3,3,3,homogenization_Nconstituents(material_homogenizationID(ce)))
|
|
||||||
real(pReal) :: Ps(3,3,homogenization_Nconstituents(material_homogenizationID(ce)))
|
|
||||||
|
|
||||||
|
|
||||||
chosenHomogenization: select case(homogenization_type(material_homogenizationID(ce)))
|
homogenization_P(1:3,1:3,ce) = phase_P(1,ce)
|
||||||
|
homogenization_dPdF(1:3,1:3,1:3,1:3,ce) = phase_mechanical_dPdF(dt,1,ce)
|
||||||
|
do co = 2, homogenization_Nconstituents(material_homogenizationID(ce))
|
||||||
|
homogenization_P(1:3,1:3,ce) = homogenization_P(1:3,1:3,ce) &
|
||||||
|
+ phase_P(co,ce)
|
||||||
|
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(dt,co,ce)
|
||||||
|
enddo
|
||||||
|
|
||||||
case (HOMOGENIZATION_NONE_ID) chosenHomogenization
|
homogenization_P(1:3,1:3,ce) = homogenization_P(1:3,1:3,ce) &
|
||||||
homogenization_P(1:3,1:3,ce) = phase_P(1,ce)
|
/ real(homogenization_Nconstituents(material_homogenizationID(ce)),pReal)
|
||||||
homogenization_dPdF(1:3,1:3,1:3,1:3,ce) = phase_mechanical_dPdF(dt,1,ce)
|
homogenization_dPdF(1:3,1:3,1:3,1:3,ce) = homogenization_dPdF(1:3,1:3,1:3,1:3,ce) &
|
||||||
|
/ real(homogenization_Nconstituents(material_homogenizationID(ce)),pReal)
|
||||||
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
|
|
||||||
do co = 1, homogenization_Nconstituents(material_homogenizationID(ce))
|
|
||||||
dPdFs(:,:,:,:,co) = phase_mechanical_dPdF(dt,co,ce)
|
|
||||||
Ps(:,:,co) = phase_P(co,ce)
|
|
||||||
enddo
|
|
||||||
call isostrain_averageStressAndItsTangent(&
|
|
||||||
homogenization_P(1:3,1:3,ce), &
|
|
||||||
homogenization_dPdF(1:3,1:3,1:3,1:3,ce),&
|
|
||||||
Ps,dPdFs, &
|
|
||||||
material_homogenizationID(ce))
|
|
||||||
|
|
||||||
case (HOMOGENIZATION_RGC_ID) chosenHomogenization
|
|
||||||
do co = 1, homogenization_Nconstituents(material_homogenizationID(ce))
|
|
||||||
dPdFs(:,:,:,:,co) = phase_mechanical_dPdF(dt,co,ce)
|
|
||||||
Ps(:,:,co) = phase_P(co,ce)
|
|
||||||
enddo
|
|
||||||
call RGC_averageStressAndItsTangent(&
|
|
||||||
homogenization_P(1:3,1:3,ce), &
|
|
||||||
homogenization_dPdF(1:3,1:3,1:3,1:3,ce),&
|
|
||||||
Ps,dPdFs, &
|
|
||||||
material_homogenizationID(ce))
|
|
||||||
|
|
||||||
end select chosenHomogenization
|
|
||||||
|
|
||||||
end subroutine mechanical_homogenize
|
end subroutine mechanical_homogenize
|
||||||
|
|
||||||
|
|
|
@ -89,7 +89,8 @@ module subroutine RGC_init(num_homogMech)
|
||||||
|
|
||||||
print'(/,a)', ' <<<+- homogenization:mechanical:RGC init -+>>>'
|
print'(/,a)', ' <<<+- homogenization:mechanical:RGC init -+>>>'
|
||||||
|
|
||||||
print'(a,i2)', ' # instances: ',count(homogenization_type == HOMOGENIZATION_RGC_ID); flush(IO_STDOUT)
|
print'(a,i2)', ' # instances: ',count(homogenization_type == HOMOGENIZATION_RGC_ID)
|
||||||
|
flush(IO_STDOUT)
|
||||||
|
|
||||||
print*, 'D.D. Tjahjanto et al., International Journal of Material Forming 2(1):939–942, 2009'
|
print*, 'D.D. Tjahjanto et al., International Journal of Material Forming 2(1):939–942, 2009'
|
||||||
print*, 'https://doi.org/10.1007/s12289-009-0619-1'//IO_EOL
|
print*, 'https://doi.org/10.1007/s12289-009-0619-1'//IO_EOL
|
||||||
|
@ -207,7 +208,7 @@ module subroutine RGC_partitionDeformation(F,avgF,ce)
|
||||||
integer :: iGrain,iFace,i,j,ho,en
|
integer :: iGrain,iFace,i,j,ho,en
|
||||||
|
|
||||||
associate(prm => param(material_homogenizationID(ce)))
|
associate(prm => param(material_homogenizationID(ce)))
|
||||||
|
|
||||||
ho = material_homogenizationID(ce)
|
ho = material_homogenizationID(ce)
|
||||||
en = material_homogenizationEntry(ce)
|
en = material_homogenizationEntry(ce)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -700,24 +701,6 @@ module function RGC_updateState(P,F,avgF,dt,dPdF,ce) result(doneAndHappy)
|
||||||
end function RGC_updateState
|
end function RGC_updateState
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief derive average stress and stiffness from constituent quantities
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module subroutine RGC_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,ho)
|
|
||||||
|
|
||||||
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) :: ho
|
|
||||||
|
|
||||||
avgP = sum(P,3) /real(product(param(ho)%N_constituents),pReal)
|
|
||||||
dAvgPdAvgF = sum(dPdF,5)/real(product(param(ho)%N_constituents),pReal)
|
|
||||||
|
|
||||||
end subroutine RGC_averageStressAndItsTangent
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief writes results to HDF5 output file
|
!> @brief writes results to HDF5 output file
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -802,7 +785,7 @@ pure function interfaceNormal(intFace,ho,en)
|
||||||
interfaceNormal(nPos) = real(intFace(1)/abs(intFace(1)),pReal) ! get the normal vector w.r.t. cluster axis
|
interfaceNormal(nPos) = real(intFace(1)/abs(intFace(1)),pReal) ! get the normal vector w.r.t. cluster axis
|
||||||
|
|
||||||
interfaceNormal = matmul(dst%orientation(1:3,1:3,en),interfaceNormal) ! map the normal vector into sample coordinate system (basis)
|
interfaceNormal = matmul(dst%orientation(1:3,1:3,en),interfaceNormal) ! map the normal vector into sample coordinate system (basis)
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
end function interfaceNormal
|
end function interfaceNormal
|
||||||
|
|
|
@ -6,21 +6,6 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
submodule(homogenization:mechanical) isostrain
|
submodule(homogenization:mechanical) isostrain
|
||||||
|
|
||||||
enum, bind(c); enumerator :: &
|
|
||||||
parallel_ID, &
|
|
||||||
average_ID
|
|
||||||
end enum
|
|
||||||
|
|
||||||
type :: tParameters !< container type for internal constitutive parameters
|
|
||||||
integer :: &
|
|
||||||
N_constituents
|
|
||||||
integer(kind(average_ID)) :: &
|
|
||||||
mapping
|
|
||||||
end type
|
|
||||||
|
|
||||||
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstances)
|
|
||||||
|
|
||||||
|
|
||||||
contains
|
contains
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -29,42 +14,21 @@ contains
|
||||||
module subroutine isostrain_init
|
module subroutine isostrain_init
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
h, &
|
ho, &
|
||||||
Nmaterialpoints
|
Nmaterialpoints
|
||||||
class(tNode), pointer :: &
|
|
||||||
material_homogenization, &
|
|
||||||
homog, &
|
|
||||||
homogMech
|
|
||||||
|
|
||||||
print'(/,a)', ' <<<+- homogenization:mechanical:isostrain init -+>>>'
|
print'(/,a)', ' <<<+- homogenization:mechanical:isostrain init -+>>>'
|
||||||
|
|
||||||
print'(a,i2)', ' # instances: ',count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID); flush(IO_STDOUT)
|
print'(a,i2)', ' # instances: ',count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)
|
||||||
|
flush(IO_STDOUT)
|
||||||
|
|
||||||
material_homogenization => config_material%get('homogenization')
|
do ho = 1, size(homogenization_type)
|
||||||
allocate(param(material_homogenization%length)) ! one container of parameters per homog
|
if (homogenization_type(ho) /= HOMOGENIZATION_ISOSTRAIN_ID) cycle
|
||||||
|
|
||||||
do h = 1, size(homogenization_type)
|
Nmaterialpoints = count(material_homogenizationAt == ho)
|
||||||
if (homogenization_type(h) /= HOMOGENIZATION_ISOSTRAIN_ID) cycle
|
homogState(ho)%sizeState = 0
|
||||||
homog => material_homogenization%get(h)
|
allocate(homogState(ho)%state0(0,Nmaterialpoints))
|
||||||
homogMech => homog%get('mechanical')
|
allocate(homogState(ho)%state (0,Nmaterialpoints))
|
||||||
associate(prm => param(h))
|
|
||||||
|
|
||||||
prm%N_constituents = homogenization_Nconstituents(h)
|
|
||||||
select case(homogMech%get_asString('mapping',defaultVal = 'sum'))
|
|
||||||
case ('sum')
|
|
||||||
prm%mapping = parallel_ID
|
|
||||||
case ('avg')
|
|
||||||
prm%mapping = average_ID
|
|
||||||
case default
|
|
||||||
call IO_error(211,ext_msg='sum'//' (isostrain)')
|
|
||||||
end select
|
|
||||||
|
|
||||||
Nmaterialpoints = count(material_homogenizationAt == h)
|
|
||||||
homogState(h)%sizeState = 0
|
|
||||||
allocate(homogState(h)%state0 (0,Nmaterialpoints))
|
|
||||||
allocate(homogState(h)%state (0,Nmaterialpoints))
|
|
||||||
|
|
||||||
end associate
|
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
@ -80,36 +44,9 @@ module subroutine isostrain_partitionDeformation(F,avgF)
|
||||||
|
|
||||||
real(pReal), dimension (3,3), intent(in) :: avgF !< average deformation gradient at material point
|
real(pReal), dimension (3,3), intent(in) :: avgF !< average deformation gradient at material point
|
||||||
|
|
||||||
|
|
||||||
F = spread(avgF,3,size(F,3))
|
F = spread(avgF,3,size(F,3))
|
||||||
|
|
||||||
end subroutine isostrain_partitionDeformation
|
end subroutine isostrain_partitionDeformation
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief derive average stress and stiffness from constituent quantities
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module subroutine isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,ho)
|
|
||||||
|
|
||||||
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) :: ho
|
|
||||||
|
|
||||||
associate(prm => param(ho))
|
|
||||||
|
|
||||||
select case (prm%mapping)
|
|
||||||
case (parallel_ID)
|
|
||||||
avgP = sum(P,3)
|
|
||||||
dAvgPdAvgF = sum(dPdF,5)
|
|
||||||
case (average_ID)
|
|
||||||
avgP = sum(P,3) /real(prm%N_constituents,pReal)
|
|
||||||
dAvgPdAvgF = sum(dPdF,5)/real(prm%N_constituents,pReal)
|
|
||||||
end select
|
|
||||||
|
|
||||||
end associate
|
|
||||||
|
|
||||||
end subroutine isostrain_averageStressAndItsTangent
|
|
||||||
|
|
||||||
end submodule isostrain
|
end submodule isostrain
|
||||||
|
|
|
@ -14,25 +14,24 @@ contains
|
||||||
module subroutine pass_init
|
module subroutine pass_init
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
Ninstances, &
|
ho, &
|
||||||
h, &
|
|
||||||
Nmaterialpoints
|
Nmaterialpoints
|
||||||
|
|
||||||
print'(/,a)', ' <<<+- homogenization:mechanical:pass init -+>>>'
|
print'(/,a)', ' <<<+- homogenization:mechanical:pass init -+>>>'
|
||||||
|
|
||||||
Ninstances = count(homogenization_type == HOMOGENIZATION_NONE_ID)
|
print'(a,i2)', ' # instances: ',count(homogenization_type == HOMOGENIZATION_NONE_ID)
|
||||||
print'(a,i2)', ' # instances: ',Ninstances; flush(IO_STDOUT)
|
flush(IO_STDOUT)
|
||||||
|
|
||||||
do h = 1, size(homogenization_type)
|
do ho = 1, size(homogenization_type)
|
||||||
if(homogenization_type(h) /= HOMOGENIZATION_NONE_ID) cycle
|
if(homogenization_type(ho) /= HOMOGENIZATION_NONE_ID) cycle
|
||||||
|
|
||||||
if(homogenization_Nconstituents(h) /= 1) &
|
if(homogenization_Nconstituents(ho) /= 1) &
|
||||||
call IO_error(211,ext_msg='N_constituents (pass)')
|
call IO_error(211,ext_msg='N_constituents (pass)')
|
||||||
|
|
||||||
Nmaterialpoints = count(material_homogenizationAt == h)
|
Nmaterialpoints = count(material_homogenizationAt == ho)
|
||||||
homogState(h)%sizeState = 0
|
homogState(ho)%sizeState = 0
|
||||||
allocate(homogState(h)%state0 (0,Nmaterialpoints))
|
allocate(homogState(ho)%state0(0,Nmaterialpoints))
|
||||||
allocate(homogState(h)%state (0,Nmaterialpoints))
|
allocate(homogState(ho)%state (0,Nmaterialpoints))
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue