intended hierarchy
This commit is contained in:
parent
190df4830c
commit
7d76752281
|
@ -70,29 +70,22 @@ module homogenization
|
|||
end subroutine mech_homogenize
|
||||
|
||||
module subroutine mech_results(group_base,h)
|
||||
|
||||
character(len=*), intent(in) :: group_base
|
||||
integer, intent(in) :: h
|
||||
|
||||
end subroutine mech_results
|
||||
|
||||
! -------- ToDo ---------------------------------------------------------
|
||||
module function mech_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
|
||||
logical, dimension(2) :: mech_RGC_updateState
|
||||
real(pReal), dimension(:,:,:), intent(in) :: &
|
||||
P,& !< partitioned stresses
|
||||
F,& !< partitioned deformation gradients
|
||||
F0 !< partitioned initial deformation gradients
|
||||
real(pReal), dimension(:,:,:,:,:), intent(in) :: dPdF !< partitioned stiffnesses
|
||||
real(pReal), dimension(3,3), intent(in) :: avgF !< average F
|
||||
real(pReal), intent(in) :: dt !< time increment
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
end function mech_RGC_updateState
|
||||
module function mech_updateState(subdt,subF,ip,el) result(doneAndHappy)
|
||||
real(pReal), intent(in) :: &
|
||||
subdt !< current time step
|
||||
real(pReal), intent(in), dimension(3,3) :: &
|
||||
subF
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point
|
||||
el !< element number
|
||||
logical, dimension(2) :: doneAndHappy
|
||||
end function mech_updateState
|
||||
|
||||
end interface
|
||||
! -----------------------------------------------------------------------
|
||||
|
||||
public :: &
|
||||
homogenization_init, &
|
||||
|
@ -241,11 +234,11 @@ subroutine materialpoint_stressAndItsTangent(dt,FEsolving_execIP,FEsolving_execE
|
|||
doneAndHappy = [.true.,.false.]
|
||||
else
|
||||
ce = (el-1)*discretization_nIPs + ip
|
||||
doneAndHappy = updateState(dt*subStep, &
|
||||
homogenization_F0(1:3,1:3,ce) &
|
||||
+ (homogenization_F(1:3,1:3,ce)-homogenization_F0(1:3,1:3,ce)) &
|
||||
doneAndHappy = mech_updateState(dt*subStep, &
|
||||
homogenization_F0(1:3,1:3,ce) &
|
||||
+ (homogenization_F(1:3,1:3,ce)-homogenization_F0(1:3,1:3,ce)) &
|
||||
*(subStep+subFrac), &
|
||||
ip,el)
|
||||
ip,el)
|
||||
converged = all(doneAndHappy)
|
||||
endif
|
||||
endif
|
||||
|
@ -276,45 +269,6 @@ subroutine materialpoint_stressAndItsTangent(dt,FEsolving_execIP,FEsolving_execE
|
|||
end subroutine materialpoint_stressAndItsTangent
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief update the internal state of the homogenization scheme and tell whether "done" and
|
||||
!> "happy" with result
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function updateState(subdt,subF,ip,el)
|
||||
|
||||
real(pReal), intent(in) :: &
|
||||
subdt !< current time step
|
||||
real(pReal), intent(in), dimension(3,3) :: &
|
||||
subF
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point
|
||||
el !< element number
|
||||
logical, dimension(2) :: updateState
|
||||
|
||||
integer :: co
|
||||
real(pReal) :: dPdFs(3,3,3,3,homogenization_Nconstituents(material_homogenizationAt(el)))
|
||||
|
||||
|
||||
if (homogenization_type(material_homogenizationAt(el)) == HOMOGENIZATION_RGC_ID) then
|
||||
do co = 1, homogenization_Nconstituents(material_homogenizationAt(el))
|
||||
dPdFs(:,:,:,:,co) = crystallite_stressTangent(co,ip,el)
|
||||
enddo
|
||||
updateState = &
|
||||
mech_RGC_updateState(crystallite_P(1:3,1:3,1:homogenization_Nconstituents(material_homogenizationAt(el)),ip,el), &
|
||||
crystallite_partitionedF(1:3,1:3,1:homogenization_Nconstituents(material_homogenizationAt(el)),ip,el), &
|
||||
crystallite_partitionedF0(1:3,1:3,1:homogenization_Nconstituents(material_homogenizationAt(el)),ip,el),&
|
||||
subF,&
|
||||
subdt, &
|
||||
dPdFs, &
|
||||
ip, &
|
||||
el)
|
||||
else
|
||||
updateState = .true.
|
||||
endif
|
||||
|
||||
end function updateState
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief writes homogenization results to HDF5 output file
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
|
|
@ -52,6 +52,21 @@ submodule(homogenization) homogenization_mech
|
|||
end subroutine mech_RGC_averageStressAndItsTangent
|
||||
|
||||
|
||||
module function mech_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el) result(doneAndHappy)
|
||||
logical, dimension(2) :: doneAndHappy
|
||||
real(pReal), dimension(:,:,:), intent(in) :: &
|
||||
P,& !< partitioned stresses
|
||||
F,& !< partitioned deformation gradients
|
||||
F0 !< partitioned initial deformation gradients
|
||||
real(pReal), dimension(:,:,:,:,:), intent(in) :: dPdF !< partitioned stiffnesses
|
||||
real(pReal), dimension(3,3), intent(in) :: avgF !< average F
|
||||
real(pReal), intent(in) :: dt !< time increment
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
end function mech_RGC_updateState
|
||||
|
||||
|
||||
module subroutine mech_RGC_results(instance,group)
|
||||
integer, intent(in) :: instance !< homogenization instance
|
||||
character(len=*), intent(in) :: group !< group name in HDF5 file
|
||||
|
@ -166,6 +181,45 @@ module subroutine mech_homogenize(ip,el)
|
|||
end subroutine mech_homogenize
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief update the internal state of the homogenization scheme and tell whether "done" and
|
||||
!> "happy" with result
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module function mech_updateState(subdt,subF,ip,el) result(doneAndHappy)
|
||||
|
||||
real(pReal), intent(in) :: &
|
||||
subdt !< current time step
|
||||
real(pReal), intent(in), dimension(3,3) :: &
|
||||
subF
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point
|
||||
el !< element number
|
||||
logical, dimension(2) :: doneAndHappy
|
||||
|
||||
integer :: co
|
||||
real(pReal) :: dPdFs(3,3,3,3,homogenization_Nconstituents(material_homogenizationAt(el)))
|
||||
|
||||
|
||||
if (homogenization_type(material_homogenizationAt(el)) == HOMOGENIZATION_RGC_ID) then
|
||||
do co = 1, homogenization_Nconstituents(material_homogenizationAt(el))
|
||||
dPdFs(:,:,:,:,co) = crystallite_stressTangent(co,ip,el)
|
||||
enddo
|
||||
doneAndHappy = &
|
||||
mech_RGC_updateState(crystallite_P(1:3,1:3,1:homogenization_Nconstituents(material_homogenizationAt(el)),ip,el), &
|
||||
crystallite_partitionedF(1:3,1:3,1:homogenization_Nconstituents(material_homogenizationAt(el)),ip,el), &
|
||||
crystallite_partitionedF0(1:3,1:3,1:homogenization_Nconstituents(material_homogenizationAt(el)),ip,el),&
|
||||
subF,&
|
||||
subdt, &
|
||||
dPdFs, &
|
||||
ip, &
|
||||
el)
|
||||
else
|
||||
doneAndHappy = .true.
|
||||
endif
|
||||
|
||||
end function mech_updateState
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief Write results to file.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
|
|
@ -242,7 +242,18 @@ end subroutine mech_RGC_partitionDeformation
|
|||
!> @brief update the internal state of the homogenization scheme and tell whether "done" and
|
||||
! "happy" with result
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module procedure mech_RGC_updateState
|
||||
module function mech_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el) result(doneAndHappy)
|
||||
logical, dimension(2) :: doneAndHappy
|
||||
real(pReal), dimension(:,:,:), intent(in) :: &
|
||||
P,& !< partitioned stresses
|
||||
F,& !< partitioned deformation gradients
|
||||
F0 !< partitioned initial deformation gradients
|
||||
real(pReal), dimension(:,:,:,:,:), intent(in) :: dPdF !< partitioned stiffnesses
|
||||
real(pReal), dimension(3,3), intent(in) :: avgF !< average F
|
||||
real(pReal), intent(in) :: dt !< time increment
|
||||
integer, intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
|
||||
integer, dimension(4) :: intFaceN,intFaceP,faceID
|
||||
integer, dimension(3) :: nGDim,iGr3N,iGr3P
|
||||
|
@ -256,7 +267,7 @@ module procedure mech_RGC_updateState
|
|||
real(pReal), dimension(:), allocatable :: resid,relax,p_relax,p_resid,drelax
|
||||
|
||||
zeroTimeStep: if(dEq0(dt)) then
|
||||
mech_RGC_updateState = .true. ! pretend everything is fine and return
|
||||
doneAndHappy = .true. ! pretend everything is fine and return
|
||||
return
|
||||
endif zeroTimeStep
|
||||
|
||||
|
@ -327,12 +338,12 @@ module procedure mech_RGC_updateState
|
|||
stresMax = maxval(abs(P)) ! get the maximum of first Piola-Kirchhoff (material) stress
|
||||
residMax = maxval(abs(tract)) ! get the maximum of the residual
|
||||
|
||||
mech_RGC_updateState = .false.
|
||||
doneAndHappy = .false.
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! If convergence reached => done and happy
|
||||
if (residMax < num%rtol*stresMax .or. residMax < num%atol) then
|
||||
mech_RGC_updateState = .true.
|
||||
doneAndHappy = .true.
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! compute/update the state for postResult, i.e., all energy densities computed by time-integration
|
||||
|
@ -354,7 +365,7 @@ module procedure mech_RGC_updateState
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
! if residual blows-up => done but unhappy
|
||||
elseif (residMax > num%relMax*stresMax .or. residMax > num%absMax) then ! try to restart when residual blows up exceeding maximum bound
|
||||
mech_RGC_updateState = [.true.,.false.] ! with direct cut-back
|
||||
doneAndHappy = [.true.,.false.] ! with direct cut-back
|
||||
return
|
||||
endif
|
||||
|
||||
|
@ -484,7 +495,7 @@ module procedure mech_RGC_updateState
|
|||
enddo; enddo
|
||||
stt%relaxationVector(:,of) = relax + drelax ! Updateing the state variable for the next iteration
|
||||
if (any(abs(drelax) > num%maxdRelax)) then ! Forcing cutback when the incremental change of relaxation vector becomes too large
|
||||
mech_RGC_updateState = [.true.,.false.]
|
||||
doneAndHappy = [.true.,.false.]
|
||||
!$OMP CRITICAL (write2out)
|
||||
print'(a,i3,a,i3,a)',' RGC_updateState: ip ',ip,' | el ',el,' enforces cutback'
|
||||
print'(a,e15.8)',' due to large relaxation change = ',maxval(abs(drelax))
|
||||
|
@ -535,7 +546,7 @@ module procedure mech_RGC_updateState
|
|||
Gmoduli = equivalentModuli(iGrain,ip,el)
|
||||
muGrain = Gmoduli(1) ! collecting the equivalent shear modulus of grain
|
||||
bgGrain = Gmoduli(2) ! and the lengthh of Burgers vector
|
||||
iGrain3 = grain1to3(iGrain,prm%N_constituents) ! get the grain ID in local 3-dimensional index (x,y,z)-position
|
||||
iGrain3 = grain1to3(iGrain,prm%N_constituents) ! get the grain ID in local 3-dimensional index (doneAndHappy,y,z)-position
|
||||
|
||||
interfaceLoop: do iFace = 1,6
|
||||
intFace = getInterface(iFace,iGrain3) ! get the 4-dimensional index of the interface in local numbering system of the grain
|
||||
|
@ -729,7 +740,7 @@ module procedure mech_RGC_updateState
|
|||
|
||||
end subroutine grainDeformation
|
||||
|
||||
end procedure mech_RGC_updateState
|
||||
end function mech_RGC_updateState
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
|
Loading…
Reference in New Issue