use cell mapping
This commit is contained in:
parent
341e8ddd6a
commit
9f78e27724
|
@ -95,12 +95,11 @@ module homogenization
|
|||
module subroutine damage_init
|
||||
end subroutine damage_init
|
||||
|
||||
module subroutine mechanical_partition(subF,ip,el)
|
||||
module subroutine mechanical_partition(subF,ce)
|
||||
real(pReal), intent(in), dimension(3,3) :: &
|
||||
subF
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point
|
||||
el !< element number
|
||||
ce
|
||||
end subroutine mechanical_partition
|
||||
|
||||
module subroutine thermal_partition(ce)
|
||||
|
@ -318,7 +317,7 @@ subroutine materialpoint_stressAndItsTangent(dt,FEsolving_execIP,FEsolving_execE
|
|||
|
||||
|
||||
if (.not. doneAndHappy(1)) then
|
||||
call mechanical_partition(homogenization_F(1:3,1:3,ce),ip,el)
|
||||
call mechanical_partition(homogenization_F(1:3,1:3,ce),ce)
|
||||
converged = .true.
|
||||
do co = 1, myNgrains
|
||||
converged = converged .and. crystallite_stress(dt,co,ip,el)
|
||||
|
|
|
@ -24,12 +24,11 @@ submodule(homogenization) mechanical
|
|||
real(pReal), dimension (3,3), intent(in) :: avgF !< average deformation gradient at material point
|
||||
end subroutine mechanical_isostrain_partitionDeformation
|
||||
|
||||
module subroutine mechanical_RGC_partitionDeformation(F,avgF,instance,of)
|
||||
module subroutine mechanical_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
|
||||
integer, intent(in) :: &
|
||||
instance, &
|
||||
of
|
||||
ce
|
||||
end subroutine mechanical_RGC_partitionDeformation
|
||||
|
||||
|
||||
|
@ -104,19 +103,18 @@ end subroutine mechanical_init
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief Partition F onto the individual constituents.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module subroutine mechanical_partition(subF,ip,el)
|
||||
module subroutine mechanical_partition(subF,ce)
|
||||
|
||||
real(pReal), intent(in), dimension(3,3) :: &
|
||||
subF
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point
|
||||
el !< element number
|
||||
ce
|
||||
|
||||
integer :: co
|
||||
real(pReal), dimension (3,3,homogenization_Nconstituents(material_homogenizationAt(el))) :: Fs
|
||||
real(pReal), dimension (3,3,homogenization_Nconstituents(material_homogenizationAt2(ce))) :: Fs
|
||||
|
||||
|
||||
chosenHomogenization: select case(homogenization_type(material_homogenizationAt(el)))
|
||||
chosenHomogenization: select case(homogenization_type(material_homogenizationAt2(ce)))
|
||||
|
||||
case (HOMOGENIZATION_NONE_ID) chosenHomogenization
|
||||
Fs(1:3,1:3,1) = subF
|
||||
|
@ -125,12 +123,12 @@ module subroutine mechanical_partition(subF,ip,el)
|
|||
call mechanical_isostrain_partitionDeformation(Fs,subF)
|
||||
|
||||
case (HOMOGENIZATION_RGC_ID) chosenHomogenization
|
||||
call mechanical_RGC_partitionDeformation(Fs,subF,ip,el)
|
||||
call mechanical_RGC_partitionDeformation(Fs,subF,ce)
|
||||
|
||||
end select chosenHomogenization
|
||||
|
||||
do co = 1,homogenization_Nconstituents(material_homogenizationAt(el))
|
||||
call phase_mechanical_setF(Fs(1:3,1:3,co),co,ip,el)
|
||||
do co = 1,homogenization_Nconstituents(material_homogenizationAt2(ce))
|
||||
call phase_mechanical_setF(Fs(1:3,1:3,co),co,ce)
|
||||
enddo
|
||||
|
||||
|
||||
|
|
|
@ -196,22 +196,22 @@ end subroutine mechanical_RGC_init
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief partitions the deformation gradient onto the constituents
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module subroutine mechanical_RGC_partitionDeformation(F,avgF,instance,of)
|
||||
module subroutine mechanical_RGC_partitionDeformation(F,avgF,ce)
|
||||
|
||||
real(pReal), dimension (:,:,:), intent(out) :: F !< partitioned F per grain
|
||||
|
||||
real(pReal), dimension (3,3), intent(in) :: avgF !< averaged F
|
||||
integer, intent(in) :: &
|
||||
instance, &
|
||||
of
|
||||
ce
|
||||
|
||||
real(pReal), dimension(3) :: aVect,nVect
|
||||
integer, dimension(4) :: intFace
|
||||
integer, dimension(3) :: iGrain3
|
||||
integer :: iGrain,iFace,i,j
|
||||
|
||||
associate(prm => param(instance))
|
||||
integer :: iGrain,iFace,i,j,me
|
||||
|
||||
associate(prm => param(homogenization_typeInstance(material_homogenizationAt2(ce))))
|
||||
|
||||
me = material_homogenizationMemberAt2(ce)
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! compute the deformation gradient of individual grains due to relaxations
|
||||
F = 0.0_pReal
|
||||
|
@ -219,8 +219,8 @@ module subroutine mechanical_RGC_partitionDeformation(F,avgF,instance,of)
|
|||
iGrain3 = grain1to3(iGrain,prm%N_constituents)
|
||||
do iFace = 1,6
|
||||
intFace = getInterface(iFace,iGrain3) ! identifying 6 interfaces of each grain
|
||||
aVect = relaxationVector(intFace,instance,of) ! get the relaxation vectors for each interface from global relaxation vector array
|
||||
nVect = interfaceNormal(intFace,instance,of)
|
||||
aVect = relaxationVector(intFace,ce,me) ! get the relaxation vectors for each interface from global relaxation vector array
|
||||
nVect = interfaceNormal(intFace,ce,me)
|
||||
forall (i=1:3,j=1:3) &
|
||||
F(i,j,iGrain) = F(i,j,iGrain) + aVect(i)*nVect(j) ! calculating deformation relaxations due to interface relaxation
|
||||
enddo
|
||||
|
@ -760,11 +760,11 @@ end subroutine mechanical_RGC_results
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief collect relaxation vectors of an interface
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
pure function relaxationVector(intFace,instance,of)
|
||||
pure function relaxationVector(intFace,ce,me)
|
||||
|
||||
real(pReal), dimension (3) :: relaxationVector
|
||||
|
||||
integer, intent(in) :: instance,of
|
||||
integer, intent(in) :: ce,me
|
||||
integer, dimension(4), intent(in) :: intFace !< set of interface ID in 4D array (normal and position)
|
||||
|
||||
integer :: iNum
|
||||
|
@ -772,29 +772,35 @@ pure function relaxationVector(intFace,instance,of)
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
! collect the interface relaxation vector from the global state array
|
||||
|
||||
iNum = interface4to1(intFace,param(instance)%N_constituents) ! identify the position of the interface in global state array
|
||||
associate (prm => param(homogenization_typeInstance(material_homogenizationAt2(ce))), &
|
||||
stt => state(homogenization_typeInstance(material_homogenizationAt2(ce))))
|
||||
|
||||
iNum = interface4to1(intFace,prm%N_constituents) ! identify the position of the interface in global state array
|
||||
if (iNum > 0) then
|
||||
relaxationVector = state(instance)%relaxationVector((3*iNum-2):(3*iNum),of)
|
||||
relaxationVector = stt%relaxationVector((3*iNum-2):(3*iNum),me)
|
||||
else
|
||||
relaxationVector = 0.0_pReal
|
||||
endif
|
||||
|
||||
end associate
|
||||
|
||||
end function relaxationVector
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief identify the normal of an interface
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
pure function interfaceNormal(intFace,instance,of)
|
||||
pure function interfaceNormal(intFace,ce,me)
|
||||
|
||||
real(pReal), dimension(3) :: interfaceNormal
|
||||
|
||||
integer, dimension(4), intent(in) :: intFace !< interface ID in 4D array (normal and position)
|
||||
integer, intent(in) :: &
|
||||
instance, &
|
||||
of
|
||||
ce, &
|
||||
me
|
||||
|
||||
integer :: nPos
|
||||
associate (dst => dependentState(homogenization_typeInstance(material_homogenizationAt2(ce))))
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! get the normal of the interface, identified from the value of intFace(1)
|
||||
|
@ -802,7 +808,9 @@ pure function interfaceNormal(intFace,instance,of)
|
|||
nPos = abs(intFace(1)) ! identify the position of the interface in global state array
|
||||
interfaceNormal(nPos) = real(intFace(1)/abs(intFace(1)),pReal) ! get the normal vector w.r.t. cluster axis
|
||||
|
||||
interfaceNormal = matmul(dependentState(instance)%orientation(1:3,1:3,of),interfaceNormal) ! map the normal vector into sample coordinate system (basis)
|
||||
interfaceNormal = matmul(dst%orientation(1:3,1:3,me),interfaceNormal) ! map the normal vector into sample coordinate system (basis)
|
||||
|
||||
end associate
|
||||
|
||||
end function interfaceNormal
|
||||
|
||||
|
|
|
@ -183,9 +183,9 @@ module phase
|
|||
end function damage_phi
|
||||
|
||||
|
||||
module subroutine phase_mechanical_setF(F,co,ip,el)
|
||||
module subroutine phase_mechanical_setF(F,co,ce)
|
||||
real(pReal), dimension(3,3), intent(in) :: F
|
||||
integer, intent(in) :: co, ip, el
|
||||
integer, intent(in) :: co, ce
|
||||
end subroutine phase_mechanical_setF
|
||||
|
||||
module subroutine phase_thermal_setField(T,dot_T, co,ce)
|
||||
|
|
|
@ -1481,13 +1481,13 @@ end function phase_mechanical_getP
|
|||
|
||||
|
||||
! setter for homogenization
|
||||
module subroutine phase_mechanical_setF(F,co,ip,el)
|
||||
module subroutine phase_mechanical_setF(F,co,ce)
|
||||
|
||||
real(pReal), dimension(3,3), intent(in) :: F
|
||||
integer, intent(in) :: co, ip, el
|
||||
integer, intent(in) :: co, ce
|
||||
|
||||
|
||||
phase_mechanical_F(material_phaseAt(co,el))%data(1:3,1:3,material_phaseMemberAt(co,ip,el)) = F
|
||||
phase_mechanical_F(material_phaseAt2(co,ce))%data(1:3,1:3,material_phaseMemberAt2(co,ce)) = F
|
||||
|
||||
end subroutine phase_mechanical_setF
|
||||
|
||||
|
|
Loading…
Reference in New Issue