tgenast.nim 8.6 KB

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