1:- module(md_line, [
    2    merge_lines/2,               % +Lines, -Codes
    3    indent//0,
    4    non_empty_line//1,           % -Codes
    5    discard_to_line_end//0,
    6    empty_lines//0,
    7    empty_line//0,
    8    inline_string//1,            % -Codes
    9    ln_or_eos//0,
   10    ln//0,
   11    string_limit//2,             % -Codes, +Limit
   12    lookahead//1,                % ?Code
   13    lookahead_ln//0,
   14    lookahead_ln_or_eos//0
   15]).

Line-based parsing primitives.

Contains line-based parsing primitives. */

   22:- use_module(library(dcg/basics)).
 merge_lines(+Lines, -Codes) is det
Merges list of lines into a flat code list.
   29merge_lines([], []).
   30
   31merge_lines([Line], Line):- !.
   32
   33merge_lines([Line|Lines], Codes):-
   34    merge_lines(Lines, Merged),
   35    append(Line, [0'\n|Merged], Codes).
 indent// is semidet
Recognizes normal indent which is a tab or 4 spaces.
   42indent --> "\t".
   43indent --> "    ".
 non_empty_line(-Codes)// is semidet
Single non-empty line ending with newline or end-of-stream.
   50non_empty_line([Code|Codes]) -->
   51    [Code], { Code \= 0'\n },
   52    non_empty_line_rest(Codes).
   53
   54non_empty_line_rest([Code|Codes]) -->
   55    [Code], { Code \= 0'\n }, !,
   56    non_empty_line_rest(Codes).
   57
   58non_empty_line_rest([]) -->
   59    "\n", !.
   60
   61non_empty_line_rest([]) -->
   62    "".
 discard_to_line_end// is det
Discards zero or more symbol codes untill the first line end or eos is reached.
   70discard_to_line_end -->
   71    ln_or_eos, !.
   72
   73discard_to_line_end -->
   74    [_], discard_to_line_end.
 empty_lines// is det
List of consequtive empty lines. Consumes as many empty lines as possible.
   82empty_lines -->
   83    eos, !.
   84
   85empty_lines -->
   86    empty_line, !,
   87    empty_lines.
   88
   89empty_lines --> "".
 empty_line// is semidet
Recognizes a single empty line.
   95empty_line -->
   96    whites, ln_or_eos.
 lookahead(?Code)// is semidet
Looks ahead a single symbol code.
  102lookahead(Code), [Code] -->
  103    [Code].
 string_limit(-Codes, +Limit)// is multi
Same as string//1 but with a length limit.
  110string_limit([], Limit) -->
  111    { Limit =< 0 }, !.
  112
  113string_limit([], Limit) -->
  114    { Limit >= 0 }.
  115
  116string_limit([Code|Codes], Limit) -->
  117    [Code],
  118    { Next is Limit - 1 },
  119    string_limit(Codes, Next).
 inline_string(-Codes)// is multi
Takes as few symbol codes as possible up to line end.
  126inline_string([]) --> "".
  127
  128inline_string([]) -->
  129    lookahead_ln, !.
  130
  131inline_string([Code|Codes]) -->
  132    [Code],
  133    inline_string(Codes).
 lookahead_ln_or_eos// is semidet
Looks ahead a line end or end-of-stream. Puts back \n when a line end is recognized.
  141lookahead_ln_or_eos -->
  142    lookahead_ln, !.
  143
  144lookahead_ln_or_eos -->
  145    eos.
 lookahead_ln// is semidet
Looks ahead a line end. Puts back \n when it is recognized.
  152lookahead_ln, "\n" --> ln.
 ln_or_eos// is semidet
Recognizes either a line end or eos.
  159ln_or_eos -->
  160    "\n", !.
  161
  162ln_or_eos -->
  163    eos.
 ln// is semidet
Recognizes line ending.
  169ln --> "\n"