pInt not needed anymore
This commit is contained in:
parent
40fda62efc
commit
7cb2203a38
106
src/config.f90
106
src/config.f90
|
@ -14,7 +14,7 @@ module config
|
||||||
private
|
private
|
||||||
type, private :: tPartitionedString
|
type, private :: tPartitionedString
|
||||||
character(len=:), allocatable :: val
|
character(len=:), allocatable :: val
|
||||||
integer(pInt), dimension(:), allocatable :: pos
|
integer, dimension(:), allocatable :: pos
|
||||||
end type tPartitionedString
|
end type tPartitionedString
|
||||||
|
|
||||||
type, private :: tPartitionedStringList
|
type, private :: tPartitionedStringList
|
||||||
|
@ -65,7 +65,7 @@ module config
|
||||||
|
|
||||||
|
|
||||||
! ToDo: Remove, use size(config_phase) etc
|
! ToDo: Remove, use size(config_phase) etc
|
||||||
integer(pInt), public, protected :: &
|
integer, public, protected :: &
|
||||||
material_Nphase, & !< number of phases
|
material_Nphase, & !< number of phases
|
||||||
material_Nhomogenization !< number of homogenizations
|
material_Nhomogenization !< number of homogenizations
|
||||||
|
|
||||||
|
@ -94,7 +94,7 @@ subroutine config_init
|
||||||
debug_levelBasic
|
debug_levelBasic
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt) :: myDebug,i
|
integer :: myDebug,i
|
||||||
|
|
||||||
character(len=pStringLen) :: &
|
character(len=pStringLen) :: &
|
||||||
line, &
|
line, &
|
||||||
|
@ -112,12 +112,12 @@ subroutine config_init
|
||||||
fileContent = read_materialConfig(trim(getSolverJobName())//'.materialConfig')
|
fileContent = read_materialConfig(trim(getSolverJobName())//'.materialConfig')
|
||||||
else
|
else
|
||||||
inquire(file='material.config',exist=fileExists)
|
inquire(file='material.config',exist=fileExists)
|
||||||
if(.not. fileExists) call IO_error(100_pInt,ext_msg='material.config')
|
if(.not. fileExists) call IO_error(100,ext_msg='material.config')
|
||||||
write(6,'(/,a)') ' reading material.config'; flush(6)
|
write(6,'(/,a)') ' reading material.config'; flush(6)
|
||||||
fileContent = read_materialConfig('material.config')
|
fileContent = read_materialConfig('material.config')
|
||||||
endif
|
endif
|
||||||
|
|
||||||
do i = 1_pInt, size(fileContent)
|
do i = 1, size(fileContent)
|
||||||
line = trim(fileContent(i))
|
line = trim(fileContent(i))
|
||||||
part = IO_lc(IO_getTag(line,'<','>'))
|
part = IO_lc(IO_getTag(line,'<','>'))
|
||||||
select case (trim(part))
|
select case (trim(part))
|
||||||
|
@ -149,11 +149,11 @@ subroutine config_init
|
||||||
material_Nhomogenization = size(config_homogenization)
|
material_Nhomogenization = size(config_homogenization)
|
||||||
material_Nphase = size(config_phase)
|
material_Nphase = size(config_phase)
|
||||||
|
|
||||||
if (material_Nhomogenization < 1) call IO_error(160_pInt,ext_msg='<homogenization>')
|
if (material_Nhomogenization < 1) call IO_error(160,ext_msg='<homogenization>')
|
||||||
if (size(config_microstructure) < 1) call IO_error(160_pInt,ext_msg='<microstructure>')
|
if (size(config_microstructure) < 1) call IO_error(160,ext_msg='<microstructure>')
|
||||||
if (size(config_crystallite) < 1) call IO_error(160_pInt,ext_msg='<crystallite>')
|
if (size(config_crystallite) < 1) call IO_error(160,ext_msg='<crystallite>')
|
||||||
if (material_Nphase < 1) call IO_error(160_pInt,ext_msg='<phase>')
|
if (material_Nphase < 1) call IO_error(160,ext_msg='<phase>')
|
||||||
if (size(config_texture) < 1) call IO_error(160_pInt,ext_msg='<texture>')
|
if (size(config_texture) < 1) call IO_error(160,ext_msg='<texture>')
|
||||||
|
|
||||||
|
|
||||||
inquire(file='numerics.config', exist=fileExists)
|
inquire(file='numerics.config', exist=fileExists)
|
||||||
|
@ -199,7 +199,7 @@ recursive function read_materialConfig(fileName,cnt) result(fileContent)
|
||||||
logical :: warned
|
logical :: warned
|
||||||
|
|
||||||
if (present(cnt)) then
|
if (present(cnt)) then
|
||||||
if (cnt>10_pInt) call IO_error(106_pInt,ext_msg=trim(fileName))
|
if (cnt>10) call IO_error(106,ext_msg=trim(fileName))
|
||||||
endif
|
endif
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -211,7 +211,7 @@ recursive function read_materialConfig(fileName,cnt) result(fileContent)
|
||||||
endif
|
endif
|
||||||
open(newunit=fileUnit, file=fileName, access='stream',&
|
open(newunit=fileUnit, file=fileName, access='stream',&
|
||||||
status='old', position='rewind', action='read',iostat=myStat)
|
status='old', position='rewind', action='read',iostat=myStat)
|
||||||
if(myStat /= 0_pInt) call IO_error(100_pInt,ext_msg=trim(fileName))
|
if(myStat /= 0) call IO_error(100,ext_msg=trim(fileName))
|
||||||
allocate(character(len=fileLength)::rawData)
|
allocate(character(len=fileLength)::rawData)
|
||||||
read(fileUnit) rawData
|
read(fileUnit) rawData
|
||||||
close(fileUnit)
|
close(fileUnit)
|
||||||
|
@ -250,7 +250,7 @@ recursive function read_materialConfig(fileName,cnt) result(fileContent)
|
||||||
l = l - 1 + size(includedContent)
|
l = l - 1 + size(includedContent)
|
||||||
else recursion
|
else recursion
|
||||||
fileContent(l) = line
|
fileContent(l) = line
|
||||||
l = l + 1_pInt
|
l = l + 1
|
||||||
endif recursion
|
endif recursion
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
@ -269,23 +269,23 @@ subroutine parse_materialConfig(sectionNames,part,line, &
|
||||||
character(len=pStringLen), intent(inout) :: line
|
character(len=pStringLen), intent(inout) :: line
|
||||||
character(len=pStringLen), dimension(:), intent(in) :: fileContent
|
character(len=pStringLen), dimension(:), intent(in) :: fileContent
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:) :: partPosition ! position of [] tags + last line in section
|
integer, allocatable, dimension(:) :: partPosition ! position of [] tags + last line in section
|
||||||
integer(pInt) :: i, j
|
integer :: i, j
|
||||||
logical :: echo
|
logical :: echo
|
||||||
|
|
||||||
echo = .false.
|
echo = .false.
|
||||||
|
|
||||||
if (allocated(part)) call IO_error(161_pInt,ext_msg=trim(line))
|
if (allocated(part)) call IO_error(161,ext_msg=trim(line))
|
||||||
allocate(partPosition(0))
|
allocate(partPosition(0))
|
||||||
|
|
||||||
do i = 1_pInt, size(fileContent)
|
do i = 1, size(fileContent)
|
||||||
line = trim(fileContent(i))
|
line = trim(fileContent(i))
|
||||||
if (IO_getTag(line,'<','>') /= '') exit
|
if (IO_getTag(line,'<','>') /= '') exit
|
||||||
nextSection: if (IO_getTag(line,'[',']') /= '') then
|
nextSection: if (IO_getTag(line,'[',']') /= '') then
|
||||||
partPosition = [partPosition, i]
|
partPosition = [partPosition, i]
|
||||||
cycle
|
cycle
|
||||||
endif nextSection
|
endif nextSection
|
||||||
if (size(partPosition) < 1_pInt) &
|
if (size(partPosition) < 1) &
|
||||||
echo = (trim(IO_getTag(line,'/','/')) == 'echo') .or. echo
|
echo = (trim(IO_getTag(line,'/','/')) == 'echo') .or. echo
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
@ -294,9 +294,9 @@ subroutine parse_materialConfig(sectionNames,part,line, &
|
||||||
|
|
||||||
partPosition = [partPosition, i] ! needed when actually storing content
|
partPosition = [partPosition, i] ! needed when actually storing content
|
||||||
|
|
||||||
do i = 1_pInt, size(partPosition) -1_pInt
|
do i = 1, size(partPosition) -1
|
||||||
sectionNames(i) = trim(adjustl(IO_getTag(fileContent(partPosition(i)),'[',']')))
|
sectionNames(i) = trim(adjustl(IO_getTag(fileContent(partPosition(i)),'[',']')))
|
||||||
do j = partPosition(i) + 1_pInt, partPosition(i+1) -1_pInt
|
do j = partPosition(i) + 1, partPosition(i+1) -1
|
||||||
call part(i)%add(trim(adjustl(fileContent(j))))
|
call part(i)%add(trim(adjustl(fileContent(j))))
|
||||||
enddo
|
enddo
|
||||||
if (echo) then
|
if (echo) then
|
||||||
|
@ -318,7 +318,7 @@ subroutine parse_debugAndNumericsConfig(config_list, &
|
||||||
character(len=pStringLen), dimension(:), intent(in) :: fileContent
|
character(len=pStringLen), dimension(:), intent(in) :: fileContent
|
||||||
integer :: i
|
integer :: i
|
||||||
|
|
||||||
do i = 1_pInt, size(fileContent)
|
do i = 1, size(fileContent)
|
||||||
call config_list%add(trim(adjustl(fileContent(i))))
|
call config_list%add(trim(adjustl(fileContent(i))))
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
@ -361,7 +361,7 @@ subroutine config_deallocate(what)
|
||||||
call config_numerics%free
|
call config_numerics%free
|
||||||
|
|
||||||
case default
|
case default
|
||||||
call IO_error(0_pInt,ext_msg='config_deallocate')
|
call IO_error(0,ext_msg='config_deallocate')
|
||||||
|
|
||||||
end select
|
end select
|
||||||
|
|
||||||
|
@ -501,7 +501,7 @@ end function keyExists
|
||||||
!> @brief count number of key appearances
|
!> @brief count number of key appearances
|
||||||
!> @details traverses list and counts each occurrence of specified key
|
!> @details traverses list and counts each occurrence of specified key
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
integer(pInt) function countKeys(this,key)
|
integer function countKeys(this,key)
|
||||||
use IO, only: &
|
use IO, only: &
|
||||||
IO_stringValue
|
IO_stringValue
|
||||||
|
|
||||||
|
@ -511,12 +511,12 @@ integer(pInt) function countKeys(this,key)
|
||||||
character(len=*), intent(in) :: key
|
character(len=*), intent(in) :: key
|
||||||
type(tPartitionedStringList), pointer :: item
|
type(tPartitionedStringList), pointer :: item
|
||||||
|
|
||||||
countKeys = 0_pInt
|
countKeys = 0
|
||||||
|
|
||||||
item => this
|
item => this
|
||||||
do while (associated(item%next))
|
do while (associated(item%next))
|
||||||
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) &
|
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) &
|
||||||
countKeys = countKeys + 1_pInt
|
countKeys = countKeys + 1
|
||||||
item => item%next
|
item => item%next
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
@ -548,13 +548,13 @@ real(pReal) function getFloat(this,key,defaultVal)
|
||||||
do while (associated(item%next))
|
do while (associated(item%next))
|
||||||
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
|
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
|
||||||
found = .true.
|
found = .true.
|
||||||
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
if (item%string%pos(1) < 2) call IO_error(143,ext_msg=key)
|
||||||
getFloat = IO_FloatValue(item%string%val,item%string%pos,2)
|
getFloat = IO_FloatValue(item%string%val,item%string%pos,2)
|
||||||
endif
|
endif
|
||||||
item => item%next
|
item => item%next
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
if (.not. found) call IO_error(140_pInt,ext_msg=key)
|
if (.not. found) call IO_error(140,ext_msg=key)
|
||||||
|
|
||||||
end function getFloat
|
end function getFloat
|
||||||
|
|
||||||
|
@ -564,7 +564,7 @@ end function getFloat
|
||||||
!> @details gets the last value if the key occurs more than once. If key is not found exits with
|
!> @details gets the last value if the key occurs more than once. If key is not found exits with
|
||||||
!! error unless default is given
|
!! error unless default is given
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
integer(pInt) function getInt(this,key,defaultVal)
|
integer function getInt(this,key,defaultVal)
|
||||||
use IO, only: &
|
use IO, only: &
|
||||||
IO_error, &
|
IO_error, &
|
||||||
IO_stringValue, &
|
IO_stringValue, &
|
||||||
|
@ -573,7 +573,7 @@ integer(pInt) function getInt(this,key,defaultVal)
|
||||||
implicit none
|
implicit none
|
||||||
class(tPartitionedStringList), target, intent(in) :: this
|
class(tPartitionedStringList), target, intent(in) :: this
|
||||||
character(len=*), intent(in) :: key
|
character(len=*), intent(in) :: key
|
||||||
integer(pInt), intent(in), optional :: defaultVal
|
integer, intent(in), optional :: defaultVal
|
||||||
type(tPartitionedStringList), pointer :: item
|
type(tPartitionedStringList), pointer :: item
|
||||||
logical :: found
|
logical :: found
|
||||||
|
|
||||||
|
@ -584,13 +584,13 @@ integer(pInt) function getInt(this,key,defaultVal)
|
||||||
do while (associated(item%next))
|
do while (associated(item%next))
|
||||||
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
|
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
|
||||||
found = .true.
|
found = .true.
|
||||||
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
if (item%string%pos(1) < 2) call IO_error(143,ext_msg=key)
|
||||||
getInt = IO_IntValue(item%string%val,item%string%pos,2)
|
getInt = IO_IntValue(item%string%val,item%string%pos,2)
|
||||||
endif
|
endif
|
||||||
item => item%next
|
item => item%next
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
if (.not. found) call IO_error(140_pInt,ext_msg=key)
|
if (.not. found) call IO_error(140,ext_msg=key)
|
||||||
|
|
||||||
end function getInt
|
end function getInt
|
||||||
|
|
||||||
|
@ -623,14 +623,14 @@ character(len=65536) function getString(this,key,defaultVal,raw)
|
||||||
found = present(defaultVal)
|
found = present(defaultVal)
|
||||||
if (found) then
|
if (found) then
|
||||||
getString = trim(defaultVal)
|
getString = trim(defaultVal)
|
||||||
if (len_trim(getString) /= len_trim(defaultVal)) call IO_error(0_pInt,ext_msg='getString')
|
if (len_trim(getString) /= len_trim(defaultVal)) call IO_error(0,ext_msg='getString')
|
||||||
endif
|
endif
|
||||||
|
|
||||||
item => this
|
item => this
|
||||||
do while (associated(item%next))
|
do while (associated(item%next))
|
||||||
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
|
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
|
||||||
found = .true.
|
found = .true.
|
||||||
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
if (item%string%pos(1) < 2) call IO_error(143,ext_msg=key)
|
||||||
|
|
||||||
if (whole) then
|
if (whole) then
|
||||||
getString = trim(item%string%val(item%string%pos(4):)) ! raw string starting a second chunk
|
getString = trim(item%string%val(item%string%pos(4):)) ! raw string starting a second chunk
|
||||||
|
@ -641,7 +641,7 @@ character(len=65536) function getString(this,key,defaultVal,raw)
|
||||||
item => item%next
|
item => item%next
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
if (.not. found) call IO_error(140_pInt,ext_msg=key)
|
if (.not. found) call IO_error(140,ext_msg=key)
|
||||||
|
|
||||||
end function getString
|
end function getString
|
||||||
|
|
||||||
|
@ -662,9 +662,9 @@ function getFloats(this,key,defaultVal,requiredSize)
|
||||||
class(tPartitionedStringList), target, intent(in) :: this
|
class(tPartitionedStringList), target, intent(in) :: this
|
||||||
character(len=*), intent(in) :: key
|
character(len=*), intent(in) :: key
|
||||||
real(pReal), dimension(:), intent(in), optional :: defaultVal
|
real(pReal), dimension(:), intent(in), optional :: defaultVal
|
||||||
integer(pInt), intent(in), optional :: requiredSize
|
integer, intent(in), optional :: requiredSize
|
||||||
type(tPartitionedStringList), pointer :: item
|
type(tPartitionedStringList), pointer :: item
|
||||||
integer(pInt) :: i
|
integer :: i
|
||||||
logical :: found, &
|
logical :: found, &
|
||||||
cumulative
|
cumulative
|
||||||
|
|
||||||
|
@ -678,8 +678,8 @@ function getFloats(this,key,defaultVal,requiredSize)
|
||||||
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
|
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
|
||||||
found = .true.
|
found = .true.
|
||||||
if (.not. cumulative) getFloats = [real(pReal)::]
|
if (.not. cumulative) getFloats = [real(pReal)::]
|
||||||
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
if (item%string%pos(1) < 2) call IO_error(143,ext_msg=key)
|
||||||
do i = 2_pInt, item%string%pos(1)
|
do i = 2, item%string%pos(1)
|
||||||
getFloats = [getFloats,IO_FloatValue(item%string%val,item%string%pos,i)]
|
getFloats = [getFloats,IO_FloatValue(item%string%val,item%string%pos,i)]
|
||||||
enddo
|
enddo
|
||||||
endif
|
endif
|
||||||
|
@ -687,7 +687,7 @@ function getFloats(this,key,defaultVal,requiredSize)
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
if (.not. found) then
|
if (.not. found) then
|
||||||
if (present(defaultVal)) then; getFloats = defaultVal; else; call IO_error(140_pInt,ext_msg=key); endif
|
if (present(defaultVal)) then; getFloats = defaultVal; else; call IO_error(140,ext_msg=key); endif
|
||||||
endif
|
endif
|
||||||
if (present(requiredSize)) then
|
if (present(requiredSize)) then
|
||||||
if(requiredSize /= size(getFloats)) call IO_error(146,ext_msg=key)
|
if(requiredSize /= size(getFloats)) call IO_error(146,ext_msg=key)
|
||||||
|
@ -708,13 +708,13 @@ function getInts(this,key,defaultVal,requiredSize)
|
||||||
IO_IntValue
|
IO_IntValue
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt), dimension(:), allocatable :: getInts
|
integer, dimension(:), allocatable :: getInts
|
||||||
class(tPartitionedStringList), target, intent(in) :: this
|
class(tPartitionedStringList), target, intent(in) :: this
|
||||||
character(len=*), intent(in) :: key
|
character(len=*), intent(in) :: key
|
||||||
integer(pInt), dimension(:), intent(in), optional :: defaultVal
|
integer, dimension(:), intent(in), optional :: defaultVal
|
||||||
integer(pInt), intent(in), optional :: requiredSize
|
integer, intent(in), optional :: requiredSize
|
||||||
type(tPartitionedStringList), pointer :: item
|
type(tPartitionedStringList), pointer :: item
|
||||||
integer(pInt) :: i
|
integer :: i
|
||||||
logical :: found, &
|
logical :: found, &
|
||||||
cumulative
|
cumulative
|
||||||
|
|
||||||
|
@ -727,9 +727,9 @@ function getInts(this,key,defaultVal,requiredSize)
|
||||||
do while (associated(item%next))
|
do while (associated(item%next))
|
||||||
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
|
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
|
||||||
found = .true.
|
found = .true.
|
||||||
if (.not. cumulative) getInts = [integer(pInt)::]
|
if (.not. cumulative) getInts = [integer::]
|
||||||
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
if (item%string%pos(1) < 2) call IO_error(143,ext_msg=key)
|
||||||
do i = 2_pInt, item%string%pos(1)
|
do i = 2, item%string%pos(1)
|
||||||
getInts = [getInts,IO_IntValue(item%string%val,item%string%pos,i)]
|
getInts = [getInts,IO_IntValue(item%string%val,item%string%pos,i)]
|
||||||
enddo
|
enddo
|
||||||
endif
|
endif
|
||||||
|
@ -737,7 +737,7 @@ function getInts(this,key,defaultVal,requiredSize)
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
if (.not. found) then
|
if (.not. found) then
|
||||||
if (present(defaultVal)) then; getInts = defaultVal; else; call IO_error(140_pInt,ext_msg=key); endif
|
if (present(defaultVal)) then; getInts = defaultVal; else; call IO_error(140,ext_msg=key); endif
|
||||||
endif
|
endif
|
||||||
if (present(requiredSize)) then
|
if (present(requiredSize)) then
|
||||||
if(requiredSize /= size(getInts)) call IO_error(146,ext_msg=key)
|
if(requiredSize /= size(getInts)) call IO_error(146,ext_msg=key)
|
||||||
|
@ -765,7 +765,7 @@ function getStrings(this,key,defaultVal,raw)
|
||||||
logical, intent(in), optional :: raw
|
logical, intent(in), optional :: raw
|
||||||
type(tPartitionedStringList), pointer :: item
|
type(tPartitionedStringList), pointer :: item
|
||||||
character(len=65536) :: str
|
character(len=65536) :: str
|
||||||
integer(pInt) :: i
|
integer :: i
|
||||||
logical :: found, &
|
logical :: found, &
|
||||||
whole, &
|
whole, &
|
||||||
cumulative
|
cumulative
|
||||||
|
@ -783,16 +783,16 @@ function getStrings(this,key,defaultVal,raw)
|
||||||
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
|
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
|
||||||
found = .true.
|
found = .true.
|
||||||
if (allocated(getStrings) .and. .not. cumulative) deallocate(getStrings)
|
if (allocated(getStrings) .and. .not. cumulative) deallocate(getStrings)
|
||||||
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
if (item%string%pos(1) < 2) call IO_error(143,ext_msg=key)
|
||||||
|
|
||||||
notAllocated: if (.not. allocated(getStrings)) then
|
notAllocated: if (.not. allocated(getStrings)) then
|
||||||
if (whole) then
|
if (whole) then
|
||||||
str = item%string%val(item%string%pos(4):)
|
str = item%string%val(item%string%pos(4):)
|
||||||
getStrings = [str]
|
getStrings = [str]
|
||||||
else
|
else
|
||||||
str = IO_StringValue(item%string%val,item%string%pos,2_pInt)
|
str = IO_StringValue(item%string%val,item%string%pos,2)
|
||||||
allocate(getStrings(1),source=str)
|
allocate(getStrings(1),source=str)
|
||||||
do i=3_pInt,item%string%pos(1)
|
do i=3,item%string%pos(1)
|
||||||
str = IO_StringValue(item%string%val,item%string%pos,i)
|
str = IO_StringValue(item%string%val,item%string%pos,i)
|
||||||
getStrings = [getStrings,str]
|
getStrings = [getStrings,str]
|
||||||
enddo
|
enddo
|
||||||
|
@ -802,7 +802,7 @@ function getStrings(this,key,defaultVal,raw)
|
||||||
str = item%string%val(item%string%pos(4):)
|
str = item%string%val(item%string%pos(4):)
|
||||||
getStrings = [getStrings,str]
|
getStrings = [getStrings,str]
|
||||||
else
|
else
|
||||||
do i=2_pInt,item%string%pos(1)
|
do i=2,item%string%pos(1)
|
||||||
str = IO_StringValue(item%string%val,item%string%pos,i)
|
str = IO_StringValue(item%string%val,item%string%pos,i)
|
||||||
getStrings = [getStrings,str]
|
getStrings = [getStrings,str]
|
||||||
enddo
|
enddo
|
||||||
|
@ -813,7 +813,7 @@ function getStrings(this,key,defaultVal,raw)
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
if (.not. found) then
|
if (.not. found) then
|
||||||
if (present(defaultVal)) then; getStrings = defaultVal; else; call IO_error(140_pInt,ext_msg=key); endif
|
if (present(defaultVal)) then; getStrings = defaultVal; else; call IO_error(140,ext_msg=key); endif
|
||||||
endif
|
endif
|
||||||
|
|
||||||
end function getStrings
|
end function getStrings
|
||||||
|
|
Loading…
Reference in New Issue