tgenast.nim 8.7 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275
  1. discard """
  2. matrix: "--mm:orc; --mm:refc"
  3. """
  4. # xxx also test on js
  5. import std/genasts
  6. import std/macros
  7. from std/strformat import `&`
  8. import std/assertions
  9. import ./mgenast
  10. proc main =
  11. block:
  12. macro bar(x0: static Foo, x1: Foo, x2: Foo, xignored: Foo): untyped =
  13. let s0 = "not captured!"
  14. let s1 = "not captured!"
  15. let xignoredLocal = kfoo4
  16. # newLit optional:
  17. let x3 = newLit kfoo4
  18. let x3b = kfoo4
  19. result = genAstOpt({kDirtyTemplate}, s1=true, s2="asdf", x0, x1=x1, x2, x3, x3b):
  20. doAssert not declared(xignored)
  21. doAssert not declared(xignoredLocal)
  22. (s1, s2, s0, x0, x1, x2, x3, x3b)
  23. let s0 = "caller scope!"
  24. doAssert bar(kfoo1, kfoo2, kfoo3, kfoo4) ==
  25. (true, "asdf", "caller scope!", kfoo1, kfoo2, kfoo3, kfoo4, kfoo4)
  26. block:
  27. # doesn't have limitation mentioned in https://github.com/nim-lang/RFCs/issues/122#issue-401636535
  28. macro abc(name: untyped): untyped =
  29. result = genAst(name):
  30. type name = object
  31. abc(Bar)
  32. doAssert Bar.default == Bar()
  33. block:
  34. # backticks parser limitations / ambiguities not are an issue with `genAst`:
  35. # (#10326 #9745 are fixed but `quote do` still has underlying ambiguity issue
  36. # with backticks)
  37. type Foo = object
  38. a: int
  39. macro m1(): untyped =
  40. # result = quote do: # Error: undeclared identifier: 'a1'
  41. result = genAst:
  42. template `a1=`(x: var Foo, val: int) =
  43. x.a = val
  44. m1()
  45. var x0: Foo
  46. x0.a1 = 10
  47. doAssert x0 == Foo(a: 10)
  48. block:
  49. # avoids bug #7375
  50. macro fun(b: static[bool], b2: bool): untyped =
  51. result = newStmtList()
  52. macro foo(c: bool): untyped =
  53. var b = false
  54. result = genAst(b, c):
  55. fun(b, c)
  56. foo(true)
  57. block:
  58. # avoids bug #7589
  59. # since `==` works with genAst, the problem goes away
  60. macro foo2(): untyped =
  61. # result = quote do: # Error: '==' cannot be passed to a procvar
  62. result = genAst:
  63. `==`(3,4)
  64. doAssert not foo2()
  65. block:
  66. # avoids bug #7726
  67. # expressions such as `a.len` are just passed as arguments to `genAst`, and
  68. # caller scope is not polluted with definitions such as `let b = newLit a.len`
  69. macro foo(): untyped =
  70. let a = @[1, 2, 3, 4, 5]
  71. result = genAst(a, b = a.len): # shows 2 ways to get a.len
  72. (a.len, b)
  73. doAssert foo() == (5, 5)
  74. block:
  75. # avoids bug #9607
  76. proc fun1(info:LineInfo): string = "bar1"
  77. proc fun2(info:int): string = "bar2"
  78. macro bar2(args: varargs[untyped]): untyped =
  79. let info = args.lineInfoObj
  80. let fun1 = bindSym"fun1" # optional; we can remove this and also the
  81. # capture of fun1, as show in next example
  82. result = genAst(info, fun1):
  83. (fun1(info), fun2(info.line))
  84. doAssert bar2() == ("bar1", "bar2")
  85. macro bar3(args: varargs[untyped]): untyped =
  86. let info = args.lineInfoObj
  87. result = genAst(info):
  88. (fun1(info), fun2(info.line))
  89. doAssert bar3() == ("bar1", "bar2")
  90. macro bar(args: varargs[untyped]): untyped =
  91. let info = args.lineInfoObj
  92. let fun1 = bindSym"fun1"
  93. let fun2 = bindSym"fun2"
  94. result = genAstOpt({kDirtyTemplate}, info):
  95. (fun1(info), fun2(info.line))
  96. doAssert bar() == ("bar1", "bar2")
  97. block:
  98. # example from bug #7889 works
  99. # after changing method call syntax to regular call syntax; this is a
  100. # limitation described in bug #7085
  101. # note that `quote do` would also work after that change in this example.
  102. doAssert bindme2() == kfoo1
  103. doAssert bindme3() == kfoo1
  104. doAssert not compiles(bindme4()) # correctly gives Error: undeclared identifier: 'myLocalPriv'
  105. proc myLocalPriv2(): auto = kfoo2
  106. doAssert bindme5UseExpose() == kfoo1
  107. # example showing hijacking behavior when using `kDirtyTemplate`
  108. doAssert bindme5UseExposeFalse() == kfoo2
  109. # local `myLocalPriv2` hijacks symbol `mgenast.myLocalPriv2`. In most
  110. # use cases this is probably not what macro writer intends as it's
  111. # surprising; hence `kDirtyTemplate` is not the default.
  112. when nimvm: # disabled because `newStringStream` is used
  113. discard
  114. else:
  115. bindme6UseExpose()
  116. bindme6UseExposeFalse()
  117. block:
  118. macro mbar(x3: Foo, x3b: static Foo): untyped =
  119. var x1=kfoo3
  120. var x2=newLit kfoo3
  121. var x4=kfoo3
  122. var xLocal=kfoo3
  123. proc funLocal(): auto = kfoo4
  124. result = genAst(x1, x2, x3, x4):
  125. # local x1 overrides remote x1
  126. when false:
  127. # one advantage of using `kDirtyTemplate` is that these would hold:
  128. doAssert not declared xLocal
  129. doAssert not compiles(echo xLocal)
  130. # however, even without it, we at least correctly generate CT error
  131. # if trying to use un-captured symbol; this correctly gives:
  132. # Error: internal error: environment misses: xLocal
  133. echo xLocal
  134. proc foo1(): auto =
  135. # note that `funLocal` is captured implicitly, according to hygienic
  136. # template rules; with `kDirtyTemplate` it would not unless
  137. # captured in `genAst` capture list explicitly
  138. (a0: xRemote, a1: x1, a2: x2, a3: x3, a4: x4, a5: funLocal())
  139. return result
  140. proc main()=
  141. var xRemote=kfoo1
  142. var x1=kfoo2
  143. mbar(kfoo4, kfoo4)
  144. doAssert foo1() == (a0: kfoo1, a1: kfoo3, a2: kfoo3, a3: kfoo4, a4: kfoo3, a5: kfoo4)
  145. main()
  146. block:
  147. # With `kDirtyTemplate`, the example from #8220 works.
  148. # See https://nim-lang.github.io/Nim/strformat.html#limitations for
  149. # an explanation of why {.dirty.} is needed.
  150. macro foo(): untyped =
  151. result = genAstOpt({kDirtyTemplate}):
  152. let bar = "Hello, World"
  153. &"Let's interpolate {bar} in the string"
  154. doAssert foo() == "Let's interpolate Hello, World in the string"
  155. block: # nested application of genAst
  156. macro createMacro(name, obj, field: untyped): untyped =
  157. result = genAst(obj = newDotExpr(obj, field), lit = 10, name, field):
  158. # can't reuse `result` here, would clash
  159. macro name(arg: untyped): untyped =
  160. genAst(arg2=arg): # somehow `arg2` rename is needed
  161. (obj, astToStr(field), lit, arg2)
  162. var x = @[1, 2, 3]
  163. createMacro foo, x, len
  164. doAssert (foo 20) == (3, "len", 10, 20)
  165. block: # test with kNoNewLit
  166. macro bar(): untyped =
  167. let s1 = true
  168. template boo(x): untyped =
  169. fun(x)
  170. result = genAstOpt({kNoNewLit}, s1=newLit(s1), s1b=s1): (s1, s1b)
  171. doAssert bar() == (true, 1)
  172. block: # sanity check: check passing `{}` also works
  173. macro bar(): untyped =
  174. result = genAstOpt({}, s1=true): s1
  175. doAssert bar() == true
  176. block: # test passing function and type symbols
  177. proc z1(): auto = 41
  178. type Z4 = type(1'i8)
  179. macro bar(Z1: typedesc): untyped =
  180. proc z2(): auto = 42
  181. proc z3[T](a: T): auto = 43
  182. let Z2 = genAst():
  183. type(true)
  184. let z4 = genAst():
  185. proc myfun(): auto = 44
  186. myfun
  187. type Z3 = type(1'u8)
  188. result = genAst(z4, Z1, Z2):
  189. # z1, z2, z3, Z3, Z4 are captured automatically
  190. # z1, z2, z3 can optionally be specified in capture list
  191. (z1(), z2(), z3('a'), z4(), $Z1, $Z2, $Z3, $Z4)
  192. type Z1 = type('c')
  193. doAssert bar(Z1) == (41, 42, 43, 44, "char", "bool", "uint8", "int8")
  194. block: # fix bug #11986
  195. proc foo(): auto =
  196. var s = { 'a', 'b' }
  197. # var n = quote do: `s` # would print {97, 98}
  198. var n = genAst(s): s
  199. n.repr
  200. static: doAssert foo() == "{'a', 'b'}"
  201. block: # also from #11986
  202. macro foo(): untyped =
  203. var s = { 'a', 'b' }
  204. # quote do:
  205. # let t = `s`
  206. # $typeof(t) # set[range 0..65535(int)]
  207. genAst(s):
  208. let t = s
  209. $typeof(t)
  210. doAssert foo() == "set[char]"
  211. block:
  212. macro foo(): untyped =
  213. type Foo = object
  214. template baz2(a: int): untyped = a*10
  215. macro baz3(a: int): untyped = newLit 13
  216. result = newStmtList()
  217. result.add genAst(Foo, baz2, baz3) do: # shows you can pass types, templates etc
  218. var x: Foo
  219. $($typeof(x), baz2(3), baz3(4))
  220. let ret = genAst() do: # shows you don't have to, since they're inject'd
  221. var x: Foo
  222. $($typeof(x), baz2(3), baz3(4))
  223. doAssert foo() == """("Foo", 30, 13)"""
  224. block: # illustrates how symbol visiblity can be controlled precisely using `mixin`
  225. proc locafun1(): auto = "in locafun1 (caller scope)" # this will be used because of `mixin locafun1` => explicit hijacking is ok
  226. proc locafun2(): auto = "in locafun2 (caller scope)" # this won't be used => no hijacking
  227. proc locafun3(): auto = "in locafun3 (caller scope)"
  228. doAssert mixinExample() == ("in locafun1 (caller scope)", "in locafun2", "in locafun3 (caller scope)")
  229. static: main()
  230. main()