Skip to content

Commit

Permalink
Decimal Ordered Lists
Browse files Browse the repository at this point in the history
  • Loading branch information
aarroyoc committed Mar 17, 2023
1 parent 45551fd commit 0fbbffa
Show file tree
Hide file tree
Showing 2 changed files with 36 additions and 18 deletions.
40 changes: 28 additions & 12 deletions djota.pl
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
:- use_module(library(pio)).
:- use_module(library(lists)).
:- use_module(library(dif)).
:- use_module(library(charsio)).

% Block syntax

Expand Down Expand Up @@ -85,13 +86,13 @@
[code(Spec, Code0, Attrs)].

% List: Line of list type same as current list
djot_list_ast_(type(Level, Type, Mode), [Line|Lines], CurrentItem, Items, _, Attrs) -->
djot_list_ast_(type(Level, Type, Mode, OrdStart), [Line|Lines], CurrentItem, Items, _, Attrs) -->
{
phrase(list_line(type(Level, Type, _), Text), Line),
phrase(list_line(type(Level, Type, _, _), Text), Line),
djot_ast(CurrentItem, ItemAst),
append(Items, [item(ItemAst)], NewItems)
},
djot_list_ast_(type(Level, Type, Mode), Lines, Text, NewItems, continue, Attrs).
djot_list_ast_(type(Level, Type, Mode, OrdStart), Lines, Text, NewItems, continue, Attrs).
% List: Line non indented in continue mode
djot_list_ast_(Type, [Line|Lines], CurrentItem, Items, continue, Attrs) -->
{
Expand All @@ -101,31 +102,31 @@
},
djot_list_ast_(Type, Lines, CurrentItem1, Items, continue, Attrs).
% List: Empty line
djot_list_ast_(type(Level, Type, _), [Line|Lines], CurrentItem, Items, _, Attrs) -->
djot_list_ast_(type(Level, Type, _, OrdStart), [Line|Lines], CurrentItem, Items, _, Attrs) -->
{
phrase(whites(_), Line),
append(CurrentItem, ['\n'|Line], CurrentItem1)
},
djot_list_ast_(type(Level, Type, loose), Lines, CurrentItem1, Items, jump, Attrs).
djot_list_ast_(type(Level, Type, loose, OrdStart), Lines, CurrentItem1, Items, jump, Attrs).

% List: Line indented in jump mode
djot_list_ast_(type(Level, Type, Mode), [Line|Lines], CurrentItem, Items, jump, Attrs) -->
djot_list_ast_(type(Level, Type, Mode, OrdStart), [Line|Lines], CurrentItem, Items, jump, Attrs) -->
{
phrase((whites(W), seq(Text)), Line),
W > Level,
append(CurrentItem, ['\n'|Text], CurrentItem1)
},
djot_list_ast_(type(Level, Type, Mode), Lines, CurrentItem1, Items, jump, Attrs).
djot_list_ast_(type(Level, Type, Mode, OrdStart), Lines, CurrentItem1, Items, jump, Attrs).

% List: Line not indented in jump mode
djot_list_ast_(type(Level, Type, Mode), [Line|Lines], CurrentItem, Items, jump, Attrs) -->
djot_list_ast_(type(Level, Type, Mode, OrdStart), [Line|Lines], CurrentItem, Items, jump, Attrs) -->
{
phrase((whites(W), seq(_)), Line),
W =< Level,
djot_ast(CurrentItem, ItemAst),
append(Items, [item(ItemAst)], NewItems)
},
[list(type(Level, Type, Mode), NewItems, Attrs)],
[list(type(Level, Type, Mode, OrdStart), NewItems, Attrs)],
djot_ast_([Line|Lines], []).

% List: No more lines
Expand All @@ -140,8 +141,13 @@
list_type(bullet("-")) --> "-".
list_type(bullet("*")) --> "*".
list_type(bullet("+")) --> "+".
list_line(type(Level, Type, tight), Text) -->
whites(Level), list_type(Type), " ", seq(Text).
list_type(decimal(".", N)) --> number_(N), ".".
list_type(decimal(")", N)) --> number_(N), ")".
list_type(decimal("()", N)) --> "(", number_(N), ")".
list_line(type(Level, bullet(BulletType), tight, ""), Text) -->
whites(Level), list_type(bullet(BulletType)), " ", seq(Text).
list_line(type(Level, decimal(DecimalType), tight, OrdStart), Text) -->
whites(Level), list_type(decimal(DecimalType, OrdStart)), " ", seq(Text).

whites(0) --> "".
whites(N) -->
Expand Down Expand Up @@ -372,11 +378,16 @@
{ phrase(ast_html_(Child), ChildHtml) },
{ attrs_html(Attrs, AttrsHtml) },
"<blockquote", AttrsHtml, ">", ChildHtml, "</blockquote>".
ast_html_node_(list(type(_, bullet(_), Mode), Items, Attrs)) -->
ast_html_node_(list(type(_, bullet(_), Mode, _), Items, Attrs)) -->
{ attrs_html(Attrs, AttrsHtml) },
"<ul", AttrsHtml, ">",
ast_html_node_items_(Items, Mode),
"</ul>".
ast_html_node_(list(type(_, decimal(_), Mode, OrdStart), Items, Attrs)) -->
{ attrs_html(["start"-OrdStart|Attrs], AttrsHtml) },
"<ol", AttrsHtml, ">",
ast_html_node_items_(Items, Mode),
"</ol>".
ast_html_node_(code(Spec, Code, Attrs)) -->
{ dif(Spec, "=html"), phrase(escape_html_(Html), Code) },
{ attrs_html(Attrs, AttrsHtml) },
Expand Down Expand Up @@ -814,3 +825,8 @@


look_ahead(T), [T] --> [T].

number_([D|Ds]) --> digit(D), number_(Ds).
number_([D]) --> digit(D).

digit(D) --> [D], { char_type(D, decimal_digit) }.
14 changes: 8 additions & 6 deletions test.lgt
Original file line number Diff line number Diff line change
Expand Up @@ -79,14 +79,16 @@ test(blockquote) :-
djota:djot("> This is a block quote.\nAnd lazy", "<blockquote><p>This is a block quote. And lazy</p></blockquote>").

test(list_ast) :-
djota:djot_ast("- Hola", [list(type(0, bullet("-"), tight),[item([paragraph([str("Hola")], [])])], [])]),
djota:djot_ast("- Hola\n- Adios", [list(type(0,bullet("-"),tight),[item([paragraph([str("Hola")],[])]),item([paragraph([str("Adios")],[])])],[])]),
djota:djot_ast("- Hola\namigos\n- Adios\namigos", [list(type(0,bullet("-"),tight),[item([paragraph([str("Hola amigos")], [])]),item([paragraph([str("Adios amigos")], [])])], [])]),
djota:djot_ast("- Hola\namigos\n\n- Adios\namigos", [list(type(0,bullet("-"),loose),[item([paragraph([str("Hola amigos")], [])]),item([paragraph([str("Adios amigos")], [])])], [])]),
djota:djot_ast("- Hola\namigos\n\n - Sublist\n- Adios\namigos", [list(type(0, bullet("-"), loose),[item([paragraph([str("Hola amigos")], []),list(type(0, bullet("-"), tight),[item([paragraph([str("Sublist")], [])])], [])]),item([paragraph([str("Adios amigos")], [])])], [])]).
djota:djot_ast("- Hola", [list(type(0, bullet("-"), tight,""),[item([paragraph([str("Hola")], [])])], [])]),
djota:djot_ast("- Hola\n- Adios", [list(type(0,bullet("-"),tight,""),[item([paragraph([str("Hola")],[])]),item([paragraph([str("Adios")],[])])],[])]),
djota:djot_ast("- Hola\namigos\n- Adios\namigos", [list(type(0,bullet("-"),tight,""),[item([paragraph([str("Hola amigos")], [])]),item([paragraph([str("Adios amigos")], [])])], [])]),
djota:djot_ast("- Hola\namigos\n\n- Adios\namigos", [list(type(0,bullet("-"),loose,""),[item([paragraph([str("Hola amigos")], [])]),item([paragraph([str("Adios amigos")], [])])], [])]),
djota:djot_ast("- Hola\namigos\n\n - Sublist\n- Adios\namigos", [list(type(0, bullet("-"), loose,""),[item([paragraph([str("Hola amigos")], []),list(type(0, bullet("-"), tight,""),[item([paragraph([str("Sublist")], [])])], [])]),item([paragraph([str("Adios amigos")], [])])], [])]),
djota:djot_ast("3. Hola\n7. Adios", [list(type(0,decimal("."),tight,"3"),[item([paragraph([str("Hola")],[])]),item([paragraph([str("Adios")],[])])],[])]).

test(list) :-
djota:djot("- Hola\namigos\n\n - Sublist\n- Adios\namigos", "<ul><li><p>Hola amigos</p><ul><li>Sublist</li></ul></li><li><p>Adios amigos</p></li></ul>").
djota:djot("- Hola\namigos\n\n - Sublist\n- Adios\namigos", "<ul><li><p>Hola amigos</p><ul><li>Sublist</li></ul></li><li><p>Adios amigos</p></li></ul>"),
djota:djot("3. Hola\n7. Adios", "<ol start=\"3\"><li>Hola</li><li>Adios</li></ol>").

test(code_block) :-
djota:djot("````\nThis is how you do a code block:\n\n``` ruby\nx = 5 * 6\n```\n````", "<pre><code>\nThis is how you do a code block:\n\n``` ruby\nx = 5 * 6\n```</pre></code>"),
Expand Down

0 comments on commit 0fbbffa

Please sign in to comment.