# # # 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, json, xmltree, cgi, trees, types, typesrenderer, astalgo, lineinfos, intsets, pathutils, trees, tables, nimpaths, renderverbatim, osproc from std/private/globs import nativeToUnixPath const exportSection = skField docCmdSkip = "skip" type TSections = array[TSymKind, Rope] ExampleGroup = ref object ## a group of runnableExamples with same rdoccmd rdoccmd: string ## from 1st arg in `runnableExamples(rdoccmd): body` docCmd: string ## from user config, eg --doccmd:-d:foo code: string ## contains imports; each import contains `body` index: int ## group index TDocumentor = object of rstgen.RstGenerator modDesc: Rope # module description module: PSym modDeprecationMsg: Rope 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 thisDir*: AbsoluteDir exampleGroups: OrderedTable[string, ExampleGroup] wroteSupportFiles*: bool PDoc* = ref TDocumentor ## Alias to type less. proc presentationPath*(conf: ConfigRef, file: AbsoluteFile, isTitle = false): RelativeFile = ## returns a relative file that will be appended to outDir let file2 = $file template bail() = result = relativeTo(file, conf.projectPath) proc nimbleDir(): AbsoluteDir = getNimbleFile(conf, file2).parentDir.AbsoluteDir case conf.docRoot: of docRootDefault: result = getRelativePathFromConfigPath(conf, file) let dir = nimbleDir() if not dir.isEmpty: let result2 = relativeTo(file, dir) if not result2.isEmpty and (result.isEmpty or result2.string.len < result.string.len): result = result2 if result.isEmpty: bail() of "@pkg": let dir = nimbleDir() if dir.isEmpty: bail() else: result = relativeTo(file, dir) of "@path": result = getRelativePathFromConfigPath(conf, file) if result.isEmpty: bail() elif conf.docRoot.len > 0: # we're (currently) requiring `isAbsolute` to avoid confusion when passing # a relative path (would it be relative wrt $PWD or to projectfile) conf.globalAssert conf.docRoot.isAbsolute, arg=conf.docRoot conf.globalAssert conf.docRoot.existsDir, arg=conf.docRoot # needed because `canonicalizePath` called on `file` result = file.relativeTo conf.docRoot.expandFilename.AbsoluteDir else: bail() if isAbsolute(result.string): result = file.string.splitPath()[1].RelativeFile if isTitle: result = result.string.nativeToUnixPath.RelativeFile else: result = result.string.replace("..", dotdotMangle).RelativeFile doAssert not result.isEmpty doAssert not isAbsolute(result.string) 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) = if conf.docCmd == docCmdSkip: return inc(gen.id) var d = TDocumentor(gen) var outp: AbsoluteFile if filename.len == 0: 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) proc interpSnippetCmd(cmd: string): string = # backward compatibility hacks; interpolation commands should explicitly use `$` if cmd.startsWith "nim ": result = "$nim " & cmd[4..^1] else: result = cmd result = result.replace("$1", "$options") % [ "nim", os.getAppFilename().quoteShell, "backend", $d.conf.backend, "options", outp.quoteShell, ] let cmd = cmd.interpSnippetCmd rawMessage(conf, hintExecuting, cmd) let (output, gotten) = execCmdEx(cmd) if gotten != status: rawMessage(conf, errGenerated, "snippet failed: cmd: '$1' status: $2 expected: $3 output: $4" % [cmd, $gotten, $status, output]) result.emitted = initIntSet() result.destFile = getOutFile2(conf, presentationPath(conf, filename), outExt, false) result.thisDir = result.destFile.splitFile.dir template dispA(conf: ConfigRef; dest: var Rope, xml, tex: string, args: openArray[Rope]) = if conf.cmd != cmdRst2tex: dest.addf(xml, args) else: dest.addf(tex, args) proc getVarIdx(varnames: openArray[string], id: string): int = for i in 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 result = nil var num = 0 while i < frmt.len: if frmt[i] == '$': inc(i) # skip '$' case frmt[i] of '#': result.add(varvalues[num]) inc(num) inc(i) of '$': result.add("$") inc(i) of '0'..'9': var j = 0 while true: j = (j * 10) + ord(frmt[i]) - ord('0') inc(i) if (i > frmt.len + 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 result.add(varvalues[j - 1]) of 'A'..'Z', 'a'..'z', '\x80'..'\xFF': var id = "" while true: id.add(frmt[i]) inc(i) if not (frmt[i] in {'A'..'Z', '_', 'a'..'z', '\x80'..'\xFF'}): break var idx = getVarIdx(varnames, id) if idx >= 0: result.add(varvalues[idx]) else: rawMessage(conf, errGenerated, "unknown substition variable: " & id) of '{': var id = "" inc(i) while i < frmt.len and frmt[i] != '}': id.add(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: result.add(varvalues[idx]) else: rawMessage(conf, errGenerated, "unknown substition variable: " & id) else: result.add("$") var start = i while i < frmt.len: if frmt[i] != '$': inc(i) else: break if i - 1 >= start: result.add(substr(frmt, start, i - 1)) proc genComment(d: PDoc, n: PNode): string = result = "" var dummyHasToc: bool if n.comment.len > 0: var comment2 = n.comment when false: # RFC: to preseve newlines in comments, this would work: comment2 = comment2.replace("\n", "\n\n") renderRstToOut(d[], parseRst(comment2, 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, nkHiddenStdConv}: # notin {nkEmpty..nkNilLit, nkEnumTy, nkTupleTy}: for i in 0.. 0: return proc belongsToPackage(conf: ConfigRef; module: PSym): bool = result = module.kind == skModule and module.getnimblePkgId == conf.mainPackageId proc externalDep(d: PDoc; module: PSym): string = if optWholeProject in d.conf.globalOptions or d.conf.docRoot.len > 0: let full = AbsoluteFile toFullPath(d.conf, FileIndex module.position) let tmp = getOutFile2(d.conf, presentationPath(d.conf, full), HtmlExt, 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 template escLit(): untyped = rope(esc(d.target, literal)) while true: getNextTok(r, kind, literal) inc tokenPos case kind of tkEof: break of tkComment: dispA(d.conf, result, "$1", "\\spanComment{$1}", [escLit]) 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}", [escLit]) of tkStrLit..tkTripleStrLit: dispA(d.conf, result, "$1", "\\spanStringLit{$1}", [escLit]) of tkCharLit: dispA(d.conf, result, "$1", "\\spanCharLit{$1}", [escLit]) of tkIntLit..tkUInt64Lit: dispA(d.conf, result, "$1", "\\spanDecNumber{$1}", [escLit]) of tkFloatLit..tkFloat128Lit: dispA(d.conf, result, "$1", "\\spanFloatNumber{$1}", [escLit]) 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}", [escLit, 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, escLit] else: dispA(d.conf, result, "$1", "\\spanIdentifier{$1}", [escLit]) of tkSpaces, tkInvalid: result.add(literal) of tkCurlyDotLe: template fun(s) = dispA(d.conf, result, s, "\\spanOther{$1}", [escLit]) if renderRunnableExamples in renderFlags: fun "$1" else: fun: "" & # This span is required for the JS to work properly """{...} $1 """.replace("\n", "") # Must remove newlines because wrapped in a
    of tkCurlyDotRi:
      template fun(s) = dispA(d.conf, result, s, "\\spanOther{$1}", [escLit])
      if renderRunnableExamples in renderFlags: fun "$1"
      else: fun """

$1
""".replace("\n", "")
    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}",
            [escLit])

proc exampleOutputDir(d: PDoc): AbsoluteDir = d.conf.getNimcacheDir / RelativeDir"runnableExamples"

proc writeExample(d: PDoc; ex: PNode, rdoccmd: string) =
  if d.conf.errorCounter > 0: return
  let outputDir = d.exampleOutputDir
  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)
  if rdoccmd notin d.exampleGroups: d.exampleGroups[rdoccmd] = ExampleGroup(rdoccmd: rdoccmd, docCmd: d.conf.docCmd, index: d.exampleGroups.len)
  d.exampleGroups[rdoccmd].code.add "import r\"$1\"\n" % outp.string

proc runAllExamples(d: PDoc) =
  let backend = d.conf.backend
  # This used to be: `let backend = if isDefined(d.conf, "js"): "js"` (etc), however
  # using `-d:js` (etc) cannot work properly, eg would fail with `importjs`
  # since semantics are affected by `config.backend`, not by isDefined(d.conf, "js")
  let outputDir = d.exampleOutputDir
  for _, group in d.exampleGroups:
    if group.docCmd == docCmdSkip: continue
    let outp = outputDir / RelativeFile("$1_group$2_examples.nim" % [d.filename.splitFile.name, $group.index])
    group.code = "# autogenerated by docgen\n# source: $1\n# rdoccmd: $2\n$3" % [d.filename, group.rdoccmd, group.code]
    writeFile(outp, group.code)
    # most useful semantics is that `docCmd` comes after `rdoccmd`, so that we can (temporarily) override
    # via command line
    let cmd = "$nim $backend -r --warning:UnusedImport:off --path:$path --nimcache:$nimcache $rdoccmd $docCmd $file" % [
      "nim", os.getAppFilename(),
      "backend", $d.conf.backend,
      "path", quoteShell(d.conf.projectPath),
      "nimcache", quoteShell(outputDir),
      "file", quoteShell(outp),
      "rdoccmd", group.rdoccmd,
      "docCmd", group.docCmd,
    ]
    if os.execShellCmd(cmd) != 0:
      quit "[runnableExamples] failed: generated file: '$1' group: '$2' cmd: $3" % [outp.string, $group[], cmd]
    else:
      # keep generated source file `outp` to allow inspection.
      rawMessage(d.conf, hintSuccess, ["runnableExamples: " & outp.string])
      # removeFile(outp.changeFileExt(ExeExt)) # it's in nimcache, no need to remove

proc prepareExample(d: PDoc; n: PNode): tuple[rdoccmd: string, code: string] =
  ## returns `rdoccmd` and source code for this runnableExamples
  var rdoccmd = ""
  if n.len < 2 or n.len > 3: globalError(d.conf, n.info, "runnableExamples invalid")
  if n.len == 3:
    let n1 = n[1]
    # xxx this should be evaluated during sempass
    if n1.kind notin nkStrKinds: globalError(d.conf, n1.info, "string litteral expected")
    rdoccmd = n1.strVal

  var docComment = newTree(nkCommentStmt)
  let loc = d.conf.toFileLineCol(n.info)

  docComment.comment = "autogenerated by docgen\nloc: $1\nrdoccmd: $2" % [loc, rdoccmd]
  var runnableExamples = newTree(nkStmtList,
      docComment,
      newTree(nkImportStmt, newStrNode(nkStrLit, d.filename)))
  runnableExamples.info = n.info
  let ret = extractRunnableExamplesSource(d.conf, n)
  for a in n.lastSon: runnableExamples.add a
  # we could also use `ret` instead here, to keep sources verbatim
  writeExample(d, runnableExamples, rdoccmd)
  result = (rdoccmd, ret)
  when false:
    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.. 0: dest.add "\n"
    inc i
    nodeToHighlightedHtml(d, b, dest, {renderRunnableExamples}, nil)

type RunnableState = enum
  rsStart
  rsComment
  rsRunnable
  rsDone

proc getAllRunnableExamplesImpl(d: PDoc; n: PNode, dest: var Rope, state: RunnableState): RunnableState =
  ##[
  Simple state machine to tell whether we render runnableExamples and doc comments.
  This is to ensure that we can interleave runnableExamples and doc comments freely;
  the logic is easy to change but currently a doc comment following another doc comment
  will not render, to avoid rendering in following case:

  proc fn* =
    runnableExamples: discard
    ## d1
    runnableExamples: discard
    ## d2

    ## internal explanation  # <- this one should be out; it's part of rest of function body and would likey not make sense in doc comment
    discard # some code
  ]##

  case n.kind
  of nkCommentStmt:
    if state in {rsStart, rsRunnable}:
      dest.add genRecComment(d, n)
      return rsComment
  of nkCallKinds:
    if isRunnableExamples(n[0]) and
        n.len >= 2 and n.lastSon.kind == nkStmtList and state in {rsStart, rsComment, rsRunnable}:
      let (rdoccmd, code) = prepareExample(d, n)
      var msg = "Example:"
      if rdoccmd.len > 0: msg.add " cmd: " & rdoccmd
      dispA(d.conf, dest, "\n

$1

\n", "\n\\textbf{$1}\n", [msg.rope]) inc d.listingCounter let id = $d.listingCounter dest.add(d.config.getOrDefault"doc.listing_start" % [id, "langNim"]) when true: var dest2 = "" renderNimCode(dest2, code, isLatex = d.conf.cmd == cmdRst2tex) dest.add dest2 else: renderNimCodeOld(d, n, dest) dest.add(d.config.getOrDefault"doc.listing_end" % id) return rsRunnable else: discard return rsDone # change this to `rsStart` if you want to keep generating doc comments # and runnableExamples that occur after some code in routine proc getRoutineBody(n: PNode): PNode = ##[ nim transforms these quite differently: proc someType*(): int = ## foo result = 3 => result = ## foo 3; proc someType*(): int = ## foo 3 => ## foo result = 3; so we normalize the results to get to the statement list containing the (0 or more) doc comments and runnableExamples. ]## result = n[bodyPos] if result.kind == nkAsgn and n.len > bodyPos+1 and n[bodyPos+1].kind == nkSym: doAssert result[0].kind == nkSym doAssert result.len == 2 result = result[1] proc getAllRunnableExamples(d: PDoc, n: PNode, dest: var Rope) = var n = n var state = rsStart template fn(n2) = state = getAllRunnableExamplesImpl(d, n2, dest, state) dest.add genComment(d, n).rope case n.kind of routineDefs: n = n.getRoutineBody case n.kind of nkCommentStmt, nkCallKinds: fn(n) else: for i in 0.. paramsPos and n[paramsPos].kind == nkFormalParams: let params = renderParamTypes(n[paramsPos]) if params.len > 0: result.add(defaultParamSeparator) result.add(params) proc isCallable(n: PNode): bool = ## Returns true if `n` contains a callable node. case n.kind of nkProcDef, nkMethodDef, nkIteratorDef, nkMacroDef, nkTemplateDef, nkConverterDef, nkFuncDef: result = true else: result = false proc docstringSummary(rstText: string): string = ## Returns just the first line or a brief chunk of text from a rst string. ## ## Most docstrings will contain a one liner summary, so stripping at the ## first newline is usually fine. If after that the content is still too big, ## it is stripped at the first comma, colon or dot, usual English sentence ## separators. ## ## No guarantees are made on the size of the output, but it should be small. ## Also, we hope to not break the rst, but maybe we do. If there is any ## trimming done, an ellipsis unicode char is added. const maxDocstringChars = 100 assert(rstText.len < 2 or (rstText[0] == '#' and rstText[1] == '#')) result = rstText.substr(2).strip var pos = result.find('\L') if pos > 0: result.delete(pos, result.len - 1) result.add("…") if pos < maxDocstringChars: return # Try to keep trimming at other natural boundaries. pos = result.find({'.', ',', ':'}) let last = result.len - 1 if pos > 0 and pos < last: result.delete(pos, last) result.add("…") proc genDeprecationMsg(d: PDoc, n: PNode): Rope = ## Given a nkPragma wDeprecated node output a well-formatted section if n == nil: return case n.safeLen: of 0: # Deprecated w/o any message result = ropeFormatNamedVars(d.conf, getConfigVar(d.conf, "doc.deprecationmsg"), ["label", "message"], [~"Deprecated", nil]) of 2: # Deprecated w/ a message if n[1].kind in {nkStrLit..nkTripleStrLit}: result = ropeFormatNamedVars(d.conf, getConfigVar(d.conf, "doc.deprecationmsg"), ["label", "message"], [~"Deprecated:", rope(xmltree.escape(n[1].strVal))]) else: doAssert false type DocFlags = enum kDefault kForceExport proc genItem(d: PDoc, n, nameNode: PNode, k: TSymKind, docFlags: DocFlags) = if (docFlags != kForceExport) and not isVisible(d, nameNode): return let name = getName(d, nameNode) nameRope = name.rope var plainDocstring = getPlainDocstring(n) # call here before genRecComment! var result: Rope = nil var literal, plainName = "" var kind = tkEof var comm: Rope = nil if n.kind in routineDefs: getAllRunnableExamples(d, n, comm) else: comm.add genRecComment(d, n) var r: TSrcGen # Obtain the plain rendered string for hyperlink titles. initTokRender(r, n, {renderNoBody, renderNoComments, renderDocComments, renderNoPragmas, renderNoProcDefs}) while true: getNextTok(r, kind, literal) if kind == tkEof: break plainName.add(literal) var pragmaNode: PNode = nil if n.isCallable and n[pragmasPos].kind != nkEmpty: pragmaNode = findPragma(n[pragmasPos], wDeprecated) inc(d.id) let plainNameRope = rope(xmltree.escape(plainName.strip)) cleanPlainSymbol = renderPlainSymbolName(nameNode) complexSymbol = complexName(k, n, cleanPlainSymbol) plainSymbolRope = rope(cleanPlainSymbol) plainSymbolEncRope = rope(encodeUrl(cleanPlainSymbol)) itemIDRope = rope(d.id) symbolOrId = d.newUniquePlainSymbol(complexSymbol) symbolOrIdRope = symbolOrId.rope symbolOrIdEncRope = encodeUrl(symbolOrId).rope deprecationMsgRope = genDeprecationMsg(d, pragmaNode) nodeToHighlightedHtml(d, n, result, {renderNoBody, renderNoComments, renderDocComments, renderSyms}, symbolOrIdEncRope) var seeSrcRope: Rope = nil let docItemSeeSrc = getConfigVar(d.conf, "doc.item.seesrc") if docItemSeeSrc.len > 0: let path = relativeTo(AbsoluteFile toFullPath(d.conf, n.info), AbsoluteDir getCurrentDir(), '/') when false: let cwd = canonicalizePath(d.conf, getCurrentDir()) var path = toFullPath(d.conf, n.info) if path.startsWith(cwd): path = path[cwd.len+1..^1].replace('\\', '/') let gitUrl = getConfigVar(d.conf, "git.url") if gitUrl.len > 0: let defaultBranch = if NimPatch mod 2 == 1: "devel" else: "version-$1-$2" % [$NimMajor, $NimMinor] let commit = getConfigVar(d.conf, "git.commit", defaultBranch) let develBranch = getConfigVar(d.conf, "git.devel", "devel") dispA(d.conf, seeSrcRope, "$1", "", [ropeFormatNamedVars(d.conf, docItemSeeSrc, ["path", "line", "url", "commit", "devel"], [rope path.string, rope($n.info.line), rope gitUrl, rope commit, rope develBranch])]) d.section[k].add(ropeFormatNamedVars(d.conf, getConfigVar(d.conf, "doc.item"), ["name", "header", "desc", "itemID", "header_plain", "itemSym", "itemSymOrID", "itemSymEnc", "itemSymOrIDEnc", "seeSrc", "deprecationMsg"], [nameRope, result, comm, itemIDRope, plainNameRope, plainSymbolRope, symbolOrIdRope, plainSymbolEncRope, symbolOrIdEncRope, seeSrcRope, deprecationMsgRope])) let external = d.destFile.relativeTo(d.conf.outDir, '/').changeFileExt(HtmlExt).string var attype: Rope if k in routineKinds and nameNode.kind == nkSym: let att = attachToType(d, nameNode.sym) if att != nil: attype = rope esc(d.target, att.name.s) elif k == skType and nameNode.kind == nkSym and nameNode.sym.typ.kind in {tyEnum, tyBool}: let etyp = nameNode.sym.typ for e in etyp.n: if e.sym.kind != skEnumField: continue let plain = renderPlainSymbolName(e) let symbolOrId = d.newUniquePlainSymbol(plain) setIndexTerm(d[], external, symbolOrId, plain, nameNode.sym.name.s & '.' & plain, xmltree.escape(getPlainDocstring(e).docstringSummary)) d.toc[k].add(ropeFormatNamedVars(d.conf, getConfigVar(d.conf, "doc.item.toc"), ["name", "header", "desc", "itemID", "header_plain", "itemSym", "itemSymOrID", "itemSymEnc", "itemSymOrIDEnc", "attype"], [rope(getName(d, nameNode, d.splitAfter)), result, comm, itemIDRope, plainNameRope, plainSymbolRope, symbolOrIdRope, plainSymbolEncRope, symbolOrIdEncRope, attype])) # Ironically for types the complexSymbol is *cleaner* than the plainName # because it doesn't include object fields or documentation comments. So we # use the plain one for callable elements, and the complex for the rest. var linkTitle = changeFileExt(extractFilename(d.filename), "") & ": " if n.isCallable: linkTitle.add(xmltree.escape(plainName.strip)) else: linkTitle.add(xmltree.escape(complexSymbol.strip)) setIndexTerm(d[], external, symbolOrId, name, linkTitle, xmltree.escape(plainDocstring.docstringSummary)) if k == skType and nameNode.kind == nkSym: d.types.strTableAdd nameNode.sym proc genJsonItem(d: PDoc, n, nameNode: PNode, k: TSymKind): JsonNode = if not isVisible(d, nameNode): return var name = getName(d, nameNode) comm = $genRecComment(d, n) r: TSrcGen initTokRender(r, n, {renderNoBody, renderNoComments, renderDocComments}) result = %{ "name": %name, "type": %($k), "line": %n.info.line.int, "col": %n.info.col} if comm.len > 0: result["description"] = %comm if r.buf.len > 0: result["code"] = %r.buf if k in routineKinds: result["signature"] = newJObject() if n[paramsPos][0].kind != nkEmpty: result["signature"]["return"] = %($n[paramsPos][0]) if n[paramsPos].len > 1: result["signature"]["arguments"] = newJArray() for paramIdx in 1 ..< n[paramsPos].len: for identIdx in 0 ..< n[paramsPos][paramIdx].len - 2: let paramName = $n[paramsPos][paramIdx][identIdx] paramType = $n[paramsPos][paramIdx][^2] if n[paramsPos][paramIdx][^1].kind != nkEmpty: let paramDefault = $n[paramsPos][paramIdx][^1] result["signature"]["arguments"].add %{"name": %paramName, "type": %paramType, "default": %paramDefault} else: result["signature"]["arguments"].add %{"name": %paramName, "type": %paramType} if n[pragmasPos].kind != nkEmpty: result["signature"]["pragmas"] = newJArray() for pragma in n[pragmasPos]: result["signature"]["pragmas"].add %($pragma) if n[genericParamsPos].kind != nkEmpty: result["signature"]["genericParams"] = newJArray() for genericParam in n[genericParamsPos]: var param = %{"name": %($genericParam)} if genericParam.sym.typ.sons.len > 0: param["types"] = newJArray() for kind in genericParam.sym.typ.sons: param["types"].add %($kind) result["signature"]["genericParams"].add param proc checkForFalse(n: PNode): bool = result = n.kind == nkIdent and cmpIgnoreStyle(n.ident.s, "false") == 0 proc traceDeps(d: PDoc, it: PNode) = const k = skModule if it.kind == nkInfix and it.len == 3 and it[2].kind == nkBracket: let sep = it[0] let dir = it[1] let a = newNodeI(nkInfix, it.info) a.add sep a.add dir a.add sep # dummy entry, replaced in the loop for x in it[2]: a[2] = x traceDeps(d, a) elif it.kind == nkSym and belongsToPackage(d.conf, it.sym): let external = externalDep(d, it.sym) if d.section[k] != nil: d.section[k].add(", ") dispA(d.conf, d.section[k], "$1", "$1", [rope esc(d.target, external.prettyLink), rope changeFileExt(external, "html")]) proc exportSym(d: PDoc; s: PSym) = const k = exportSection if s.kind == skModule and belongsToPackage(d.conf, s): let external = externalDep(d, s) if d.section[k] != nil: d.section[k].add(", ") dispA(d.conf, d.section[k], "$1", "$1", [rope esc(d.target, external.prettyLink), rope changeFileExt(external, "html")]) elif s.kind != skModule and s.owner != nil: let module = originatingModule(s) if belongsToPackage(d.conf, module): let external = externalDep(d, module) if d.section[k] != nil: d.section[k].add(", ") # XXX proper anchor generation here dispA(d.conf, d.section[k], "$1", "$1", [rope esc(d.target, s.name.s), rope changeFileExt(external, "html")]) proc documentNewEffect(cache: IdentCache; n: PNode): PNode = let s = n[namePos].sym if tfReturnsNew in s.typ.flags: result = newIdentNode(getIdent(cache, "new"), n.info) proc documentEffect(cache: IdentCache; n, x: PNode, effectType: TSpecialWord, idx: int): PNode = let spec = effectSpec(x, effectType) if isNil(spec): let s = n[namePos].sym let actual = s.typ.n[0] if actual.len != effectListLen: return let real = actual[idx] # warning: hack ahead: var effects = newNodeI(nkBracket, n.info, real.len) for i in 0.. 0: result = newNode(nkExprColonExpr, n.info, @[ newIdentNode(getIdent(cache, pragmaName), n.info), effects]) proc documentRaises*(cache: IdentCache; n: PNode) = if n[namePos].kind != nkSym: return let pragmas = n[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[pragmasPos] = newNodeI(nkPragma, n.info) if p1 != nil: n[pragmasPos].add p1 if p2 != nil: n[pragmasPos].add p2 if p3 != nil: n[pragmasPos].add p3 if p4 != nil: n[pragmasPos].add p4 if p5 != nil: n[pragmasPos].add p5 proc generateDoc*(d: PDoc, n, orig: PNode, docFlags: DocFlags = kDefault) = template genItemAux(skind) = genItem(d, n, n[namePos], skind, docFlags) case n.kind of nkPragma: let pragmaNode = findPragma(n, wDeprecated) d.modDeprecationMsg.add(genDeprecationMsg(d, pragmaNode)) of nkCommentStmt: d.modDesc.add(genComment(d, n)) of nkProcDef: when useEffectSystem: documentRaises(d.cache, n) genItemAux(skProc) of nkFuncDef: when useEffectSystem: documentRaises(d.cache, n) genItemAux(skFunc) of nkMethodDef: when useEffectSystem: documentRaises(d.cache, n) genItemAux(skMethod) of nkIteratorDef: when useEffectSystem: documentRaises(d.cache, n) genItemAux(skIterator) of nkMacroDef: genItemAux(skMacro) of nkTemplateDef: genItemAux(skTemplate) of nkConverterDef: when useEffectSystem: documentRaises(d.cache, n) genItemAux(skConverter) of nkTypeSection, nkVarSection, nkLetSection, nkConstSection: for i in 0..