diff options
Diffstat (limited to 'lib')
-rw-r--r-- | lib/packages/docutils/rst.nim | 392 | ||||
-rw-r--r-- | lib/packages/docutils/rstast.nim | 11 | ||||
-rw-r--r-- | lib/packages/docutils/rstgen.nim | 49 |
3 files changed, 417 insertions, 35 deletions
diff --git a/lib/packages/docutils/rst.nim b/lib/packages/docutils/rst.nim index a79242c39..c130ec3fd 100644 --- a/lib/packages/docutils/rst.nim +++ b/lib/packages/docutils/rst.nim @@ -17,9 +17,12 @@ ## A few `extra features`_ of the `Markdown`:idx: syntax are ## also supported. ## -## Nim can output the result to HTML (commands ``nim doc`` for -## ``*.nim`` files and ``nim rst2html`` for ``*.rst`` files) or -## Latex (command ``nim rst2tex`` for ``*.rst``). +## Nim can output the result to HTML [#html]_ or Latex [#latex]_. +## +## .. [#html] commands ``nim doc`` for ``*.nim`` files and +## ``nim rst2html`` for ``*.rst`` files +## +## .. [#latex] command ``nim rst2tex`` for ``*.rst``. ## ## If you are new to RST please consider reading the following: ## @@ -39,6 +42,8 @@ ## + bullet lists using \+, \*, \- ## + enumerated lists using arabic numerals or alphabet ## characters: 1. ... 2. ... *or* a. ... b. ... *or* A. ... B. ... +## + footnotes (including manually numbered, auto-numbered, auto-numbered +## with label, and auto-symbol footnotes) and citations ## + definition lists ## + field lists ## + option lists @@ -67,11 +72,16 @@ ## ## Additional Nim-specific features: ## -## * directives: ``code-block``, ``title``, ``index`` +## * directives: ``code-block`` [cmp:Sphinx]_, ``title``, +## ``index`` [cmp:Sphinx]_ +## ## * ***triple emphasis*** (bold and italic) using \*\*\* ## * ``:idx:`` role for \`interpreted text\` to include the link to this ## text into an index (example: `Nim index`_). ## +## .. [cmp:Sphinx] similar but different from the directives of +## Python `Sphinx directives`_ extensions +## ## .. _`extra features`: ## ## Optional additional features, turned on by ``options: RstParseOption`` in @@ -107,7 +117,6 @@ ## ``header``, ``footer``, ``meta``, ``class`` ## - no ``role`` directives and no custom interpreted text roles ## - some standard roles are not supported (check `RST roles list`_) -## - no footnotes & citations support ## * inline markup ## - no simple-inline-markup ## - no embedded aliases @@ -130,9 +139,10 @@ ## .. _RST directives list: https://docutils.sourceforge.io/docs/ref/rst/directives.html ## .. _RST roles list: https://docutils.sourceforge.io/docs/ref/rst/roles.html ## .. _Nim index: https://nim-lang.org/docs/theindex.html +## .. _Sphinx directives: https://www.sphinx-doc.org/en/master/usage/restructuredtext/directives.html import - os, strutils, rstast + os, strutils, rstast, algorithm, lists, sequtils type RstParseOption* = enum ## options for the RST parser @@ -158,6 +168,7 @@ type meNewSectionExpected = "new section expected", meGeneralParseError = "general parse error", meInvalidDirective = "invalid directive: '$1'", + meFootnoteMismatch = "mismatch in number of footnotes and their refs: $1", mwRedefinitionOfLabel = "redefinition of label '$1'", mwUnknownSubstitution = "unknown substitution '$1'", mwUnsupportedLanguage = "language '$1' not supported", @@ -405,6 +416,19 @@ type AnchorSubst = tuple mainAnchor: string aliases: seq[string] + FootnoteType = enum + fnManualNumber, # manually numbered footnote like [3] + fnAutoNumber, # auto-numbered footnote [#] + fnAutoNumberLabel, # auto-numbered with label [#label] + fnAutoSymbol, # auto-symbol footnote [*] + fnCitation # simple text label like [citation2021] + FootnoteSubst = tuple + kind: FootnoteType # discriminator + number: int # valid for fnManualNumber (always) and fnAutoNumber, + # fnAutoNumberLabel after resolveSubs is called + autoNumIdx: int # order of occurence: fnAutoNumber, fnAutoNumberLabel + autoSymIdx: int # order of occurence: fnAutoSymbol + label: string # valid for fnAutoNumberLabel SharedState = object options: RstParseOptions # parsing options @@ -412,6 +436,12 @@ type subs: seq[Substitution] # substitutions refs: seq[Substitution] # references anchors: seq[AnchorSubst] # internal target substitutions + lineFootnoteNum: seq[int] # footnote line, auto numbers .. [#] + lineFootnoteNumRef: seq[int] # footnote line, their reference [#]_ + lineFootnoteSym: seq[int] # footnote line, auto symbols .. [*] + lineFootnoteSymRef: seq[int] # footnote line, their reference [*]_ + footnotes: seq[FootnoteSubst] # correspondence b/w footnote label, + # number, order of occurrence underlineToLevel: LevelMap # Saves for each possible title adornment # character its level in the # current document. @@ -470,13 +500,15 @@ proc newSharedState(options: RstParseOptions, result.msgHandler = if not isNil(msgHandler): msgHandler else: defaultMsgHandler result.findFile = if not isNil(findFile): findFile else: defaultFindFile +proc curLine(p: RstParser): int = p.line + currentTok(p).line + proc findRelativeFile(p: RstParser; filename: string): string = result = p.filename.splitFile.dir / filename if not fileExists(result): result = p.s.findFile(filename) proc rstMessage(p: RstParser, msgKind: MsgKind, arg: string) = - p.s.msgHandler(p.filename, p.line + currentTok(p).line, + p.s.msgHandler(p.filename, curLine(p), p.col + currentTok(p).col, msgKind, arg) proc rstMessage(p: RstParser, msgKind: MsgKind, arg: string, line, col: int) = @@ -484,7 +516,7 @@ proc rstMessage(p: RstParser, msgKind: MsgKind, arg: string, line, col: int) = p.col + col, msgKind, arg) proc rstMessage(p: RstParser, msgKind: MsgKind) = - p.s.msgHandler(p.filename, p.line + currentTok(p).line, + p.s.msgHandler(p.filename, curLine(p), p.col + currentTok(p).col, msgKind, currentTok(p).symbol) @@ -630,6 +662,122 @@ proc findMainAnchor(p: RstParser, refn: string): string = if toLeave: break +proc addFootnoteNumManual(p: var RstParser, num: int) = + ## add manually-numbered footnote + for fnote in p.s.footnotes: + if fnote.number == num: + rstMessage(p, mwRedefinitionOfLabel, $num) + return + p.s.footnotes.add((fnManualNumber, num, -1, -1, $num)) + +proc addFootnoteNumAuto(p: var RstParser, label: string) = + ## add auto-numbered footnote. + ## Empty label [#] means it'll be resolved by the occurrence. + if label == "": # simple auto-numbered [#] + p.s.lineFootnoteNum.add curLine(p) + p.s.footnotes.add((fnAutoNumber, -1, p.s.lineFootnoteNum.len, -1, label)) + else: # auto-numbered with label [#label] + for fnote in p.s.footnotes: + if fnote.label == label: + rstMessage(p, mwRedefinitionOfLabel, label) + return + p.s.footnotes.add((fnAutoNumberLabel, -1, -1, -1, label)) + +proc addFootnoteSymAuto(p: var RstParser) = + p.s.lineFootnoteSym.add curLine(p) + p.s.footnotes.add((fnAutoSymbol, -1, -1, p.s.lineFootnoteSym.len, "")) + +proc orderFootnotes(p: var RstParser) = + ## numerate auto-numbered footnotes taking into account that all + ## manually numbered ones always have preference. + ## Save the result back to p.s.footnotes. + + # Report an error if found any mismatch in number of automatic footnotes + proc listFootnotes(lines: seq[int]): string = + result.add $lines.len & " (lines " & join(lines, ", ") & ")" + if p.s.lineFootnoteNum.len != p.s.lineFootnoteNumRef.len: + rstMessage(p, meFootnoteMismatch, + "$1 != $2" % [listFootnotes(p.s.lineFootnoteNum), + listFootnotes(p.s.lineFootnoteNumRef)] & + " for auto-numbered footnotes") + if p.s.lineFootnoteSym.len != p.s.lineFootnoteSymRef.len: + rstMessage(p, meFootnoteMismatch, + "$1 != $2" % [listFootnotes(p.s.lineFootnoteSym), + listFootnotes(p.s.lineFootnoteSymRef)] & + " for auto-symbol footnotes") + + var result: seq[FootnoteSubst] + var manuallyN, autoN, autoSymbol: seq[FootnoteSubst] + for fs in p.s.footnotes: + if fs.kind == fnManualNumber: manuallyN.add fs + elif fs.kind in {fnAutoNumber, fnAutoNumberLabel}: autoN.add fs + else: autoSymbol.add fs + + if autoN.len == 0: + result = manuallyN + else: + # fill gaps between manually numbered footnotes in ascending order + manuallyN.sort() # sort by number - its first field + var lst = initSinglyLinkedList[FootnoteSubst]() + for elem in manuallyN: lst.append(elem) + var firstAuto = 0 + if lst.head == nil or lst.head.value.number != 1: + # no manual footnote [1], start numeration from 1 for auto-numbered + lst.prepend (autoN[0].kind, 1, autoN[0].autoNumIdx, -1, autoN[0].label) + firstAuto = 1 + var curNode = lst.head + var nextNode: SinglyLinkedNode[FootnoteSubst] + # go simultaneously through `autoN` and `lst` looking for gaps + for (kind, x, autoNumIdx, y, label) in autoN[firstAuto .. ^1]: + while (nextNode = curNode.next; nextNode != nil): + if nextNode.value.number - curNode.value.number > 1: + # gap found, insert new node `n` between curNode and nextNode: + var n = newSinglyLinkedNode((kind, curNode.value.number + 1, + autoNumIdx, -1, label)) + curNode.next = n + n.next = nextNode + curNode = n + break + else: + curNode = nextNode + if nextNode == nil: # no gap found, just append + lst.append (kind, curNode.value.number + 1, autoNumIdx, -1, label) + curNode = lst.tail + result = lst.toSeq + + # we use ASCII symbols instead of those recommended in RST specification: + const footnoteAutoSymbols = ["*", "^", "+", "=", "~", "$", "@", "%", "&"] + for fs in autoSymbol: + # assignment order: *, **, ***, ^, ^^, ^^^, ... &&&, ****, *****, ... + let i = fs.autoSymIdx - 1 + let symbolNum = (i div 3) mod footnoteAutoSymbols.len + let nSymbols = (1 + i mod 3) + 3 * (i div (3 * footnoteAutoSymbols.len)) + let label = footnoteAutoSymbols[symbolNum].repeat(nSymbols) + result.add((fs.kind, -1, -1, fs.autoSymIdx, label)) + + p.s.footnotes = result + +proc getFootnoteNum(p: var RstParser, label: string): int = + ## get number from label. Must be called after `orderFootnotes`. + result = -1 + for fnote in p.s.footnotes: + if fnote.label == label: + return fnote.number + +proc getFootnoteNum(p: var RstParser, order: int): int = + ## get number from occurrence. Must be called after `orderFootnotes`. + result = -1 + for fnote in p.s.footnotes: + if fnote.autoNumIdx == order: + return fnote.number + +proc getAutoSymbol(p: var RstParser, order: int): string = + ## get symbol from occurrence of auto-symbol footnote. + result = "???" + for fnote in p.s.footnotes: + if fnote.autoSymIdx == order: + return fnote.label + proc newRstNodeA(p: var RstParser, kind: RstNodeKind): PRstNode = ## create node and consume the current anchor result = newRstNode(kind) @@ -968,7 +1116,60 @@ proc parseMarkdownLink(p: var RstParser; father: PRstNode): bool = p.idx = i result = true +proc getFootnoteType(label: PRstNode): (FootnoteType, int) = + if label.sons.len >= 1 and label.sons[0].kind == rnLeaf and + label.sons[0].text == "#": + if label.sons.len == 1: + result = (fnAutoNumber, -1) + else: + result = (fnAutoNumberLabel, -1) + elif label.len == 1 and label.sons[0].kind == rnLeaf and + label.sons[0].text == "*": + result = (fnAutoSymbol, -1) + elif label.len == 1 and label.sons[0].kind == rnLeaf: + try: + result = (fnManualNumber, parseInt(label.sons[0].text)) + except: + result = (fnCitation, -1) + else: + result = (fnCitation, -1) + +proc validRefnamePunct(x: string): bool = + ## https://docutils.sourceforge.io/docs/ref/rst/restructuredtext.html#reference-names + x.len == 1 and x[0] in {'-', '_', '.', ':', '+'} + +proc parseFootnoteName(p: var RstParser, reference: bool): PRstNode = + ## parse footnote/citation label. Precondition: start at `[`. + ## Label text should be valid ref. name symbol, otherwise nil is returned. + var i = p.idx + 1 + result = newRstNode(rnInner) + while true: + if p.tok[i].kind in {tkEof, tkIndent, tkWhite}: + return nil + if p.tok[i].kind == tkPunct: + case p.tok[i].symbol: + of "]": + if i > p.idx + 1 and (not reference or (p.tok[i+1].kind == tkPunct and p.tok[i+1].symbol == "_")): + inc i # skip ] + if reference: inc i # skip _ + break # to succeed, it's a footnote/citation indeed + else: + return nil + of "#": + if i != p.idx + 1: + return nil + of "*": + if i != p.idx + 1 and p.tok[i].kind != tkPunct and p.tok[i+1].symbol != "]": + return nil + else: + if not validRefnamePunct(p.tok[i].symbol): + return nil + result.add newRstNode(rnLeaf, p.tok[i].symbol) + inc i + p.idx = i + proc parseInline(p: var RstParser, father: PRstNode) = + var n: PRstNode # to be used in `if` condition case currentTok(p).kind of tkPunct: if isInlineMarkupStart(p, "***"): @@ -1010,6 +1211,20 @@ proc parseInline(p: var RstParser, father: PRstNode) = currentTok(p).symbol == "[" and nextTok(p).symbol != "[" and parseMarkdownLink(p, father): discard "parseMarkdownLink already processed it" + elif isInlineMarkupStart(p, "[") and nextTok(p).symbol != "[" and + (n = parseFootnoteName(p, reference=true); n != nil): + var nn = newRstNode(rnFootnoteRef) + nn.add n + let (fnType, _) = getFootnoteType(n) + case fnType + of fnAutoSymbol: + p.s.lineFootnoteSymRef.add curLine(p) + nn.order = p.s.lineFootnoteSymRef.len + of fnAutoNumber: + p.s.lineFootnoteNumRef.add curLine(p) + nn.order = p.s.lineFootnoteNumRef.len + else: discard + father.add(nn) else: if roSupportSmilies in p.s.options: let n = parseSmiley(p) @@ -1809,6 +2024,20 @@ proc parseDirective(p: var RstParser, flags: DirFlags): PRstNode = proc indFollows(p: RstParser): bool = result = currentTok(p).kind == tkIndent and currentTok(p).ival > currInd(p) +proc parseBlockContent(p: var RstParser, father: var PRstNode, + contentParser: SectionParser): bool = + ## parse the final content part of explicit markup blocks (directives, + ## footnotes, etc). Returns true if succeeded. + if currentTok(p).kind != tkIndent or indFollows(p): + var nextIndent = p.tok[tokenAfterNewline(p)-1].ival + if nextIndent <= currInd(p): # parse only this line + nextIndent = currentTok(p).col + pushInd(p, nextIndent) + var content = contentParser(p) + popInd(p) + father.add content + result = true + proc parseDirective(p: var RstParser, flags: DirFlags, contentParser: SectionParser): PRstNode = ## A helper proc that does main work for specific directive procs. @@ -1821,14 +2050,8 @@ proc parseDirective(p: var RstParser, flags: DirFlags, ## .. warning:: Any of the 3 children may be nil. result = parseDirective(p, flags) if not isNil(contentParser) and - (currentTok(p).kind != tkIndent or indFollows(p)): - var nextIndent = p.tok[tokenAfterNewline(p)-1].ival - if nextIndent <= currInd(p): # parse only this line - nextIndent = currentTok(p).col - pushInd(p, nextIndent) - var content = contentParser(p) - popInd(p) - result.add(content) + parseBlockContent(p, result, contentParser): + discard "result is updated by parseBlockContent" else: result.add(PRstNode(nil)) @@ -2045,9 +2268,58 @@ proc selectDir(p: var RstParser, d: string): PRstNode = else: rstMessage(p, meInvalidDirective, d) +proc prefix(ftnType: FootnoteType): string = + case ftnType + of fnManualNumber: result = "footnote-" + of fnAutoNumber: result = "footnoteauto-" + of fnAutoNumberLabel: result = "footnote-" + of fnAutoSymbol: result = "footnotesym-" + of fnCitation: result = "citation-" + +proc parseFootnote(p: var RstParser): PRstNode = + ## Parses footnotes and citations, always returns 2 sons: + ## + ## 1) footnote label, always containing rnInner with 1 or more sons + ## 2) footnote body, which may be nil + inc p.idx + let label = parseFootnoteName(p, reference=false) + if label == nil: + dec p.idx + return nil + result = newRstNode(rnFootnote) + result.add label + let (fnType, i) = getFootnoteType(label) + var name = "" + var anchor = fnType.prefix + case fnType + of fnManualNumber: + addFootnoteNumManual(p, i) + anchor.add $i + of fnAutoNumber, fnAutoNumberLabel: + name = rstnodeToRefname(label) + addFootnoteNumAuto(p, name) + if fnType == fnAutoNumberLabel: + anchor.add name + else: # fnAutoNumber + result.order = p.s.lineFootnoteNum.len + anchor.add $result.order + of fnAutoSymbol: + addFootnoteSymAuto(p) + result.order = p.s.lineFootnoteSym.len + anchor.add $p.s.lineFootnoteSym.len + of fnCitation: + anchor.add rstnodeToRefname(label) + addAnchor(p, anchor, reset=true) + result.anchor = anchor + if currentTok(p).kind == tkWhite: inc p.idx + discard parseBlockContent(p, result, parseSectionWrapper) + if result.len < 2: + result.add nil + proc parseDotDot(p: var RstParser): PRstNode = # parse "explicit markup blocks" result = nil + var n: PRstNode # to store result, workaround for bug 16855 var col = currentTok(p).col inc p.idx var d = getDirective(p) @@ -2081,18 +2353,16 @@ proc parseDotDot(p: var RstParser): PRstNode = else: rstMessage(p, meInvalidDirective, currentTok(p).symbol) setSub(p, addNodes(a), b) - elif match(p, p.idx, " ["): - # footnotes, citations - inc p.idx, 2 - var a = getReferenceName(p, "]") - if currentTok(p).kind == tkWhite: inc p.idx - var b = untilEol(p) - setRef(p, rstnodeToRefname(a), b) + elif match(p, p.idx, " [") and + (n = parseFootnote(p); n != nil): + result = n else: result = parseComment(p) proc resolveSubs(p: var RstParser, n: PRstNode): PRstNode = - ## resolve substitutions and anchor aliases + ## Resolves substitutions and anchor aliases, groups footnotes. + ## Takes input node `n` and returns the same node with recursive + ## substitutions to `result`. result = n if n == nil: return case n.kind @@ -2118,14 +2388,81 @@ proc resolveSubs(p: var RstParser, n: PRstNode): PRstNode = if s != "": result = newRstNode(rnInternalRef) n.kind = rnInner - result.add(n) - result.add(newRstNode(rnLeaf, s)) + result.add(n) # visible text of reference + result.add(newRstNode(rnLeaf, s)) # link itself + of rnFootnote: + var (fnType, num) = getFootnoteType(n.sons[0]) + case fnType + of fnManualNumber, fnCitation: + discard "no need to alter fixed text" + of fnAutoNumberLabel, fnAutoNumber: + if fnType == fnAutoNumberLabel: + let labelR = rstnodeToRefname(n.sons[0]) + num = getFootnoteNum(p, labelR) + else: + num = getFootnoteNum(p, n.order) + var nn = newRstNode(rnInner) + nn.add newRstNode(rnLeaf, $num) + result.sons[0] = nn + of fnAutoSymbol: + let sym = getAutoSymbol(p, n.order) + n.sons[0].sons[0].text = sym + n.sons[1] = resolveSubs(p, n.sons[1]) + of rnFootnoteRef: + var (fnType, num) = getFootnoteType(n.sons[0]) + template addLabel(number: int | string) = + var nn = newRstNode(rnInner) + nn.add newRstNode(rnLeaf, $number) + result.add(nn) + var refn = fnType.prefix + # create new rnFootnoteRef, add final label, and finalize target refn: + result = newRstNode(rnFootnoteRef) + case fnType + of fnManualNumber: + addLabel num + refn.add $num + of fnAutoNumber: + addLabel getFootnoteNum(p, n.order) + refn.add $n.order + of fnAutoNumberLabel: + addLabel getFootnoteNum(p, rstnodeToRefname(n)) + refn.add rstnodeToRefname(n) + of fnAutoSymbol: + addLabel getAutoSymbol(p, n.order) + refn.add $n.order + of fnCitation: + result.add n.sons[0] + refn.add rstnodeToRefname(n) + let s = findMainAnchor(p, refn) + if s != "": + result.add(newRstNode(rnLeaf, s)) # add link + else: + rstMessage(p, mwUnknownSubstitution, refn) + result.add(newRstNode(rnLeaf, refn)) # add link of rnLeaf: discard of rnContents: p.hasToc = true else: - for i in 0 ..< n.len: n.sons[i] = resolveSubs(p, n.sons[i]) + var regroup = false + for i in 0 ..< n.len: + n.sons[i] = resolveSubs(p, n.sons[i]) + if n.sons[i] != nil and n.sons[i].kind == rnFootnote: + regroup = true + if regroup: # group footnotes together into rnFootnoteGroup + var newSons: seq[PRstNode] + var i = 0 + while i < n.len: + if n.sons[i] != nil and n.sons[i].kind == rnFootnote: + var grp = newRstNode(rnFootnoteGroup) + while i < n.len and n.sons[i].kind == rnFootnote: + grp.sons.add n.sons[i] + inc i + newSons.add grp + else: + newSons.add n.sons[i] + inc i + result.sons = newSons proc rstParse*(text, filename: string, line, column: int, hasToc: var bool, @@ -2138,5 +2475,6 @@ proc rstParse*(text, filename: string, p.line = line p.col = column + getTokens(text, roSkipPounds in options, p.tok) let unresolved = parseDoc(p) + orderFootnotes(p) result = resolveSubs(p, unresolved) hasToc = p.hasToc diff --git a/lib/packages/docutils/rstast.nim b/lib/packages/docutils/rstast.nim index 6ba12c9be..41dadd035 100644 --- a/lib/packages/docutils/rstast.nim +++ b/lib/packages/docutils/rstast.nim @@ -41,8 +41,10 @@ type rnTable, rnGridTable, rnMarkdownTable, rnTableRow, rnTableHeaderCell, rnTableDataCell, rnLabel, # used for footnotes and other things rnFootnote, # a footnote - rnCitation, # similar to footnote - rnStandaloneHyperlink, rnHyperlink, rnRef, rnInternalRef, + rnCitation, # similar to footnote, so use rnFootnote instead + rnFootnoteGroup, # footnote group - exists for a purely stylistic + # reason: to display a few footnotes as 1 block + rnStandaloneHyperlink, rnHyperlink, rnRef, rnInternalRef, rnFootnoteRef, rnDirective, # a general directive rnDirArg, # a directive argument (for some directives). # here are directives that are not rnDirective: @@ -78,6 +80,8 @@ type ## the document or the section; and rnEnumList ## and rnAdmonition; and rnLineBlockItem level*: int ## valid for headlines/overlines only + order*: int ## footnote order (for auto-symbol footnotes and + ## auto-numbered ones without a label) anchor*: string ## anchor, internal link target ## (aka HTML id tag, aka Latex label/hypertarget) sons*: RstNodeSeq ## the node's sons @@ -329,7 +333,7 @@ proc renderRstToJson*(node: PRstNode): string = proc renderRstToStr*(node: PRstNode, indent=0): string = ## Writes the parsed RST `node` into a compact string ## representation in the format (one line per every sub-node): - ## ``indent - kind - text - level (if non-zero)`` + ## ``indent - kind - text - level - order - anchor (if non-zero)`` ## (suitable for debugging of RST parsing). if node == nil: result.add " ".repeat(indent) & "[nil]\n" @@ -337,6 +341,7 @@ proc renderRstToStr*(node: PRstNode, indent=0): string = result.add " ".repeat(indent) & $node.kind & (if node.text == "": "" else: "\t'" & node.text & "'") & (if node.level == 0: "" else: "\tlevel=" & $node.level) & + (if node.order == 0: "" else: "\torder=" & $node.order) & (if node.anchor == "": "" else: "\tanchor='" & node.anchor & "'") & "\n" for son in node.sons: result.add renderRstToStr(son, indent=indent+2) diff --git a/lib/packages/docutils/rstgen.nim b/lib/packages/docutils/rstgen.nim index df6ffa4c4..e2dd60ca1 100644 --- a/lib/packages/docutils/rstgen.nim +++ b/lib/packages/docutils/rstgen.nim @@ -23,7 +23,23 @@ ## many options and tweaking, but you are not limited to snippets and can ## generate `LaTeX documents <https://en.wikipedia.org/wiki/LaTeX>`_ too. ## -## **Note:** Import ``packages/docutils/rstgen`` to use this module +## `Docutils configuration files`_ are not supported. Instead HTML generation +## can be tweaked by editing file ``config/nimdoc.cfg``. +## +## .. _Docutils configuration files: https://docutils.sourceforge.io/docs/user/config.htm +## +## There are stylistic difference between how this module renders some elements +## and how original Python Docutils does: +## +## * Backreferences to TOC in section headings are not generated. +## In HTML each section is also a link that points to the section itself: +## this is done for user to be able to copy the link into clipboard. +## +## * The same goes for footnotes/citations links: they point to themselves. +## No backreferences are generated since finding all references of a footnote +## can be done by simply searching for [footnoteName]. +## +## .. Tip: Import ``packages/docutils/rstgen`` to use this module import strutils, os, hashes, strtabs, rstast, rst, highlite, tables, sequtils, algorithm, parseutils @@ -1219,10 +1235,24 @@ proc renderRstToOut(d: PDoc, n: PRstNode, result: var string) = renderAux(d, n, "<th>$1</th>", "\\textbf{$1}", result) of rnLabel: doAssert false, "renderRstToOut" # used for footnotes and other - of rnFootnote: - doAssert false, "renderRstToOut" # a footnote - of rnCitation: - doAssert false, "renderRstToOut" # similar to footnote + of rnFootnoteGroup: + renderAux(d, n, + "<hr class=\"footnote\">" & + "<div class=\"footnote-group\">\n$1</div>\n", + "\n\n\\noindent\\rule{0.25\\linewidth}{.4pt}\n" & + "\\begin{rstfootnote}\n$1\\end{rstfootnote}\n\n", + result) + of rnFootnote, rnCitation: + var mark = "" + renderAux(d, n.sons[0], mark) + var body = "" + renderRstToOut(d, n.sons[1], body) + dispA(d.target, result, + "<div$2><div class=\"footnote-label\">" & + "<sup><strong><a href=\"#$4\">[$3]</a></strong></sup>" & + "</div>   $1\n</div>\n", + "\\item[\\textsuperscript{[$3]}]$2 $1\n", + [body, n.anchor.idS, mark, n.anchor]) of rnRef: var tmp = "" renderAux(d, n, tmp) @@ -1239,6 +1269,15 @@ proc renderRstToOut(d: PDoc, n: PRstNode, result: var string) = dispA(d.target, result, "<a class=\"reference internal\" href=\"#$2\">$1</a>", "\\hyperlink{$2}{$1} (p.~\\pageref{$2})", [tmp, n.sons[1].text]) + of rnFootnoteRef: + var tmp = "[" + renderAux(d, n.sons[0], tmp) + tmp.add "]" + dispA(d.target, result, + "<sup><strong><a class=\"reference internal\" href=\"#$2\">" & + "$1</a></strong></sup>", + "\\textsuperscript{\\hyperlink{$2}{\\textbf{$1}}}", + [tmp, n.sons[1].text]) of rnHyperlink: var tmp0 = "" var tmp1 = "" |