1:- module(md_list_item, [
    2    md_bullet_list_item//2, % -Codes
    3    md_ordered_list_item//2 % -Codes
    4]).

List item parser

Parser for items of bulleted and ordered lists. Separated into its own module for code clarity. */

   12:- use_module(library(dcg/basics)).   13:- use_module(md_line).   14:- use_module(md_hr).
 md_bullet_list_item(+Codes, -Mode)// is det
Recognizes a single bulleted list item.
   20% Lookahead for horisontal ruler prevents
   21% recognizing * * * as a list item.
   22
   23md_bullet_list_item(Codes, Mode) -->
   24    (   md_lookahead_hr
   25    ->  { fail }
   26    ;   bullet_start(Indent, _), whites, !,
   27        list_item_unintented(Indent, Codes, Mode)).
 md_ordered_list_item(-Codes, -Mode)// is det
Recognizes a single ordered list item.
   33md_ordered_list_item(Codes, Mode) -->
   34    ordered_start(Indent, _), whites, !,
   35    list_item_unintented(Indent, Codes, Mode).
   36
   37% Bulleted-list item start.
   38% Gives codes that make up the start.
   39
   40bullet_start(Indent, Codes) -->
   41    item_indent(Indent),
   42    list_bullet(Bullet),
   43    marker_follow(Follow),
   44    { flatten([Indent, Bullet, Follow], Codes) }.
   45
   46% Ordered-list item start.
   47% Gives codes that make up the start.
   48
   49ordered_start(Indent, Codes) -->
   50    item_indent(Indent),
   51    one_or_more_digits(Number), ".",
   52    marker_follow(Follow),
   53    { flatten([Indent, Number, [0'.|Follow]], Codes) }.
   54
   55% Looks ahead an item start.
   56% Used for detecting where the
   57% previous list item ends.
   58
   59lookahead_item_start(Indent), Codes -->
   60    item_start(Indent, Codes).
   61
   62item_start(Indent, Codes) -->
   63    bullet_start(Indent, Codes), !.
   64
   65item_start(Indent, Codes) -->
   66    ordered_start(Indent, Codes).
   67
   68% List bullet might be indented
   69% with up to 3 spaces.
   70
   71item_indent([0' ,0' ,0' ]) --> "   ".
   72item_indent([0' ,0' ]) --> "  ".
   73item_indent([0' ]) --> " ".
   74item_indent([]) --> "".
   75
   76% List item marker must be followed
   77% by a space or tab.
   78
   79marker_follow([0' ]) --> " ".
   80marker_follow([0'\t]) --> "\t".
   81
   82% Sames as list_item_text but
   83% removes possible indentation.
   84
   85list_item_unintented(Indent, Codes, Mode) -->
   86    list_item_text(Indent, Indented, Mode), !,
   87    {
   88        (   phrase(find_indent(BodyIndent), Indented, _)
   89        ->  phrase(strip_indent(BodyIndent, Codes), Indented)
   90        ;   Codes = Indented)
   91    }.
   92
   93% Recognizes list item body and mode.
   94% Mode can be either normal or para.
   95% This is implemented by recognizing
   96% end conditions first.
   97
   98list_item_text(Indent, [], Mode) -->
   99    list_item_end(Indent, Mode), !.
  100
  101% Other cases, just consume input.
  102
  103list_item_text(Indent, [Code|Codes], Mode) -->
  104    [Code], list_item_text(Indent, Codes, Mode).
  105
  106% Recognizes list item end and
  107% item mode.
  108
  109list_item_end(_, normal) -->
  110    eos.
  111
  112% Item and next item are separated
  113% with an empty line.
  114
  115list_item_end(Indent, para) -->
  116    ln, empty_line,
  117    lookahead_item_start(StartIndent),
  118    {
  119        length(Indent, I),
  120        length(StartIndent, S),
  121        S =< I
  122    }.
  123
  124% No empty line before next item.
  125
  126list_item_end(Indent, normal) -->
  127    ln, lookahead_item_start(StartIndent),
  128    {
  129        length(Indent, I),
  130        length(StartIndent, S),
  131        S =< I
  132    }.
  133
  134% Next line is horisontal ruler.
  135
  136list_item_end(_, normal) -->
  137    ln, md_lookahead_hr.
  138
  139% Empty line and next line has
  140% no indent.
  141
  142list_item_end(_, normal) -->
  143    ln, empty_line, lookahead_no_indent.
  144
  145% Looks ahead non-indented line begin.
  146
  147lookahead_no_indent -->
  148    lookahead_no_white.
  149
  150lookahead_no_white, [Code] -->
  151    [Code], { \+ code_type(Code, white) }.
  152
  153% Recognizes bulleted list item
  154% token.
  155
  156list_bullet(0'*) --> "*".
  157list_bullet(0'-) --> "-".
  158list_bullet(0'+) --> "+".
  159
  160% Recognizes sequence of
  161% one or more digits. Used for
  162% recognizing ordered list items.
  163
  164one_or_more_digits([Digit]) -->
  165    digit(Digit).
  166
  167one_or_more_digits([Digit|Digits]) -->
  168    digit(Digit),
  169    one_or_more_digits(Digits).
  170
  171% Detects indent from the second
  172% line.
  173
  174find_indent(Indent) -->
  175    non_empty_line(_),
  176    detect_indent(Indent).
  177
  178detect_indent([0'\t]) --> "\t".
  179
  180detect_indent([0' ,0' ,0' ,0' ]) --> "    ".
  181
  182detect_indent([0' ,0' ,0' ]) --> "   ".
  183
  184detect_indent([0' ,0' ]) --> "  ".
  185
  186detect_indent([0' ]) --> " ".
  187
  188detect_indent([]) --> "".
  189
  190% Strips indent
  191% from line beginnings.
  192
  193strip_indent(BodyIndent, Codes) -->
  194    strip_indent_begin(BodyIndent, Codes).
  195
  196strip_indent_begin(BodyIndent, Codes) -->
  197    strip_line_indent(BodyIndent), !,
  198    strip_rest_indent(BodyIndent, Codes).
  199
  200strip_indent_begin(BodyIndent, Codes) -->
  201    strip_rest_indent(BodyIndent, Codes).
  202
  203strip_rest_indent(BodyIndent, [0'\n|Codes]) -->
  204    ln, strip_line_indent(BodyIndent), !,
  205    strip_rest_indent(BodyIndent, Codes).
  206
  207strip_rest_indent(BodyIndent, [Code|Codes]) -->
  208    [Code], !, strip_rest_indent(BodyIndent, Codes).
  209
  210strip_rest_indent(_, []) -->
  211    eos.
  212
  213% Strip a tab when the target indent
  214% was also a tab.
  215
  216strip_line_indent([0'\t]) --> "\t".
  217
  218% Strip a tab when the target indent
  219% was 4 spaces.
  220
  221strip_line_indent([0' ,0' ,0' ,0' ]) --> "\t".
  222
  223% Strip 4 spaces when the target indent
  224% was 4 spaces.
  225
  226strip_line_indent([0' ,0' ,0' ,0' ]) --> "    ".
  227
  228% Strip 4 spaces when the target indent
  229% was a tab.
  230
  231strip_line_indent([0'\t]) --> "    ".
  232
  233% Strip 3 spaces when the target indent
  234% was at least 3 spaces.
  235
  236strip_line_indent([0' ,0' ,0' |_]) --> "   ".
  237
  238% Strip 2 spaces when the target indent
  239% was 2 spaces.
  240
  241strip_line_indent([0' ,0' |_]) --> "  ".
  242
  243% Strip a space when the target indent
  244% was at least 1 space.
  245
  246strip_line_indent([0' |_]) --> " "