using less global variables
This commit is contained in:
parent
11bb6f1f47
commit
57c6271894
|
@ -792,7 +792,7 @@ function homogenization_updateState(ip,el)
|
||||||
homogenization_type, &
|
homogenization_type, &
|
||||||
thermal_type, &
|
thermal_type, &
|
||||||
damage_type, &
|
damage_type, &
|
||||||
homogenization_maxNgrains, &
|
homogenization_Ngrains, &
|
||||||
HOMOGENIZATION_RGC_ID, &
|
HOMOGENIZATION_RGC_ID, &
|
||||||
THERMAL_adiabatic_ID, &
|
THERMAL_adiabatic_ID, &
|
||||||
DAMAGE_local_ID
|
DAMAGE_local_ID
|
||||||
|
@ -819,12 +819,12 @@ function homogenization_updateState(ip,el)
|
||||||
case (HOMOGENIZATION_RGC_ID) chosenHomogenization
|
case (HOMOGENIZATION_RGC_ID) chosenHomogenization
|
||||||
homogenization_updateState = &
|
homogenization_updateState = &
|
||||||
homogenization_updateState .and. &
|
homogenization_updateState .and. &
|
||||||
homogenization_RGC_updateState(crystallite_P(1:3,1:3,1:homogenization_maxNgrains,ip,el), &
|
homogenization_RGC_updateState(crystallite_P(1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)),ip,el), &
|
||||||
crystallite_partionedF(1:3,1:3,1:homogenization_maxNgrains,ip,el), &
|
crystallite_partionedF(1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)),ip,el), &
|
||||||
crystallite_partionedF0(1:3,1:3,1:homogenization_maxNgrains,ip,el),&
|
crystallite_partionedF0(1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)),ip,el),&
|
||||||
materialpoint_subF(1:3,1:3,ip,el),&
|
materialpoint_subF(1:3,1:3,ip,el),&
|
||||||
materialpoint_subdt(ip,el), &
|
materialpoint_subdt(ip,el), &
|
||||||
crystallite_dPdF(1:3,1:3,1:3,1:3,1:homogenization_maxNgrains,ip,el), &
|
crystallite_dPdF(1:3,1:3,1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)),ip,el), &
|
||||||
ip, &
|
ip, &
|
||||||
el)
|
el)
|
||||||
end select chosenHomogenization
|
end select chosenHomogenization
|
||||||
|
|
|
@ -332,8 +332,7 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
|
||||||
use material, only: &
|
use material, only: &
|
||||||
material_homogenizationAt, &
|
material_homogenizationAt, &
|
||||||
homogenization_typeInstance, &
|
homogenization_typeInstance, &
|
||||||
mappingHomogenization, &
|
mappingHomogenization
|
||||||
homogenization_maxNgrains
|
|
||||||
use numerics, only: &
|
use numerics, only: &
|
||||||
absTol_RGC, &
|
absTol_RGC, &
|
||||||
relTol_RGC, &
|
relTol_RGC, &
|
||||||
|
@ -347,11 +346,11 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: &
|
real(pReal), dimension (:,:,:), intent(in) :: &
|
||||||
P,& !< array of P
|
P,& !< array of P
|
||||||
F,& !< array of F
|
F,& !< array of F
|
||||||
F0 !< array of initial F
|
F0 !< array of initial F
|
||||||
real(pReal), dimension (3,3,3,3,homogenization_maxNgrains), intent(in) :: dPdF !< array of current grain stiffness
|
real(pReal), dimension (:,:,:,:,:), intent(in) :: dPdF !< array of current grain stiffness
|
||||||
real(pReal), dimension (3,3), intent(in) :: avgF !< average F
|
real(pReal), dimension (3,3), intent(in) :: avgF !< average F
|
||||||
real(pReal), intent(in) :: dt !< time increment
|
real(pReal), intent(in) :: dt !< time increment
|
||||||
integer(pInt), intent(in) :: &
|
integer(pInt), intent(in) :: &
|
||||||
|
@ -359,18 +358,21 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
|
||||||
el !< element number
|
el !< element number
|
||||||
|
|
||||||
logical, dimension(2) :: homogenization_RGC_updateState
|
logical, dimension(2) :: homogenization_RGC_updateState
|
||||||
|
|
||||||
integer(pInt), dimension (4) :: intFaceN,intFaceP,faceID
|
integer(pInt), dimension (4) :: intFaceN,intFaceP,faceID
|
||||||
integer(pInt), dimension (3) :: nGDim,iGr3N,iGr3P,stresLoc
|
integer(pInt), dimension (3) :: nGDim,iGr3N,iGr3P,stresLoc
|
||||||
integer(pInt), dimension (2) :: residLoc
|
integer(pInt) :: instance,iNum,i,j,nIntFaceTot,iGrN,iGrP,iMun,iFace,k,l,ipert,iGrain,nGrain, of
|
||||||
integer(pInt) instance,iNum,i,j,nIntFaceTot,iGrN,iGrP,iMun,iFace,k,l,ipert,iGrain,nGrain, of
|
real(pReal), dimension (3,3,size(P,3)) :: R,pF,pR,D,pD
|
||||||
real(pReal), dimension (3,3,homogenization_maxNgrains) :: R,pF,pR,D,pD
|
real(pReal), dimension (3,size(P,3)) :: NN,devNull
|
||||||
real(pReal), dimension (3,homogenization_maxNgrains) :: NN,devNull33
|
|
||||||
real(pReal), dimension (3) :: normP,normN,mornP,mornN
|
real(pReal), dimension (3) :: normP,normN,mornP,mornN
|
||||||
real(pReal) :: residMax,stresMax,devNull
|
real(pReal) :: residMax,stresMax
|
||||||
logical error
|
logical :: error
|
||||||
|
|
||||||
real(pReal), dimension(:,:), allocatable :: tract,jmatrix,jnverse,smatrix,pmatrix,rmatrix
|
real(pReal), dimension(:,:), allocatable :: tract,jmatrix,jnverse,smatrix,pmatrix,rmatrix
|
||||||
real(pReal), dimension(:), allocatable :: resid,relax,p_relax,p_resid,drelax
|
real(pReal), dimension(:), allocatable :: resid,relax,p_relax,p_resid,drelax
|
||||||
|
#ifdef DEBUG
|
||||||
|
integer(pInt), dimension (3) :: stresLoc
|
||||||
|
integer(pInt), dimension (2) :: residLoc
|
||||||
|
#endif
|
||||||
|
|
||||||
zeroTimeStep: if(dEq0(dt)) then
|
zeroTimeStep: if(dEq0(dt)) then
|
||||||
homogenization_RGC_updateState = .true. ! pretend everything is fine and return
|
homogenization_RGC_updateState = .true. ! pretend everything is fine and return
|
||||||
|
@ -475,13 +477,13 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! convergence check for stress residual
|
! convergence check for stress residual
|
||||||
stresMax = maxval(abs(P)) ! get the maximum of first Piola-Kirchhoff (material) stress
|
stresMax = maxval(abs(P)) ! get the maximum of first Piola-Kirchhoff (material) stress
|
||||||
stresLoc = int(maxloc(abs(P)),pInt) ! get the location of the maximum stress
|
|
||||||
residMax = maxval(abs(tract)) ! get the maximum of the residual
|
residMax = maxval(abs(tract)) ! get the maximum of the residual
|
||||||
residLoc = int(maxloc(abs(tract)),pInt) ! get the position of the maximum residual
|
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (iand(debug_level(debug_homogenization),debug_levelExtensive) /= 0_pInt &
|
if (iand(debug_level(debug_homogenization),debug_levelExtensive) /= 0_pInt &
|
||||||
.and. debug_e == el .and. debug_i == ip) then
|
.and. debug_e == el .and. debug_i == ip) then
|
||||||
|
stresLoc = int(maxloc(abs(P)),pInt) ! get the location of the maximum stress
|
||||||
|
residLoc = int(maxloc(abs(tract)),pInt) ! get the position of the maximum residual
|
||||||
write(6,'(1x,a)')' '
|
write(6,'(1x,a)')' '
|
||||||
write(6,'(1x,a,1x,i2,1x,i4)')'RGC residual check ...',ip,el
|
write(6,'(1x,a,1x,i2,1x,i4)')'RGC residual check ...',ip,el
|
||||||
write(6,'(1x,a15,1x,e15.8,1x,a7,i3,1x,a12,i2,i2)')'Max stress: ',stresMax, &
|
write(6,'(1x,a15,1x,e15.8,1x,a7,i3,1x,a12,i2,i2)')'Max stress: ',stresMax, &
|
||||||
|
@ -637,8 +639,8 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
|
||||||
p_relax(ipert) = relax(ipert) + pPert_RGC ! perturb the relaxation vector
|
p_relax(ipert) = relax(ipert) + pPert_RGC ! perturb the relaxation vector
|
||||||
stt%relaxationVector(:,of) = p_relax
|
stt%relaxationVector(:,of) = p_relax
|
||||||
call grainDeformation(pF,avgF,instance,of) ! rain deformation from perturbed state
|
call grainDeformation(pF,avgF,instance,of) ! rain deformation from perturbed state
|
||||||
call stressPenalty(pR,DevNull33, avgF,pF,ip,el,instance,of) ! stress penalty due to interface mismatch from perturbed state
|
call stressPenalty(pR,DevNull, avgF,pF,ip,el,instance,of) ! stress penalty due to interface mismatch from perturbed state
|
||||||
call volumePenalty(pD,devNull, avgF,pF,nGrain,instance,of) ! stress penalty due to volume discrepancy from perturbed state
|
call volumePenalty(pD,devNull(1,1), avgF,pF,nGrain,instance,of) ! stress penalty due to volume discrepancy from perturbed state
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! computing the global stress residual array from the perturbed state
|
! computing the global stress residual array from the perturbed state
|
||||||
|
@ -774,10 +776,10 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
|
||||||
xSmoo_RGC
|
xSmoo_RGC
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(out) :: rPen !< stress-like penalty
|
real(pReal), dimension (:,:,:), intent(out) :: rPen !< stress-like penalty
|
||||||
real(pReal), dimension (3,homogenization_maxNgrains), intent(out) :: nMis !< total amount of mismatch
|
real(pReal), dimension (:,:), intent(out) :: nMis !< total amount of mismatch
|
||||||
|
|
||||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: fDef !< deformation gradients
|
real(pReal), dimension (:,:,:), intent(in) :: fDef !< deformation gradients
|
||||||
real(pReal), dimension (3,3), intent(in) :: avgF !< initial effective stretch tensor
|
real(pReal), dimension (3,3), intent(in) :: avgF !< initial effective stretch tensor
|
||||||
integer(pInt), intent(in) :: ip,el,instance,of
|
integer(pInt), intent(in) :: ip,el,instance,of
|
||||||
|
|
||||||
|
@ -894,17 +896,17 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
|
||||||
volDiscrPow_RGC
|
volDiscrPow_RGC
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(out) :: vPen ! stress-like penalty due to volume
|
real(pReal), dimension (:,:,:), intent(out) :: vPen ! stress-like penalty due to volume
|
||||||
real(pReal), intent(out) :: vDiscrep ! total volume discrepancy
|
real(pReal), intent(out) :: vDiscrep ! total volume discrepancy
|
||||||
|
|
||||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: fDef ! deformation gradients
|
real(pReal), dimension (:,:,:), intent(in) :: fDef ! deformation gradients
|
||||||
real(pReal), dimension (3,3), intent(in) :: fAvg ! overall deformation gradient
|
real(pReal), dimension (3,3), intent(in) :: fAvg ! overall deformation gradient
|
||||||
integer(pInt), intent(in) :: &
|
integer(pInt), intent(in) :: &
|
||||||
Ngrain, &
|
Ngrain, &
|
||||||
instance, &
|
instance, &
|
||||||
of
|
of
|
||||||
|
|
||||||
real(pReal), dimension (homogenization_maxNgrains) :: gVol
|
real(pReal), dimension(size(vPen,3)) :: gVol
|
||||||
integer(pInt) :: i
|
integer(pInt) :: i
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
|
Loading…
Reference in New Issue