1:- module(util, [
    2                 read_yaml/2,       % +FilePath, -YAML
    3                 write_yaml/2       % +FilePath, +YAML
    4                ]).

YAML file helper.

author
- Hongxin Liang
license
- Apache License Version 2.0 */
   12:- use_module(library(readutil)).
 read_yaml(+Source, -YAML) is semidet
Read YAML file specified by Source where Source could be a file path or an atom representing raw YAML with all the comments not being filtered out. Output YAML will have all the comments been removed.

Source could be:

   25read_yaml(atom(Atom), YAML) :-
   26    setup_call_cleanup(open_string(Atom, Stream),
   27                       read_yaml0(Stream, [], YAML),
   28                       close(Stream)).
   29
   30read_yaml(file(FilePath), YAML) :-
   31    setup_call_cleanup(open(FilePath, read, Stream),
   32                       read_yaml0(Stream, [], YAML),
   33                       close(Stream)).
   34
   35read_yaml0(Stream, YAML0, YAML) :-
   36    read_line_to_codes(Stream, Codes),
   37    (   Codes = end_of_file
   38    ->  YAML = YAML0
   39    ;   (   \+ first_non_space_code(Codes, 35)
   40        ->  maplist(char_code, Line, Codes),
   41            append(YAML0, ['\n'|Line], YAML1),
   42            read_yaml0(Stream, YAML1, YAML)
   43        ;   read_yaml0(Stream, YAML0, YAML)
   44        )
   45    ).
 write_yaml(+FilePath, +YAML) is semidet
Write YAML atom to file specified by FilePath.
   51write_yaml(FilePath, YAML) :-
   52    open(FilePath, write, Stream),
   53    write(Stream, '# generated by prolog yaml pack\n'),
   54    write(Stream, YAML),
   55    close(Stream).
   56
   57first_non_space_code([], _) :- !, false.
   58first_non_space_code([H|T], Code) :-
   59    (   H = 32
   60    ->  first_non_space_code(T, Code)
   61    ;   H = Code
   62    )