1:- module(md_links, [
    2    md_links/3, % +CodesIn, -CodesOut, -Links
    3    md_links/2, % +CodesIn, -CodesOut,
    4    md_link/3   % ?Id, ?Url, ?Title
    5]).

Markdown reference link parser

Parses and removes reference links from the stream of symbol codes. Replaces line ends with canonical line ends. */

   14:- use_module(library(dcg/basics)).   15:- use_module(md_line).   16
   17% link_definition(Id, Url, Title).
   18
   19:- thread_local(link_definition/3).
 md_link(?Id, ?Url, ?Title) is det
Retrieves recorded link from the last invocation of md_links/2.
   26md_link(Id, Url, Title):-
   27    link_definition(Id, Url, Title).
 md_links(+CodesIn, -CodesOut) is det
Same as md_links/3 but stores links in threadlocal predicate which is cleared on each invocation of this predicate.
   35md_links(CodesIn, CodesOut):-
   36    retractall(link_definition(_, _, _)),
   37    md_links(CodesIn, CodesOut, Links),
   38    maplist(assert_link, Links).
   39
   40assert_link(link(Id, Url, Title)):-
   41    assertz(link_definition(Id, Url, Title)).
 md_links(+CodesIn, -CodesOut, -Links) is det
Markdown reference link definition parser. Removes link definitions from the symbol code list.
   48md_links(CodesIn, CodesOut, Links):-
   49    phrase(links_begin(TmpCodes, TmpLinks), CodesIn),
   50    CodesOut = TmpCodes,
   51    Links = TmpLinks.
   52
   53links_begin(Codes, [Link|Links]) -->
   54    link(Link), !, links(Codes, Links).
   55
   56links_begin(Codes, Links) -->
   57    links(Codes, Links).
   58
   59links([Code|Codes], Links) -->
   60    [Code], { \+code_type(Code, end_of_line) }, !,
   61    links(Codes, Links).
   62
   63links(Codes, [Link|Links]) -->
   64    ln_full, link(Link), !, links(Codes, Links).
   65
   66links([0'\n|Codes], Links) -->
   67    ln_full, !, links(Codes, Links).
   68
   69links([], []) --> eos, !.
   70
   71ln_full --> "\r\n", !.
   72ln_full --> "\n", !.
   73ln_full --> "\r".
   74
   75% Recognizes a reference link definition.
   76% Example: [foo]: http://example.com/ "Optional Title Here"
   77% Records the link but outputs nothing.
   78
   79link(link(Id, Url, Title)) -->
   80    link_indent, link_id(Id),
   81    whites, link_url(Url),
   82    whites, link_title(Title).
   83
   84% Link might be indented with
   85% up to 3 spaces. More info:
   86% http://daringfireball.net/projects/markdown/syntax#link
   87
   88link_indent --> "   ".
   89link_indent --> "  ".
   90link_indent --> " ".
   91link_indent --> "".
   92
   93% Recognizes a link title.
   94% When no title is found, Title is
   95% an empty atom ('').
   96
   97link_title(Title) -->
   98    link_title_same_line(Title), !.
   99
  100link_title(Title) -->
  101    ln_full, whites, link_title_same_line(Title), !.
  102
  103link_title('') --> "".
  104
  105link_title_same_line(Title) -->
  106    "'", !, inline_string(Codes), "'",
  107    whites, lookahead_ln_or_eos,
  108    { atom_codes(Title, Codes) }.
  109
  110link_title_same_line(Title) -->
  111    "(", !, inline_string(Codes), ")",
  112    whites, lookahead_ln_or_eos,
  113    { atom_codes(Title, Codes) }.
  114
  115link_title_same_line(Title) -->
  116    "\"", inline_string(Codes), "\"",
  117    whites, lookahead_ln_or_eos,
  118    { atom_codes(Title, Codes) }.
  119
  120% Recognizes a link identifier.
  121
  122link_id(Id) -->
  123    "[", whites, inline_string(Codes), whites, "]:",
  124    {
  125        atom_codes(Tmp, Codes),
  126        downcase_atom(Tmp, Id)
  127    }.
  128
  129% Recognizes a link URL.
  130
  131link_url(Url) -->
  132    "<", !, inline_string(Codes), ">",
  133    { atom_codes(Url, Codes) }.
  134
  135link_url(Url) -->
  136    string_without([0'\n, 0'\t, 0' ], Codes),
  137    { atom_codes(Url, Codes) }