using parameters from linked list and removed output
homogenization models should only provide model specific output in accordance with http://dx.doi.org/10.1007/s40192-017-0084-5
This commit is contained in:
parent
2ad13a08e8
commit
49ae38d0f9
|
@ -147,7 +147,7 @@ subroutine homogenization_init
|
||||||
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(FILEUNIT)
|
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(FILEUNIT)
|
||||||
|
|
||||||
|
@ -207,16 +207,11 @@ subroutine homogenization_init
|
||||||
i = homogenization_typeInstance(p) ! which instance of this homogenization type
|
i = homogenization_typeInstance(p) ! which instance of this homogenization type
|
||||||
valid = .true. ! assume valid
|
valid = .true. ! assume valid
|
||||||
select case(homogenization_type(p)) ! split per homogenization type
|
select case(homogenization_type(p)) ! split per homogenization type
|
||||||
case (HOMOGENIZATION_NONE_ID)
|
case (HOMOGENIZATION_NONE_ID,HOMOGENIZATION_ISOSTRAIN_ID)
|
||||||
outputName = HOMOGENIZATION_NONE_label
|
outputName = HOMOGENIZATION_NONE_label
|
||||||
thisNoutput => null()
|
thisNoutput => null()
|
||||||
thisOutput => null()
|
thisOutput => null()
|
||||||
thisSize => null()
|
thisSize => null()
|
||||||
case (HOMOGENIZATION_ISOSTRAIN_ID)
|
|
||||||
outputName = HOMOGENIZATION_ISOSTRAIN_label
|
|
||||||
thisNoutput => homogenization_isostrain_Noutput
|
|
||||||
thisOutput => homogenization_isostrain_output
|
|
||||||
thisSize => homogenization_isostrain_sizePostResult
|
|
||||||
case (HOMOGENIZATION_RGC_ID)
|
case (HOMOGENIZATION_RGC_ID)
|
||||||
outputName = HOMOGENIZATION_RGC_label
|
outputName = HOMOGENIZATION_RGC_label
|
||||||
thisNoutput => homogenization_RGC_Noutput
|
thisNoutput => homogenization_RGC_Noutput
|
||||||
|
@ -1246,8 +1241,6 @@ function homogenization_postResults(ip,el)
|
||||||
POROSITY_phasefield_ID, &
|
POROSITY_phasefield_ID, &
|
||||||
HYDROGENFLUX_isoconc_ID, &
|
HYDROGENFLUX_isoconc_ID, &
|
||||||
HYDROGENFLUX_cahnhilliard_ID
|
HYDROGENFLUX_cahnhilliard_ID
|
||||||
use homogenization_isostrain, only: &
|
|
||||||
homogenization_isostrain_postResults
|
|
||||||
use homogenization_RGC, only: &
|
use homogenization_RGC, only: &
|
||||||
homogenization_RGC_postResults
|
homogenization_RGC_postResults
|
||||||
use thermal_adiabatic, only: &
|
use thermal_adiabatic, only: &
|
||||||
|
@ -1286,15 +1279,8 @@ function homogenization_postResults(ip,el)
|
||||||
startPos = 1_pInt
|
startPos = 1_pInt
|
||||||
endPos = homogState(mappingHomogenization(2,ip,el))%sizePostResults
|
endPos = homogState(mappingHomogenization(2,ip,el))%sizePostResults
|
||||||
chosenHomogenization: select case (homogenization_type(mesh_element(3,el)))
|
chosenHomogenization: select case (homogenization_type(mesh_element(3,el)))
|
||||||
case (HOMOGENIZATION_NONE_ID) chosenHomogenization
|
case (HOMOGENIZATION_NONE_ID,HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
|
||||||
|
|
||||||
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
|
|
||||||
homogenization_postResults(startPos:endPos) = &
|
|
||||||
homogenization_isostrain_postResults(&
|
|
||||||
ip, &
|
|
||||||
el, &
|
|
||||||
materialpoint_P(1:3,1:3,ip,el), &
|
|
||||||
materialpoint_F(1:3,1:3,ip,el))
|
|
||||||
case (HOMOGENIZATION_RGC_ID) chosenHomogenization
|
case (HOMOGENIZATION_RGC_ID) chosenHomogenization
|
||||||
homogenization_postResults(startPos:endPos) = &
|
homogenization_postResults(startPos:endPos) = &
|
||||||
homogenization_RGC_postResults(&
|
homogenization_RGC_postResults(&
|
||||||
|
|
|
@ -9,30 +9,14 @@ module homogenization_isostrain
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
homogenization_isostrain_sizePostResults
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
homogenization_isostrain_sizePostResult
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
homogenization_isostrain_output !< name of each post result output
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
homogenization_isostrain_Noutput !< number of outputs per homog instance
|
|
||||||
integer(pInt), dimension(:), allocatable, private :: &
|
integer(pInt), dimension(:), allocatable, private :: &
|
||||||
homogenization_isostrain_Ngrains
|
homogenization_isostrain_Ngrains
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: undefined_ID, &
|
|
||||||
nconstituents_ID, &
|
|
||||||
ipcoords_ID, &
|
|
||||||
avgdefgrad_ID, &
|
|
||||||
avgfirstpiola_ID
|
|
||||||
end enum
|
|
||||||
enum, bind(c)
|
enum, bind(c)
|
||||||
enumerator :: parallel_ID, &
|
enumerator :: parallel_ID, &
|
||||||
average_ID
|
average_ID
|
||||||
end enum
|
end enum
|
||||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
|
||||||
homogenization_isostrain_outputID !< ID of each post result output
|
|
||||||
integer(kind(average_ID)), dimension(:), allocatable, private :: &
|
integer(kind(average_ID)), dimension(:), allocatable, private :: &
|
||||||
homogenization_isostrain_mapping !< mapping type
|
homogenization_isostrain_mapping !< mapping type
|
||||||
|
|
||||||
|
@ -40,15 +24,14 @@ module homogenization_isostrain
|
||||||
public :: &
|
public :: &
|
||||||
homogenization_isostrain_init, &
|
homogenization_isostrain_init, &
|
||||||
homogenization_isostrain_partitionDeformation, &
|
homogenization_isostrain_partitionDeformation, &
|
||||||
homogenization_isostrain_averageStressAndItsTangent, &
|
homogenization_isostrain_averageStressAndItsTangent
|
||||||
homogenization_isostrain_postResults
|
|
||||||
|
|
||||||
contains
|
contains
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief allocates all neccessary fields, reads information from material configuration file
|
!> @brief allocates all neccessary fields, reads information from material configuration file
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine homogenization_isostrain_init(fileUnit)
|
subroutine homogenization_isostrain_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, &
|
||||||
|
@ -65,19 +48,15 @@ subroutine homogenization_isostrain_init(fileUnit)
|
||||||
use config
|
use config
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt), intent(in) :: fileUnit
|
|
||||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
|
||||||
integer(pInt) :: &
|
integer(pInt) :: &
|
||||||
section = 0_pInt, i, mySize, o
|
h
|
||||||
integer :: &
|
integer :: &
|
||||||
maxNinstance, &
|
maxNinstance, &
|
||||||
homog, &
|
|
||||||
instance
|
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) :: &
|
||||||
tag = '', &
|
tag = ''
|
||||||
line = ''
|
|
||||||
|
|
||||||
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()
|
||||||
|
@ -88,114 +67,35 @@ subroutine homogenization_isostrain_init(fileUnit)
|
||||||
|
|
||||||
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:',maxNinstance
|
||||||
allocate(homogenization_isostrain_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(homogenization_isostrain_sizePostResult(maxval(homogenization_Noutput),maxNinstance), &
|
|
||||||
source=0_pInt)
|
|
||||||
allocate(homogenization_isostrain_Noutput(maxNinstance), source=0_pInt)
|
|
||||||
allocate(homogenization_isostrain_Ngrains(maxNinstance), source=0_pInt)
|
|
||||||
allocate(homogenization_isostrain_mapping(maxNinstance), source=average_ID)
|
|
||||||
allocate(homogenization_isostrain_output(maxval(homogenization_Noutput),maxNinstance))
|
|
||||||
homogenization_isostrain_output = ''
|
|
||||||
allocate(homogenization_isostrain_outputID(maxval(homogenization_Noutput),maxNinstance), &
|
|
||||||
source=undefined_ID)
|
|
||||||
|
|
||||||
rewind(fileUnit)
|
allocate(homogenization_isostrain_Ngrains(maxNinstance),source=0_pInt)
|
||||||
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= material_partHomogenization)! wind forward to <homogenization>
|
allocate(homogenization_isostrain_mapping(maxNinstance),source=average_ID)
|
||||||
line = IO_read(fileUnit)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
parsingFile: do while (trim(line) /= IO_EOF) ! read through sections of homogenization part
|
do h = 1_pInt, size(homogenization_type)
|
||||||
line = IO_read(fileUnit)
|
if (homogenization_type(h) /= HOMOGENIZATION_ISOSTRAIN_ID) cycle
|
||||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
instance = homogenization_typeInstance(h)
|
||||||
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
|
|
||||||
line = IO_read(fileUnit, .true.) ! reset IO_read
|
|
||||||
exit
|
|
||||||
endif
|
|
||||||
if (IO_getTag(line,'[',']') /= '') then ! next section
|
|
||||||
section = section + 1_pInt
|
|
||||||
cycle
|
|
||||||
endif
|
|
||||||
if (section > 0_pInt ) then ! do not short-circuit here (.and. with next if-statement). It's not safe in Fortran
|
|
||||||
if (homogenization_type(section) == HOMOGENIZATION_ISOSTRAIN_ID) then ! one of my sections
|
|
||||||
i = homogenization_typeInstance(section) ! which instance of my type is present homogenization
|
|
||||||
chunkPos = IO_stringPos(line)
|
|
||||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
|
||||||
select case(tag)
|
|
||||||
case ('(output)')
|
|
||||||
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
|
|
||||||
case('nconstituents','ngrains')
|
|
||||||
homogenization_isostrain_Noutput(i) = homogenization_isostrain_Noutput(i) + 1_pInt
|
|
||||||
homogenization_isostrain_outputID(homogenization_isostrain_Noutput(i),i) = nconstituents_ID
|
|
||||||
homogenization_isostrain_output(homogenization_isostrain_Noutput(i),i) = &
|
|
||||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
|
||||||
case('ipcoords')
|
|
||||||
homogenization_isostrain_Noutput(i) = homogenization_isostrain_Noutput(i) + 1_pInt
|
|
||||||
homogenization_isostrain_outputID(homogenization_isostrain_Noutput(i),i) = ipcoords_ID
|
|
||||||
homogenization_isostrain_output(homogenization_isostrain_Noutput(i),i) = &
|
|
||||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
|
||||||
case('avgdefgrad','avgf')
|
|
||||||
homogenization_isostrain_Noutput(i) = homogenization_isostrain_Noutput(i) + 1_pInt
|
|
||||||
homogenization_isostrain_outputID(homogenization_isostrain_Noutput(i),i) = avgdefgrad_ID
|
|
||||||
homogenization_isostrain_output(homogenization_isostrain_Noutput(i),i) = &
|
|
||||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
|
||||||
case('avgp','avgfirstpiola','avg1stpiola')
|
|
||||||
homogenization_isostrain_Noutput(i) = homogenization_isostrain_Noutput(i) + 1_pInt
|
|
||||||
homogenization_isostrain_outputID(homogenization_isostrain_Noutput(i),i) = avgfirstpiola_ID
|
|
||||||
homogenization_isostrain_output(homogenization_isostrain_Noutput(i),i) = &
|
|
||||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
|
||||||
|
|
||||||
end select
|
homogenization_isostrain_Ngrains(instance) = config_homogenization(h)%getInt('nconstituents')
|
||||||
case ('nconstituents','ngrains')
|
tag = 'sum'
|
||||||
homogenization_isostrain_Ngrains(i) = IO_intValue(line,chunkPos,2_pInt)
|
tag = config_homogenization(h)%getString('mapping',defaultVal = tag)
|
||||||
case ('mapping')
|
select case(trim(tag))
|
||||||
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
|
|
||||||
case ('parallel','sum')
|
case ('parallel','sum')
|
||||||
homogenization_isostrain_mapping(i) = parallel_ID
|
homogenization_isostrain_mapping(instance) = parallel_ID
|
||||||
case ('average','mean','avg')
|
case ('average','mean','avg')
|
||||||
homogenization_isostrain_mapping(i) = average_ID
|
homogenization_isostrain_mapping(instance) = average_ID
|
||||||
case default
|
case default
|
||||||
call IO_error(211_pInt,ext_msg=trim(tag)//' ('//HOMOGENIZATION_isostrain_label//')')
|
call IO_error(211_pInt,ext_msg=trim(tag)//' ('//HOMOGENIZATION_isostrain_label//')')
|
||||||
end select
|
end select
|
||||||
|
|
||||||
end select
|
NofMyHomog = count(material_homog == h)
|
||||||
endif
|
|
||||||
endif
|
|
||||||
enddo parsingFile
|
|
||||||
|
|
||||||
initializeInstances: do homog = 1_pInt, material_Nhomogenization
|
homogState(h)%sizeState = 0_pInt
|
||||||
myHomog: if (homogenization_type(homog) == HOMOGENIZATION_ISOSTRAIN_ID) then
|
homogState(h)%sizePostResults = 0_pInt
|
||||||
NofMyHomog = count(material_homog == homog)
|
allocate(homogState(h)%state0 (0_pInt,NofMyHomog), source=0.0_pReal)
|
||||||
instance = homogenization_typeInstance(homog)
|
allocate(homogState(h)%subState0(0_pInt,NofMyHomog), source=0.0_pReal)
|
||||||
|
allocate(homogState(h)%state (0_pInt,NofMyHomog), source=0.0_pReal)
|
||||||
|
|
||||||
! * Determine size of postResults array
|
enddo
|
||||||
outputsLoop: do o = 1_pInt, homogenization_isostrain_Noutput(instance)
|
|
||||||
select case(homogenization_isostrain_outputID(o,instance))
|
|
||||||
case(nconstituents_ID)
|
|
||||||
mySize = 1_pInt
|
|
||||||
case(ipcoords_ID)
|
|
||||||
mySize = 3_pInt
|
|
||||||
case(avgdefgrad_ID, avgfirstpiola_ID)
|
|
||||||
mySize = 9_pInt
|
|
||||||
case default
|
|
||||||
mySize = 0_pInt
|
|
||||||
end select
|
|
||||||
|
|
||||||
outputFound: if (mySize > 0_pInt) then
|
|
||||||
homogenization_isostrain_sizePostResult(o,instance) = mySize
|
|
||||||
homogenization_isostrain_sizePostResults(instance) = &
|
|
||||||
homogenization_isostrain_sizePostResults(instance) + mySize
|
|
||||||
endif outputFound
|
|
||||||
enddo outputsLoop
|
|
||||||
|
|
||||||
! allocate state arrays
|
|
||||||
homogState(homog)%sizeState = 0_pInt
|
|
||||||
homogState(homog)%sizePostResults = homogenization_isostrain_sizePostResults(instance)
|
|
||||||
allocate(homogState(homog)%state0 (0_pInt,NofMyHomog), source=0.0_pReal)
|
|
||||||
allocate(homogState(homog)%subState0(0_pInt,NofMyHomog), source=0.0_pReal)
|
|
||||||
allocate(homogState(homog)%state (0_pInt,NofMyHomog), source=0.0_pReal)
|
|
||||||
|
|
||||||
endif myHomog
|
|
||||||
enddo initializeInstances
|
|
||||||
|
|
||||||
end subroutine homogenization_isostrain_init
|
end subroutine homogenization_isostrain_init
|
||||||
|
|
||||||
|
@ -217,8 +117,8 @@ subroutine homogenization_isostrain_partitionDeformation(F,avgF,el)
|
||||||
real(pReal), dimension (3,3), intent(in) :: avgF !< my average def grad
|
real(pReal), dimension (3,3), intent(in) :: avgF !< my average def grad
|
||||||
integer(pInt), intent(in) :: &
|
integer(pInt), intent(in) :: &
|
||||||
el !< element number
|
el !< element number
|
||||||
F=0.0_pReal
|
F = 0.0_pReal
|
||||||
F(1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)))= &
|
F(1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el))) = &
|
||||||
spread(avgF,3,homogenization_Ngrains(mesh_element(3,el)))
|
spread(avgF,3,homogenization_Ngrains(mesh_element(3,el)))
|
||||||
|
|
||||||
end subroutine homogenization_isostrain_partitionDeformation
|
end subroutine homogenization_isostrain_partitionDeformation
|
||||||
|
@ -261,56 +161,4 @@ subroutine homogenization_isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P
|
||||||
|
|
||||||
end subroutine homogenization_isostrain_averageStressAndItsTangent
|
end subroutine homogenization_isostrain_averageStressAndItsTangent
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief return array of homogenization results for post file inclusion
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
pure function homogenization_isostrain_postResults(ip,el,avgP,avgF)
|
|
||||||
use prec, only: &
|
|
||||||
pReal
|
|
||||||
use mesh, only: &
|
|
||||||
mesh_element, &
|
|
||||||
mesh_ipCoordinates
|
|
||||||
use material, only: &
|
|
||||||
homogenization_typeInstance, &
|
|
||||||
homogenization_Noutput
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
real(pReal), dimension(3,3), intent(in) :: &
|
|
||||||
avgP, & !< average stress at material point
|
|
||||||
avgF !< average deformation gradient at material point
|
|
||||||
real(pReal), dimension(homogenization_isostrain_sizePostResults &
|
|
||||||
(homogenization_typeInstance(mesh_element(3,el)))) :: &
|
|
||||||
homogenization_isostrain_postResults
|
|
||||||
|
|
||||||
integer(pInt) :: &
|
|
||||||
homID, &
|
|
||||||
o, c
|
|
||||||
|
|
||||||
c = 0_pInt
|
|
||||||
homID = homogenization_typeInstance(mesh_element(3,el))
|
|
||||||
homogenization_isostrain_postResults = 0.0_pReal
|
|
||||||
|
|
||||||
do o = 1_pInt,homogenization_Noutput(mesh_element(3,el))
|
|
||||||
select case(homogenization_isostrain_outputID(o,homID))
|
|
||||||
case (nconstituents_ID)
|
|
||||||
homogenization_isostrain_postResults(c+1_pInt) = real(homogenization_isostrain_Ngrains(homID),pReal)
|
|
||||||
c = c + 1_pInt
|
|
||||||
case (avgdefgrad_ID)
|
|
||||||
homogenization_isostrain_postResults(c+1_pInt:c+9_pInt) = reshape(avgF,[9])
|
|
||||||
c = c + 9_pInt
|
|
||||||
case (avgfirstpiola_ID)
|
|
||||||
homogenization_isostrain_postResults(c+1_pInt:c+9_pInt) = reshape(avgP,[9])
|
|
||||||
c = c + 9_pInt
|
|
||||||
case (ipcoords_ID)
|
|
||||||
homogenization_isostrain_postResults(c+1_pInt:c+3_pInt) = mesh_ipCoordinates(1:3,ip,el) ! current ip coordinates
|
|
||||||
c = c + 3_pInt
|
|
||||||
end select
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end function homogenization_isostrain_postResults
|
|
||||||
|
|
||||||
end module homogenization_isostrain
|
end module homogenization_isostrain
|
||||||
|
|
Loading…
Reference in New Issue