using parameters from config.f90
This commit is contained in:
parent
1f9a614388
commit
6b45afa72f
|
@ -38,11 +38,7 @@ module homogenization_RGC
|
||||||
integer(pInt), dimension(:,:), allocatable, private :: &
|
integer(pInt), dimension(:,:), allocatable, private :: &
|
||||||
homogenization_RGC_Ngrains
|
homogenization_RGC_Ngrains
|
||||||
real(pReal), dimension(:,:), allocatable, private :: &
|
real(pReal), dimension(:,:), allocatable, private :: &
|
||||||
homogenization_RGC_dAlpha, &
|
|
||||||
homogenization_RGC_angles
|
homogenization_RGC_angles
|
||||||
real(pReal), dimension(:), allocatable, private :: &
|
|
||||||
homogenization_RGC_xiAlpha, &
|
|
||||||
homogenization_RGC_ciAlpha
|
|
||||||
! END DEPRECATED
|
! END DEPRECATED
|
||||||
|
|
||||||
real(pReal), dimension(:,:,:,:), allocatable, private :: &
|
real(pReal), dimension(:,:,:,:), allocatable, private :: &
|
||||||
|
@ -155,10 +151,6 @@ subroutine homogenization_RGC_init(fileUnit)
|
||||||
|
|
||||||
allocate(homogenization_RGC_Noutput(maxNinstance), source=0_pInt)
|
allocate(homogenization_RGC_Noutput(maxNinstance), source=0_pInt)
|
||||||
allocate(homogenization_RGC_Ngrains(3,maxNinstance), source=0_pInt)
|
allocate(homogenization_RGC_Ngrains(3,maxNinstance), source=0_pInt)
|
||||||
allocate(homogenization_RGC_ciAlpha(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(homogenization_RGC_xiAlpha(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(homogenization_RGC_dAlpha(3,maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(homogenization_RGC_angles(3,maxNinstance), source=400.0_pReal)
|
|
||||||
allocate(homogenization_RGC_output(maxval(homogenization_Noutput),maxNinstance))
|
allocate(homogenization_RGC_output(maxval(homogenization_Noutput),maxNinstance))
|
||||||
homogenization_RGC_output=''
|
homogenization_RGC_output=''
|
||||||
allocate(homogenization_RGC_outputID(maxval(homogenization_Noutput),maxNinstance),source=undefined_ID)
|
allocate(homogenization_RGC_outputID(maxval(homogenization_Noutput),maxNinstance),source=undefined_ID)
|
||||||
|
@ -261,18 +253,6 @@ subroutine homogenization_RGC_init(fileUnit)
|
||||||
homogenization_RGC_Ngrains(3,i) = IO_intValue(line,chunkPos,4_pInt)
|
homogenization_RGC_Ngrains(3,i) = IO_intValue(line,chunkPos,4_pInt)
|
||||||
if (homogenization_Ngrains(section) /= product(homogenization_RGC_Ngrains(1:3,i))) &
|
if (homogenization_Ngrains(section) /= product(homogenization_RGC_Ngrains(1:3,i))) &
|
||||||
call IO_error(211_pInt,ext_msg=trim(tag)//' ('//HOMOGENIZATION_RGC_label//')')
|
call IO_error(211_pInt,ext_msg=trim(tag)//' ('//HOMOGENIZATION_RGC_label//')')
|
||||||
case ('scalingparameter')
|
|
||||||
homogenization_RGC_xiAlpha(i) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
case ('overproportionality')
|
|
||||||
homogenization_RGC_ciAlpha(i) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
case ('grainsize')
|
|
||||||
homogenization_RGC_dAlpha(1,i) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
homogenization_RGC_dAlpha(2,i) = IO_floatValue(line,chunkPos,3_pInt)
|
|
||||||
homogenization_RGC_dAlpha(3,i) = IO_floatValue(line,chunkPos,4_pInt)
|
|
||||||
case ('clusterorientation')
|
|
||||||
homogenization_RGC_angles(1,i) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
homogenization_RGC_angles(2,i) = IO_floatValue(line,chunkPos,3_pInt)
|
|
||||||
homogenization_RGC_angles(3,i) = IO_floatValue(line,chunkPos,4_pInt)
|
|
||||||
|
|
||||||
end select
|
end select
|
||||||
endif
|
endif
|
||||||
|
@ -895,7 +875,6 @@ subroutine homogenization_RGC_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,
|
||||||
use mesh, only: mesh_element
|
use mesh, only: mesh_element
|
||||||
use material, only: &
|
use material, only: &
|
||||||
homogenization_maxNgrains, &
|
homogenization_maxNgrains, &
|
||||||
homogenization_Ngrains, &
|
|
||||||
homogenization_typeInstance
|
homogenization_typeInstance
|
||||||
use math, only: math_Plain3333to99
|
use math, only: math_Plain3333to99
|
||||||
|
|
||||||
|
@ -1042,6 +1021,7 @@ subroutine stressPenalty(rPen,nMis,avgF,fDef,ip,el,instance)
|
||||||
integer(pInt) :: iGrain,iGNghb,iFace,i,j,k,l
|
integer(pInt) :: iGrain,iGNghb,iFace,i,j,k,l
|
||||||
real(pReal) :: muGrain,muGNghb,nDefNorm,bgGrain,bgGNghb
|
real(pReal) :: muGrain,muGNghb,nDefNorm,bgGrain,bgGNghb
|
||||||
|
|
||||||
|
type(tParameters) :: prm
|
||||||
integer(pInt), parameter :: nFace = 6_pInt
|
integer(pInt), parameter :: nFace = 6_pInt
|
||||||
real(pReal), parameter :: nDefToler = 1.0e-10_pReal
|
real(pReal), parameter :: nDefToler = 1.0e-10_pReal
|
||||||
|
|
||||||
|
@ -1054,6 +1034,7 @@ subroutine stressPenalty(rPen,nMis,avgF,fDef,ip,el,instance)
|
||||||
! the interfaces due to deformations
|
! the interfaces due to deformations
|
||||||
surfCorr = surfaceCorrection(avgF,ip,el)
|
surfCorr = surfaceCorrection(avgF,ip,el)
|
||||||
|
|
||||||
|
associate(prm => param(instance))
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! debugging the surface correction factor
|
! debugging the surface correction factor
|
||||||
if (iand(debug_level(debug_homogenization),debug_levelExtensive) /= 0_pInt &
|
if (iand(debug_level(debug_homogenization),debug_levelExtensive) /= 0_pInt &
|
||||||
|
@ -1120,9 +1101,9 @@ subroutine stressPenalty(rPen,nMis,avgF,fDef,ip,el,instance)
|
||||||
! compute the stress penalty of all interfaces
|
! compute the stress penalty of all interfaces
|
||||||
do i = 1_pInt,3_pInt; do j = 1_pInt,3_pInt
|
do i = 1_pInt,3_pInt; do j = 1_pInt,3_pInt
|
||||||
do k = 1_pInt,3_pInt; do l = 1_pInt,3_pInt
|
do k = 1_pInt,3_pInt; do l = 1_pInt,3_pInt
|
||||||
rPen(i,j,iGrain) = rPen(i,j,iGrain) + 0.5_pReal*(muGrain*bgGrain + muGNghb*bgGNghb)*homogenization_RGC_xiAlpha(instance) &
|
rPen(i,j,iGrain) = rPen(i,j,iGrain) + 0.5_pReal*(muGrain*bgGrain + muGNghb*bgGNghb)*prm%xiAlpha &
|
||||||
*surfCorr(abs(intFace(1)))/homogenization_RGC_dAlpha(abs(intFace(1)),instance) &
|
*surfCorr(abs(intFace(1)))/prm%dAlpha(abs(intFace(1))) &
|
||||||
*cosh(homogenization_RGC_ciAlpha(instance)*nDefNorm) &
|
*cosh(prm%ciAlpha*nDefNorm) &
|
||||||
*0.5_pReal*nVect(l)*nDef(i,k)/nDefNorm*math_civita(k,l,j) &
|
*0.5_pReal*nVect(l)*nDef(i,k)/nDefNorm*math_civita(k,l,j) &
|
||||||
*tanh(nDefNorm/xSmoo_RGC)
|
*tanh(nDefNorm/xSmoo_RGC)
|
||||||
enddo; enddo
|
enddo; enddo
|
||||||
|
@ -1142,6 +1123,7 @@ subroutine stressPenalty(rPen,nMis,avgF,fDef,ip,el,instance)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
end associate
|
||||||
|
|
||||||
end subroutine stressPenalty
|
end subroutine stressPenalty
|
||||||
|
|
||||||
|
@ -1383,9 +1365,9 @@ function grain1to3(grain1,instance)
|
||||||
integer(pInt), dimension (3) :: nGDim
|
integer(pInt), dimension (3) :: nGDim
|
||||||
|
|
||||||
nGDim = param(instance)%Nconstituents
|
nGDim = param(instance)%Nconstituents
|
||||||
grain1to3(3) = 1_pInt+(grain1-1_pInt)/(nGDim(1)*nGDim(2))
|
grain1to3 = 1_pInt + [mod((grain1-1_pInt),nGDim(1)), &
|
||||||
grain1to3(2) = 1_pInt+mod((grain1-1_pInt)/nGDim(1),nGDim(2))
|
mod((grain1-1_pInt)/nGDim(1),nGDim(2)), &
|
||||||
grain1to3(1) = 1_pInt+mod((grain1-1_pInt),nGDim(1))
|
(grain1-1_pInt)/(nGDim(1)*nGDim(2))]
|
||||||
|
|
||||||
end function grain1to3
|
end function grain1to3
|
||||||
|
|
||||||
|
@ -1414,8 +1396,8 @@ integer(pInt) pure function interface4to1(iFace4D, instance)
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt), dimension (4), intent(in) :: iFace4D !< interface ID in 4D array (n.dir,pos.x,pos.y,pos.z)
|
integer(pInt), dimension (4), intent(in) :: iFace4D !< interface ID in 4D array (n.dir,pos.x,pos.y,pos.z)
|
||||||
integer(pInt), dimension (3) :: nGDim,nIntFace
|
|
||||||
integer(pInt), intent(in) :: instance
|
integer(pInt), intent(in) :: instance
|
||||||
|
integer(pInt), dimension (3) :: nGDim,nIntFace
|
||||||
|
|
||||||
nGDim = param(instance)%Nconstituents
|
nGDim = param(instance)%Nconstituents
|
||||||
|
|
||||||
|
@ -1454,8 +1436,8 @@ pure function interface1to4(iFace1D, instance)
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt), dimension (4) :: interface1to4
|
integer(pInt), dimension (4) :: interface1to4
|
||||||
integer(pInt), intent(in) :: iFace1D !< interface ID in 1D array
|
integer(pInt), intent(in) :: iFace1D !< interface ID in 1D array
|
||||||
integer(pInt), dimension (3) :: nGDim,nIntFace
|
|
||||||
integer(pInt), intent(in) :: instance
|
integer(pInt), intent(in) :: instance
|
||||||
|
integer(pInt), dimension (3) :: nGDim,nIntFace
|
||||||
|
|
||||||
nGDim = param(instance)%Nconstituents
|
nGDim = param(instance)%Nconstituents
|
||||||
|
|
||||||
|
@ -1542,7 +1524,7 @@ subroutine grainDeformation(F, avgF, ip, el)
|
||||||
! compute the deformation gradient of individual grains due to relaxations
|
! compute the deformation gradient of individual grains due to relaxations
|
||||||
instance = homogenization_typeInstance(mesh_element(3,el))
|
instance = homogenization_typeInstance(mesh_element(3,el))
|
||||||
F = 0.0_pReal
|
F = 0.0_pReal
|
||||||
do iGrain = 1_pInt,homogenization_Ngrains(mesh_element(3,el))
|
do iGrain = 1_pInt,sum(param(instance)%Nconstituents)
|
||||||
iGrain3 = grain1to3(iGrain,instance)
|
iGrain3 = grain1to3(iGrain,instance)
|
||||||
do iFace = 1_pInt,nFace
|
do iFace = 1_pInt,nFace
|
||||||
intFace = getInterface(iFace,iGrain3)
|
intFace = getInterface(iFace,iGrain3)
|
||||||
|
|
Loading…
Reference in New Issue