Merge branch 'fast-list-append' into 'development'
Performance improvements when storing/retrieving data from YAML Closes #180 See merge request damask/DAMASK!561
This commit is contained in:
commit
dff78154a0
|
@ -88,7 +88,7 @@ void inflate_c(const uLong *s_deflated, const uLong *s_inflated, const Byte defl
|
||||||
#ifdef FYAML
|
#ifdef FYAML
|
||||||
void to_flow_c(char **flow, int* length_flow, const char *mixed){
|
void to_flow_c(char **flow, int* length_flow, const char *mixed){
|
||||||
struct fy_document *fyd = NULL;
|
struct fy_document *fyd = NULL;
|
||||||
enum fy_emitter_cfg_flags emit_flags = FYECF_MODE_FLOW_ONELINE | FYECF_STRIP_LABELS | FYECF_STRIP_DOC;
|
enum fy_emitter_cfg_flags emit_flags = FYECF_MODE_FLOW_ONELINE | FYECF_STRIP_LABELS | FYECF_STRIP_TAGS |FYECF_STRIP_DOC;
|
||||||
|
|
||||||
fyd = fy_document_build_from_string(NULL, mixed, -1);
|
fyd = fy_document_build_from_string(NULL, mixed, -1);
|
||||||
if (!fyd) {
|
if (!fyd) {
|
||||||
|
|
|
@ -83,7 +83,7 @@ recursive function parse_flow(YAML_flow) result(node)
|
||||||
s, & ! start position of dictionary or list
|
s, & ! start position of dictionary or list
|
||||||
d ! position of key: value separator (':')
|
d ! position of key: value separator (':')
|
||||||
|
|
||||||
flow_string = trim(adjustl(YAML_flow(:)))
|
flow_string = trim(adjustl(YAML_flow))
|
||||||
if (len_trim(flow_string) == 0) then
|
if (len_trim(flow_string) == 0) then
|
||||||
node => emptyDict
|
node => emptyDict
|
||||||
return
|
return
|
||||||
|
@ -168,8 +168,11 @@ logical function quotedString(line)
|
||||||
|
|
||||||
character(len=*), intent(in) :: line
|
character(len=*), intent(in) :: line
|
||||||
|
|
||||||
|
|
||||||
quotedString = .false.
|
quotedString = .false.
|
||||||
|
|
||||||
|
if (len(line) == 0) return
|
||||||
|
|
||||||
if (scan(line(:1),IO_QUOTES) == 1) then
|
if (scan(line(:1),IO_QUOTES) == 1) then
|
||||||
quotedString = .true.
|
quotedString = .true.
|
||||||
if(line(len(line):len(line)) /= line(:1)) call IO_error(710,ext_msg=line)
|
if(line(len(line):len(line)) /= line(:1)) call IO_error(710,ext_msg=line)
|
||||||
|
@ -198,7 +201,7 @@ function to_flow(mixed) result(flow)
|
||||||
block
|
block
|
||||||
character(len=strlen,kind=c_char), pointer :: s
|
character(len=strlen,kind=c_char), pointer :: s
|
||||||
call c_f_pointer(str_ptr,s)
|
call c_f_pointer(str_ptr,s)
|
||||||
flow = s
|
flow = s(:len(s)-1)
|
||||||
end block
|
end block
|
||||||
|
|
||||||
call free_C(str_ptr)
|
call free_C(str_ptr)
|
||||||
|
|
|
@ -119,7 +119,8 @@ module YAML_types
|
||||||
|
|
||||||
type, extends(tNode), public :: tList
|
type, extends(tNode), public :: tList
|
||||||
|
|
||||||
class(tItem), pointer :: first => NULL()
|
class(tItem), pointer :: first => NULL(), &
|
||||||
|
last => NULL()
|
||||||
|
|
||||||
contains
|
contains
|
||||||
procedure :: asFormattedString => tList_asFormattedString
|
procedure :: asFormattedString => tList_asFormattedString
|
||||||
|
@ -144,7 +145,7 @@ module YAML_types
|
||||||
end type tDict
|
end type tDict
|
||||||
|
|
||||||
|
|
||||||
type :: tItem
|
type, public :: tItem
|
||||||
character(len=:), allocatable :: key
|
character(len=:), allocatable :: key
|
||||||
class(tNode), pointer :: node => NULL()
|
class(tNode), pointer :: node => NULL()
|
||||||
class(tItem), pointer :: next => NULL()
|
class(tItem), pointer :: next => NULL()
|
||||||
|
@ -1348,15 +1349,13 @@ subroutine tList_append(self,node)
|
||||||
type(tItem), pointer :: item
|
type(tItem), pointer :: item
|
||||||
|
|
||||||
if (.not. associated(self%first)) then
|
if (.not. associated(self%first)) then
|
||||||
allocate(self%first)
|
allocate(item)
|
||||||
item => self%first
|
self%first => item
|
||||||
|
self%last => item
|
||||||
else
|
else
|
||||||
item => self%first
|
allocate(self%last%next)
|
||||||
do while (associated(item%next))
|
item => self%last%next
|
||||||
item => item%next
|
self%last => item
|
||||||
enddo
|
|
||||||
allocate(item%next)
|
|
||||||
item => item%next
|
|
||||||
end if
|
end if
|
||||||
|
|
||||||
item%node => node
|
item%node => node
|
||||||
|
|
112
src/material.f90
112
src/material.f90
|
@ -91,9 +91,13 @@ subroutine parse()
|
||||||
homogenizations, &
|
homogenizations, &
|
||||||
homogenization
|
homogenization
|
||||||
|
|
||||||
|
class(tItem), pointer :: item
|
||||||
integer, dimension(:), allocatable :: &
|
integer, dimension(:), allocatable :: &
|
||||||
counterPhase, &
|
counterPhase, &
|
||||||
counterHomogenization
|
counterHomogenization, &
|
||||||
|
ho_of
|
||||||
|
integer, dimension(:,:), allocatable :: ph_of
|
||||||
|
real(pReal), dimension(:,:), allocatable :: v_of
|
||||||
|
|
||||||
real(pReal) :: v
|
real(pReal) :: v
|
||||||
integer :: &
|
integer :: &
|
||||||
|
@ -102,11 +106,14 @@ subroutine parse()
|
||||||
co, ce, &
|
co, ce, &
|
||||||
ma
|
ma
|
||||||
|
|
||||||
|
|
||||||
materials => config_material%get('material')
|
materials => config_material%get('material')
|
||||||
phases => config_material%get('phase')
|
phases => config_material%get('phase')
|
||||||
homogenizations => config_material%get('homogenization')
|
homogenizations => config_material%get('homogenization')
|
||||||
|
|
||||||
call sanityCheck(materials, homogenizations)
|
|
||||||
|
if (maxval(discretization_materialAt) > materials%length) &
|
||||||
|
call IO_error(155,ext_msg='More materials requested than found in material.yaml')
|
||||||
|
|
||||||
#if defined (__GFORTRAN__)
|
#if defined (__GFORTRAN__)
|
||||||
material_name_phase = getKeys(phases)
|
material_name_phase = getKeys(phases)
|
||||||
|
@ -123,6 +130,49 @@ subroutine parse()
|
||||||
end do
|
end do
|
||||||
homogenization_maxNconstituents = maxval(homogenization_Nconstituents)
|
homogenization_maxNconstituents = maxval(homogenization_Nconstituents)
|
||||||
|
|
||||||
|
allocate(material_v(homogenization_maxNconstituents,discretization_Ncells),source=0.0_pReal)
|
||||||
|
|
||||||
|
allocate(material_O_0(materials%length))
|
||||||
|
allocate(material_F_i_0(materials%length))
|
||||||
|
|
||||||
|
allocate(ho_of(materials%length))
|
||||||
|
allocate(ph_of(materials%length,homogenization_maxNconstituents),source=-1)
|
||||||
|
allocate( v_of(materials%length,homogenization_maxNconstituents),source=0.0_pReal)
|
||||||
|
|
||||||
|
! parse YAML structure
|
||||||
|
select type(materials)
|
||||||
|
|
||||||
|
class is(tList)
|
||||||
|
|
||||||
|
item => materials%first
|
||||||
|
do ma = 1, materials%length
|
||||||
|
material => item%node
|
||||||
|
ho_of(ma) = homogenizations%getIndex(material%get_asString('homogenization'))
|
||||||
|
constituents => material%get('constituents')
|
||||||
|
|
||||||
|
homogenization => homogenizations%get(ho_of(ma))
|
||||||
|
if (constituents%length /= homogenization%get_asInt('N_constituents')) call IO_error(148)
|
||||||
|
|
||||||
|
allocate(material_O_0(ma)%data(constituents%length))
|
||||||
|
allocate(material_F_i_0(ma)%data(1:3,1:3,constituents%length))
|
||||||
|
|
||||||
|
do co = 1, constituents%length
|
||||||
|
constituent => constituents%get(co)
|
||||||
|
v_of(ma,co) = constituent%get_asFloat('v')
|
||||||
|
ph_of(ma,co) = phases%getIndex(constituent%get_asString('phase'))
|
||||||
|
|
||||||
|
call material_O_0(ma)%data(co)%fromQuaternion(constituent%get_as1dFloat('O',requiredSize=4))
|
||||||
|
material_F_i_0(ma)%data(1:3,1:3,co) = constituent%get_as2dFloat('F_i',defaultVal=math_I3,requiredShape=[3,3])
|
||||||
|
|
||||||
|
end do
|
||||||
|
if (dNeq(sum(v_of(ma,:)),1.0_pReal,1.e-9_pReal)) call IO_error(153,ext_msg='constituent')
|
||||||
|
|
||||||
|
item => item%next
|
||||||
|
end do
|
||||||
|
|
||||||
|
end select
|
||||||
|
|
||||||
|
|
||||||
allocate(counterPhase(phases%length),source=0)
|
allocate(counterPhase(phases%length),source=0)
|
||||||
allocate(counterHomogenization(homogenizations%length),source=0)
|
allocate(counterHomogenization(homogenizations%length),source=0)
|
||||||
|
|
||||||
|
@ -132,12 +182,13 @@ subroutine parse()
|
||||||
allocate(material_phaseID(homogenization_maxNconstituents,discretization_Ncells),source=0)
|
allocate(material_phaseID(homogenization_maxNconstituents,discretization_Ncells),source=0)
|
||||||
allocate(material_phaseEntry(homogenization_maxNconstituents,discretization_Ncells),source=0)
|
allocate(material_phaseEntry(homogenization_maxNconstituents,discretization_Ncells),source=0)
|
||||||
|
|
||||||
allocate(material_v(homogenization_maxNconstituents,discretization_Ncells),source=0.0_pReal)
|
|
||||||
|
|
||||||
|
! build mappings
|
||||||
do el = 1, discretization_Nelems
|
do el = 1, discretization_Nelems
|
||||||
material => materials%get(discretization_materialAt(el))
|
|
||||||
|
|
||||||
ho = homogenizations%getIndex(material%get_asString('homogenization'))
|
ma = discretization_materialAt(el)
|
||||||
|
ho = ho_of(ma)
|
||||||
|
|
||||||
do ip = 1, discretization_nIPs
|
do ip = 1, discretization_nIPs
|
||||||
ce = (el-1)*discretization_nIPs + ip
|
ce = (el-1)*discretization_nIPs + ip
|
||||||
material_homogenizationID(ce) = ho
|
material_homogenizationID(ce) = ho
|
||||||
|
@ -145,13 +196,11 @@ subroutine parse()
|
||||||
material_homogenizationEntry(ce) = counterHomogenization(ho)
|
material_homogenizationEntry(ce) = counterHomogenization(ho)
|
||||||
end do
|
end do
|
||||||
|
|
||||||
constituents => material%get('constituents')
|
do co = 1, size(ph_of(ma,:)>0)
|
||||||
do co = 1, constituents%length
|
|
||||||
constituent => constituents%get(co)
|
|
||||||
|
|
||||||
v = constituent%get_asFloat('v')
|
v = v_of(ma,co)
|
||||||
|
ph = ph_of(ma,co)
|
||||||
|
|
||||||
ph = phases%getIndex(constituent%get_asString('phase'))
|
|
||||||
do ip = 1, discretization_nIPs
|
do ip = 1, discretization_nIPs
|
||||||
ce = (el-1)*discretization_nIPs + ip
|
ce = (el-1)*discretization_nIPs + ip
|
||||||
material_phaseID(co,ce) = ph
|
material_phaseID(co,ce) = ph
|
||||||
|
@ -161,54 +210,11 @@ subroutine parse()
|
||||||
end do
|
end do
|
||||||
|
|
||||||
end do
|
end do
|
||||||
if (dNeq(sum(material_v(1:constituents%length,ce)),1.0_pReal,1.e-9_pReal)) &
|
|
||||||
call IO_error(153,ext_msg='constituent')
|
|
||||||
|
|
||||||
end do
|
end do
|
||||||
|
|
||||||
allocate(material_O_0(materials%length))
|
|
||||||
allocate(material_F_i_0(materials%length))
|
|
||||||
|
|
||||||
do ma = 1, materials%length
|
|
||||||
material => materials%get(ma)
|
|
||||||
constituents => material%get('constituents')
|
|
||||||
allocate(material_O_0(ma)%data(constituents%length))
|
|
||||||
allocate(material_F_i_0(ma)%data(1:3,1:3,constituents%length))
|
|
||||||
do co = 1, constituents%length
|
|
||||||
constituent => constituents%get(co)
|
|
||||||
call material_O_0(ma)%data(co)%fromQuaternion(constituent%get_as1dFloat('O',requiredSize=4))
|
|
||||||
material_F_i_0(ma)%data(1:3,1:3,co) = constituent%get_as2dFloat('F_i',defaultVal=math_I3,requiredShape=[3,3])
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end subroutine parse
|
end subroutine parse
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief Check if material.yaml is consistent and contains sufficient # of materials
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine sanityCheck(materials,homogenizations)
|
|
||||||
|
|
||||||
class(tNode), intent(in) :: materials, &
|
|
||||||
homogenizations
|
|
||||||
|
|
||||||
class(tNode), pointer :: material, &
|
|
||||||
homogenization, &
|
|
||||||
constituents
|
|
||||||
integer :: m
|
|
||||||
|
|
||||||
if (maxval(discretization_materialAt) > materials%length) &
|
|
||||||
call IO_error(155,ext_msg='More materials requested than found in material.yaml')
|
|
||||||
|
|
||||||
do m = 1, materials%length
|
|
||||||
material => materials%get(m)
|
|
||||||
constituents => material%get('constituents')
|
|
||||||
homogenization => homogenizations%get(material%get_asString('homogenization'))
|
|
||||||
if (constituents%length /= homogenization%get_asInt('N_constituents')) call IO_error(148)
|
|
||||||
end do
|
|
||||||
|
|
||||||
end subroutine sanityCheck
|
|
||||||
|
|
||||||
#if defined (__GFORTRAN__)
|
#if defined (__GFORTRAN__)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief %keys() is broken on gfortran
|
!> @brief %keys() is broken on gfortran
|
||||||
|
|
Loading…
Reference in New Issue