tmacros.nim 8.4 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350
  1. discard """
  2. matrix: "--mm:refc; --mm:orc"
  3. """
  4. #[
  5. xxx macros tests need to be reorganized to makes sure each API is tested once
  6. See also:
  7. tests/macros/tdumpast.nim for treeRepr + friends
  8. ]#
  9. import std/macros
  10. import std/assertions
  11. block: # hasArgOfName
  12. macro m(u: untyped): untyped =
  13. for name in ["s","i","j","k","b","xs","ys"]:
  14. doAssert hasArgOfName(params u,name)
  15. doAssert not hasArgOfName(params u,"nonexistent")
  16. proc p(s: string; i,j,k: int; b: bool; xs,ys: seq[int] = @[]) {.m.} = discard
  17. block: # bug #17454
  18. proc f(v: NimNode): string {.raises: [].} = $v
  19. block: # unpackVarargs
  20. block:
  21. proc bar1(a: varargs[int]): string =
  22. for ai in a: result.add " " & $ai
  23. proc bar2(a: varargs[int]) =
  24. let s1 = bar1(a)
  25. let s2 = unpackVarargs(bar1, a) # `unpackVarargs` makes no difference here
  26. doAssert s1 == s2
  27. bar2(1, 2, 3)
  28. bar2(1)
  29. bar2()
  30. block:
  31. template call1(fun: typed; args: varargs[untyped]): untyped =
  32. unpackVarargs(fun, args)
  33. template call2(fun: typed; args: varargs[untyped]): untyped =
  34. # fun(args) # works except for last case with empty `args`, pending bug #9996
  35. when varargsLen(args) > 0: fun(args)
  36. else: fun()
  37. proc fn1(a = 0, b = 1) = discard (a, b)
  38. call1(fn1)
  39. call1(fn1, 10)
  40. call1(fn1, 10, 11)
  41. call2(fn1)
  42. call2(fn1, 10)
  43. call2(fn1, 10, 11)
  44. block:
  45. template call1(fun: typed; args: varargs[typed]): untyped =
  46. unpackVarargs(fun, args)
  47. template call2(fun: typed; args: varargs[typed]): untyped =
  48. # xxx this would give a confusing error message:
  49. # required type for a: varargs[typed] [varargs] but expression '[10]' is of type: varargs[typed] [varargs]
  50. when varargsLen(args) > 0: fun(args)
  51. else: fun()
  52. macro toString(a: varargs[typed, `$`]): string =
  53. var msg = genSym(nskVar, "msg")
  54. result = newStmtList()
  55. result.add quote do:
  56. var `msg` = ""
  57. for ai in a:
  58. result.add quote do: `msg`.add $`ai`
  59. result.add quote do: `msg`
  60. doAssert call1(toString) == ""
  61. doAssert call1(toString, 10) == "10"
  62. doAssert call1(toString, 10, 11) == "1011"
  63. block: # SameType
  64. type
  65. A = int
  66. B = distinct int
  67. C = object
  68. Generic[T, Y] = object
  69. macro isSameType(a, b: typed): untyped =
  70. newLit(sameType(a, b))
  71. static:
  72. assert Generic[int, int].isSameType(Generic[int, int])
  73. assert Generic[A, string].isSameType(Generic[int, string])
  74. assert not Generic[A, string].isSameType(Generic[B, string])
  75. assert not Generic[int, string].isSameType(Generic[int, int])
  76. assert isSameType(int, A)
  77. assert isSameType(10, 20)
  78. assert isSameType("Hello", "world")
  79. assert not isSameType("Hello", cstring"world")
  80. assert not isSameType(int, B)
  81. assert not isSameType(int, Generic[int, int])
  82. assert not isSameType(C, string)
  83. assert not isSameType(C, int)
  84. #[
  85. # compiler sameType fails for the following, read more in `types.nim`'s `sameTypeAux`.
  86. type
  87. D[T] = C
  88. G[T] = T
  89. static:
  90. assert isSameType(D[int], C)
  91. assert isSameType(D[int], D[float])
  92. assert isSameType(G[float](1.0), float(1.0))
  93. assert isSameType(float(1.0), G[float](1.0))
  94. ]#
  95. type Tensor[T] = object
  96. data: T
  97. macro testTensorInt(x: typed): untyped =
  98. let
  99. tensorIntType = getTypeInst(Tensor[int])[1]
  100. xTyp = x.getTypeInst
  101. newLit(xTyp.sameType(tensorIntType))
  102. var
  103. x: Tensor[int]
  104. x1 = Tensor[float]()
  105. x2 = Tensor[A]()
  106. x3 = Tensor[B]()
  107. static:
  108. assert testTensorInt(x)
  109. assert not testTensorInt(x1)
  110. assert testTensorInt(x2)
  111. assert not testTensorInt(x3)
  112. block: # extractDocCommentsAndRunnables
  113. macro checkRunnables(prc: untyped) =
  114. let runnables = prc.body.extractDocCommentsAndRunnables()
  115. doAssert runnables[0][0].eqIdent("runnableExamples")
  116. macro checkComments(comment: static[string], prc: untyped) =
  117. let comments = prc.body.extractDocCommentsAndRunnables()
  118. doAssert comments[0].strVal == comment
  119. proc a() {.checkRunnables.} =
  120. runnableExamples: discard
  121. discard
  122. proc b() {.checkRunnables.} =
  123. runnableExamples "-d:ssl": discard
  124. discard
  125. proc c() {.checkComments("Hello world").} =
  126. ## Hello world
  127. block: # bug #19020
  128. type
  129. foo = object
  130. template typ(T:typedesc) {.pragma.}
  131. proc bar() {.typ: foo.} = discard
  132. static:
  133. doAssert $bar.getCustomPragmaVal(typ) == "foo"
  134. doAssert $bar.getCustomPragmaVal(typ) == "foo"
  135. block hasCustomPragmaGeneric:
  136. template examplePragma() {.pragma.}
  137. type
  138. Foo[T] {.examplePragma.} = object
  139. x {.examplePragma.}: T
  140. var f: Foo[string]
  141. doAssert f.hasCustomPragma(examplePragma)
  142. doAssert f.x.hasCustomPragma(examplePragma)
  143. block getCustomPragmaValGeneric:
  144. template examplePragma(x: int) {.pragma.}
  145. type
  146. Foo[T] {.examplePragma(42).} = object
  147. x {.examplePragma(25).}: T
  148. var f: Foo[string]
  149. doAssert f.getCustomPragmaVal(examplePragma) == 42
  150. doAssert f.x.getCustomPragmaVal(examplePragma) == 25
  151. block: # bug #21326
  152. macro foo(body: untyped): untyped =
  153. let a = body.lineInfoObj()
  154. let aLit = a.newLit
  155. result = quote do:
  156. doAssert $`a` == $`aLit`
  157. foo:
  158. let c = 1
  159. template name(a: LineInfo): untyped =
  160. discard a # `aLit` works though
  161. macro foo3(body: untyped): untyped =
  162. let a = body.lineInfoObj()
  163. # let ax = newLit(a)
  164. result = getAst(name(a))
  165. foo3:
  166. let c = 1
  167. block: # bug #7375
  168. macro fails(b: static[bool]): untyped =
  169. doAssert b == false
  170. result = newStmtList()
  171. macro foo(): untyped =
  172. var b = false
  173. ## Fails
  174. result = quote do:
  175. fails(`b`)
  176. foo()
  177. macro someMacro(): untyped =
  178. template tmpl(boolean: bool) =
  179. when boolean:
  180. discard "it's true!"
  181. else:
  182. doAssert false
  183. result = getAst(tmpl(true))
  184. someMacro()
  185. block:
  186. macro foo(): untyped =
  187. result = quote do: `littleEndian`
  188. doAssert littleEndian == foo()
  189. block:
  190. macro eqSym(x, y: untyped): untyped =
  191. let eq = $x == $y # Unfortunately eqIdent compares to string.
  192. result = quote do: `eq`
  193. var r, a, b: int
  194. template fma(result: var int, a, b: int, op: untyped) =
  195. # fused multiple-add
  196. when eqSym(op, `+=`):
  197. discard "+="
  198. else:
  199. discard "+"
  200. fma(r, a, b, `+=`)
  201. block:
  202. template test(boolArg: bool) =
  203. static:
  204. doAssert typeof(boolArg) is bool
  205. let x: bool = boolArg # compile error here, because boolArg became an int
  206. macro testWrapped1(boolArg: bool): untyped =
  207. # forwarding boolArg directly works
  208. result = getAst(test(boolArg))
  209. macro testWrapped2(boolArg: bool): untyped =
  210. # forwarding boolArg via a local variable also works
  211. let b = boolArg
  212. result = getAst(test(b))
  213. macro testWrapped3(boolArg: bool): untyped =
  214. # but using a literal `true` as a local variable will be converted to int
  215. let b = true
  216. result = getAst(test(b))
  217. test(true) # ok
  218. testWrapped1(true) # ok
  219. testWrapped2(true) # ok
  220. testWrapped3(true)
  221. block:
  222. macro foo(): untyped =
  223. var s = { 'a', 'b' }
  224. quote do:
  225. let t = `s`
  226. doAssert $typeof(t) == "set[char]"
  227. foo()
  228. block: # bug #9607
  229. proc fun1(info:LineInfo): string = "bar"
  230. proc fun2(info:int): string = "bar"
  231. macro echoL(args: varargs[untyped]): untyped =
  232. let info = args.lineInfoObj
  233. let fun1 = bindSym"fun1"
  234. let fun2 = bindSym"fun2"
  235. # this would work instead
  236. # result = newCall(bindSym"fun2", info.line.newLit)
  237. result = quote do:
  238. # BUG1: ???(0, 0) Error: internal error: genLiteral: ty is nil
  239. `fun1`(`info`)
  240. macro echoM(args: varargs[untyped]): untyped =
  241. let info = args.lineInfoObj
  242. let fun1 = bindSym"fun1"
  243. let fun2 = bindSym"fun2"
  244. # this would work instead
  245. # result = newCall(bindSym"fun2", info.line.newLit)
  246. result = quote do:
  247. # BUG1: ???(0, 0) Error: internal error: genLiteral: ty is nil
  248. `fun2`(`info`.line)
  249. doAssert echoL() == "bar"
  250. doAssert echoM() == "bar"
  251. block:
  252. macro hello[T](x: T): untyped =
  253. result = quote do:
  254. let m: `T` = `x`
  255. discard m
  256. hello(12)
  257. block:
  258. proc hello(x: int, y: typedesc) =
  259. discard
  260. macro main =
  261. let x = 12
  262. result = quote do:
  263. `hello`(12, type(x))
  264. main()
  265. block: # bug #22947
  266. macro bar[N: static int](a: var array[N, int]) =
  267. result = quote do:
  268. for i in 0 ..< `N`:
  269. `a`[i] = i
  270. func foo[N: static int](a: var array[N, int]) =
  271. bar(a)
  272. var a: array[4, int]
  273. foo(a)