cleaned and unified
This commit is contained in:
parent
08c692bfc1
commit
fdbc20b739
|
@ -129,11 +129,11 @@ subroutine homogenization_init
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! parse homogenization from config file
|
! parse homogenization from config file
|
||||||
if (any(homogenization_type == HOMOGENIZATION_NONE_ID)) &
|
if (any(homogenization_type == HOMOGENIZATION_NONE_ID)) &
|
||||||
call homogenization_none_init()
|
call homogenization_none_init
|
||||||
if (any(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)) &
|
if (any(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)) &
|
||||||
call homogenization_isostrain_init()
|
call homogenization_isostrain_init
|
||||||
if (any(homogenization_type == HOMOGENIZATION_RGC_ID)) &
|
if (any(homogenization_type == HOMOGENIZATION_RGC_ID)) &
|
||||||
call homogenization_RGC_init(FILEUNIT)
|
call homogenization_RGC_init
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! parse thermal from config file
|
! parse thermal from config file
|
||||||
|
|
|
@ -49,21 +49,23 @@ module homogenization_RGC
|
||||||
end type
|
end type
|
||||||
|
|
||||||
type, private :: tRGCState
|
type, private :: tRGCState
|
||||||
real(pReal), pointer, dimension(:,:) :: &
|
real(pReal), pointer, dimension(:) :: &
|
||||||
work, &
|
work, &
|
||||||
mismatch, &
|
|
||||||
penaltyEnergy, &
|
penaltyEnergy, &
|
||||||
volumeDiscrepancy, &
|
volumeDiscrepancy, &
|
||||||
relaxationRate_avg, &
|
relaxationRate_avg, &
|
||||||
relaxationRage_max
|
relaxationRage_max
|
||||||
end type
|
real(pReal), pointer, dimension(:,:) :: &
|
||||||
|
mismatch
|
||||||
|
end type tRGCState
|
||||||
|
|
||||||
! START: Could be improved
|
! START: Could be improved
|
||||||
real(pReal), dimension(:,:,:,:), allocatable, private :: &
|
real(pReal), dimension(:,:,:,:), allocatable, private :: &
|
||||||
homogenization_RGC_orientation
|
homogenization_RGC_orientation
|
||||||
! END: Could be improved
|
! END: Could be improved
|
||||||
|
|
||||||
type(tParameters), dimension(:), allocatable, private :: param !< containers of constitutive parameters (len Ninstance)
|
type(tParameters), dimension(:), allocatable, private :: param !< containers of parameters (len Ninstance)
|
||||||
|
type(tRGCState), dimension(:), allocatable, private :: state
|
||||||
|
|
||||||
public :: &
|
public :: &
|
||||||
homogenization_RGC_init, &
|
homogenization_RGC_init, &
|
||||||
|
@ -90,7 +92,7 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief allocates all necessary fields, reads information from material configuration file
|
!> @brief allocates all necessary fields, reads information from material configuration file
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine homogenization_RGC_init(fileUnit)
|
subroutine homogenization_RGC_init()
|
||||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||||
use, intrinsic :: iso_fortran_env, only: &
|
use, intrinsic :: iso_fortran_env, only: &
|
||||||
compiler_version, &
|
compiler_version, &
|
||||||
|
@ -121,13 +123,12 @@ subroutine homogenization_RGC_init(fileUnit)
|
||||||
use config
|
use config
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt), intent(in) :: fileUnit !< file pointer to material configuration
|
integer(pInt) :: &
|
||||||
integer :: &
|
|
||||||
NofMyHomog, &
|
NofMyHomog, &
|
||||||
o, h, &
|
o, h, &
|
||||||
outputSize, &
|
outputSize, &
|
||||||
instance, &
|
instance, &
|
||||||
sizeHState
|
sizeHState, nIntFaceTot
|
||||||
integer(pInt) :: section=0_pInt, maxNinstance, i,j,e, mySize
|
integer(pInt) :: section=0_pInt, maxNinstance, i,j,e, mySize
|
||||||
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
|
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
|
||||||
integer(kind(undefined_ID)) :: &
|
integer(kind(undefined_ID)) :: &
|
||||||
|
@ -150,6 +151,7 @@ subroutine homogenization_RGC_init(fileUnit)
|
||||||
allocate(homogenization_RGC_sizePostResults(maxNinstance), source=0_pInt)
|
allocate(homogenization_RGC_sizePostResults(maxNinstance), source=0_pInt)
|
||||||
|
|
||||||
allocate(param(maxNinstance)) ! one container of parameters per instance
|
allocate(param(maxNinstance)) ! one container of parameters per instance
|
||||||
|
allocate(state(maxNinstance)) ! one container per instance
|
||||||
|
|
||||||
allocate(homogenization_RGC_Noutput(maxNinstance), source=0_pInt)
|
allocate(homogenization_RGC_Noutput(maxNinstance), source=0_pInt)
|
||||||
allocate(homogenization_RGC_output(maxval(homogenization_Noutput),maxNinstance))
|
allocate(homogenization_RGC_output(maxval(homogenization_Noutput),maxNinstance))
|
||||||
|
@ -200,7 +202,6 @@ subroutine homogenization_RGC_init(fileUnit)
|
||||||
end select
|
end select
|
||||||
if (outputID /= undefined_ID) then
|
if (outputID /= undefined_ID) then
|
||||||
homogenization_RGC_output(i,instance) = outputs(i)
|
homogenization_RGC_output(i,instance) = outputs(i)
|
||||||
print*, homogenization_RGC_output(i,instance)
|
|
||||||
homogenization_RGC_sizePostResult(i,instance) = outputSize
|
homogenization_RGC_sizePostResult(i,instance) = outputSize
|
||||||
prm%outputID = [prm%outputID , outputID]
|
prm%outputID = [prm%outputID , outputID]
|
||||||
endif
|
endif
|
||||||
|
@ -234,11 +235,10 @@ subroutine homogenization_RGC_init(fileUnit)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
NofMyHomog = count(material_homog == h)
|
NofMyHomog = count(material_homog == h)
|
||||||
|
nIntFaceTot = 3_pInt*( (prm%Nconstituents(1)-1_pInt)*prm%Nconstituents(2)*prm%Nconstituents(3) &
|
||||||
sizeHState = &
|
+ prm%Nconstituents(1)*(prm%Nconstituents(2)-1_pInt)*prm%Nconstituents(3) &
|
||||||
3_pInt*(prm%Nconstituents(1)-1_pInt)*prm%Nconstituents(2)*prm%Nconstituents(3) &
|
+ prm%Nconstituents(1)*prm%Nconstituents(2)*(prm%Nconstituents(3)-1_pInt))
|
||||||
+ 3_pInt*prm%Nconstituents(1)*(prm%Nconstituents(2)-1_pInt)* prm%Nconstituents(3) &
|
sizeHState = nIntFaceTot &
|
||||||
+ 3_pInt*prm%Nconstituents(1)*prm%Nconstituents(2)*(prm%Nconstituents(3)-1_pInt) &
|
|
||||||
+ 8_pInt ! (1) Average constitutive work, (2-4) Overall mismatch, (5) Average penalty energy,
|
+ 8_pInt ! (1) Average constitutive work, (2-4) Overall mismatch, (5) Average penalty energy,
|
||||||
! (6) Volume discrepancy, (7) Avg relaxation rate component, (8) Max relaxation rate component
|
! (6) Volume discrepancy, (7) Avg relaxation rate component, (8) Max relaxation rate component
|
||||||
|
|
||||||
|
@ -361,6 +361,7 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
|
||||||
integer(pInt), intent(in) :: &
|
integer(pInt), intent(in) :: &
|
||||||
ip, & !< integration point number
|
ip, & !< integration point number
|
||||||
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
|
||||||
|
@ -394,12 +395,9 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
|
||||||
! allocate the size of the global relaxation arrays/jacobian matrices depending on the size of the cluster
|
! allocate the size of the global relaxation arrays/jacobian matrices depending on the size of the cluster
|
||||||
allocate(resid(3_pInt*nIntFaceTot), source=0.0_pReal)
|
allocate(resid(3_pInt*nIntFaceTot), source=0.0_pReal)
|
||||||
allocate(tract(nIntFaceTot,3), source=0.0_pReal)
|
allocate(tract(nIntFaceTot,3), source=0.0_pReal)
|
||||||
allocate(relax(3_pInt*nIntFaceTot)); relax= homogState(mappingHomogenization(2,ip,el))% &
|
relax = homogState(mappingHomogenization(2,ip,el))%state (1:3_pInt*nIntFaceTot,mappingHomogenization(1,ip,el))
|
||||||
state(1:3_pInt*nIntFaceTot,mappingHomogenization(1,ip,el))
|
drelax = relax &
|
||||||
allocate(drelax(3_pInt*nIntFaceTot)); drelax= homogState(mappingHomogenization(2,ip,el))% &
|
- homogState(mappingHomogenization(2,ip,el))%state0(1:3_pInt*nIntFaceTot,mappingHomogenization(1,ip,el))
|
||||||
state(1:3_pInt*nIntFaceTot,mappingHomogenization(1,ip,el)) - &
|
|
||||||
homogState(mappingHomogenization(2,ip,el))% &
|
|
||||||
state0(1:3_pInt*nIntFaceTot,mappingHomogenization(1,ip,el))
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! debugging the obtained state
|
! debugging the obtained state
|
||||||
if (iand(debug_level(debug_homogenization),debug_levelExtensive) /= 0_pInt) then
|
if (iand(debug_level(debug_homogenization),debug_levelExtensive) /= 0_pInt) then
|
||||||
|
@ -1145,25 +1143,21 @@ function surfaceCorrection(avgF,ip,el)
|
||||||
real(pReal), dimension(3,3), intent(in) :: avgF !< average F
|
real(pReal), dimension(3,3), intent(in) :: avgF !< average F
|
||||||
integer(pInt), intent(in) :: ip,& !< integration point number
|
integer(pInt), intent(in) :: ip,& !< integration point number
|
||||||
el !< element number
|
el !< element number
|
||||||
real(pReal), dimension(3,3) :: invC,avgC
|
real(pReal), dimension(3,3) :: invC
|
||||||
real(pReal), dimension(3) :: nVect
|
real(pReal), dimension(3) :: nVect
|
||||||
real(pReal) :: detF
|
real(pReal) :: detF
|
||||||
integer(pInt), dimension(4) :: intFace
|
|
||||||
integer(pInt) :: i,j,iBase
|
integer(pInt) :: i,j,iBase
|
||||||
logical :: error
|
logical :: error
|
||||||
|
|
||||||
avgC = math_mul33x33(transpose(avgF),avgF)
|
call math_invert33(math_mul33x33(transpose(avgF),avgF),invC,detF,error)
|
||||||
call math_invert33(avgC,invC,detF,error)
|
|
||||||
surfaceCorrection = 0.0_pReal
|
surfaceCorrection = 0.0_pReal
|
||||||
do iBase = 1_pInt,3_pInt
|
do iBase = 1_pInt,3_pInt
|
||||||
intFace = [iBase,1_pInt,1_pInt,1_pInt]
|
nVect = interfaceNormal([iBase,1_pInt,1_pInt,1_pInt],ip,el) ! get the normal of the interface
|
||||||
nVect = interfaceNormal(intFace,ip,el) ! get the normal of the interface
|
|
||||||
do i = 1_pInt,3_pInt; do j = 1_pInt,3_pInt
|
do i = 1_pInt,3_pInt; do j = 1_pInt,3_pInt
|
||||||
surfaceCorrection(iBase) = & ! compute the component of (the inverse of) the stretch in the direction of the normal
|
surfaceCorrection(iBase) = surfaceCorrection(iBase) + invC(i,j)*nVect(i)*nVect(j) ! compute the component of (the inverse of) the stretch in the direction of the normal
|
||||||
surfaceCorrection(iBase) + invC(i,j)*nVect(i)*nVect(j)
|
|
||||||
enddo; enddo
|
enddo; enddo
|
||||||
surfaceCorrection(iBase) = & ! get the surface correction factor (area contraction/enlargement)
|
surfaceCorrection(iBase) = sqrt(surfaceCorrection(iBase))*detF ! get the surface correction factor (area contraction/enlargement)
|
||||||
sqrt(surfaceCorrection(iBase))*detF
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end function surfaceCorrection
|
end function surfaceCorrection
|
||||||
|
@ -1314,7 +1308,7 @@ pure function grain3to1(grain3,instance)
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt), dimension (3), intent(in) :: grain3 !< grain ID in 3D array (pos.x,pos.y,pos.z)
|
integer(pInt), dimension (3), intent(in) :: grain3 !< grain ID in 3D array (pos.x,pos.y,pos.z)
|
||||||
integer(pInt), intent(in) :: instance ! homogenization ID
|
integer(pInt), intent(in) :: instance ! homogenization ID
|
||||||
integer(pInt) :: grain3to1
|
integer(pInt) :: grain3to1
|
||||||
integer(pInt), dimension (3) :: nGDim
|
integer(pInt), dimension (3) :: nGDim
|
||||||
|
|
||||||
|
|
|
@ -64,8 +64,7 @@ subroutine homogenization_isostrain_init()
|
||||||
integer(pInt) :: &
|
integer(pInt) :: &
|
||||||
h
|
h
|
||||||
integer :: &
|
integer :: &
|
||||||
maxNinstance, &
|
Ninstance
|
||||||
instance
|
|
||||||
integer :: &
|
integer :: &
|
||||||
NofMyHomog ! no pInt (stores a system dependen value from 'count'
|
NofMyHomog ! no pInt (stores a system dependen value from 'count'
|
||||||
character(len=65536) :: &
|
character(len=65536) :: &
|
||||||
|
@ -76,18 +75,17 @@ subroutine homogenization_isostrain_init()
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||||
#include "compilation_info.f90"
|
#include "compilation_info.f90"
|
||||||
|
|
||||||
maxNinstance = count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)
|
Ninstance = count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)
|
||||||
if (maxNinstance == 0) return
|
if (Ninstance == 0) return
|
||||||
|
|
||||||
if (iand(debug_level(debug_HOMOGENIZATION),debug_levelBasic) /= 0_pInt) &
|
if (iand(debug_level(debug_HOMOGENIZATION),debug_levelBasic) /= 0_pInt) &
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
||||||
|
|
||||||
allocate(param(maxNinstance)) ! one container of parameters per instance
|
allocate(param(Ninstance)) ! one container of parameters per instance
|
||||||
|
|
||||||
do h = 1_pInt, size(homogenization_type)
|
do h = 1_pInt, size(homogenization_type)
|
||||||
if (homogenization_type(h) /= HOMOGENIZATION_ISOSTRAIN_ID) cycle
|
if (homogenization_type(h) /= HOMOGENIZATION_ISOSTRAIN_ID) cycle
|
||||||
instance = homogenization_typeInstance(h)
|
associate(prm => param(homogenization_typeInstance(h)))
|
||||||
associate(prm => param(instance))
|
|
||||||
|
|
||||||
prm%Nconstituents = config_homogenization(h)%getInt('nconstituents')
|
prm%Nconstituents = config_homogenization(h)%getInt('nconstituents')
|
||||||
tag = 'sum'
|
tag = 'sum'
|
||||||
|
|
Loading…
Reference in New Issue