phasing out postResults
starting with RGC because it is rarely used and removing it here allows to go ahead with the submodule structure for homogenization
This commit is contained in:
parent
0958c4bb88
commit
39a75c2015
|
@ -120,7 +120,6 @@ subroutine homogenization_init
|
|||
character(len=32) :: outputName !< name of output, intermediate fix until HDF5 output is ready
|
||||
logical :: valid
|
||||
|
||||
|
||||
if (any(homogenization_type == HOMOGENIZATION_NONE_ID)) call mech_none_init
|
||||
if (any(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)) call mech_isostrain_init
|
||||
if (any(homogenization_type == HOMOGENIZATION_RGC_ID)) call homogenization_RGC_init
|
||||
|
@ -139,35 +138,9 @@ subroutine homogenization_init
|
|||
call IO_write_jobFile(FILEUNIT,'outputHomogenization')
|
||||
do p = 1,size(config_homogenization)
|
||||
if (any(material_homogenizationAt == p)) then
|
||||
i = homogenization_typeInstance(p) ! which instance of this homogenization type
|
||||
valid = .true. ! assume valid
|
||||
select case(homogenization_type(p)) ! split per homogenization type
|
||||
case (HOMOGENIZATION_NONE_ID)
|
||||
outputName = HOMOGENIZATION_NONE_label
|
||||
thisOutput => null()
|
||||
thisSize => null()
|
||||
case (HOMOGENIZATION_ISOSTRAIN_ID)
|
||||
outputName = HOMOGENIZATION_ISOSTRAIN_label
|
||||
thisOutput => null()
|
||||
thisSize => null()
|
||||
case (HOMOGENIZATION_RGC_ID)
|
||||
outputName = HOMOGENIZATION_RGC_label
|
||||
thisOutput => homogenization_RGC_output
|
||||
thisSize => homogenization_RGC_sizePostResult
|
||||
case default
|
||||
valid = .false.
|
||||
end select
|
||||
write(FILEUNIT,'(/,a,/)') '['//trim(homogenization_name(p))//']'
|
||||
if (valid) then
|
||||
write(FILEUNIT,'(a)') '(type)'//char(9)//trim(outputName)
|
||||
write(FILEUNIT,'(a,i4)') '(ngrains)'//char(9),homogenization_Ngrains(p)
|
||||
if (homogenization_type(p) /= HOMOGENIZATION_NONE_ID .and. &
|
||||
homogenization_type(p) /= HOMOGENIZATION_ISOSTRAIN_ID) then
|
||||
do e = 1,size(thisOutput(:,i))
|
||||
write(FILEUNIT,'(a,i4)') trim(thisOutput(e,i))//char(9),thisSize(e,i)
|
||||
enddo
|
||||
endif
|
||||
endif
|
||||
write(FILEUNIT,'(a,i4)') '(ngrains)'//char(9),homogenization_Ngrains(p)
|
||||
|
||||
i = thermal_typeInstance(p) ! which instance of this thermal type
|
||||
valid = .true. ! assume valid
|
||||
select case(thermal_type(p)) ! split per thermal type
|
||||
|
@ -837,8 +810,6 @@ end subroutine averageStressAndItsTangent
|
|||
function postResults(ip,el)
|
||||
use mesh, only: &
|
||||
mesh_element
|
||||
use homogenization_mech_RGC, only: &
|
||||
homogenization_RGC_postResults
|
||||
use thermal_adiabatic, only: &
|
||||
thermal_adiabatic_postResults
|
||||
use thermal_conduction, only: &
|
||||
|
@ -861,17 +832,6 @@ function postResults(ip,el)
|
|||
|
||||
|
||||
postResults = 0.0_pReal
|
||||
startPos = 1
|
||||
endPos = homogState(material_homogenizationAt(el))%sizePostResults
|
||||
chosenHomogenization: select case (homogenization_type(mesh_element(3,el)))
|
||||
|
||||
case (HOMOGENIZATION_RGC_ID) chosenHomogenization
|
||||
instance = homogenization_typeInstance(material_homogenizationAt(el))
|
||||
of = mappingHomogenization(1,ip,el)
|
||||
postResults(startPos:endPos) = homogenization_RGC_postResults(instance,of)
|
||||
|
||||
end select chosenHomogenization
|
||||
|
||||
startPos = endPos + 1
|
||||
endPos = endPos + thermalState(material_homogenizationAt(el))%sizePostResults
|
||||
chosenThermal: select case (thermal_type(mesh_element(3,el)))
|
||||
|
|
|
@ -12,10 +12,6 @@ module homogenization_mech_RGC
|
|||
|
||||
implicit none
|
||||
private
|
||||
integer, dimension(:,:), allocatable,target, public :: &
|
||||
homogenization_RGC_sizePostResult
|
||||
character(len=64), dimension(:,:), allocatable,target, public :: &
|
||||
homogenization_RGC_output ! name of each post result output
|
||||
|
||||
enum, bind(c)
|
||||
enumerator :: &
|
||||
|
@ -28,7 +24,7 @@ module homogenization_mech_RGC
|
|||
magnitudemismatch_ID
|
||||
end enum
|
||||
|
||||
type, private :: tParameters
|
||||
type :: tParameters
|
||||
integer, dimension(:), allocatable :: &
|
||||
Nconstituents
|
||||
real(pReal) :: &
|
||||
|
@ -43,7 +39,7 @@ module homogenization_mech_RGC
|
|||
outputID
|
||||
end type tParameters
|
||||
|
||||
type, private :: tRGCstate
|
||||
type :: tRGCstate
|
||||
real(pReal), pointer, dimension(:) :: &
|
||||
work, &
|
||||
penaltyEnergy
|
||||
|
@ -51,7 +47,7 @@ module homogenization_mech_RGC
|
|||
relaxationVector
|
||||
end type tRGCstate
|
||||
|
||||
type, private :: tRGCdependentState
|
||||
type :: tRGCdependentState
|
||||
real(pReal), allocatable, dimension(:) :: &
|
||||
volumeDiscrepancy, &
|
||||
relaxationRate_avg, &
|
||||
|
@ -62,12 +58,12 @@ module homogenization_mech_RGC
|
|||
orientation
|
||||
end type tRGCdependentState
|
||||
|
||||
type(tparameters), dimension(:), allocatable, private :: &
|
||||
type(tparameters), dimension(:), allocatable :: &
|
||||
param
|
||||
type(tRGCstate), dimension(:), allocatable, private :: &
|
||||
type(tRGCstate), dimension(:), allocatable :: &
|
||||
state, &
|
||||
state0
|
||||
type(tRGCdependentState), dimension(:), allocatable, private :: &
|
||||
type(tRGCdependentState), dimension(:), allocatable :: &
|
||||
dependentState
|
||||
|
||||
public :: &
|
||||
|
@ -75,16 +71,7 @@ module homogenization_mech_RGC
|
|||
homogenization_RGC_partitionDeformation, &
|
||||
homogenization_RGC_averageStressAndItsTangent, &
|
||||
homogenization_RGC_updateState, &
|
||||
homogenization_RGC_postResults, &
|
||||
mech_RGC_results ! name suited for planned submodule situation
|
||||
private :: &
|
||||
relaxationVector, &
|
||||
interfaceNormal, &
|
||||
getInterface, &
|
||||
grain1to3, &
|
||||
grain3to1, &
|
||||
interface4to1, &
|
||||
interface1to4
|
||||
|
||||
contains
|
||||
|
||||
|
@ -111,7 +98,7 @@ subroutine homogenization_RGC_init()
|
|||
integer :: &
|
||||
Ninstance, &
|
||||
h, i, &
|
||||
NofMyHomog, outputSize, &
|
||||
NofMyHomog, &
|
||||
sizeState, nIntFaceTot
|
||||
|
||||
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
|
||||
|
@ -139,9 +126,6 @@ subroutine homogenization_RGC_init()
|
|||
allocate(state0(Ninstance))
|
||||
allocate(dependentState(Ninstance))
|
||||
|
||||
allocate(homogenization_RGC_sizePostResult(maxval(homogenization_Noutput),Ninstance),source=0)
|
||||
allocate(homogenization_RGC_output(maxval(homogenization_Noutput),Ninstance))
|
||||
homogenization_RGC_output=''
|
||||
|
||||
do h = 1, size(homogenization_type)
|
||||
if (homogenization_type(h) /= HOMOGENIZATION_RGC_ID) cycle
|
||||
|
@ -176,28 +160,20 @@ subroutine homogenization_RGC_init()
|
|||
|
||||
case('constitutivework')
|
||||
outputID = constitutivework_ID
|
||||
outputSize = 1
|
||||
case('penaltyenergy')
|
||||
outputID = penaltyenergy_ID
|
||||
outputSize = 1
|
||||
case('volumediscrepancy')
|
||||
outputID = volumediscrepancy_ID
|
||||
outputSize = 1
|
||||
case('averagerelaxrate')
|
||||
outputID = averagerelaxrate_ID
|
||||
outputSize = 1
|
||||
case('maximumrelaxrate')
|
||||
outputID = maximumrelaxrate_ID
|
||||
outputSize = 1
|
||||
case('magnitudemismatch')
|
||||
outputID = magnitudemismatch_ID
|
||||
outputSize = 3
|
||||
|
||||
end select
|
||||
|
||||
if (outputID /= undefined_ID) then
|
||||
homogenization_RGC_output(i,homogenization_typeInstance(h)) = outputs(i)
|
||||
homogenization_RGC_sizePostResult(i,homogenization_typeInstance(h)) = outputSize
|
||||
prm%outputID = [prm%outputID , outputID]
|
||||
endif
|
||||
|
||||
|
@ -211,7 +187,7 @@ subroutine homogenization_RGC_init()
|
|||
+ size(['avg constitutive work ','average penalty energy'])
|
||||
|
||||
homogState(h)%sizeState = sizeState
|
||||
homogState(h)%sizePostResults = sum(homogenization_RGC_sizePostResult(:,homogenization_typeInstance(h)))
|
||||
homogState(h)%sizePostResults = 0
|
||||
allocate(homogState(h)%state0 (sizeState,NofMyHomog), source=0.0_pReal)
|
||||
allocate(homogState(h)%subState0(sizeState,NofMyHomog), source=0.0_pReal)
|
||||
allocate(homogState(h)%state (sizeState,NofMyHomog), source=0.0_pReal)
|
||||
|
@ -1033,54 +1009,6 @@ subroutine homogenization_RGC_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,
|
|||
end subroutine homogenization_RGC_averageStressAndItsTangent
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief return array of homogenization results for post file inclusion
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
pure function homogenization_RGC_postResults(instance,of) result(postResults)
|
||||
|
||||
integer, intent(in) :: &
|
||||
instance, &
|
||||
of
|
||||
|
||||
integer :: &
|
||||
o,c
|
||||
real(pReal), dimension(sum(homogenization_RGC_sizePostResult(:,instance))) :: &
|
||||
postResults
|
||||
|
||||
associate(stt => state(instance), dst => dependentState(instance), prm => param(instance))
|
||||
|
||||
c = 0
|
||||
|
||||
outputsLoop: do o = 1,size(prm%outputID)
|
||||
select case(prm%outputID(o))
|
||||
|
||||
case (constitutivework_ID)
|
||||
postResults(c+1) = stt%work(of)
|
||||
c = c + 1
|
||||
case (magnitudemismatch_ID)
|
||||
postResults(c+1:c+3) = dst%mismatch(1:3,of)
|
||||
c = c + 3
|
||||
case (penaltyenergy_ID)
|
||||
postResults(c+1) = stt%penaltyEnergy(of)
|
||||
c = c + 1
|
||||
case (volumediscrepancy_ID)
|
||||
postResults(c+1) = dst%volumeDiscrepancy(of)
|
||||
c = c + 1
|
||||
case (averagerelaxrate_ID)
|
||||
postResults(c+1) = dst%relaxationrate_avg(of)
|
||||
c = c + 1
|
||||
case (maximumrelaxrate_ID)
|
||||
postResults(c+1) = dst%relaxationrate_max(of)
|
||||
c = c + 1
|
||||
end select
|
||||
|
||||
enddo outputsLoop
|
||||
|
||||
end associate
|
||||
|
||||
end function homogenization_RGC_postResults
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief writes results to HDF5 output file
|
||||
! ToDo: check wheter units are correct
|
||||
|
|
Loading…
Reference in New Issue