consistent names

This commit is contained in:
Martin Diehl 2021-04-07 21:06:29 +02:00
parent c4b4ea8c21
commit 0fc7f66ef8
8 changed files with 44 additions and 47 deletions

View File

@ -196,7 +196,7 @@ function grid_damage_spectral_solution(timeinc) result(solution)
ce = 0
do k = 1, grid3; do j = 1, grid(2); do i = 1,grid(1)
ce = ce + 1
call damage_nonlocal_putNonLocalDamage(phi_current(i,j,k),ce)
call homogenization_set_phi(phi_current(i,j,k),ce)
enddo; enddo; enddo
call VecMin(solution_vec,devNull,phi_min,ierr); CHKERRQ(ierr)
@ -233,7 +233,7 @@ subroutine grid_damage_spectral_forward(cutBack)
call DMDAVecRestoreArrayF90(dm_local,solution_vec,x_scal,ierr); CHKERRQ(ierr)
do k = 1, grid3; do j = 1, grid(2); do i = 1,grid(1)
ce = ce + 1
call damage_nonlocal_putNonLocalDamage(phi_current(i,j,k),ce)
call homogenization_set_phi(phi_current(i,j,k),ce)
enddo; enddo; enddo
else
phi_lastInc = phi_current

View File

@ -176,11 +176,11 @@ module homogenization
phiDot
end subroutine damage_nonlocal_getSourceAndItsTangent
module subroutine damage_nonlocal_putNonLocalDamage(phi,ce)
module subroutine homogenization_set_phi(phi,ce)
integer, intent(in) :: ce
real(pReal), intent(in) :: &
phi
end subroutine damage_nonlocal_putNonLocalDamage
end subroutine homogenization_set_phi
end interface
@ -192,7 +192,7 @@ module homogenization
thermal_conduction_getSource, &
damage_nonlocal_getMobility, &
damage_nonlocal_getSourceAndItsTangent, &
damage_nonlocal_putNonLocalDamage, &
homogenization_set_phi, &
homogenization_thermal_setfield, &
homogenization_thermal_T, &
homogenization_forward, &

View File

@ -138,7 +138,7 @@ end subroutine damage_nonlocal_getSourceAndItsTangent
!--------------------------------------------------------------------------------------------------
!> @brief updated nonlocal damage field with solution from damage phase field PDE
!--------------------------------------------------------------------------------------------------
module subroutine damage_nonlocal_putNonLocalDamage(phi,ce)
module subroutine homogenization_set_phi(phi,ce)
integer, intent(in) :: ce
real(pReal), intent(in) :: &
@ -152,7 +152,7 @@ module subroutine damage_nonlocal_putNonLocalDamage(phi,ce)
damagestate_h(ho)%state(1,en) = phi
current(ho)%phi(en) = phi
end subroutine damage_nonlocal_putNonLocalDamage
end subroutine homogenization_set_phi
!--------------------------------------------------------------------------------------------------

View File

@ -132,7 +132,7 @@ module subroutine mechanical_partition(subF,ce)
end select chosenHomogenization
do co = 1,homogenization_Nconstituents(material_homogenizationID(ce))
call phase_mechanical_setF(Fs(1:3,1:3,co),co,ce)
call phase_set_F(Fs(1:3,1:3,co),co,ce)
enddo
@ -155,13 +155,13 @@ module subroutine mechanical_homogenize(dt,ce)
chosenHomogenization: select case(homogenization_type(material_homogenizationID(ce)))
case (HOMOGENIZATION_NONE_ID) chosenHomogenization
homogenization_P(1:3,1:3,ce) = phase_mechanical_getP(1,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)
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
do co = 1, homogenization_Nconstituents(material_homogenizationID(ce))
dPdFs(:,:,:,:,co) = phase_mechanical_dPdF(dt,co,ce)
Ps(:,:,co) = phase_mechanical_getP(co,ce)
Ps(:,:,co) = phase_P(co,ce)
enddo
call isostrain_averageStressAndItsTangent(&
homogenization_P(1:3,1:3,ce), &
@ -172,7 +172,7 @@ module subroutine mechanical_homogenize(dt,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_mechanical_getP(co,ce)
Ps(:,:,co) = phase_P(co,ce)
enddo
call RGC_averageStressAndItsTangent(&
homogenization_P(1:3,1:3,ce), &
@ -208,8 +208,8 @@ module function mechanical_updateState(subdt,subF,ce) result(doneAndHappy)
if (homogenization_type(material_homogenizationID(ce)) == HOMOGENIZATION_RGC_ID) then
do co = 1, homogenization_Nconstituents(material_homogenizationID(ce))
dPdFs(:,:,:,:,co) = phase_mechanical_dPdF(subdt,co,ce)
Fs(:,:,co) = phase_mechanical_getF(co,ce)
Ps(:,:,co) = phase_mechanical_getP(co,ce)
Fs(:,:,co) = phase_F(co,ce)
Ps(:,:,co) = phase_P(co,ce)
enddo
doneAndHappy = RGC_updateState(Ps,Fs,subF,subdt,dPdFs,ce)
else

View File

@ -145,20 +145,20 @@ module phase
real(pReal), dimension(3,3) :: L_p
end function mechanical_L_p
module function phase_mechanical_getF(co,ce) result(F)
module function phase_F(co,ce) result(F)
integer, intent(in) :: co, ce
real(pReal), dimension(3,3) :: F
end function phase_mechanical_getF
end function phase_F
module function mechanical_F_e(ph,me) result(F_e)
integer, intent(in) :: ph,me
real(pReal), dimension(3,3) :: F_e
end function mechanical_F_e
module function phase_mechanical_getP(co,ce) result(P)
module function phase_P(co,ce) result(P)
integer, intent(in) :: co, ce
real(pReal), dimension(3,3) :: P
end function phase_mechanical_getP
end function phase_P
module function phase_damage_get_phi(co,ip,el) result(phi)
integer, intent(in) :: co, ip, el
@ -181,10 +181,10 @@ module phase
end function damage_phi
module subroutine phase_mechanical_setF(F,co,ce)
module subroutine phase_set_F(F,co,ce)
real(pReal), dimension(3,3), intent(in) :: F
integer, intent(in) :: co, ce
end subroutine phase_mechanical_setF
end subroutine phase_set_F
module subroutine phase_thermal_setField(T,dot_T, co,ce)
real(pReal), intent(in) :: T, dot_T
@ -320,9 +320,9 @@ module phase
phase_thermal_setField, &
phase_damage_set_phi, &
phase_damage_get_phi, &
phase_mechanical_getP, &
phase_mechanical_setF, &
phase_mechanical_getF
phase_P, &
phase_set_F, &
phase_F
contains
@ -588,7 +588,7 @@ function crystallite_push33ToRef(co,ce, tensor33)
ph = material_phaseID(co,ce)
en = material_phaseEntry(co,ce)
T = matmul(material_orientation0(co,ph,en)%asMatrix(),transpose(math_inv33(phase_mechanical_getF(co,ce)))) ! ToDo: initial orientation correct?
T = matmul(material_orientation0(co,ph,en)%asMatrix(),transpose(math_inv33(phase_F(co,ce)))) ! ToDo: initial orientation correct?
crystallite_push33ToRef = matmul(transpose(T),matmul(tensor33,T))

View File

@ -120,9 +120,6 @@ module subroutine anisobrittle_dotState(S, ph,me)
S
integer :: &
sourceOffset, &
damageOffset, &
homog, &
i
real(pReal) :: &
traction_d, traction_t, traction_n, traction_crit

View File

@ -1421,20 +1421,6 @@ module function mechanical_L_p(ph,me) result(L_p)
end function mechanical_L_p
!----------------------------------------------------------------------------------------------
!< @brief Get deformation gradient (for use by homogenization)
!----------------------------------------------------------------------------------------------
module function phase_mechanical_getF(co,ce) result(F)
integer, intent(in) :: co, ce
real(pReal), dimension(3,3) :: F
F = phase_mechanical_F(material_phaseID(co,ce))%data(1:3,1:3,material_phaseEntry(co,ce))
end function phase_mechanical_getF
!----------------------------------------------------------------------------------------------
!< @brief Get elastic deformation gradient (for use by non-mech physics)
!----------------------------------------------------------------------------------------------
@ -1449,11 +1435,10 @@ module function mechanical_F_e(ph,me) result(F_e)
end function mechanical_F_e
!----------------------------------------------------------------------------------------------
!< @brief Get second Piola-Kichhoff stress (for use by homogenization)
!----------------------------------------------------------------------------------------------
module function phase_mechanical_getP(co,ce) result(P)
module function phase_P(co,ce) result(P)
integer, intent(in) :: co, ce
real(pReal), dimension(3,3) :: P
@ -1461,11 +1446,27 @@ module function phase_mechanical_getP(co,ce) result(P)
P = phase_mechanical_P(material_phaseID(co,ce))%data(1:3,1:3,material_phaseEntry(co,ce))
end function phase_mechanical_getP
end function phase_P
! setter for homogenization
module subroutine phase_mechanical_setF(F,co,ce)
!----------------------------------------------------------------------------------------------
!< @brief Get deformation gradient (for use by homogenization)
!----------------------------------------------------------------------------------------------
module function phase_F(co,ce) result(F)
integer, intent(in) :: co, ce
real(pReal), dimension(3,3) :: F
F = phase_mechanical_F(material_phaseID(co,ce))%data(1:3,1:3,material_phaseEntry(co,ce))
end function phase_F
!----------------------------------------------------------------------------------------------
!< @brief Set deformation gradient (for use by homogenization)
!----------------------------------------------------------------------------------------------
module subroutine phase_set_F(F,co,ce)
real(pReal), dimension(3,3), intent(in) :: F
integer, intent(in) :: co, ce
@ -1473,7 +1474,7 @@ module subroutine phase_mechanical_setF(F,co,ce)
phase_mechanical_F(material_phaseID(co,ce))%data(1:3,1:3,material_phaseEntry(co,ce)) = F
end subroutine phase_mechanical_setF
end subroutine phase_set_F
end submodule mechanical

View File

@ -46,7 +46,6 @@ module subroutine eigendeformation_init(phases)
class(tNode), pointer :: &
phase, &
kinematics, &
damage, &
mechanics
print'(/,a)', ' <<<+- phase:mechanical:eigen init -+>>>'