DAMASK_EICMD/src/YAML.f90

1078 lines
40 KiB
Fortran
Raw Normal View History

2020-05-26 15:16:28 +05:30
!----------------------------------------------------------------------------------------------------
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @author Sharan Roongta, Max-Planck-Institut für Eisenforschung GmbH
!> @brief Parser for YAML files.
!> @details Module converts a YAML input file to an equivalent YAML flow style which is then parsed.
2020-05-26 15:16:28 +05:30
!----------------------------------------------------------------------------------------------------
2023-12-14 10:39:37 +05:30
module YAML
2020-05-22 00:11:40 +05:30
use prec
use misc
2020-05-22 00:11:40 +05:30
use IO
use types
#ifdef FYAML
use system_routines
#endif
2020-05-22 00:11:40 +05:30
implicit none(type,external)
2020-05-22 00:11:40 +05:30
private
2020-08-15 19:32:10 +05:30
public :: &
2023-12-14 10:39:37 +05:30
YAML_init, &
YAML_str_asList, &
YAML_str_asDict
2020-05-22 00:11:40 +05:30
#ifdef FYAML
interface
subroutine to_flow_C(flow,length_flow,mixed) bind(C)
use, intrinsic :: ISO_C_Binding, only: C_LONG, C_CHAR, C_PTR
implicit none(type,external)
type(C_PTR), intent(out) :: flow
integer(C_LONG), intent(out) :: length_flow
character(kind=C_CHAR), dimension(*), intent(in) :: mixed
end subroutine to_flow_C
end interface
#endif
2020-05-22 00:11:40 +05:30
contains
2020-05-25 16:24:43 +05:30
!--------------------------------------------------------------------------------------------------
2020-09-13 16:13:49 +05:30
!> @brief Do sanity checks.
2020-05-25 16:24:43 +05:30
!--------------------------------------------------------------------------------------------------
2023-12-14 10:39:37 +05:30
subroutine YAML_init()
2020-05-22 00:11:40 +05:30
2023-12-14 10:39:37 +05:30
print'(/,1x,a)', '<<<+- YAML init -+>>>'
#ifdef FYAML
print'(/,1x,a)', 'libfyaml powered'
#else
2023-12-14 10:39:37 +05:30
call YAML_selfTest()
#endif
2020-05-22 00:11:40 +05:30
2023-12-14 10:39:37 +05:30
end subroutine YAML_init
2020-09-13 16:13:49 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Parse a YAML string with list at root into a structure of nodes.
!> @details The string needs to end with a newline (unless using libfyaml).
2020-09-13 16:13:49 +05:30
!--------------------------------------------------------------------------------------------------
2023-12-14 10:39:37 +05:30
function YAML_str_asList(str) result(list)
2020-09-13 16:13:49 +05:30
2021-07-27 12:05:52 +05:30
character(len=*), intent(in) :: str
type(tList), pointer :: list
class(tNode), pointer :: node
node => parse_flow(to_flow(str))
list => node%asList()
2023-12-14 10:39:37 +05:30
end function YAML_str_asList
!--------------------------------------------------------------------------------------------------
!> @brief Parse a YAML string with dict at root into a structure of nodes.
!> @details The string needs to end with a newline (unless using libfyaml).
!--------------------------------------------------------------------------------------------------
2023-12-14 10:39:37 +05:30
function YAML_str_asDict(str) result(dict)
character(len=*), intent(in) :: str
type(tDict), pointer :: dict
class(tNode), pointer :: node
2020-09-13 16:13:49 +05:30
2021-07-27 12:05:52 +05:30
node => parse_flow(to_flow(str))
dict => node%asDict()
2020-09-13 16:13:49 +05:30
2023-12-14 10:39:37 +05:30
end function YAML_str_asDict
2020-05-22 00:11:40 +05:30
2020-05-25 16:24:43 +05:30
2020-05-22 00:11:40 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Read a string in flow style and store it in the form of dictionaries, lists, and scalars.
!> @details A node-type pointer can either point to a dictionary, list, or scalar type entities.
2020-05-22 00:11:40 +05:30
!--------------------------------------------------------------------------------------------------
2020-08-15 19:32:10 +05:30
recursive function parse_flow(YAML_flow) result(node)
2020-05-22 00:11:40 +05:30
character(len=*), intent(in) :: YAML_flow !< YAML file in flow style
class(tNode), pointer :: node
2020-06-29 18:39:13 +05:30
class(tNode), pointer :: &
2020-08-15 19:32:10 +05:30
myVal
character(len=:), allocatable :: &
2020-08-15 19:32:10 +05:30
flow_string, &
key
integer(pI64) :: &
2020-08-15 19:32:10 +05:30
e, & ! end position of dictionary or list
s, & ! start position of dictionary or list
d ! position of key: value separator (':')
flow_string = trim(adjustl(YAML_flow))
if (len_trim(flow_string,pI64) == 0_pI64) then
2020-06-24 15:26:21 +05:30
node => emptyDict
return
2020-06-23 14:36:41 +05:30
elseif (flow_string(1:1) == '{') then ! start of a dictionary
e = 1_pI64
2020-05-22 00:11:40 +05:30
allocate(tDict::node)
do while (e < len_trim(flow_string,pI64))
2020-05-22 00:11:40 +05:30
s = e
d = s + scan(flow_string(s+1_pI64:),':',kind=pI64)
e = d + find_end(flow_string(d+1_pI64:),'}')
key = trim(adjustl(flow_string(s+1_pI64:d-1_pI64)))
2023-06-04 10:47:38 +05:30
if (quotedStr(key)) key = key(2:len(key)-1)
2023-02-14 22:07:43 +05:30
myVal => parse_flow(flow_string(d+1_pI64:e-1_pI64)) ! parse items (recursively)
2020-05-22 00:11:40 +05:30
select type (node)
class is (tDict)
call node%set(key,myVal)
end select
2022-06-09 02:36:01 +05:30
end do
2020-05-22 00:11:40 +05:30
elseif (flow_string(1:1) == '[') then ! start of a list
e = 1_pI64
2020-05-22 00:11:40 +05:30
allocate(tList::node)
do while (e < len_trim(flow_string,pI64))
2020-05-22 00:11:40 +05:30
s = e
e = s + find_end(flow_string(s+1_pI64:),']')
2023-02-14 22:07:43 +05:30
myVal => parse_flow(flow_string(s+1_pI64:e-1_pI64)) ! parse items (recursively)
2020-05-22 00:11:40 +05:30
select type (node)
class is (tList)
call node%append(myVal)
end select
2022-06-09 02:36:01 +05:30
end do
2020-05-22 00:11:40 +05:30
else ! scalar value
allocate(tScalar::node)
select type (node)
class is (tScalar)
2023-06-04 10:47:38 +05:30
if (quotedStr(flow_string)) then
node = trim(adjustl(flow_string(2:len(flow_string)-1)))
2021-07-23 19:51:56 +05:30
else
node = trim(adjustl(flow_string))
end if
2020-05-22 00:11:40 +05:30
end select
end if
2020-05-22 00:11:40 +05:30
end function parse_flow
!--------------------------------------------------------------------------------------------------
!> @brief Find location of chunk end: ',' '}', or ']'.
2020-05-22 00:11:40 +05:30
!> @details leaves nested lists ( '[...]' and dicts '{...}') intact
!--------------------------------------------------------------------------------------------------
2023-07-31 02:47:21 +05:30
integer(pI64) function find_end(str,e_char)
2020-05-22 00:11:40 +05:30
2020-06-24 20:48:16 +05:30
character(len=*), intent(in) :: str !< chunk of YAML flow string
2020-05-22 00:11:40 +05:30
character, intent(in) :: e_char !< end of list/dict ( '}' or ']')
integer(pI64) :: N_sq, & !< number of open square brackets
N_cu, & !< number of open curly brackets
2020-05-22 00:11:40 +05:30
i
N_sq = 0_pI64
N_cu = 0_pI64
i = 1_pI64
do while(i<=len_trim(str,pI64))
if (scan(str(i:i),IO_QUOTES,kind=pI64) == 1_pI64) i = i + scan(str(i+1:),str(i:i),kind=pI64)
if (N_sq==0 .and. N_cu==0 .and. scan(str(i:i),e_char//',',kind=pI64) == 1_pI64) exit
N_sq = N_sq + merge(1_pI64,0_pI64,str(i:i) == '[')
N_cu = N_cu + merge(1_pI64,0_pI64,str(i:i) == '{')
N_sq = N_sq - merge(1_pI64,0_pI64,str(i:i) == ']')
N_cu = N_cu - merge(1_pI64,0_pI64,str(i:i) == '}')
i = i + 1_pI64
2022-06-09 02:36:01 +05:30
end do
2020-05-22 00:11:40 +05:30
find_end = i
end function find_end
!--------------------------------------------------------------------------------------------------
2023-02-14 22:07:43 +05:30
! @brief Check whether a string is enclosed with single or double quotes.
!--------------------------------------------------------------------------------------------------
2023-06-04 10:47:38 +05:30
logical function quotedStr(line)
character(len=*), intent(in) :: line
2022-04-14 10:49:56 +05:30
2023-06-04 10:47:38 +05:30
quotedStr = .false.
2022-04-14 10:49:56 +05:30
if (len(line) == 0) return
2021-08-02 15:19:25 +05:30
if (scan(line(:1),IO_QUOTES) == 1) then
2023-06-04 10:47:38 +05:30
quotedStr = .true.
2022-12-07 22:59:03 +05:30
if (line(len(line):len(line)) /= line(:1)) call IO_error(710,ext_msg=line)
end if
2023-06-04 10:47:38 +05:30
end function quotedStr
#ifdef FYAML
!--------------------------------------------------------------------------------------------------
! @brief Convert all block-style YAML parts to flow style.
2020-05-22 00:11:40 +05:30
!--------------------------------------------------------------------------------------------------
function to_flow(mixed) result(flow)
character(len=*), intent(in) :: mixed
character(:,C_CHAR), allocatable :: flow
type(C_PTR) :: str_ptr
integer(C_LONG) :: strlen
call to_flow_C(str_ptr,strlen,f_c_string(mixed))
2023-02-10 04:04:45 +05:30
if (strlen < 1_C_LONG) call IO_error(703,ext_msg='libyfaml')
allocate(character(len=strlen,kind=c_char) :: flow)
block
character(len=strlen,kind=c_char), pointer :: s
call c_f_pointer(str_ptr,s)
flow = s(:len(s,pI64)-1_pI64)
end block
call free_C(str_ptr)
end function to_flow
#else
!--------------------------------------------------------------------------------------------------
! @brief Determine indentation depth.
! @details Indentation level is determined for a given block/line.
! In case of nested lists, an offset is added to determine the indent of the item block (skip
! leading dashes).
2020-05-22 00:11:40 +05:30
!--------------------------------------------------------------------------------------------------
integer function indentDepth(line,offset)
character(len=*), intent(in) :: line
integer, optional,intent(in) :: offset
indentDepth = verify(line,IO_WHITESPACE) - 1 + misc_optional(offset,0)
2020-05-22 00:11:40 +05:30
end function indentDepth
!--------------------------------------------------------------------------------------------------
! @brief Check whether a string is in flow style, i.e. starts with '{' or '['.
2020-05-22 00:11:40 +05:30
!--------------------------------------------------------------------------------------------------
logical function isFlow(line)
character(len=*), intent(in) :: line
2020-05-22 00:11:40 +05:30
isFlow = index(adjustl(line),'[') == 1 .or. index(adjustl(line),'{') == 1
end function isFlow
!--------------------------------------------------------------------------------------------------
! @brief Check whether a string is a scalar item, i.e. starts without any special symbols.
2020-05-22 00:11:40 +05:30
!--------------------------------------------------------------------------------------------------
logical function isScalar(line)
character(len=*), intent(in) :: line
2022-01-31 19:35:15 +05:30
isScalar = (.not. isKeyValue(line) .and. &
.not. isKey(line) .and. &
.not. isListItem(line) .and. &
.not. isFlow(line))
2020-05-22 00:11:40 +05:30
end function isScalar
!--------------------------------------------------------------------------------------------------
! @brief Check whether a string is a list item, i.e. starts with '-'.
2020-05-22 00:11:40 +05:30
!--------------------------------------------------------------------------------------------------
logical function isListItem(line)
character(len=*), intent(in) :: line
2020-08-15 19:32:10 +05:30
isListItem = .false.
2022-12-07 22:59:03 +05:30
if (len_trim(adjustl(line))> 2 .and. index(trim(adjustl(line)), '-') == 1) then
2020-08-15 19:32:10 +05:30
isListItem = scan(trim(adjustl(line)),' ') == 2
else
isListItem = trim(adjustl(line)) == '-'
end if
2020-05-22 00:11:40 +05:30
end function isListItem
!--------------------------------------------------------------------------------------------------
! @brief Check whether a string contains a key-value pair of the form '<key>: <value>'.
2020-05-22 00:11:40 +05:30
!--------------------------------------------------------------------------------------------------
logical function isKeyValue(line)
character(len=*), intent(in) :: line
isKeyValue = .false.
2024-02-06 22:04:07 +05:30
if ( .not. isKey(line) .and. index(clean(line),':') > 0 .and. .not. isFlow(line)) then
if (index(clean(line),': ') > 0) isKeyValue = .true.
end if
2020-05-22 00:11:40 +05:30
end function isKeyValue
!--------------------------------------------------------------------------------------------------
! @brief Check whether a string contains a key without a value, i.e. it ends in ':'.
! ToDo: check whether this is safe for trailing spaces followed by a newline character
2020-05-22 00:11:40 +05:30
!--------------------------------------------------------------------------------------------------
logical function isKey(line)
character(len=*), intent(in) :: line
2024-02-06 22:04:07 +05:30
if (len(clean(line)) == 0) then
2020-05-22 00:11:40 +05:30
isKey = .false.
else
2024-02-06 22:04:07 +05:30
isKey = index(clean(line),':',back=.false.) == len(clean(line)) .and. &
index(clean(line),':',back=.true.) == len(clean(line)) .and. &
2020-10-07 13:07:48 +05:30
.not. isFlow(line)
end if
2020-05-22 00:11:40 +05:30
end function isKey
2020-10-05 22:23:05 +05:30
!--------------------------------------------------------------------------------------------------
! @brief Check whether a string is a list in flow style.
2020-10-05 22:23:05 +05:30
!--------------------------------------------------------------------------------------------------
logical function isFlowList(line)
character(len=*), intent(in) :: line
2020-10-05 22:23:05 +05:30
isFlowList = index(adjustl(line),'[') == 1
end function isFlowList
!--------------------------------------------------------------------------------------------------
! @brief Skip empty lines.
! @details Update start position in the block by skipping empty lines if present.
!--------------------------------------------------------------------------------------------------
subroutine skip_empty_lines(blck,s_blck)
character(len=*), intent(in) :: blck
integer, intent(inout) :: s_blck
2020-09-25 08:22:03 +05:30
logical :: empty
2020-09-25 08:22:03 +05:30
empty = .true.
2023-06-28 15:53:00 +05:30
do while (empty .and. len_trim(blck(s_blck:)) /= 0)
2024-02-06 22:04:07 +05:30
empty = len_trim(clean(blck(s_blck:s_blck + index(blck(s_blck:),IO_EOL) - 2))) == 0
2022-12-07 22:59:03 +05:30
if (empty) s_blck = s_blck + index(blck(s_blck:),IO_EOL)
2022-06-09 02:36:01 +05:30
end do
end subroutine skip_empty_lines
!--------------------------------------------------------------------------------------------------
! @brief Skip file header.
! @details Update start position in the block by skipping file header if present.
!--------------------------------------------------------------------------------------------------
subroutine skip_file_header(blck,s_blck)
character(len=*), intent(in) :: blck
integer, intent(inout) :: s_blck
character(len=:), allocatable :: line
2024-02-06 22:04:07 +05:30
line = clean(blck(s_blck:s_blck + index(blck(s_blck:),IO_EOL) - 2))
2022-12-07 22:59:03 +05:30
if (index(adjustl(line),'%YAML') == 1) then
s_blck = s_blck + index(blck(s_blck:),IO_EOL)
call skip_empty_lines(blck,s_blck)
2024-02-06 22:04:07 +05:30
if (trim(clean(blck(s_blck:s_blck + index(blck(s_blck:),IO_EOL) - 2))) == '---') then
s_blck = s_blck + index(blck(s_blck:),IO_EOL)
else
call IO_error(708,ext_msg = line)
end if
end if
end subroutine skip_file_header
2020-10-06 21:39:53 +05:30
2020-10-05 22:23:05 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Check whether a line in flow style starts and ends on the same line.
2020-10-05 22:23:05 +05:30
!--------------------------------------------------------------------------------------------------
2020-10-06 21:39:53 +05:30
logical function flow_is_closed(str,e_char)
2020-10-05 22:23:05 +05:30
character(len=*), intent(in) :: str
character, intent(in) :: e_char !< end of list/dict ( '}' or ']')
integer :: N_sq, & !< number of open square brackets
N_cu, & !< number of open curly brackets
i
character(len=:), allocatable:: line
2020-10-06 21:39:53 +05:30
flow_is_closed = .false.
2020-10-05 22:23:05 +05:30
N_sq = 0
N_cu = 0
2022-12-07 22:59:03 +05:30
if (e_char == ']') line = str(index(str(:),'[')+1:)
if (e_char == '}') line = str(index(str(:),'{')+1:)
2020-10-05 22:23:05 +05:30
do i = 1, len_trim(line)
2020-10-06 21:39:53 +05:30
flow_is_closed = (N_sq==0 .and. N_cu==0 .and. scan(line(i:i),e_char) == 1)
2020-10-05 22:23:05 +05:30
N_sq = N_sq + merge(1,0,line(i:i) == '[')
N_cu = N_cu + merge(1,0,line(i:i) == '{')
N_sq = N_sq - merge(1,0,line(i:i) == ']')
N_cu = N_cu - merge(1,0,line(i:i) == '}')
2022-06-09 02:36:01 +05:30
end do
2020-10-05 22:23:05 +05:30
2020-10-06 21:39:53 +05:30
end function flow_is_closed
2020-10-05 22:23:05 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Return a flow-style line without line break.
2020-10-05 22:23:05 +05:30
!--------------------------------------------------------------------------------------------------
2020-10-06 21:39:53 +05:30
subroutine remove_line_break(blck,s_blck,e_char,flow_line)
2020-10-05 22:23:05 +05:30
character(len=*), intent(in) :: blck !< YAML in mixed style
integer, intent(inout) :: s_blck
character, intent(in) :: e_char !< end of list/dict ( '}' or ']')
2020-10-06 21:39:53 +05:30
character(len=:), allocatable, intent(out) :: flow_line
2020-10-05 22:23:05 +05:30
logical :: line_end
2023-06-28 15:53:00 +05:30
line_end = .false.
2020-10-06 21:39:53 +05:30
flow_line = ''
2020-10-05 22:23:05 +05:30
2023-06-28 15:53:00 +05:30
do while (.not. line_end)
2024-02-06 22:04:07 +05:30
flow_line = flow_line//clean(blck(s_blck:s_blck + index(blck(s_blck:),IO_EOL) - 2))//' '
2020-10-06 21:39:53 +05:30
line_end = flow_is_closed(flow_line,e_char)
s_blck = s_blck + index(blck(s_blck:),IO_EOL)
2022-06-09 02:36:01 +05:30
end do
2020-10-05 22:23:05 +05:30
2020-10-06 21:39:53 +05:30
end subroutine remove_line_break
2020-10-05 22:23:05 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Return a scalar list item without line break.
!--------------------------------------------------------------------------------------------------
subroutine list_item_inline(blck,s_blck,inline,offset)
2023-07-31 02:47:21 +05:30
character(len=*), intent(in) :: blck !< YAML in mixed style
integer, intent(inout) :: s_blck
character(len=:), allocatable, intent(out) :: inline
integer, intent(inout) :: offset
character(len=:), allocatable :: line
integer :: indent,indent_next
indent = indentDepth(blck(s_blck:),offset)
2024-02-06 22:04:07 +05:30
line = clean(blck(s_blck:s_blck + index(blck(s_blck:),IO_EOL) - 2))
inline = line(indent-offset+3:)
s_blck = s_blck + index(blck(s_blck:),IO_EOL)
indent_next = indentDepth(blck(s_blck:))
2023-06-28 15:53:00 +05:30
do while (indent_next > indent)
2024-02-06 22:04:07 +05:30
inline = inline//' '//trim(adjustl(clean(blck(s_blck:s_blck + index(blck(s_blck:),IO_EOL) - 2))))
s_blck = s_blck + index(blck(s_blck:),IO_EOL)
indent_next = indentDepth(blck(s_blck:))
2022-06-09 02:36:01 +05:30
end do
2022-12-07 22:59:03 +05:30
if (scan(inline,",") > 0) inline = '"'//inline//'"'
end subroutine list_item_inline
2020-05-22 00:11:40 +05:30
!--------------------------------------------------------------------------------------------------
! @brief Read a line of YAML block that is already in flow style.
! @details A dict should be enclosed within '{}' for it to be consistent with the DAMASK YAML parser.
2020-05-22 00:11:40 +05:30
!--------------------------------------------------------------------------------------------------
recursive subroutine line_isFlow(flow,s_flow,line)
character(len=*), intent(inout) :: flow !< YAML in flow style only
integer, intent(inout) :: s_flow !< start position in flow
character(len=*), intent(in) :: line
2020-05-22 00:11:40 +05:30
integer :: &
s, &
list_chunk, &
dict_chunk
2022-12-07 22:59:03 +05:30
if (index(adjustl(line),'[') == 1) then
2020-05-22 00:11:40 +05:30
s = index(line,'[')
flow(s_flow:s_flow) = '['
2023-06-28 15:53:00 +05:30
s_flow = s_flow+1
do while (s < len_trim(line))
2020-05-22 00:11:40 +05:30
list_chunk = s + find_end(line(s+1:),']')
2022-12-07 22:59:03 +05:30
if (iskeyValue(line(s+1:list_chunk-1))) then
2020-05-22 00:11:40 +05:30
flow(s_flow:s_flow) = '{'
2023-06-28 15:53:00 +05:30
s_flow = s_flow+1
2020-05-22 00:11:40 +05:30
call keyValue_toFlow(flow,s_flow,line(s+1:list_chunk-1))
flow(s_flow:s_flow) = '}'
2023-06-28 15:53:00 +05:30
s_flow = s_flow+1
2022-12-07 22:59:03 +05:30
elseif (isFlow(line(s+1:list_chunk-1))) then
2020-05-22 00:11:40 +05:30
call line_isFlow(flow,s_flow,line(s+1:list_chunk-1))
else
call line_toFlow(flow,s_flow,line(s+1:list_chunk-1))
end if
2020-05-22 00:11:40 +05:30
flow(s_flow:s_flow+1) = ', '
2023-06-28 15:53:00 +05:30
s_flow = s_flow+2
2020-05-22 00:11:40 +05:30
s = s + find_end(line(s+1:),']')
2022-06-09 02:36:01 +05:30
end do
2023-06-28 15:53:00 +05:30
s_flow = s_flow-1
if (flow(s_flow-1:s_flow-1) == ',') s_flow = s_flow-1
2020-05-22 00:11:40 +05:30
flow(s_flow:s_flow) = ']'
s_flow = s_flow+1
2022-12-07 22:59:03 +05:30
elseif (index(adjustl(line),'{') == 1) then
2020-05-22 00:11:40 +05:30
s = index(line,'{')
flow(s_flow:s_flow) = '{'
2023-06-28 15:53:00 +05:30
s_flow = s_flow+1
do while (s < len_trim(line))
2020-05-22 00:11:40 +05:30
dict_chunk = s + find_end(line(s+1:),'}')
2023-06-28 15:53:00 +05:30
if (.not. iskeyValue(line(s+1:dict_chunk-1))) call IO_error(705,ext_msg=line)
2020-05-22 00:11:40 +05:30
call keyValue_toFlow(flow,s_flow,line(s+1:dict_chunk-1))
flow(s_flow:s_flow+1) = ', '
2023-06-28 15:53:00 +05:30
s_flow = s_flow+2
2020-05-22 00:11:40 +05:30
s = s + find_end(line(s+1:),'}')
2022-06-09 02:36:01 +05:30
end do
2023-06-28 15:53:00 +05:30
s_flow = s_flow-1
if (flow(s_flow-1:s_flow-1) == ',') s_flow = s_flow-1
2020-05-22 00:11:40 +05:30
flow(s_flow:s_flow) = '}'
2023-06-28 15:53:00 +05:30
s_flow = s_flow+1
2020-05-22 00:11:40 +05:30
else
call line_toFlow(flow,s_flow,line)
end if
2020-05-22 00:11:40 +05:30
end subroutine line_isFlow
!-------------------------------------------------------------------------------------------------
! @brief Transform a line of YAML of type <key>: <value> to flow style.
! @details Ensures that the <value> is consistent with the input required in the DAMASK YAML parser.
2020-05-22 00:11:40 +05:30
!-------------------------------------------------------------------------------------------------
recursive subroutine keyValue_toFlow(flow,s_flow,line)
2020-05-22 00:11:40 +05:30
character(len=*), intent(inout) :: flow !< YAML in flow style only
integer, intent(inout) :: s_flow !< start position in flow
character(len=*), intent(in) :: line
character(len=:), allocatable :: line_asStandard ! standard form of <key>: <value>
2020-05-22 00:11:40 +05:30
integer :: &
d_flow, &
col_pos, &
offset_value
2020-05-22 00:11:40 +05:30
col_pos = index(line,':')
2022-12-07 22:59:03 +05:30
if (line(col_pos+1:col_pos+1) /= ' ') call IO_error(704,ext_msg=line)
if (isFlow(line(col_pos+1:))) then
2020-05-22 00:11:40 +05:30
d_flow = len_trim(adjustl(line(:col_pos)))
flow(s_flow:s_flow+d_flow+1) = trim(adjustl(line(:col_pos)))//' '
s_flow = s_flow + d_flow+1
call line_isFlow(flow,s_flow,line(col_pos+1:))
else
offset_value = indentDepth(line(col_pos+2:))
line_asStandard = line(:col_pos+1)//line(col_pos+2+offset_value:)
call line_toFlow(flow,s_flow,line_asStandard)
end if
2020-05-22 00:11:40 +05:30
end subroutine keyValue_toFlow
!-------------------------------------------------------------------------------------------------
! @brief Transform a line of YAML to flow style.
2020-05-22 00:11:40 +05:30
!-------------------------------------------------------------------------------------------------
subroutine line_toFlow(flow,s_flow,line)
character(len=*), intent(inout) :: flow !< YAML in flow style only
integer, intent(inout) :: s_flow !< start position in flow
character(len=*), intent(in) :: line
2020-05-22 00:11:40 +05:30
integer :: &
d_flow
d_flow = len_trim(adjustl(line))
flow(s_flow:s_flow+d_flow) = trim(adjustl(line))
s_flow = s_flow + d_flow
end subroutine line_toFlow
!-------------------------------------------------------------------------------------------------
! @brief Transform a block-style list to flow style.
2020-05-22 00:11:40 +05:30
! @details enters the function when encountered with the list indicator '- '
! reads each scalar list item and separates each other with a ','
! If list item is non scalar, it stores the offset for that list item block
2023-02-11 20:00:12 +05:30
! Call the 'decide' function if there is an increase in the indentation level or the list item is not a scalar
2020-05-22 00:11:40 +05:30
! decrease in indentation level indicates the end of an indentation block
!-------------------------------------------------------------------------------------------------
recursive subroutine lst(blck,flow,s_blck,s_flow,offset)
character(len=*), intent(in) :: blck !< YAML in mixed style
character(len=*), intent(inout) :: flow !< YAML in flow style only
integer, intent(inout) :: s_blck, & !< start position in blck
s_flow, & !< start position in flow
offset !< stores leading '- ' in nested lists
character(len=:), allocatable :: line,flow_line,inline
2020-05-22 00:11:40 +05:30
integer :: e_blck,indent
indent = indentDepth(blck(s_blck:),offset)
do while (s_blck <= len_trim(blck))
e_blck = s_blck + index(blck(s_blck:),IO_EOL) - 2
2024-02-06 22:04:07 +05:30
line = clean(blck(s_blck:e_blck))
2022-12-07 22:59:03 +05:30
if (trim(line) == '---' .or. trim(line) == '...') then
exit
elseif (len_trim(line) == 0) then
2020-05-22 00:11:40 +05:30
s_blck = e_blck + 2 ! forward to next line
cycle
2022-12-07 22:59:03 +05:30
elseif (indentDepth(line,offset) > indent) then
2020-05-22 00:11:40 +05:30
call decide(blck,flow,s_blck,s_flow,offset)
offset = 0
flow(s_flow:s_flow+1) = ', '
s_flow = s_flow + 2
2022-12-07 22:59:03 +05:30
elseif (indentDepth(line,offset) < indent .or. .not. isListItem(line)) then
2020-05-22 00:11:40 +05:30
offset = 0
exit ! job done (lower level)
else
2022-12-07 22:59:03 +05:30
if (trim(adjustl(line)) == '-') then ! list item in next line
2020-05-22 00:11:40 +05:30
s_blck = e_blck + 2
call skip_empty_lines(blck,s_blck)
e_blck = s_blck + index(blck(s_blck:),IO_EOL) - 2
2024-02-06 22:04:07 +05:30
line = clean(blck(s_blck:e_blck))
2022-12-07 22:59:03 +05:30
if (trim(line) == '---') call IO_error(707,ext_msg=line)
if (indentDepth(line) < indent .or. indentDepth(line) == indent) &
2020-05-22 00:11:40 +05:30
call IO_error(701,ext_msg=line)
2022-12-07 22:59:03 +05:30
if (isScalar(line)) then
2020-05-22 00:11:40 +05:30
call line_toFlow(flow,s_flow,line)
s_blck = e_blck +2
offset = 0
2022-12-07 22:59:03 +05:30
elseif (isFlow(line)) then
if (isFlowList(line)) then
2020-10-06 21:39:53 +05:30
call remove_line_break(blck,s_blck,']',flow_line)
2020-10-05 22:23:05 +05:30
else
2020-10-06 21:39:53 +05:30
call remove_line_break(blck,s_blck,'}',flow_line)
end if
2020-10-06 21:39:53 +05:30
call line_isFlow(flow,s_flow,flow_line)
2020-05-22 00:11:40 +05:30
offset = 0
end if
2020-05-22 00:11:40 +05:30
else ! list item in the same line
line = line(indentDepth(line)+3:)
2022-12-07 22:59:03 +05:30
if (isScalar(line)) then
call list_item_inline(blck,s_blck,inline,offset)
2020-05-22 00:11:40 +05:30
offset = 0
call line_toFlow(flow,s_flow,inline)
2022-12-07 22:59:03 +05:30
elseif (isFlow(line)) then
2020-10-05 22:23:05 +05:30
s_blck = s_blck + index(blck(s_blck:),'-')
2022-12-07 22:59:03 +05:30
if (isFlowList(line)) then
2020-10-06 21:39:53 +05:30
call remove_line_break(blck,s_blck,']',flow_line)
2020-10-05 22:23:05 +05:30
else
2020-10-06 21:39:53 +05:30
call remove_line_break(blck,s_blck,'}',flow_line)
end if
2020-10-06 21:39:53 +05:30
call line_isFlow(flow,s_flow,flow_line)
2020-05-22 00:11:40 +05:30
offset = 0
else ! non scalar list item
offset = offset + indentDepth(blck(s_blck:))+1 ! offset in spaces to be ignored
s_blck = s_blck + index(blck(s_blck:e_blck),'-') ! s_blck after '-' symbol
end if
2020-05-22 00:11:40 +05:30
end if
end if
2022-12-07 22:59:03 +05:30
if (isScalar(line) .or. isFlow(line)) then
2020-05-22 00:11:40 +05:30
flow(s_flow:s_flow+1) = ', '
2023-06-28 15:53:00 +05:30
s_flow = s_flow+2
end if
2020-05-22 00:11:40 +05:30
2022-06-09 02:36:01 +05:30
end do
2020-05-22 00:11:40 +05:30
2023-06-28 15:53:00 +05:30
s_flow = s_flow-1
if (flow(s_flow-1:s_flow-1) == ',') s_flow = s_flow-1
2020-05-22 00:11:40 +05:30
end subroutine lst
!--------------------------------------------------------------------------------------------------
! @brief Transform a block-style dict to flow style.
2020-05-22 00:11:40 +05:30
! @details enters the function when encountered with the dictionary indicator ':'
! parses each line in the block and compares indentation of a line with the preceding line
! upon increase in indentation level -> 'decide' function decides if the line is a list or dict
! decrease in indentation indicates the end of an indentation block
!--------------------------------------------------------------------------------------------------
recursive subroutine dct(blck,flow,s_blck,s_flow,offset)
character(len=*), intent(in) :: blck !< YAML in mixed style
character(len=*), intent(inout) :: flow !< YAML in flow style only
integer, intent(inout) :: s_blck, & !< start position in blck
s_flow, & !< start position in flow
offset
2020-10-06 21:39:53 +05:30
character(len=:), allocatable :: line,flow_line
2020-10-05 22:23:05 +05:30
integer :: e_blck,indent,col_pos
2020-05-22 00:11:40 +05:30
logical :: previous_isKey
previous_isKey = .false.
indent = indentDepth(blck(s_blck:),offset)
do while (s_blck <= len_trim(blck))
e_blck = s_blck + index(blck(s_blck:),IO_EOL) - 2
2024-02-06 22:04:07 +05:30
line = clean(blck(s_blck:e_blck))
2022-12-07 22:59:03 +05:30
if (trim(line) == '---' .or. trim(line) == '...') then
exit
elseif (len_trim(line) == 0) then
2020-05-22 00:11:40 +05:30
s_blck = e_blck + 2 ! forward to next line
cycle
2022-12-07 22:59:03 +05:30
elseif (indentDepth(line,offset) < indent) then
if (isScalar(line) .or. isFlow(line) .and. previous_isKey) &
2020-05-22 00:11:40 +05:30
call IO_error(701,ext_msg=line)
offset = 0
2020-05-22 00:11:40 +05:30
exit ! job done (lower level)
2022-12-07 22:59:03 +05:30
elseif (indentDepth(line,offset) > indent .or. isListItem(line)) then
2020-05-22 00:11:40 +05:30
offset = 0
call decide(blck,flow,s_blck,s_flow,offset)
else
2022-12-07 22:59:03 +05:30
if (isScalar(line)) call IO_error(701,ext_msg=line)
if (isFlow(line)) call IO_error(702,ext_msg=line)
2020-05-22 00:11:40 +05:30
line = line(indentDepth(line)+1:)
2022-12-07 22:59:03 +05:30
if (previous_isKey) then
2020-05-22 00:11:40 +05:30
flow(s_flow-1:s_flow) = ', '
2023-06-28 15:53:00 +05:30
s_flow = s_flow+1
end if
2022-12-07 22:59:03 +05:30
if (isKeyValue(line)) then
2020-10-05 22:23:05 +05:30
col_pos = index(line,':')
2022-12-07 22:59:03 +05:30
if (isFlow(line(col_pos+1:))) then
if (isFlowList(line(col_pos+1:))) then
2020-10-06 21:39:53 +05:30
call remove_line_break(blck,s_blck,']',flow_line)
2020-10-05 22:23:05 +05:30
else
2020-10-06 21:39:53 +05:30
call remove_line_break(blck,s_blck,'}',flow_line)
end if
2020-10-06 21:39:53 +05:30
call keyValue_toFlow(flow,s_flow,flow_line)
2020-10-05 22:23:05 +05:30
else
call keyValue_toFlow(flow,s_flow,line)
s_blck = e_blck + 2
end if
2020-05-22 00:11:40 +05:30
else
call line_toFlow(flow,s_flow,line)
2020-10-05 22:23:05 +05:30
s_blck = e_blck + 2
end if
2020-05-22 00:11:40 +05:30
end if
2022-12-07 22:59:03 +05:30
if (isScalar(line) .or. isKeyValue(line)) then
2020-05-22 00:11:40 +05:30
flow(s_flow:s_flow) = ','
2023-06-28 15:53:00 +05:30
s_flow = s_flow+1
previous_isKey = .false.
2020-05-22 00:11:40 +05:30
else
previous_isKey = .true.
end if
2020-05-22 00:11:40 +05:30
flow(s_flow:s_flow) = ' '
2023-06-28 15:53:00 +05:30
s_flow = s_flow+1
2020-05-22 00:11:40 +05:30
offset = 0
2022-06-09 02:36:01 +05:30
end do
2020-05-22 00:11:40 +05:30
2023-06-28 15:53:00 +05:30
s_flow = s_flow-1
if (flow(s_flow-1:s_flow-1) == ',') s_flow = s_flow-1
2020-05-22 00:11:40 +05:30
end subroutine dct
!--------------------------------------------------------------------------------------------------
2022-12-02 00:14:53 +05:30
! @brief Decide whether next block is list or dict.
2020-05-22 00:11:40 +05:30
!--------------------------------------------------------------------------------------------------
recursive subroutine decide(blck,flow,s_blck,s_flow,offset)
character(len=*), intent(in) :: blck !< YAML in mixed style
character(len=*), intent(inout) :: flow !< YAML in flow style only
integer, intent(inout) :: s_blck, & !< start position in blck
s_flow, & !< start position in flow
offset
integer :: e_blck
2020-10-06 21:39:53 +05:30
character(len=:), allocatable :: line,flow_line
2020-05-22 00:11:40 +05:30
2022-12-07 22:59:03 +05:30
if (s_blck <= len(blck)) then
call skip_empty_lines(blck,s_blck)
2020-05-22 00:11:40 +05:30
e_blck = s_blck + index(blck(s_blck:),IO_EOL) - 2
2024-02-06 22:04:07 +05:30
line = clean(blck(s_blck:e_blck))
2022-12-07 22:59:03 +05:30
if (trim(line) == '---' .or. trim(line) == '...') then
continue ! end parsing at this point but not stop the simulation
2022-12-07 22:59:03 +05:30
elseif (len_trim(line) == 0) then
2023-06-28 15:53:00 +05:30
s_blck = e_blck + 2
call decide(blck,flow,s_blck,s_flow,offset)
2023-06-28 15:53:00 +05:30
elseif (isListItem(line)) then
2020-05-22 00:11:40 +05:30
flow(s_flow:s_flow) = '['
2023-06-28 15:53:00 +05:30
s_flow = s_flow+1
2020-05-22 00:11:40 +05:30
call lst(blck,flow,s_blck,s_flow,offset)
flow(s_flow:s_flow) = ']'
2023-06-28 15:53:00 +05:30
s_flow = s_flow+1
2022-12-07 22:59:03 +05:30
elseif (isKey(line) .or. isKeyValue(line)) then
2020-05-22 00:11:40 +05:30
flow(s_flow:s_flow) = '{'
2023-06-28 15:53:00 +05:30
s_flow = s_flow+1
2020-05-22 00:11:40 +05:30
call dct(blck,flow,s_blck,s_flow,offset)
flow(s_flow:s_flow) = '}'
2023-06-28 15:53:00 +05:30
s_flow = s_flow+1
2022-12-07 22:59:03 +05:30
elseif (isFlow(line)) then
if (isFlowList(line)) then
2020-10-06 21:39:53 +05:30
call remove_line_break(blck,s_blck,']',flow_line)
2020-10-05 22:23:05 +05:30
else
2020-10-06 21:39:53 +05:30
call remove_line_break(blck,s_blck,'}',flow_line)
end if
2020-05-22 00:11:40 +05:30
call line_isFlow(flow,s_flow,line)
else
line = line(indentDepth(line)+1:)
call line_toFlow(flow,s_flow,line)
2023-06-28 15:53:00 +05:30
s_blck = e_blck + 2
end if
end if
2020-05-22 00:11:40 +05:30
2022-12-02 00:14:53 +05:30
end subroutine decide
2020-05-22 00:11:40 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Convert all block-style parts to flow style.
!> @details The input needs to end with a newline.
2020-05-22 00:11:40 +05:30
!--------------------------------------------------------------------------------------------------
function to_flow(blck)
character(len=:), allocatable :: to_flow
character(len=*), intent(in) :: blck !< YAML mixed style
character(len=:), allocatable :: line
2020-05-22 00:11:40 +05:30
integer :: s_blck, & !< start position in blck
s_flow, & !< start position in flow
offset, & !< counts leading '- ' in nested lists
end_line
allocate(character(len=len(blck)*2)::to_flow)
s_flow = 1
s_blck = 1
offset = 0
2022-12-07 22:59:03 +05:30
if (len_trim(blck) /= 0) then
call skip_empty_lines(blck,s_blck)
call skip_file_header(blck,s_blck)
2024-02-06 22:04:07 +05:30
line = clean(blck(s_blck:s_blck + index(blck(s_blck:),IO_EOL) - 2))
2022-12-07 22:59:03 +05:30
if (trim(line) == '---') s_blck = s_blck + index(blck(s_blck:),IO_EOL)
call decide(blck,to_flow,s_blck,s_flow,offset)
end if
2024-02-06 22:04:07 +05:30
line = clean(blck(s_blck:s_blck+index(blck(s_blck:),IO_EOL)-2))
2022-12-07 22:59:03 +05:30
if (trim(line)== '---') call IO_warning(709,ext_msg=line)
to_flow = trim(to_flow(:s_flow-1))
end_line = index(to_flow,IO_EOL)
2022-12-07 22:59:03 +05:30
if (end_line > 0) to_flow = to_flow(:end_line-1)
2020-05-22 00:11:40 +05:30
end function to_flow
2020-05-25 16:24:43 +05:30
!--------------------------------------------------------------------------------------------------
! @brief Remove comments (characters beyond '#') and trailing space.
!--------------------------------------------------------------------------------------------------
2024-02-06 22:04:07 +05:30
function clean(line)
character(len=*), intent(in) :: line
2024-02-06 22:04:07 +05:30
character(len=:), allocatable :: clean
integer :: split
2024-02-06 22:04:07 +05:30
character, parameter :: COMMENT_CHAR = '#'
2024-02-06 22:04:07 +05:30
split = index(line,COMMENT_CHAR)
if (split == 0) then
2024-02-06 22:04:07 +05:30
clean = trim(line)
else
2024-02-06 22:04:07 +05:30
clean = trim(line(:split-1))
end if
2024-02-06 22:04:07 +05:30
end function clean
2020-05-22 00:11:40 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Check correctness of some YAML functions.
!--------------------------------------------------------------------------------------------------
2023-12-14 10:39:37 +05:30
subroutine YAML_selfTest()
if (indentDepth(' a') /= 1) error stop 'indentDepth'
if (indentDepth('a') /= 0) error stop 'indentDepth'
if (indentDepth('x ') /= 0) error stop 'indentDepth'
2023-06-04 10:47:38 +05:30
if (.not. quotedStr("'a'")) error stop 'quotedStr'
if ( isFlow(' a')) error stop 'isFLow'
if (.not. isFlow('{')) error stop 'isFlow'
if (.not. isFlow(' [')) error stop 'isFlow'
if ( isListItem(' a')) error stop 'isListItem'
if ( isListItem(' -b')) error stop 'isListItem'
if (.not. isListItem('- a ')) error stop 'isListItem'
if (.not. isListItem('- -a ')) error stop 'isListItem'
if ( isKeyValue(' a')) error stop 'isKeyValue'
if ( isKeyValue(' a: ')) error stop 'isKeyValue'
if (.not. isKeyValue(' a: b')) error stop 'isKeyValue'
if ( isKey(' a')) error stop 'isKey'
if ( isKey('{a:b}')) error stop 'isKey'
if ( isKey(' a:b')) error stop 'isKey'
if (.not. isKey(' a: ')) error stop 'isKey'
if (.not. isKey(' a:')) error stop 'isKey'
if (.not. isKey(' a: #')) error stop 'isKey'
2022-12-07 22:59:03 +05:30
if ( isScalar('a: ')) error stop 'isScalar'
if ( isScalar('a: b')) error stop 'isScalar'
if ( isScalar('{a:b}')) error stop 'isScalar'
if ( isScalar('- a:')) error stop 'isScalar'
if (.not. isScalar(' a')) error stop 'isScalar'
2020-05-22 00:11:40 +05:30
basic_list: block
2022-12-07 22:59:03 +05:30
character(len=*), parameter :: block_list = &
" - Casablanca"//IO_EOL//&
" - North by Northwest"//IO_EOL
character(len=*), parameter :: block_list_newline = &
" -"//IO_EOL//&
" Casablanca"//IO_EOL//&
" -"//IO_EOL//&
" North by Northwest"//IO_EOL
character(len=*), parameter :: flow_list = &
"[Casablanca, North by Northwest]"
if (.not. to_flow(block_list) == flow_list) error stop 'to_flow'
if (.not. to_flow(block_list_newline) == flow_list) error stop 'to_flow'
2020-05-22 00:11:40 +05:30
end block basic_list
basic_dict: block
2022-12-07 22:59:03 +05:30
character(len=*), parameter :: block_dict = &
" aa: Casablanca"//IO_EOL//&
" bb: North by Northwest"//IO_EOL
character(len=*), parameter :: block_dict_newline = &
" aa:"//IO_EOL//&
" Casablanca"//IO_EOL//&
" bb:"//IO_EOL//&
" North by Northwest"//IO_EOL
character(len=*), parameter :: flow_dict = &
"{aa: Casablanca, bb: North by Northwest}"
if (.not. to_flow(block_dict) == flow_dict) error stop 'to_flow'
if (.not. to_flow(block_dict_newline) == flow_dict) error stop 'to_flow'
2020-05-22 00:11:40 +05:30
end block basic_dict
only_flow: block
2022-12-07 22:59:03 +05:30
character(len=*), parameter :: flow_dict = &
" {a: [b,c: {d: e}, f: g, e]}"//IO_EOL
character(len=*), parameter :: flow_list = &
" [a,b: c, d,e: {f: g}]"//IO_EOL
character(len=*), parameter :: flow_1 = &
"{a: [b, {c: {d: e}}, {f: g}, e]}"
character(len=*), parameter :: flow_2 = &
"[a, {b: c}, d, {e: {f: g}}]"
if (.not. to_flow(flow_dict) == flow_1) error stop 'to_flow'
if (.not. to_flow(flow_list) == flow_2) error stop 'to_flow'
end block only_flow
2020-05-22 00:11:40 +05:30
basic_flow: block
2022-12-07 22:59:03 +05:30
character(len=*), parameter :: flow_braces = &
" source: [{param: 1}, {param: 2}, {param: 3}, {param: 4}]"//IO_EOL
character(len=*), parameter :: flow_mixed_braces = &
" source: [param: 1, {param: 2}, param: 3, {param: 4}]"//IO_EOL
character(len=*), parameter :: flow = &
"{source: [{param: 1}, {param: 2}, {param: 3}, {param: 4}]}"
if (.not. to_flow(flow_braces) == flow) error stop 'to_flow'
if (.not. to_flow(flow_mixed_braces) == flow) error stop 'to_flow'
2020-05-22 00:11:40 +05:30
end block basic_flow
2020-10-05 22:43:40 +05:30
multi_line_flow1: block
2022-12-07 22:59:03 +05:30
character(len=*), parameter :: flow_multi = &
'%YAML 1.1'//IO_EOL//&
'---'//IO_EOL//&
'a: ["b",'//IO_EOL//&
'c: '//IO_EOL//&
'"d", "e"]'//IO_EOL
2020-10-05 22:43:40 +05:30
2022-12-07 22:59:03 +05:30
character(len=*), parameter :: flow = &
'{a: ["b", {c: "d"}, "e"]}'
2022-12-07 22:59:03 +05:30
if ( .not. to_flow(flow_multi) == flow) error stop 'to_flow'
2020-10-05 22:43:40 +05:30
end block multi_line_flow1
multi_line_flow2: block
2022-12-07 22:59:03 +05:30
character(len=*), parameter :: flow_multi = &
"%YAML 1.1"//IO_EOL//&
"---"//IO_EOL//&
"-"//IO_EOL//&
" a: {b:"//IO_EOL//&
"[c,"//IO_EOL//&
"d"//IO_EOL//&
"e, f]}"//IO_EOL
character(len=*), parameter :: flow = &
"[{a: {b: [c, d e, f]}}]"
if ( .not. to_flow(flow_multi) == flow) error stop 'to_flow'
2020-10-05 22:43:40 +05:30
end block multi_line_flow2
2020-10-05 22:23:05 +05:30
2020-05-22 00:11:40 +05:30
basic_mixed: block
2022-12-07 22:59:03 +05:30
character(len=*), parameter :: block_flow = &
"%YAML 1.1"//IO_EOL//&
" "//IO_EOL//&
" "//IO_EOL//&
"---"//IO_EOL//&
" aa:"//IO_EOL//&
" - "//IO_EOL//&
" "//IO_EOL//&
" "//IO_EOL//&
" param_1: [a: b, c, {d: {e: [f: g, h]}}]"//IO_EOL//&
" - c:d"//IO_EOL//&
" e.f,"//IO_EOL//&
" bb:"//IO_EOL//&
" "//IO_EOL//&
" - "//IO_EOL//&
" {param_1: [{a: b}, c, {d: {e: [{f: g}, h]}}]}"//IO_EOL//&
"..."//IO_EOL
character(len=*), parameter :: mixed_flow = &
'{aa: [{param_1: [{a: b}, c, {d: {e: [{f: g}, h]}}]}, "c:d e.f,"], bb: [{param_1: [{a: b}, c, {d: {e: [{f: g}, h]}}]}]}'
if (.not. to_flow(block_flow) == mixed_flow) error stop 'to_flow'
2020-05-22 00:11:40 +05:30
end block basic_mixed
parse: block
type(tDict), pointer :: dict
type(tList), pointer :: list
character(len=*), parameter :: &
lst = '[1, 2, 3, 4]', &
dct = '{a: 1, b: 2}'
2023-12-14 10:39:37 +05:30
list => YAML_str_asList(lst//IO_EOL)
2023-06-04 10:47:38 +05:30
if (list%asFormattedStr() /= lst) error stop 'str_asList'
2023-12-14 10:39:37 +05:30
dict => YAML_str_asDict(dct//IO_EOL)
2023-06-04 10:47:38 +05:30
if (dict%asFormattedStr() /= dct) error stop 'str_asDict'
end block parse
comment: block
character(len=:), allocatable :: str,out
2024-02-06 22:04:07 +05:30
str='#';out=clean(str)
if (out /= '' .or. len(out) /= 0) error stop 'clean/1'
str=' #';out=clean(str)
if (out /= '' .or. len(out) /= 0) error stop 'clean/2'
str=' # ';out=clean(str)
if (out /= '' .or. len(out) /= 0) error stop 'clean/3'
str=' # a';out=clean(str)
if (out /= '' .or. len(out) /= 0) error stop 'clean/4'
str=' a#';out=clean(str)
if (out /= ' a' .or. len(out) /= 2) error stop 'clean/5'
str=' ab #';out=clean(str)
if (out /= ' ab'.or. len(out) /= 3) error stop 'clean/6'
end block comment
2023-12-14 10:39:37 +05:30
end subroutine YAML_selfTest
#endif
2020-05-22 00:11:40 +05:30
2023-12-14 10:39:37 +05:30
end module YAML