tmacros.nim 7.9 KB

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