getStrings works for cumulative and non-cumulative
This commit is contained in:
parent
8d5d306076
commit
fc54104599
|
@ -23,10 +23,6 @@ module linked_list
|
||||||
|
|
||||||
procedure :: keyExists => exist
|
procedure :: keyExists => exist
|
||||||
procedure :: countKeys => count
|
procedure :: countKeys => count
|
||||||
procedure :: getStringsRaw => strings
|
|
||||||
|
|
||||||
procedure :: getRaw => getRaw
|
|
||||||
procedure :: getRaws => getRaws
|
|
||||||
|
|
||||||
procedure :: getFloat => getFloat
|
procedure :: getFloat => getFloat
|
||||||
procedure :: getFloatArray => getFloats
|
procedure :: getFloatArray => getFloats
|
||||||
|
@ -34,6 +30,7 @@ module linked_list
|
||||||
procedure :: getInt => getInt
|
procedure :: getInt => getInt
|
||||||
procedure :: getIntArray => getInts
|
procedure :: getIntArray => getInts
|
||||||
|
|
||||||
|
procedure :: getStringsRaw => strings
|
||||||
procedure :: getString => getString
|
procedure :: getString => getString
|
||||||
procedure :: getStrings => getStrings
|
procedure :: getStrings => getStrings
|
||||||
|
|
||||||
|
@ -195,89 +192,6 @@ function strings(this)
|
||||||
end function strings
|
end function strings
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief gets first string that matches given key (i.e. first chunk)
|
|
||||||
!> @details returns raw string and start/end position of chunks in this string
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine getRaw(this,key,string,stringPos)
|
|
||||||
use IO, only : &
|
|
||||||
IO_error, &
|
|
||||||
IO_stringValue
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
class(tPartitionedStringList), intent(in) :: this
|
|
||||||
character(len=*), intent(in) :: key
|
|
||||||
character(len=*), intent(out) :: string
|
|
||||||
integer(pInt), dimension(:), allocatable, intent(out) :: stringPos
|
|
||||||
type(tPartitionedStringList), pointer :: item
|
|
||||||
logical :: found
|
|
||||||
|
|
||||||
found = .false.
|
|
||||||
|
|
||||||
item => this%next
|
|
||||||
do while (associated(item) .and. .not. found)
|
|
||||||
found = trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)
|
|
||||||
if (found) then
|
|
||||||
stringPos = item%string%pos
|
|
||||||
string = item%string%val
|
|
||||||
endif
|
|
||||||
item => item%next
|
|
||||||
end do
|
|
||||||
|
|
||||||
if (.not. found) call IO_error(140_pInt,ext_msg=key)
|
|
||||||
|
|
||||||
end subroutine getRaw
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief gets all strings that matches given key (i.e. first chunk)
|
|
||||||
!> @details returns raw strings and start/end positions of chunks in these strings.
|
|
||||||
! Will fail if number of positions in strings differs.
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine getRaws(this,key,string,stringPos)
|
|
||||||
use IO, only: &
|
|
||||||
IO_error, &
|
|
||||||
IO_stringValue
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
class(tPartitionedStringList), intent(in) :: this
|
|
||||||
character(len=*), intent(in) :: key
|
|
||||||
character(len=65536), dimension(:), allocatable, intent(out) :: string
|
|
||||||
integer(pInt), dimension(:,:), allocatable, intent(out) :: stringPos
|
|
||||||
|
|
||||||
character(len=65536) :: string_tmp
|
|
||||||
integer(pInt) :: posSize
|
|
||||||
integer(pInt), dimension(:), allocatable :: stringPosFlat
|
|
||||||
type(tPartitionedStringList), pointer :: item
|
|
||||||
|
|
||||||
posSize = -1_pInt
|
|
||||||
item => this%next
|
|
||||||
do
|
|
||||||
if (.not. associated(item)) then
|
|
||||||
if (posSize < 0_pInt) call IO_error(140_pInt,ext_msg=key)
|
|
||||||
stringPos = reshape(stringPosFlat,[posSize,size(string)])
|
|
||||||
exit
|
|
||||||
endif
|
|
||||||
foundKey: if (trim(IO_stringValue(item%string%val,item%string%pos,1))==trim(key)) then
|
|
||||||
if (posSize < 0_pInt) then
|
|
||||||
posSize = size(item%string%pos)
|
|
||||||
stringPosFlat = item%string%pos
|
|
||||||
allocate(string(1))
|
|
||||||
string(1) = item%string%val
|
|
||||||
else
|
|
||||||
if (size(item%string%pos) /= posSize) &
|
|
||||||
call IO_error(141_pInt,ext_msg=trim(item%string%val),el=posSize)
|
|
||||||
stringPosFlat = [stringPosFlat,item%string%pos]
|
|
||||||
string_tmp = item%string%val
|
|
||||||
string = [string,string_tmp]
|
|
||||||
endif
|
|
||||||
endif foundKey
|
|
||||||
item => item%next
|
|
||||||
end do
|
|
||||||
|
|
||||||
end subroutine getRaws
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief gets float value of first string that matches given key (i.e. first chunk)
|
!> @brief gets float value of first string that matches given key (i.e. first chunk)
|
||||||
!> @details gets one float value. If key is not found exits with error unless default is given
|
!> @details gets one float value. If key is not found exits with error unless default is given
|
||||||
|
@ -367,7 +281,7 @@ character(len=65536) function getString(this,key,defaultVal,raw)
|
||||||
split
|
split
|
||||||
|
|
||||||
if (present(defaultVal)) getString = defaultVal
|
if (present(defaultVal)) getString = defaultVal
|
||||||
split = merge(raw,.true.,present(raw))
|
split = merge(.not. raw,.true.,present(raw))
|
||||||
found = present(defaultVal)
|
found = present(defaultVal)
|
||||||
|
|
||||||
item => this%next
|
item => this%next
|
||||||
|
@ -411,9 +325,8 @@ function getStrings(this,key,defaultVal,raw)
|
||||||
cumulative
|
cumulative
|
||||||
|
|
||||||
cumulative = (key(1:1) == '(' .and. key(len_trim(key):len_trim(key)) == ')')
|
cumulative = (key(1:1) == '(' .and. key(len_trim(key):len_trim(key)) == ')')
|
||||||
split = merge(raw,.true.,present(raw))
|
split = merge(.not. raw,.true.,present(raw))
|
||||||
found = present(defaultVal)
|
found = present(defaultVal)
|
||||||
|
|
||||||
if (present(defaultVal)) getStrings = defaultVal
|
if (present(defaultVal)) getStrings = defaultVal
|
||||||
|
|
||||||
|
|
||||||
|
@ -451,7 +364,6 @@ function getStrings(this,key,defaultVal,raw)
|
||||||
end do
|
end do
|
||||||
|
|
||||||
if (.not. found) call IO_error(140_pInt,ext_msg=key)
|
if (.not. found) call IO_error(140_pInt,ext_msg=key)
|
||||||
|
|
||||||
end function
|
end function
|
||||||
|
|
||||||
|
|
||||||
|
|
|
@ -670,6 +670,7 @@ subroutine material_parseMicrostructure
|
||||||
IO_floatValue, &
|
IO_floatValue, &
|
||||||
IO_intValue, &
|
IO_intValue, &
|
||||||
IO_stringValue, &
|
IO_stringValue, &
|
||||||
|
IO_stringPos, &
|
||||||
IO_error
|
IO_error
|
||||||
use mesh, only: &
|
use mesh, only: &
|
||||||
mesh_element, &
|
mesh_element, &
|
||||||
|
@ -678,7 +679,7 @@ subroutine material_parseMicrostructure
|
||||||
implicit none
|
implicit none
|
||||||
character(len=65536), dimension(:), allocatable :: &
|
character(len=65536), dimension(:), allocatable :: &
|
||||||
str
|
str
|
||||||
integer(pInt), allocatable, dimension(:,:) :: chunkPoss
|
integer(pInt), allocatable, dimension(:) :: chunkPos
|
||||||
integer(pInt) :: e, m, c, i
|
integer(pInt) :: e, m, c, i
|
||||||
character(len=65536) :: &
|
character(len=65536) :: &
|
||||||
tag
|
tag
|
||||||
|
@ -705,18 +706,20 @@ subroutine material_parseMicrostructure
|
||||||
allocate(microstructure_fraction(microstructure_maxNconstituents,material_Nmicrostructure),source=0.0_pReal)
|
allocate(microstructure_fraction(microstructure_maxNconstituents,material_Nmicrostructure),source=0.0_pReal)
|
||||||
|
|
||||||
do m=1_pInt, material_Nmicrostructure
|
do m=1_pInt, material_Nmicrostructure
|
||||||
call microstructureConfig(m)%getRaws('(constituent)',str,chunkPoss)
|
str = microstructureConfig(m)%getStrings('(constituent)',raw=.true.)
|
||||||
do c = 1_pInt, size(str)
|
do c = 1_pInt, size(str)
|
||||||
do i = 2_pInt,6_pInt,2_pInt
|
chunkPos = IO_stringPos(str(c))
|
||||||
tag = IO_stringValue(str(c),chunkPoss(:,c),i)
|
|
||||||
|
do i = 1_pInt,5_pInt,2_pInt
|
||||||
|
tag = IO_stringValue(str(c),chunkPos,i)
|
||||||
|
|
||||||
select case (tag)
|
select case (tag)
|
||||||
case('phase')
|
case('phase')
|
||||||
microstructure_phase(c,m) = IO_intValue(str(c),chunkPoss(:,c),i+1_pInt)
|
microstructure_phase(c,m) = IO_intValue(str(c),chunkPos,i+1_pInt)
|
||||||
case('texture')
|
case('texture')
|
||||||
microstructure_texture(c,m) = IO_intValue(str(c),chunkPoss(:,c),i+1_pInt)
|
microstructure_texture(c,m) = IO_intValue(str(c),chunkPos,i+1_pInt)
|
||||||
case('fraction')
|
case('fraction')
|
||||||
microstructure_fraction(c,m) = IO_floatValue(str(c),chunkPoss(:,c),i+1_pInt)
|
microstructure_fraction(c,m) = IO_floatValue(str(c),chunkPos,i+1_pInt)
|
||||||
end select
|
end select
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
Loading…
Reference in New Issue