# # # The Nim Compiler # (c) Copyright 2012 Andreas Rumpf # # See the file "copying.txt", included in this # distribution, for details about the copyright. # # This is the documentation generator. It is currently pretty simple: No # semantic checking is done for the code. Cross-references are generated # by knowing how the anchors are going to be named. import ast, strutils, strtabs, options, msgs, os, ropes, idents, wordrecg, syntaxes, renderer, lexer, packages/docutils/rstast, packages/docutils/rst, packages/docutils/rstgen, packages/docutils/highlite, json, xmltree, cgi, trees, types, typesrenderer, astalgo, modulepaths, lineinfos, sequtils, intsets, pathutils const exportSection = skField type TSections = array[TSymKind, Rope] TDocumentor = object of rstgen.RstGenerator modDesc: Rope # module description toc, section: TSections indexValFilename: string analytics: string # Google Analytics javascript, "" if doesn't exist seenSymbols: StringTableRef # avoids duplicate symbol generation for HTML. jArray: JsonNode types: TStrTable isPureRst: bool conf*: ConfigRef cache*: IdentCache exampleCounter: int emitted: IntSet # we need to track which symbols have been emitted # already. See bug #3655 destFile*: AbsoluteFile thisDir*: AbsoluteDir examples: string PDoc* = ref TDocumentor ## Alias to type less. proc whichType(d: PDoc; n: PNode): PSym = if n.kind == nkSym: if d.types.strTableContains(n.sym): result = n.sym else: for i in 0.. 1: check(1) if params.len > 0: check(0) for i in 2.. (function(i,s,o,g,r,a,m){i['GoogleAnalyticsObject']=r;i[r]=i[r]||function(){ (i[r].q=i[r].q||[]).push(arguments)},i[r].l=1*new Date();a=s.createElement(o), m=s.getElementsByTagName(o)[0];a.async=1;a.src=g;m.parentNode.insertBefore(a,m) })(window,document,'script','//www.google-analytics.com/analytics.js','ga'); ga('create', '$1', 'auto'); ga('send', 'pageview'); """ % [conf.configVars.getOrDefault"doc.googleAnalytics"] else: result.analytics = "" result.seenSymbols = newStringTable(modeCaseInsensitive) result.id = 100 result.jArray = newJArray() initStrTable result.types result.onTestSnippet = proc (gen: var RstGenerator; filename, cmd: string; status: int; content: string) = var d = TDocumentor(gen) var outp: AbsoluteFile if filename.len == 0: inc(d.id) let nameOnly = splitFile(d.filename).name outp = getNimcacheDir(conf) / RelativeDir(nameOnly) / RelativeFile(nameOnly & "_snippet_" & $d.id & ".nim") elif isAbsolute(filename): outp = AbsoluteFile(filename) else: # Nim's convention: every path is relative to the file it was written in: let nameOnly = splitFile(d.filename).name outp = AbsoluteDir(nameOnly) / RelativeFile(filename) # Make sure the destination directory exists createDir(outp.splitFile.dir) # Include the current file if we're parsing a nim file let importStmt = if d.isPureRst: "" else: "import \"$1\"\n" % [d.filename.replace("\\", "/")] writeFile(outp, importStmt & content) let c = if cmd.startsWith("nim "): os.getAppFilename() & cmd.substr(3) else: cmd let c2 = c % quoteShell(outp) rawMessage(conf, hintExecuting, c2) if execShellCmd(c2) != status: rawMessage(conf, errGenerated, "executing of external program failed: " & c2) result.emitted = initIntSet() result.destFile = getOutFile2(conf, relativeTo(filename, conf.projectPath), outExt, RelativeDir"htmldocs", false) result.thisDir = result.destFile.splitFile.dir proc dispA(conf: ConfigRef; dest: var Rope, xml, tex: string, args: openArray[Rope]) = if conf.cmd != cmdRst2tex: addf(dest, xml, args) else: addf(dest, tex, args) proc getVarIdx(varnames: openArray[string], id: string): int = for i in countup(0, high(varnames)): if cmpIgnoreStyle(varnames[i], id) == 0: return i result = -1 proc ropeFormatNamedVars(conf: ConfigRef; frmt: FormatStr, varnames: openArray[string], varvalues: openArray[Rope]): Rope = var i = 0 var L = len(frmt) result = nil var num = 0 while i < L: if frmt[i] == '$': inc(i) # skip '$' case frmt[i] of '#': add(result, varvalues[num]) inc(num) inc(i) of '$': add(result, "$") inc(i) of '0'..'9': var j = 0 while true: j = (j * 10) + ord(frmt[i]) - ord('0') inc(i) if (i > L + 0 - 1) or not (frmt[i] in {'0'..'9'}): break if j > high(varvalues) + 1: rawMessage(conf, errGenerated, "Invalid format string; too many $s: " & frmt) num = j add(result, varvalues[j - 1]) of 'A'..'Z', 'a'..'z', '\x80'..'\xFF': var id = "" while true: add(id, frmt[i]) inc(i) if not (frmt[i] in {'A'..'Z', '_', 'a'..'z', '\x80'..'\xFF'}): break var idx = getVarIdx(varnames, id) if idx >= 0: add(result, varvalues[idx]) else: rawMessage(conf, errGenerated, "unknown substition variable: " & id) of '{': var id = "" inc(i) while i < frmt.len and frmt[i] != '}': add(id, frmt[i]) inc(i) if i >= frmt.len: rawMessage(conf, errGenerated, "expected closing '}'") else: inc(i) # skip } # search for the variable: let idx = getVarIdx(varnames, id) if idx >= 0: add(result, varvalues[idx]) else: rawMessage(conf, errGenerated, "unknown substition variable: " & id) else: add(result, "$") var start = i while i < L: if frmt[i] != '$': inc(i) else: break if i - 1 >= start: add(result, substr(frmt, start, i - 1)) proc genComment(d: PDoc, n: PNode): string = result = "" var dummyHasToc: bool if n.comment.len > 0: renderRstToOut(d[], parseRst(n.comment, toFullPath(d.conf, n.info), toLinenumber(n.info), toColumn(n.info), dummyHasToc, d.options, d.conf), result) proc genRecCommentAux(d: PDoc, n: PNode): Rope = if n == nil: return nil result = genComment(d, n).rope if result == nil: if n.kind in {nkStmtList, nkStmtListExpr, nkTypeDef, nkConstDef, nkObjectTy, nkRefTy, nkPtrTy, nkAsgn, nkFastAsgn}: # notin {nkEmpty..nkNilLit, nkEnumTy, nkTupleTy}: for i in countup(0, len(n)-1): result = genRecCommentAux(d, n.sons[i]) if result != nil: return else: when defined(nimNoNilSeqs): n.comment = "" else: n.comment = nil proc genRecComment(d: PDoc, n: PNode): Rope = if n == nil: return nil result = genComment(d, n).rope if result == nil: if n.kind in {nkProcDef, nkFuncDef, nkMethodDef, nkIteratorDef, nkMacroDef, nkTemplateDef, nkConverterDef}: result = genRecCommentAux(d, n[bodyPos]) else: result = genRecCommentAux(d, n) proc getPlainDocstring(n: PNode): string = ## Gets the plain text docstring of a node non destructively. ## ## You need to call this before genRecComment, whose side effects are removal ## of comments from the tree. The proc will recursively scan and return all ## the concatenated ``##`` comments of the node. result = "" if n == nil: return if startsWith(n.comment, "##"): result = n.comment if result.len < 1: for i in countup(0, safeLen(n)-1): result = getPlainDocstring(n.sons[i]) if result.len > 0: return proc belongsToPackage(conf: ConfigRef; module: PSym): bool = result = module.kind == skModule and module.owner != nil and module.owner.id == conf.mainPackageId proc externalDep(d: PDoc; module: PSym): string = if optWholeProject in d.conf.globalOptions: let full = AbsoluteFile toFullPath(d.conf, FileIndex module.position) let tmp = getOutFile2(d.conf, full.relativeTo(d.conf.projectPath), HtmlExt, RelativeDir"htmldocs", sfMainModule notin module.flags) result = relativeTo(tmp, d.thisDir, '/').string else: result = extractFilename toFullPath(d.conf, FileIndex module.position) proc nodeToHighlightedHtml(d: PDoc; n: PNode; result: var Rope; renderFlags: TRenderFlags = {}; procLink: Rope) = var r: TSrcGen var literal = "" initTokRender(r, n, renderFlags) var kind = tkEof var tokenPos = 0 var procTokenPos = 0 while true: getNextTok(r, kind, literal) inc tokenPos case kind of tkEof: break of tkComment: dispA(d.conf, result, "$1", "\\spanComment{$1}", [rope(esc(d.target, literal))]) of tokKeywordLow..tokKeywordHigh: if kind in {tkProc, tkMethod, tkIterator, tkMacro, tkTemplate, tkFunc, tkConverter}: procTokenPos = tokenPos dispA(d.conf, result, "$1", "\\spanKeyword{$1}", [rope(literal)]) of tkOpr: dispA(d.conf, result, "$1", "\\spanOperator{$1}", [rope(esc(d.target, literal))]) of tkStrLit..tkTripleStrLit: dispA(d.conf, result, "$1", "\\spanStringLit{$1}", [rope(esc(d.target, literal))]) of tkCharLit: dispA(d.conf, result, "$1", "\\spanCharLit{$1}", [rope(esc(d.target, literal))]) of tkIntLit..tkUInt64Lit: dispA(d.conf, result, "$1", "\\spanDecNumber{$1}", [rope(esc(d.target, literal))]) of tkFloatLit..tkFloat128Lit: dispA(d.conf, result, "$1", "\\spanFloatNumber{$1}", [rope(esc(d.target, literal))]) of tkSymbol: let s = getTokSym(r) # -2 because of the whitespace in between: if procTokenPos == tokenPos-2 and procLink != nil: dispA(d.conf, result, "$1", "\\spanIdentifier{$1}", [rope(esc(d.target, literal)), procLink]) elif s != nil and s.kind in {skType, skVar, skLet, skConst} and sfExported in s.flags and s.owner != nil and belongsToPackage(d.conf, s.owner) and d.target == outHtml: let external = externalDep(d, s.owner) result.addf "$3", [rope changeFileExt(external, "html"), rope literal, rope(esc(d.target, literal))] else: dispA(d.conf, result, "$1", "\\spanIdentifier{$1}", [rope(esc(d.target, literal))]) of tkSpaces, tkInvalid: add(result, literal) of tkCurlyDotLe: dispA(d.conf, result, "" & # This span is required for the JS to work properly """{...} $1 """.replace("\n", ""), # Must remove newlines because wrapped in a
                    "\\spanOther{$1}",
                  [rope(esc(d.target, literal))])
    of tkCurlyDotRi:
      dispA(d.conf, result, """

$1
""".replace("\n", ""),
                    "\\spanOther{$1}",
                  [rope(esc(d.target, literal))])
    of tkParLe, tkParRi, tkBracketLe, tkBracketRi, tkCurlyLe, tkCurlyRi,
       tkBracketDotLe, tkBracketDotRi, tkParDotLe,
       tkParDotRi, tkComma, tkSemiColon, tkColon, tkEquals, tkDot, tkDotDot,
       tkAccent, tkColonColon,
       tkGStrLit, tkGTripleStrLit, tkInfixOpr, tkPrefixOpr, tkPostfixOpr,
       tkBracketLeColon:
      dispA(d.conf, result, "$1", "\\spanOther{$1}",
            [rope(esc(d.target, literal))])

proc testExample(d: PDoc; ex: PNode) =
  if d.conf.errorCounter > 0: return
  let outputDir = d.conf.getNimcacheDir / RelativeDir"runnableExamples"
  createDir(outputDir)
  inc d.exampleCounter
  let outp = outputDir / RelativeFile(extractFilename(d.filename.changeFileExt"" &
      "_examples" & $d.exampleCounter & ".nim"))
  #let nimcache = outp.changeFileExt"" & "_nimcache"
  renderModule(ex, d.filename, outp.string, conf = d.conf)
  d.examples.add "import r\"" & outp.string & "\"\n"

proc runAllExamples(d: PDoc) =
  if d.examples.len == 0: return
  let outputDir = d.conf.getNimcacheDir / RelativeDir"runnableExamples"
  let outp = outputDir / RelativeFile(extractFilename(d.filename.changeFileExt"" &
      "_examples.nim"))
  writeFile(outp, d.examples)
  let backend = if isDefined(d.conf, "js"): "js"
                elif isDefined(d.conf, "cpp"): "cpp"
                elif isDefined(d.conf, "objc"): "objc"
                else: "c"
  if os.execShellCmd(os.getAppFilename() & " " & backend &
                    " --path:" & quoteShell(d.conf.projectPath) &
                    " --nimcache:" & quoteShell(outputDir) &
                    " -r " & quoteShell(outp)) != 0:
    quit "[Examples] failed: see " & outp.string
  else:
    # keep generated source file `outp` to allow inspection.
    rawMessage(d.conf, hintSuccess, ["runnableExamples: " & outp.string])
    removeFile(outp.changeFileExt(ExeExt))

proc extractImports(n: PNode; result: PNode) =
  if n.kind in {nkImportStmt, nkImportExceptStmt, nkFromStmt}:
    result.add copyTree(n)
    n.kind = nkEmpty
    return
  for i in 0..pre { line-height: 125%; }
td.linenos .normal { color: inherit; background-color: transparent; padding-left: 5px; padding-right: 5px; }
span.linenos { color: inherit; background-color: transparent; padding-left: 5px; padding-right: 5px; }
td.linenos .special { color: #000000; background-color: #ffffc0; padding-left: 5px; padding-right: 5px; }
span.linenos.special { color: #000000; background-color: #ffffc0; padding-left: 5px; padding-right: 5px; }
.highlight .hll { background-color: #ffffcc }
.highlight .c { color: #888888 } /* Comment */
.highlight .err { color: #a61717; background-color: #e3d2d2 } /* Error */
.highlight .k { color: #008800; font-weight: bold } /* Keyword */
.highlight .ch { color: #888888 } /* Comment.Hashbang */
.highlight .cm { color: #888888 } /* Comment.Multiline */
.highlight .cp { color: #cc0000; font-weight: bold } /* Comment.Preproc */
.highlight .cpf { color: #888888 } /* Comment.PreprocFile */
.highlight .c1 { color: #888888 } /* Comment.Single */
.highlight .cs { color: #cc0000; font-weight: bold; background-color: #fff0f0 } /* Comment.Special */
.highlight .gd { color: #000000; background-color: #ffdddd } /* Generic.Deleted */
.highlight .ge { font-style: italic } /* Generic.Emph */
.highlight .ges { font-weight: bold; font-style: italic } /* Generic.EmphStrong */
.highlight .gr { color: #aa0000 } /* Generic.Error */
.highlight .gh { color: #333333 } /* Generic.Heading */
.highlight .gi { color: #000000; background-color: #ddffdd } /* Generic.Inserted */
.highlight .go { color: #888888 } /* Generic.Output */
.highlight .gp { color: #555555 } /* Generic.Prompt */
.highlight .gs { font-weight: bold } /* Generic.Strong */
.highlight .gu { color: #666666 } /* Generic.Subheading */
.highlight .gt { color: #aa0000 } /* Generic.Traceback */
.highlight .kc { color: #008800; font-weight: bold } /* Keyword.Constant */
.highlight .kd { color: #008800; font-weight: bold } /* Keyword.Declaration */
.highlight .kn { color: #008800; font-weight: bold } /* Keyword.Namespace */
.highlight .kp { color: #008800 } /* Keyword.Pseudo */
.highlight .kr { color: #008800; font-weight: bold } /* Keyword.Reserved */
.highlight .kt { color: #888888; font-weight: bold } /* Keyword.Type */
.highlight .m { color: #0000DD; font-weight: bold } /* Literal.Number */
.highlight .s { color: #dd2200; background-color: #fff0f0 } /* Literal.String */
.highlight .na { color: #336699 } /* Name.Attribute */
.highlight .nb { color: #003388 } /* Name.Builtin */
.highlight .nc { color: #bb0066; font-weight: bold } /* Name.Class */
.highlight .no { color: #003366; font-weight: bold } /* Name.Constant */
.highlight .nd { color: #555555 } /* Name.Decorator */
.highlight .ne { color: #bb0066; font-weight: bold } /* Name.Exception */
.highlight .nf { color: #0066bb; font-weight: bold } /* Name.Function */
.highlight .nl { color: #336699; font-style: italic } /* Name.Label */
.highlight .nn { color: #bb0066; font-weight: bold } /* Name.Namespace */
.highlight .py { color: #336699; font-weight: bold } /* Name.Property */
.highlight .nt { color: #bb0066; font-weight: bold } /* Name.Tag */
.highlight .nv { color: #336699 } /* Name.Variable */
.highlight .ow { color: #008800 } /* Operator.Word */
.highlight .w { color: #bbbbbb } /* Text.Whitespace */
.highlight .mb { color: #0000DD; font-weight: bold } /* Literal.Number.Bin */
.highlight .mf { color: #0000DD; font-weight: bold } /* Literal.Number.Float */
.highlight .mh { color: #0000DD; font-weight: bold } /* Literal.Number.Hex */
.highlight .mi { color: #0000DD; font-weight: bold } /* Literal.Number.Integer */
.highlight .mo { color: #0000DD; font-weight: bold } /* Literal.Number.Oct */
.highlight .sa { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Affix */
.highlight .sb { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Backtick */
.highlight .sc { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Char */
.highlight .dl { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Delimiter */
.highlight .sd { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Doc */
.highlight .s2 { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Double */
.highlight .se { color: #0044dd; background-color: #fff0f0 } /* Literal.String.Escape */
.highlight .sh { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Heredoc */
.highlight .si { color: #3333bb; background-color: #fff0f0 } /* Literal.String.Interpol */
.highlight .sx { color: #22bb22; background-color: #f0fff0 } /* Literal.String.Other */
.highlight .sr { color: #008800; background-color: #fff0ff } /* Literal.String.Regex */
.highlight .s1 { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Single */
.highlight .ss { color: #aa6600; background-color: #fff0f0 } /* Literal.String.Symbol */
.highlight .bp { color: #003388 } /* Name.Builtin.Pseudo */
.highlight .fm { color: #0066bb; font-weight: bold } /* Name.Function.Magic */
.highlight .vc { color: #336699 } /* Name.Variable.Class */
.highlight .vg { color: #dd7700 } /* Name.Variable.Global */
.highlight .vi { color: #3333bb } /* Name.Variable.Instance */
.highlight .vm { color: #336699 } /* Name.Variable.Magic */
.highlight .il { color: #0000DD; font-weight: bold } /* Literal.Number.Integer.Long */
#
#
#            Nim's Runtime Library
#        (c) Copyright 2012 Andreas Rumpf
#
#    See the file "copying.txt", included in this
#    distribution, for details about the copyright.
#


# Bare-bones implementation of some things for embedded targets.

proc chckIndx(i, a, b: int): int {.inline, compilerproc.}
proc chckRange(i, a, b: int): int {.inline, compilerproc.}
proc chckRangeF(x, a, b: float): float {.inline, compilerproc.}
proc chckNil(p: pointer) {.inline, compilerproc.}

proc nimFrame(s: PFrame) {.compilerRtl, inl, exportc: "nimFrame".} = discard
proc popFrame {.compilerRtl, inl.} = discard

proc setFrame(s: PFrame) {.compilerRtl, inl.} = discard
proc pushSafePoint(s: PSafePoint) {.compilerRtl, inl.} = discard
proc popSafePoint {.compilerRtl, inl.} = discard
proc pushCurrentException(e: ref Exception) {.compilerRtl, inl.} = discard
proc popCurrentException {.compilerRtl, inl.} = discard

# some platforms have native support for stack traces:
const
  nativeStackTraceSupported = false
  hasSomeStackTrace = false

proc quitOrDebug() {.inline.} =
  quit(1)

proc raiseException(e: ref Exception, ename: cstring) {.compilerRtl.} =
  sysFatal(ReraiseError, "exception handling is not available")

proc reraiseException() {.compilerRtl.} =
  sysFatal(ReraiseError, "no exception to reraise")

proc writeStackTrace() = discard

proc setControlCHook(hook: proc () {.noconv.} not nil) = discard
s[0] if actual.len != effectListLen: return let real = actual.sons[idx] # warning: hack ahead: var effects = newNodeI(nkBracket, n.info, real.len) for i in 0 ..< real.len: var t = typeToString(real[i].typ) if t.startsWith("ref "): t = substr(t, 4) effects.sons[i] = newIdentNode(getIdent(cache, t), n.info) # set the type so that the following analysis doesn't screw up: effects.sons[i].typ = real[i].typ result = newNode(nkExprColonExpr, n.info, @[ newIdentNode(getIdent(cache, specialWords[effectType]), n.info), effects]) proc documentWriteEffect(cache: IdentCache; n: PNode; flag: TSymFlag; pragmaName: string): PNode = let s = n.sons[namePos].sym let params = s.typ.n var effects = newNodeI(nkBracket, n.info) for i in 1 ..< params.len: if params[i].kind == nkSym and flag in params[i].sym.flags: effects.add params[i] if effects.len > 0: result = newNode(nkExprColonExpr, n.info, @[ newIdentNode(getIdent(cache, pragmaName), n.info), effects]) proc documentRaises*(cache: IdentCache; n: PNode) = if n.sons[namePos].kind != nkSym: return let pragmas = n.sons[pragmasPos] let p1 = documentEffect(cache, n, pragmas, wRaises, exceptionEffects) let p2 = documentEffect(cache, n, pragmas, wTags, tagEffects) let p3 = documentWriteEffect(cache, n, sfWrittenTo, "writes") let p4 = documentNewEffect(cache, n) let p5 = documentWriteEffect(cache, n, sfEscapes, "escapes") if p1 != nil or p2 != nil or p3 != nil or p4 != nil or p5 != nil: if pragmas.kind == nkEmpty: n.sons[pragmasPos] = newNodeI(nkPragma, n.info) if p1 != nil: n.sons[pragmasPos].add p1 if p2 != nil: n.sons[pragmasPos].add p2 if p3 != nil: n.sons[pragmasPos].add p3 if p4 != nil: n.sons[pragmasPos].add p4 if p5 != nil: n.sons[pragmasPos].add p5 proc generateDoc*(d: PDoc, n, orig: PNode) = case n.kind of nkCommentStmt: add(d.modDesc, genComment(d, n)) of nkProcDef: when useEffectSystem: documentRaises(d.cache, n) genItem(d, n, n.sons[namePos], skProc) of nkFuncDef: when useEffectSystem: documentRaises(d.cache, n) genItem(d, n, n.sons[namePos], skFunc) of nkMethodDef: when useEffectSystem: documentRaises(d.cache, n) genItem(d, n, n.sons[namePos], skMethod) of nkIteratorDef: when useEffectSystem: documentRaises(d.cache, n) genItem(d, n, n.sons[namePos], skIterator) of nkMacroDef: genItem(d, n, n.sons[namePos], skMacro) of nkTemplateDef: genItem(d, n, n.sons[namePos], skTemplate) of nkConverterDef: when useEffectSystem: documentRaises(d.cache, n) genItem(d, n, n.sons[namePos], skConverter) of nkTypeSection, nkVarSection, nkLetSection, nkConstSection: for i in countup(0, sonsLen(n) - 1): if n.sons[i].kind != nkCommentStmt: # order is always 'type var let const': genItem(d, n.sons[i], n.sons[i].sons[0], succ(skType, ord(n.kind)-ord(nkTypeSection))) of nkStmtList: for i in countup(0, sonsLen(n) - 1): generateDoc(d, n.sons[i], orig) of nkWhenStmt: # generate documentation for the first branch only: if not checkForFalse(n.sons[0].sons[0]): generateDoc(d, lastSon(n.sons[0]), orig) of nkImportStmt: for it in n: traceDeps(d, it) of nkExportStmt: for it in n: if it.kind == nkSym: exportSym(d, it.sym) of nkExportExceptStmt: discard "transformed into nkExportStmt by semExportExcept" of nkFromStmt, nkImportExceptStmt: traceDeps(d, n.sons[0]) of nkCallKinds: var comm: Rope = nil getAllRunnableExamples(d, n, comm) if comm != nil: add(d.modDesc, comm) else: discard proc add(d: PDoc; j: JsonNode) = if j != nil: d.jArray.add j proc generateJson*(d: PDoc, n: PNode, includeComments: bool = true) = case n.kind of nkCommentStmt: if includeComments: d.add %*{"comment": genComment(d, n)} else: add(d.modDesc, genComment(d, n)) of nkProcDef: when useEffectSystem: documentRaises(d.cache, n) d.add genJsonItem(d, n, n.sons[namePos], skProc) of nkFuncDef: when useEffectSystem: documentRaises(d.cache, n) d.add genJsonItem(d, n, n.sons[namePos], skFunc) of nkMethodDef: when useEffectSystem: documentRaises(d.cache, n) d.add genJsonItem(d, n, n.sons[namePos], skMethod) of nkIteratorDef: when useEffectSystem: documentRaises(d.cache, n) d.add genJsonItem(d, n, n.sons[namePos], skIterator) of nkMacroDef: d.add genJsonItem(d, n, n.sons[namePos], skMacro) of nkTemplateDef: d.add genJsonItem(d, n, n.sons[namePos], skTemplate) of nkConverterDef: when useEffectSystem: documentRaises(d.cache, n) d.add genJsonItem(d, n, n.sons[namePos], skConverter) of nkTypeSection, nkVarSection, nkLetSection, nkConstSection: for i in countup(0, sonsLen(n) - 1): if n.sons[i].kind != nkCommentStmt: # order is always 'type var let const': d.add genJsonItem(d, n.sons[i], n.sons[i].sons[0], succ(skType, ord(n.kind)-ord(nkTypeSection))) of nkStmtList: for i in countup(0, sonsLen(n) - 1): generateJson(d, n.sons[i], includeComments) of nkWhenStmt: # generate documentation for the first branch only: if not checkForFalse(n.sons[0].sons[0]): generateJson(d, lastSon(n.sons[0]), includeComments) else: discard proc genTagsItem(d: PDoc, n, nameNode: PNode, k: TSymKind): string = result = getName(d, nameNode) & "\n" proc generateTags*(d: PDoc, n: PNode, r: var Rope) = case n.kind of nkCommentStmt: if startsWith(n.comment, "##"): let stripped = n.comment.substr(2).strip r.add stripped of nkProcDef: when useEffectSystem: documentRaises(d.cache, n) r.add genTagsItem(d, n, n.sons[namePos], skProc) of nkFuncDef: when useEffectSystem: documentRaises(d.cache, n) r.add genTagsItem(d, n, n.sons[namePos], skFunc) of nkMethodDef: when useEffectSystem: documentRaises(d.cache, n) r.add genTagsItem(d, n, n.sons[namePos], skMethod) of nkIteratorDef: when useEffectSystem: documentRaises(d.cache, n) r.add genTagsItem(d, n, n.sons[namePos], skIterator) of nkMacroDef: r.add genTagsItem(d, n, n.sons[namePos], skMacro) of nkTemplateDef: r.add genTagsItem(d, n, n.sons[namePos], skTemplate) of nkConverterDef: when useEffectSystem: documentRaises(d.cache, n) r.add genTagsItem(d, n, n.sons[namePos], skConverter) of nkTypeSection, nkVarSection, nkLetSection, nkConstSection: for i in countup(0, sonsLen(n) - 1): if n.sons[i].kind != nkCommentStmt: # order is always 'type var let const': r.add genTagsItem(d, n.sons[i], n.sons[i].sons[0], succ(skType, ord(n.kind)-ord(nkTypeSection))) of nkStmtList: for i in countup(0, sonsLen(n) - 1): generateTags(d, n.sons[i], r) of nkWhenStmt: # generate documentation for the first branch only: if not checkForFalse(n.sons[0].sons[0]): generateTags(d, lastSon(n.sons[0]), r) else: discard proc genSection(d: PDoc, kind: TSymKind) = const sectionNames: array[skModule..skField, string] = [ "Imports", "Types", "Vars", "Lets", "Consts", "Vars", "Procs", "Funcs", "Methods", "Iterators", "Converters", "Macros", "Templates", "Exports" ] if d.section[kind] == nil: return var title = sectionNames[kind].rope d.section[kind] = ropeFormatNamedVars(d.conf, getConfigVar(d.conf, "doc.section"), [ "sectionid", "sectionTitle", "sectionTitleID", "content"], [ ord(kind).rope, title, rope(ord(kind) + 50), d.section[kind]]) d.toc[kind] = ropeFormatNamedVars(d.conf, getConfigVar(d.conf, "doc.section.toc"), [ "sectionid", "sectionTitle", "sectionTitleID", "content"], [ ord(kind).rope, title, rope(ord(kind) + 50), d.toc[kind]]) proc genOutFile(d: PDoc): Rope = var code, content: Rope title = "" var j = 0 var tmp = "" renderTocEntries(d[], j, 1, tmp) var toc = tmp.rope for i in countup(low(TSymKind), high(TSymKind)): genSection(d, i) add(toc, d.toc[i]) if toc != nil: toc = ropeFormatNamedVars(d.conf, getConfigVar(d.conf, "doc.toc"), ["content"], [toc]) for i in countup(low(TSymKind), high(TSymKind)): add(code, d.section[i]) # Extract the title. Non API modules generate an entry in the index table. if d.meta[metaTitle].len != 0: title = d.meta[metaTitle] let external = AbsoluteFile(d.filename).relativeTo(d.conf.projectPath, '/').changeFileExt(HtmlExt).string setIndexTerm(d[], external, "", title) else: # Modules get an automatic title for the HTML, but no entry in the index. title = extractFilename(changeFileExt(d.filename, "")) let bodyname = if d.hasToc and not d.isPureRst: "doc.body_toc_group" elif d.hasToc: "doc.body_toc" else: "doc.body_no_toc" content = ropeFormatNamedVars(d.conf, getConfigVar(d.conf, bodyname), ["title", "tableofcontents", "moduledesc", "date", "time", "content"], [title.rope, toc, d.modDesc, rope(getDateStr()), rope(getClockStr()), code]) if optCompileOnly notin d.conf.globalOptions: # XXX what is this hack doing here? 'optCompileOnly' means raw output!? code = ropeFormatNamedVars(d.conf, getConfigVar(d.conf, "doc.file"), ["title", "tableofcontents", "moduledesc", "date", "time", "content", "author", "version", "analytics"], [title.rope, toc, d.modDesc, rope(getDateStr()), rope(getClockStr()), content, d.meta[metaAuthor].rope, d.meta[metaVersion].rope, d.analytics.rope]) else: code = content result = code proc generateIndex*(d: PDoc) = if optGenIndex in d.conf.globalOptions: let dir = if not d.conf.outDir.isEmpty: d.conf.outDir else: d.conf.projectPath / RelativeDir"htmldocs" createDir(dir) let dest = dir / changeFileExt(relativeTo(AbsoluteFile d.filename, d.conf.projectPath), IndexExt) writeIndexFile(d[], dest.string) proc writeOutput*(d: PDoc, useWarning = false) = runAllExamples(d) var content = genOutFile(d) if optStdout in d.conf.globalOptions: writeRope(stdout, content) else: template outfile: untyped = d.destFile #let outfile = getOutFile2(d.conf, shortenDir(d.conf, filename), outExt, "htmldocs") createDir(outfile.splitFile.dir) if not writeRope(content, outfile): rawMessage(d.conf, if useWarning: warnCannotOpenFile else: errCannotOpenFile, outfile.string) proc writeOutputJson*(d: PDoc, useWarning = false) = runAllExamples(d) var modDesc: string for desc in d.modDesc: modDesc &= desc let content = %*{"orig": d.filename, "nimble": getPackageName(d.conf, d.filename), "moduleDescription": modDesc, "entries": d.jArray} if optStdout in d.conf.globalOptions: write(stdout, $content) else: var f: File if open(f, d.destFile.string, fmWrite): write(f, $content) close(f) else: localError(d.conf, newLineInfo(d.conf, AbsoluteFile d.filename, -1, -1), warnUser, "unable to open file \"" & d.destFile.string & "\" for writing") proc handleDocOutputOptions*(conf: ConfigRef) = if optWholeProject in conf.globalOptions: # Backward compatibility with previous versions conf.outDir = AbsoluteDir(conf.outDir / conf.outFile) proc commandDoc*(cache: IdentCache, conf: ConfigRef) = handleDocOutputOptions conf var ast = parseFile(conf.projectMainIdx, cache, conf) if ast == nil: return var d = newDocumentor(conf.projectFull, cache, conf) d.hasToc = true generateDoc(d, ast, ast) writeOutput(d) generateIndex(d) proc commandRstAux(cache: IdentCache, conf: ConfigRef; filename: AbsoluteFile, outExt: string) = var filen = addFileExt(filename, "txt") var d = newDocumentor(filen, cache, conf, outExt) d.isPureRst = true var rst = parseRst(readFile(filen.string), filen.string, 0, 1, d.hasToc, {roSupportRawDirective, roSupportMarkdown}, conf) var modDesc = newStringOfCap(30_000) renderRstToOut(d[], rst, modDesc) d.modDesc = rope(modDesc) writeOutput(d) generateIndex(d) proc commandRst2Html*(cache: IdentCache, conf: ConfigRef) = commandRstAux(cache, conf, conf.projectFull, HtmlExt) proc commandRst2TeX*(cache: IdentCache, conf: ConfigRef) = commandRstAux(cache, conf, conf.projectFull, TexExt) proc commandJson*(cache: IdentCache, conf: ConfigRef) = var ast = parseFile(conf.projectMainIdx, cache, conf) if ast == nil: return var d = newDocumentor(conf.projectFull, cache, conf) d.onTestSnippet = proc (d: var RstGenerator; filename, cmd: string; status: int; content: string) = localError(conf, newLineInfo(conf, AbsoluteFile d.filename, -1, -1), warnUser, "the ':test:' attribute is not supported by this backend") d.hasToc = true generateJson(d, ast) let json = d.jArray let content = rope(pretty(json)) if optStdout in d.conf.globalOptions: writeRope(stdout, content) else: #echo getOutFile(gProjectFull, JsonExt) let filename = getOutFile(conf, RelativeFile conf.projectName, JsonExt) if not writeRope(content, filename): rawMessage(conf, errCannotOpenFile, filename.string) proc commandTags*(cache: IdentCache, conf: ConfigRef) = var ast = parseFile(conf.projectMainIdx, cache, conf) if ast == nil: return var d = newDocumentor(conf.projectFull, cache, conf) d.onTestSnippet = proc (d: var RstGenerator; filename, cmd: string; status: int; content: string) = localError(conf, newLineInfo(conf, AbsoluteFile d.filename, -1, -1), warnUser, "the ':test:' attribute is not supported by this backend") d.hasToc = true var content: Rope generateTags(d, ast, content) if optStdout in d.conf.globalOptions: writeRope(stdout, content) else: #echo getOutFile(gProjectFull, TagsExt) let filename = getOutFile(conf, RelativeFile conf.projectName, TagsExt) if not writeRope(content, filename): rawMessage(conf, errCannotOpenFile, filename.string) proc commandBuildIndex*(cache: IdentCache, conf: ConfigRef) = var content = mergeIndexes(conf.projectFull.string).rope let code = ropeFormatNamedVars(conf, getConfigVar(conf, "doc.file"), ["title", "tableofcontents", "moduledesc", "date", "time", "content", "author", "version", "analytics"], ["Index".rope, nil, nil, rope(getDateStr()), rope(getClockStr()), content, nil, nil, nil]) # no analytics because context is not available let filename = getOutFile(conf, RelativeFile"theindex", HtmlExt) if not writeRope(code, filename): rawMessage(conf, errCannotOpenFile, filename.string)