cleaning
This commit is contained in:
parent
3d95d05e19
commit
e43057adb3
|
@ -19,19 +19,17 @@ module homogenization_RGC
|
||||||
homogenization_RGC_output ! name of each post result output
|
homogenization_RGC_output ! name of each post result output
|
||||||
|
|
||||||
enum, bind(c)
|
enum, bind(c)
|
||||||
enumerator :: undefined_ID, &
|
enumerator :: &
|
||||||
constitutivework_ID, &
|
undefined_ID, &
|
||||||
penaltyenergy_ID, &
|
constitutivework_ID, &
|
||||||
volumediscrepancy_ID, &
|
penaltyenergy_ID, &
|
||||||
averagerelaxrate_ID,&
|
volumediscrepancy_ID, &
|
||||||
maximumrelaxrate_ID,&
|
averagerelaxrate_ID,&
|
||||||
ipcoords_ID,&
|
maximumrelaxrate_ID,&
|
||||||
magnitudemismatch_ID,&
|
magnitudemismatch_ID
|
||||||
avgdefgrad_ID,&
|
|
||||||
avgfirstpiola_ID
|
|
||||||
end enum
|
end enum
|
||||||
|
|
||||||
type, private :: tParameters !< container type for internal constitutive parameters
|
type, private :: tParameters
|
||||||
integer(pInt), dimension(:), allocatable :: &
|
integer(pInt), dimension(:), allocatable :: &
|
||||||
Nconstituents
|
Nconstituents
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
|
@ -40,8 +38,10 @@ module homogenization_RGC
|
||||||
real(pReal), dimension(:), allocatable :: &
|
real(pReal), dimension(:), allocatable :: &
|
||||||
dAlpha, &
|
dAlpha, &
|
||||||
angles
|
angles
|
||||||
|
integer(pInt) :: &
|
||||||
|
of_debug
|
||||||
integer(kind(undefined_ID)), dimension(:), allocatable :: &
|
integer(kind(undefined_ID)), dimension(:), allocatable :: &
|
||||||
outputID !< ID of each post result output
|
outputID
|
||||||
end type
|
end type
|
||||||
|
|
||||||
type, private :: tRGCstate
|
type, private :: tRGCstate
|
||||||
|
@ -61,8 +61,8 @@ module homogenization_RGC
|
||||||
orientation
|
orientation
|
||||||
end type tRGCdependentState
|
end type tRGCdependentState
|
||||||
|
|
||||||
type(tparameters), dimension(:), allocatable, private :: param !< containers of parameters (len Ninstance)
|
type(tparameters), dimension(:), allocatable, private :: param !< containers of parameters (len Ninstance)
|
||||||
type(tRGCstate), dimension(:), allocatable, private :: state
|
type(tRGCstate), dimension(:), allocatable, private :: state
|
||||||
type(tRGCdependentState), dimension(:), allocatable, private :: dependentState
|
type(tRGCdependentState), dimension(:), allocatable, private :: dependentState
|
||||||
|
|
||||||
public :: &
|
public :: &
|
||||||
|
@ -102,25 +102,27 @@ subroutine homogenization_RGC_init()
|
||||||
use math, only: &
|
use math, only: &
|
||||||
math_EulerToR,&
|
math_EulerToR,&
|
||||||
INRAD
|
INRAD
|
||||||
use mesh, only: &
|
use IO, only: &
|
||||||
mesh_NcpElems,&
|
IO_error, &
|
||||||
mesh_NipsPerElem
|
IO_timeStamp
|
||||||
use IO
|
|
||||||
use material
|
use material
|
||||||
use config
|
use config, only: &
|
||||||
|
config_homogenization
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt) :: &
|
integer(pInt) :: &
|
||||||
NofMyHomog, &
|
Ninstance, &
|
||||||
h, &
|
h, i, j, &
|
||||||
outputSize, &
|
NofMyHomog, outputSize, &
|
||||||
instance, &
|
sizeState, nIntFaceTot
|
||||||
sizeHState, nIntFaceTot
|
|
||||||
integer(pInt) :: maxNinstance, i,j,e, of
|
|
||||||
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
|
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
|
||||||
integer(kind(undefined_ID)) :: &
|
|
||||||
outputID !< ID of each post result output
|
integer(kind(undefined_ID)) :: &
|
||||||
character(len=65536), dimension(:), allocatable :: outputs
|
outputID
|
||||||
|
|
||||||
|
character(len=65536), dimension(:), allocatable :: &
|
||||||
|
outputs
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- homogenization_'//HOMOGENIZATION_RGC_label//' init -+>>>'
|
write(6,'(/,a)') ' <<<+- homogenization_'//HOMOGENIZATION_RGC_label//' init -+>>>'
|
||||||
write(6,'(/,a)') ' Tjahjanto et al., International Journal of Material Forming, 2(1):939–942, 2009'
|
write(6,'(/,a)') ' Tjahjanto et al., International Journal of Material Forming, 2(1):939–942, 2009'
|
||||||
|
@ -130,39 +132,47 @@ subroutine homogenization_RGC_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 = int(count(homogenization_type == HOMOGENIZATION_RGC_ID),pInt)
|
Ninstance = int(count(homogenization_type == HOMOGENIZATION_RGC_ID),pInt)
|
||||||
if (maxNinstance == 0_pInt) return
|
if (Ninstance == 0_pInt) 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))
|
||||||
allocate(state(maxNinstance)) ! one container per instance
|
allocate(state(Ninstance))
|
||||||
allocate(dependentState(maxNinstance)) ! one container per instance
|
allocate(dependentState(Ninstance))
|
||||||
|
|
||||||
allocate(homogenization_RGC_output(maxval(homogenization_Noutput),maxNinstance))
|
allocate(homogenization_RGC_sizePostResult(maxval(homogenization_Noutput),Ninstance),source=0_pInt)
|
||||||
homogenization_RGC_output=''
|
allocate(homogenization_RGC_output(maxval(homogenization_Noutput),Ninstance))
|
||||||
allocate(homogenization_RGC_sizePostResult(maxval(homogenization_Noutput),maxNinstance),&
|
homogenization_RGC_output=''
|
||||||
source=0_pInt)
|
|
||||||
|
|
||||||
do h = 1_pInt, size(homogenization_type)
|
do h = 1_pInt, size(homogenization_type)
|
||||||
if (homogenization_type(h) /= HOMOGENIZATION_RGC_ID) cycle
|
if (homogenization_type(h) /= HOMOGENIZATION_RGC_ID) cycle
|
||||||
instance = homogenization_typeInstance(h)
|
associate(prm => param(homogenization_typeInstance(h)), &
|
||||||
associate(prm => param(instance))
|
stt => state(homogenization_typeInstance(h)), &
|
||||||
|
dst => dependentState(homogenization_typeInstance(h)), &
|
||||||
|
config => config_homogenization(h))
|
||||||
|
|
||||||
|
#ifdef DEBUG
|
||||||
|
if (h==material_homogenizationAt(debug_e)) then
|
||||||
|
prm%of_debug = mappingHomogenization(1,debug_i,debug_e)
|
||||||
|
endif
|
||||||
|
#endif
|
||||||
|
|
||||||
prm%Nconstituents = config_homogenization(h)%getInts('clustersize',requiredShape=[3])
|
prm%Nconstituents = config%getInts('clustersize',requiredShape=[3])
|
||||||
if (homogenization_Ngrains(h) /= product(prm%Nconstituents)) &
|
if (homogenization_Ngrains(h) /= product(prm%Nconstituents)) &
|
||||||
call IO_error(211_pInt,ext_msg='clustersize ('//HOMOGENIZATION_RGC_label//')')
|
call IO_error(211_pInt,ext_msg='clustersize ('//HOMOGENIZATION_RGC_label//')')
|
||||||
prm%xiAlpha = config_homogenization(h)%getFloat('scalingparameter')
|
prm%xiAlpha = config%getFloat('scalingparameter')
|
||||||
prm%ciAlpha = config_homogenization(h)%getFloat('overproportionality')
|
prm%ciAlpha = config%getFloat('overproportionality')
|
||||||
prm%dAlpha = config_homogenization(h)%getFloats('grainsize',requiredShape=[3])
|
prm%dAlpha = config%getFloats('grainsize',requiredShape=[3])
|
||||||
prm%angles = config_homogenization(h)%getFloats('clusterorientation',requiredShape=[3])
|
prm%angles = config%getFloats('clusterorientation',requiredShape=[3])
|
||||||
|
|
||||||
outputs = config_homogenization(h)%getStrings('(output)',defaultVal=emptyStringArray)
|
outputs = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||||
allocate(prm%outputID(0))
|
allocate(prm%outputID(0))
|
||||||
|
|
||||||
do i=1_pInt, size(outputs)
|
do i=1_pInt, size(outputs)
|
||||||
outputID = undefined_ID
|
outputID = undefined_ID
|
||||||
select case(outputs(i))
|
select case(outputs(i))
|
||||||
|
|
||||||
case('constitutivework')
|
case('constitutivework')
|
||||||
outputID = constitutivework_ID
|
outputID = constitutivework_ID
|
||||||
outputSize = 1_pInt
|
outputSize = 1_pInt
|
||||||
|
@ -181,17 +191,19 @@ subroutine homogenization_RGC_init()
|
||||||
case('magnitudemismatch')
|
case('magnitudemismatch')
|
||||||
outputID = magnitudemismatch_ID
|
outputID = magnitudemismatch_ID
|
||||||
outputSize = 3_pInt
|
outputSize = 3_pInt
|
||||||
case default
|
|
||||||
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,homogenization_typeInstance(h)) = outputs(i)
|
||||||
homogenization_RGC_sizePostResult(i,instance) = outputSize
|
homogenization_RGC_sizePostResult(i,homogenization_typeInstance(h)) = outputSize
|
||||||
prm%outputID = [prm%outputID , outputID]
|
prm%outputID = [prm%outputID , outputID]
|
||||||
endif
|
endif
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
if (iand(debug_level(debug_homogenization),debug_levelExtensive) /= 0_pInt) then
|
if (iand(debug_level(debug_homogenization),debug_levelExtensive) /= 0_pInt) then
|
||||||
write(6,'(a15,1x,i4,/)') 'instance: ', instance
|
write(6,'(a15,1x,i4,/)') 'instance: ', homogenization_typeInstance(h)
|
||||||
write(6,'(a25,3(1x,i8))') 'cluster size: ',(prm%Nconstituents(j),j=1_pInt,3_pInt)
|
write(6,'(a25,3(1x,i8))') 'cluster size: ',(prm%Nconstituents(j),j=1_pInt,3_pInt)
|
||||||
write(6,'(a25,1x,e10.3)') 'scaling parameter: ', prm%xiAlpha
|
write(6,'(a25,1x,e10.3)') 'scaling parameter: ', prm%xiAlpha
|
||||||
write(6,'(a25,1x,e10.3)') 'over-proportionality: ', prm%ciAlpha
|
write(6,'(a25,1x,e10.3)') 'over-proportionality: ', prm%ciAlpha
|
||||||
|
@ -203,38 +215,36 @@ subroutine homogenization_RGC_init()
|
||||||
nIntFaceTot = 3_pInt*( (prm%Nconstituents(1)-1_pInt)*prm%Nconstituents(2)*prm%Nconstituents(3) &
|
nIntFaceTot = 3_pInt*( (prm%Nconstituents(1)-1_pInt)*prm%Nconstituents(2)*prm%Nconstituents(3) &
|
||||||
+ prm%Nconstituents(1)*(prm%Nconstituents(2)-1_pInt)*prm%Nconstituents(3) &
|
+ prm%Nconstituents(1)*(prm%Nconstituents(2)-1_pInt)*prm%Nconstituents(3) &
|
||||||
+ prm%Nconstituents(1)*prm%Nconstituents(2)*(prm%Nconstituents(3)-1_pInt))
|
+ prm%Nconstituents(1)*prm%Nconstituents(2)*(prm%Nconstituents(3)-1_pInt))
|
||||||
sizeHState = nIntFaceTot &
|
sizeState = nIntFaceTot &
|
||||||
+ 8_pInt ! (1) Average constitutive work, (2-4) Overall mismatch, (5) Average penalty energy,
|
+ size(['avg constitutive work']) + size(['overall mismatch']) * 3_pInt &
|
||||||
! (6) Volume discrepancy, (7) Avg relaxation rate component, (8) Max relaxation rate component
|
+ size(['average penalty energy ','volume discrepancy ',&
|
||||||
|
'avg relaxation rate component ','max relaxation rate componenty'])
|
||||||
homogState(h)%sizeState = sizeHState
|
|
||||||
homogState(h)%sizePostResults = sum(homogenization_RGC_sizePostResult(:,instance))
|
|
||||||
allocate(homogState(h)%state0 (sizeHState,NofMyHomog), source=0.0_pReal)
|
|
||||||
allocate(homogState(h)%subState0(sizeHState,NofMyHomog), source=0.0_pReal)
|
|
||||||
allocate(homogState(h)%state (sizeHState,NofMyHomog), source=0.0_pReal)
|
|
||||||
|
|
||||||
state(instance)%relaxationVector => homogState(h)%state(1:nIntFaceTot,:)
|
homogState(h)%sizeState = sizeState
|
||||||
state(instance)%work => homogState(h)%state(nIntFaceTot+1,:)
|
homogState(h)%sizePostResults = sum(homogenization_RGC_sizePostResult(:,homogenization_typeInstance(h)))
|
||||||
state(instance)%mismatch => homogState(h)%state(nIntFaceTot+2:nIntFaceTot+4,:)
|
allocate(homogState(h)%state0 (sizeState,NofMyHomog), source=0.0_pReal)
|
||||||
state(instance)%penaltyEnergy => homogState(h)%state(nIntFaceTot+5,:)
|
allocate(homogState(h)%subState0(sizeState,NofMyHomog), source=0.0_pReal)
|
||||||
state(instance)%volumeDiscrepancy => homogState(h)%state(nIntFaceTot+6,:)
|
allocate(homogState(h)%state (sizeState,NofMyHomog), source=0.0_pReal)
|
||||||
state(instance)%relaxationRate_avg => homogState(h)%state(nIntFaceTot+7,:)
|
|
||||||
state(instance)%relaxationRate_max => homogState(h)%state(nIntFaceTot+8,:)
|
|
||||||
|
|
||||||
allocate(dependentState(instance)%orientation(3,3,NofMyHomog))
|
stt%relaxationVector => homogState(h)%state(1:nIntFaceTot,:)
|
||||||
|
stt%work => homogState(h)%state(nIntFaceTot+1,:)
|
||||||
|
stt%mismatch => homogState(h)%state(nIntFaceTot+2:nIntFaceTot+4,:)
|
||||||
|
stt%penaltyEnergy => homogState(h)%state(nIntFaceTot+5,:)
|
||||||
|
stt%volumeDiscrepancy => homogState(h)%state(nIntFaceTot+6,:)
|
||||||
|
stt%relaxationRate_avg => homogState(h)%state(nIntFaceTot+7,:)
|
||||||
|
stt%relaxationRate_max => homogState(h)%state(nIntFaceTot+8,:)
|
||||||
|
|
||||||
|
allocate(dst%orientation(3,3,NofMyHomog))
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! * assigning cluster orientations
|
! assigning cluster orientations
|
||||||
elementLooping: do e = 1_pInt,mesh_NcpElems
|
do j=1, NofMyHomog
|
||||||
if (homogenization_typeInstance(material_homogenizationAt(e)) == instance .and. NofMyHomog > 0_pInt) then
|
dst%orientation(1:3,1:3,j) = math_EulerToR(prm%angles*inRad) !ToDo: use spread
|
||||||
do i = 1_pInt,mesh_NipsPerElem
|
enddo
|
||||||
of = mappingHomogenization(1,i,e)
|
|
||||||
dependentState(instance)%orientation(1:3,1:3,of) = math_EulerToR(prm%angles*inRad)
|
|
||||||
enddo
|
|
||||||
endif
|
|
||||||
enddo elementLooping
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end subroutine homogenization_RGC_init
|
end subroutine homogenization_RGC_init
|
||||||
|
@ -244,19 +254,23 @@ end subroutine homogenization_RGC_init
|
||||||
!> @brief partitions the deformation gradient onto the constituents
|
!> @brief partitions the deformation gradient onto the constituents
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine homogenization_RGC_partitionDeformation(F,avgF,instance,of)
|
subroutine homogenization_RGC_partitionDeformation(F,avgF,instance,of)
|
||||||
|
#ifdef DEBUG
|
||||||
use debug, only: &
|
use debug, only: &
|
||||||
debug_level, &
|
debug_level, &
|
||||||
debug_homogenization, &
|
debug_homogenization, &
|
||||||
debug_levelExtensive
|
debug_levelExtensive
|
||||||
|
#endif
|
||||||
use material, only: &
|
use material, only: &
|
||||||
homogenization_maxNgrains
|
homogenization_maxNgrains
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(out) :: F !< partioned F per grain
|
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(out) :: F !< partioned F per grain
|
||||||
|
|
||||||
real(pReal), dimension (3,3), intent(in) :: avgF !< averaged F
|
real(pReal), dimension (3,3), intent(in) :: avgF !< averaged F
|
||||||
integer(pInt), intent(in) :: &
|
integer(pInt), intent(in) :: &
|
||||||
instance, &
|
instance, &
|
||||||
of !< element number
|
of
|
||||||
|
|
||||||
real(pReal), dimension (3) :: aVect,nVect
|
real(pReal), dimension (3) :: aVect,nVect
|
||||||
integer(pInt), dimension (4) :: intFace
|
integer(pInt), dimension (4) :: intFace
|
||||||
integer(pInt), dimension (3) :: iGrain3
|
integer(pInt), dimension (3) :: iGrain3
|
||||||
|
@ -265,6 +279,7 @@ subroutine homogenization_RGC_partitionDeformation(F,avgF,instance,of)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! compute the deformation gradient of individual grains due to relaxations
|
! compute the deformation gradient of individual grains due to relaxations
|
||||||
associate(prm => param(instance))
|
associate(prm => param(instance))
|
||||||
|
|
||||||
F = 0.0_pReal
|
F = 0.0_pReal
|
||||||
do iGrain = 1_pInt,product(prm%Nconstituents)
|
do iGrain = 1_pInt,product(prm%Nconstituents)
|
||||||
iGrain3 = grain1to3(iGrain,prm%Nconstituents)
|
iGrain3 = grain1to3(iGrain,prm%Nconstituents)
|
||||||
|
@ -279,18 +294,18 @@ subroutine homogenization_RGC_partitionDeformation(F,avgF,instance,of)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! debugging the grain deformation gradients
|
! debugging the grain deformation gradients
|
||||||
|
#ifdef DEBUG
|
||||||
if (iand(debug_level(debug_homogenization),debug_levelExtensive) /= 0_pInt) then
|
if (iand(debug_level(debug_homogenization),debug_levelExtensive) /= 0_pInt) then
|
||||||
!$OMP CRITICAL (write2out)
|
|
||||||
write(6,'(1x,a32,1x,i3)')'Deformation gradient of grain: ',iGrain
|
write(6,'(1x,a32,1x,i3)')'Deformation gradient of grain: ',iGrain
|
||||||
do i = 1_pInt,3_pInt
|
do i = 1_pInt,3_pInt
|
||||||
write(6,'(1x,3(e15.8,1x))')(F(i,j,iGrain), j = 1_pInt,3_pInt)
|
write(6,'(1x,3(e15.8,1x))')(F(i,j,iGrain), j = 1_pInt,3_pInt)
|
||||||
enddo
|
enddo
|
||||||
write(6,*)' '
|
write(6,*)' '
|
||||||
flush(6)
|
flush(6)
|
||||||
!$OMP END CRITICAL (write2out)
|
|
||||||
endif
|
endif
|
||||||
|
#endif
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
end subroutine homogenization_RGC_partitionDeformation
|
end subroutine homogenization_RGC_partitionDeformation
|
||||||
|
@ -378,17 +393,16 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
|
||||||
relax = homogState(mappingHomogenization(2,ip,el))%state (1:3_pInt*nIntFaceTot,of)
|
relax = homogState(mappingHomogenization(2,ip,el))%state (1:3_pInt*nIntFaceTot,of)
|
||||||
drelax = relax &
|
drelax = relax &
|
||||||
- homogState(mappingHomogenization(2,ip,el))%state0(1:3_pInt*nIntFaceTot,of)
|
- homogState(mappingHomogenization(2,ip,el))%state0(1:3_pInt*nIntFaceTot,of)
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! debugging the obtained state
|
#ifdef DEBUG
|
||||||
if (iand(debug_level(debug_homogenization),debug_levelExtensive) /= 0_pInt) then
|
if (iand(debug_level(debug_homogenization),debug_levelExtensive) /= 0_pInt) then
|
||||||
!$OMP CRITICAL (write2out)
|
|
||||||
write(6,'(1x,a30)')'Obtained state: '
|
write(6,'(1x,a30)')'Obtained state: '
|
||||||
do i = 1_pInt,3_pInt*nIntFaceTot
|
do i = 1_pInt,3_pInt*nIntFaceTot
|
||||||
write(6,'(1x,2(e15.8,1x))')homogState(mappingHomogenization(2,ip,el))%state(i,of)
|
write(6,'(1x,2(e15.8,1x))')homogState(mappingHomogenization(2,ip,el))%state(i,of)
|
||||||
enddo
|
enddo
|
||||||
write(6,*)' '
|
write(6,*)' '
|
||||||
!$OMP END CRITICAL (write2out)
|
|
||||||
endif
|
endif
|
||||||
|
#endif
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! computing interface mismatch and stress penalty tensor for all interfaces of all grains
|
! computing interface mismatch and stress penalty tensor for all interfaces of all grains
|
||||||
|
@ -398,10 +412,8 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
|
||||||
! calculating volume discrepancy and stress penalty related to overall volume discrepancy
|
! calculating volume discrepancy and stress penalty related to overall volume discrepancy
|
||||||
call volumePenalty(D,volDiscrep,F,avgF,ip,el)
|
call volumePenalty(D,volDiscrep,F,avgF,ip,el)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
#ifdef DEBUG
|
||||||
! debugging the mismatch, stress and penalties of grains
|
|
||||||
if (iand(debug_level(debug_homogenization),debug_levelExtensive) /= 0_pInt) then
|
if (iand(debug_level(debug_homogenization),debug_levelExtensive) /= 0_pInt) then
|
||||||
!$OMP CRITICAL (write2out)
|
|
||||||
do iGrain = 1_pInt,nGrain
|
do iGrain = 1_pInt,nGrain
|
||||||
write(6,'(1x,a30,1x,i3,1x,a4,3(1x,e15.8))')'Mismatch magnitude of grain(',iGrain,') :',&
|
write(6,'(1x,a30,1x,i3,1x,a4,3(1x,e15.8))')'Mismatch magnitude of grain(',iGrain,') :',&
|
||||||
NN(1,iGrain),NN(2,iGrain),NN(3,iGrain)
|
NN(1,iGrain),NN(2,iGrain),NN(3,iGrain)
|
||||||
|
@ -413,8 +425,8 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
|
||||||
enddo
|
enddo
|
||||||
write(6,*)' '
|
write(6,*)' '
|
||||||
enddo
|
enddo
|
||||||
!$OMP END CRITICAL (write2out)
|
|
||||||
endif
|
endif
|
||||||
|
#endif
|
||||||
|
|
||||||
!------------------------------------------------------------------------------------------------
|
!------------------------------------------------------------------------------------------------
|
||||||
! computing the residual stress from the balance of traction at all (interior) interfaces
|
! computing the residual stress from the balance of traction at all (interior) interfaces
|
||||||
|
@ -448,15 +460,13 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
#ifdef DEBUG
|
||||||
! debugging the residual stress
|
|
||||||
if (iand(debug_level(debug_homogenization),debug_levelExtensive) /= 0_pInt) then
|
if (iand(debug_level(debug_homogenization),debug_levelExtensive) /= 0_pInt) then
|
||||||
!$OMP CRITICAL (write2out)
|
|
||||||
write(6,'(1x,a30,1x,i3)')'Traction at interface: ',iNum
|
write(6,'(1x,a30,1x,i3)')'Traction at interface: ',iNum
|
||||||
write(6,'(1x,3(e15.8,1x))')(tract(iNum,j), j = 1_pInt,3_pInt)
|
write(6,'(1x,3(e15.8,1x))')(tract(iNum,j), j = 1_pInt,3_pInt)
|
||||||
write(6,*)' '
|
write(6,*)' '
|
||||||
!$OMP END CRITICAL (write2out)
|
|
||||||
endif
|
endif
|
||||||
|
#endif
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -466,8 +476,7 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
|
||||||
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
|
residLoc = int(maxloc(abs(tract)),pInt) ! get the position of the maximum residual
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
#ifdef DEBUG
|
||||||
! Debugging the convergent criteria
|
|
||||||
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
|
||||||
!$OMP CRITICAL (write2out)
|
!$OMP CRITICAL (write2out)
|
||||||
|
@ -478,8 +487,8 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
|
||||||
write(6,'(1x,a15,1x,e15.8,1x,a7,i3,1x,a12,i2)')'Max residual: ',residMax, &
|
write(6,'(1x,a15,1x,e15.8,1x,a7,i3,1x,a12,i2)')'Max residual: ',residMax, &
|
||||||
'@ iface',residLoc(1),'in direction',residLoc(2)
|
'@ iface',residLoc(1),'in direction',residLoc(2)
|
||||||
flush(6)
|
flush(6)
|
||||||
!$OMP END CRITICAL (write2out)
|
|
||||||
endif
|
endif
|
||||||
|
#endif
|
||||||
|
|
||||||
homogenization_RGC_updateState = .false.
|
homogenization_RGC_updateState = .false.
|
||||||
|
|
||||||
|
|
|
@ -7,12 +7,13 @@
|
||||||
module homogenization_isostrain
|
module homogenization_isostrain
|
||||||
use prec, only: &
|
use prec, only: &
|
||||||
pInt
|
pInt
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
enum, bind(c)
|
enum, bind(c)
|
||||||
enumerator :: parallel_ID, &
|
enumerator :: &
|
||||||
average_ID
|
parallel_ID, &
|
||||||
|
average_ID
|
||||||
end enum
|
end enum
|
||||||
|
|
||||||
type, private :: tParameters !< container type for internal constitutive parameters
|
type, private :: tParameters !< container type for internal constitutive parameters
|
||||||
|
@ -59,22 +60,17 @@ subroutine homogenization_isostrain_init()
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt) :: &
|
integer(pInt) :: &
|
||||||
h
|
Ninstance, &
|
||||||
integer :: &
|
h, &
|
||||||
Ninstance
|
NofMyHomog
|
||||||
integer :: &
|
|
||||||
NofMyHomog ! no pInt (stores a system dependen value from 'count'
|
|
||||||
character(len=65536) :: &
|
character(len=65536) :: &
|
||||||
tag = ''
|
tag = ''
|
||||||
type(tParameters) :: prm
|
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- homogenization_'//HOMOGENIZATION_ISOSTRAIN_label//' init -+>>>'
|
write(6,'(/,a)') ' <<<+- homogenization_'//HOMOGENIZATION_ISOSTRAIN_label//' 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"
|
||||||
|
|
||||||
Ninstance = count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)
|
Ninstance = int(count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID),pInt)
|
||||||
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:',Ninstance
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
||||||
|
|
||||||
|
@ -82,12 +78,13 @@ subroutine homogenization_isostrain_init()
|
||||||
|
|
||||||
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
|
||||||
associate(prm => param(homogenization_typeInstance(h)))
|
|
||||||
|
associate(prm => param(homogenization_typeInstance(h)),&
|
||||||
|
config => config_homogenization(h))
|
||||||
|
|
||||||
prm%Nconstituents = config_homogenization(h)%getInt('nconstituents')
|
prm%Nconstituents = config_homogenization(h)%getInt('nconstituents')
|
||||||
tag = 'sum'
|
tag = 'sum'
|
||||||
tag = config_homogenization(h)%getString('mapping',defaultVal = tag)
|
select case(trim(config%getString('mapping',defaultVal = tag)))
|
||||||
select case(trim(tag))
|
|
||||||
case ('sum')
|
case ('sum')
|
||||||
prm%mapping = parallel_ID
|
prm%mapping = parallel_ID
|
||||||
case ('avg')
|
case ('avg')
|
||||||
|
@ -97,12 +94,12 @@ subroutine homogenization_isostrain_init()
|
||||||
end select
|
end select
|
||||||
|
|
||||||
NofMyHomog = count(material_homog == h)
|
NofMyHomog = count(material_homog == h)
|
||||||
|
|
||||||
homogState(h)%sizeState = 0_pInt
|
homogState(h)%sizeState = 0_pInt
|
||||||
homogState(h)%sizePostResults = 0_pInt
|
homogState(h)%sizePostResults = 0_pInt
|
||||||
allocate(homogState(h)%state0 (0_pInt,NofMyHomog))
|
allocate(homogState(h)%state0 (0_pInt,NofMyHomog))
|
||||||
allocate(homogState(h)%subState0(0_pInt,NofMyHomog))
|
allocate(homogState(h)%subState0(0_pInt,NofMyHomog))
|
||||||
allocate(homogState(h)%state (0_pInt,NofMyHomog))
|
allocate(homogState(h)%state (0_pInt,NofMyHomog))
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
@ -120,16 +117,18 @@ subroutine homogenization_isostrain_partitionDeformation(F,avgF,instance)
|
||||||
homogenization_maxNgrains
|
homogenization_maxNgrains
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(out) :: F !< partioned def grad per grain
|
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(out) :: F !< partitioned deformation gradient
|
||||||
real(pReal), dimension (3,3), intent(in) :: avgF !< my average def grad
|
|
||||||
|
real(pReal), dimension (3,3), intent(in) :: avgF !< average deformation gradient at material point
|
||||||
integer(pInt), intent(in) :: instance
|
integer(pInt), intent(in) :: instance
|
||||||
type(tParameters) :: &
|
|
||||||
prm
|
|
||||||
|
|
||||||
associate(prm => param(instance))
|
associate(prm => param(instance))
|
||||||
|
|
||||||
F(1:3,1:3,1:prm%Nconstituents) = spread(avgF,3,prm%Nconstituents)
|
F(1:3,1:3,1:prm%Nconstituents) = spread(avgF,3,prm%Nconstituents)
|
||||||
if (homogenization_maxNgrains > prm%Nconstituents) &
|
if (homogenization_maxNgrains > prm%Nconstituents) &
|
||||||
F(1:3,1:3,prm%Nconstituents+1_pInt:homogenization_maxNgrains) = 0.0_pReal
|
F(1:3,1:3,prm%Nconstituents+1_pInt:homogenization_maxNgrains) = 0.0_pReal
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
end subroutine homogenization_isostrain_partitionDeformation
|
end subroutine homogenization_isostrain_partitionDeformation
|
||||||
|
@ -147,13 +146,13 @@ subroutine homogenization_isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P
|
||||||
implicit none
|
implicit none
|
||||||
real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point
|
real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point
|
||||||
real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF !< average stiffness at material point
|
real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF !< average stiffness at material point
|
||||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: P !< array of current grain stresses
|
|
||||||
real(pReal), dimension (3,3,3,3,homogenization_maxNgrains), intent(in) :: dPdF !< array of current grain stiffnesses
|
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: P !< partitioned stresses
|
||||||
|
real(pReal), dimension (3,3,3,3,homogenization_maxNgrains), intent(in) :: dPdF !< partitioned stiffnesses
|
||||||
integer(pInt), intent(in) :: instance
|
integer(pInt), intent(in) :: instance
|
||||||
type(tParameters) :: &
|
|
||||||
prm
|
|
||||||
|
|
||||||
associate(prm => param(instance))
|
associate(prm => param(instance))
|
||||||
|
|
||||||
select case (prm%mapping)
|
select case (prm%mapping)
|
||||||
case (parallel_ID)
|
case (parallel_ID)
|
||||||
avgP = sum(P,3)
|
avgP = sum(P,3)
|
||||||
|
@ -162,6 +161,7 @@ subroutine homogenization_isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P
|
||||||
avgP = sum(P,3) /real(prm%Nconstituents,pReal)
|
avgP = sum(P,3) /real(prm%Nconstituents,pReal)
|
||||||
dAvgPdAvgF = sum(dPdF,5)/real(prm%Nconstituents,pReal)
|
dAvgPdAvgF = sum(dPdF,5)/real(prm%Nconstituents,pReal)
|
||||||
end select
|
end select
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
end subroutine homogenization_isostrain_averageStressAndItsTangent
|
end subroutine homogenization_isostrain_averageStressAndItsTangent
|
||||||
|
|
|
@ -2,7 +2,7 @@
|
||||||
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
!> @brief dummy homogenization homogenization scheme
|
!> @brief dummy homogenization homogenization scheme for 1 constituent per material point
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module homogenization_none
|
module homogenization_none
|
||||||
|
|
||||||
|
@ -24,9 +24,14 @@ subroutine homogenization_none_init()
|
||||||
compiler_options
|
compiler_options
|
||||||
#endif
|
#endif
|
||||||
use prec, only: &
|
use prec, only: &
|
||||||
pInt
|
pInt
|
||||||
|
use debug, only: &
|
||||||
|
debug_HOMOGENIZATION, &
|
||||||
|
debug_level, &
|
||||||
|
debug_levelBasic
|
||||||
use IO, only: &
|
use IO, only: &
|
||||||
IO_timeStamp
|
IO_timeStamp
|
||||||
|
|
||||||
use material, only: &
|
use material, only: &
|
||||||
homogenization_type, &
|
homogenization_type, &
|
||||||
material_homog, &
|
material_homog, &
|
||||||
|
@ -36,6 +41,7 @@ subroutine homogenization_none_init()
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt) :: &
|
integer(pInt) :: &
|
||||||
|
Ninstance, &
|
||||||
h, &
|
h, &
|
||||||
NofMyHomog
|
NofMyHomog
|
||||||
|
|
||||||
|
@ -43,6 +49,10 @@ subroutine homogenization_none_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"
|
||||||
|
|
||||||
|
Ninstance = int(count(homogenization_type == HOMOGENIZATION_NONE_ID),pInt)
|
||||||
|
if (iand(debug_level(debug_HOMOGENIZATION),debug_levelBasic) /= 0_pInt) &
|
||||||
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
||||||
|
|
||||||
do h = 1_pInt, size(homogenization_type)
|
do h = 1_pInt, size(homogenization_type)
|
||||||
if (homogenization_type(h) /= HOMOGENIZATION_NONE_ID) cycle
|
if (homogenization_type(h) /= HOMOGENIZATION_NONE_ID) cycle
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue