summary refs log tree commit diff stats
path: root/tests/stdlib/tdochelpers.nim
blob: 8dcb158cacd1eaec57772ff2961864284821165d (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
discard """
  output: '''

[Suite] Integration with Nim
'''
"""

# tests for dochelpers.nim module

import ../../lib/packages/docutils/[rstast, rst, dochelpers]
import unittest

proc rstParseTest(text: string): PRstNode =
  proc testMsgHandler(filename: string, line, col: int, msgkind: MsgKind,
                      arg: string) =
    doAssert msgkind == mwBrokenLink
  let r = rstParse(text, "-input-", LineRstInit, ColRstInit,
                   {roPreferMarkdown, roSupportMarkdown, roNimFile},
                   msgHandler=testMsgHandler)
  result = r.node

suite "Integration with Nim":
  test "simple symbol parsing (shortest form)":
    let input1 = "g_".rstParseTest
    check input1.toLangSymbol == LangSymbol(symKind: "", name: "g")

  test "simple symbol parsing (group of words)":
    let input1 = "`Y`_".rstParseTest
    check input1.toLangSymbol == LangSymbol(symKind: "", name: "Y")

    # this means not a statement 'type', it's a backticked identifier `type`:
    let input2 = "`type`_".rstParseTest
    check input2.toLangSymbol == LangSymbol(symKind: "", name: "type")

    let input3 = "`[]`_".rstParseTest
    check input3.toLangSymbol == LangSymbol(symKind: "", name: "[]")

    let input4 = "`X Y Z`_".rstParseTest
    check input4.toLangSymbol == LangSymbol(symKind: "", name: "Xyz")

  test "simple proc parsing":
    let input1 = "proc f".rstParseTest
    check input1.toLangSymbol == LangSymbol(symKind: "proc", name: "f")

  test "another backticked name":
    let input1 = """`template \`type\``_""".rstParseTest
    check input1.toLangSymbol == LangSymbol(symKind: "template", name: "type")

  test "simple proc parsing with parameters":
    let input1 = "`proc f*()`_".rstParseTest
    let input2 = "`proc f()`_".rstParseTest
    let expected = LangSymbol(symKind: "proc", name: "f",
                              parametersProvided: true)
    check input1.toLangSymbol == expected
    check input2.toLangSymbol == expected

  test "symbol parsing with 1 parameter":
    let input = "`f(G[int])`_".rstParseTest
    let expected = LangSymbol(symKind: "", name: "f",
                              parameters: @[("G[int]", "")],
                              parametersProvided: true)
    check input.toLangSymbol == expected

  test "more proc parsing":
    let input1 = "`proc f[T](x:G[T]):M[T]`_".rstParseTest
    let input2 = "`proc f[ T ] ( x: G [T] ): M[T]`_".rstParseTest
    let input3 = "`proc f*[T](x: G[T]): M[T]`_".rstParseTest
    let expected = LangSymbol(symKind: "proc",
                              name: "f",
                              generics: "[T]",
                              parameters: @[("x", "G[T]")],
                              parametersProvided: true,
                              outType: "M[T]")
    check(input1.toLangSymbol == expected)
    check(input2.toLangSymbol == expected)
    check(input3.toLangSymbol == expected)

  test "advanced proc parsing with Nim identifier normalization":
    let input = """`proc binarySearch*[T, K](a: openarray[T]; key: K;
                    cmp: proc (x: T; y: K): int)`_""".rstParseTest
    let expected = LangSymbol(symKind: "proc",
                              name: "binarysearch",
                              generics: "[T,K]",
                              parameters: @[
                                ("a", "openarray[T]"),
                                ("key", "K"),
                                ("cmp", "proc(x:T;y:K):int")],
                              parametersProvided: true,
                              outType: "")
    check(input.toLangSymbol == expected)

  test "the same without proc":
    let input = """`binarySearch*[T, K](a: openarray[T]; key: K;
                    cmp: proc (x: T; y: K): int {.closure.})`_""".rstParseTest
    let expected = LangSymbol(symKind: "",
                              name: "binarysearch",
                              generics: "[T,K]",
                              parameters: @[
                                ("a", "openarray[T]"),
                                ("key", "K"),
                                ("cmp", "proc(x:T;y:K):int")],
                              parametersProvided: true,
                              outType: "")
    check(input.toLangSymbol == expected)

  test "operator $ with and without backticks":
    let input1 = """`func \`$\`*[T](a: \`open Array\`[T]): string`_""".
                  rstParseTest
    let input2 = """`func $*[T](a: \`open Array\`[T]): string`_""".
                  rstParseTest
    let expected = LangSymbol(symKind: "func",
                              name: "$",
                              generics: "[T]",
                              parameters: @[("a", "openarray[T]")],
                              parametersProvided: true,
                              outType: "string")
    check(input1.toLangSymbol == expected)
    check(input2.toLangSymbol == expected)

  test "operator [] with and without backticks":
    let input1 = """`func \`[]\`[T](a: \`open Array\`[T], idx: int): T`_""".
                  rstParseTest
    let input2 = """`func [][T](a: \`open Array\`[T], idx: int): T`_""".
                  rstParseTest
    let expected = LangSymbol(symKind: "func",
                              name: "[]",
                              generics: "[T]",
                              parameters: @[("a", "openarray[T]"),
                                            ("idx", "int")],
                              parametersProvided: true,
                              outType: "T")
    check(input1.toLangSymbol == expected)
    check(input2.toLangSymbol == expected)

  test "postfix symbol specifier #1":
    let input = """`walkDir iterator`_""".
                  rstParseTest
    let expected = LangSymbol(symKind: "iterator",
                              name: "walkdir")
    check(input.toLangSymbol == expected)

  test "postfix symbol specifier #2":
    let input1 = """`\`[]\`[T](a: \`open Array\`[T], idx: int): T func`_""".
                  rstParseTest
    let input2 = """`[][T](a: \`open Array\`[T], idx: int): T func`_""".
                  rstParseTest
    let expected = LangSymbol(symKind: "func",
                              name: "[]",
                              generics: "[T]",
                              parameters: @[("a", "openarray[T]"),
                                            ("idx", "int")],
                              parametersProvided: true,
                              outType: "T")
    check(input1.toLangSymbol == expected)
    check(input2.toLangSymbol == expected)

  test "type of type":
    check ("`CopyFlag enum`_".rstParseTest.toLangSymbol ==
           LangSymbol(symKind: "type",
                      symTypeKind: "enum",
                      name: "Copyflag"))