summary refs log tree commit diff stats
path: root/tests/stdlib/tgenast.nim
blob: 0904b83dd1a0f7b1ade7e9c9d53f420a149bb535 (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
pre { line-height: 125%; }
td.linenos .normal { color: inherit; background-color: transparent; padding-left: 5px; padding-right: 5px; }
span.linenos { color: inherit; background-color: transparent; padding-left: 5px; padding-right: 5px; }
td.linenos .special { color: #000000; background-color: #ffffc0; padding-left: 5px; padding-right: 5px; }
span.linenos.special { color: #000000; background-color: #ffffc0; padding-left: 5px; padding-right: 5px; }
.highlight .hll { background-color: #ffffcc }
.highlight .c { color: #888888 } /* Comment */
.highlight .err { color: #a61717; background-color: #e3d2d2 } /* Error */
.highlight .k { color: #008800; font-weight: bold } /* Keyword */
.highlight .ch { color: #888888 } /* Comment.Hashbang */
.highlight .cm { color: #888888 } /* Comment.Multiline */
.highlight .cp { color: #cc0000; font-weight: bold } /* Comment.Preproc */
.highlight .cpf { color: #888888 } /* Comment.PreprocFile */
.highlight .c1 { color: #888888 } /* Comment.Single */
.highlight .cs { color: #cc0000; font-weight: bold; background-color: #fff0f0 } /* Comment.Special */
.highlight .gd { color: #000000; background-color: #ffdddd } /* Generic.Deleted */
.highlight .ge { font-style: italic } /* Generic.Emph */
.highlight .ges { font-weight: bold; font-style: italic } /* Generic.EmphStrong */
.highlight .gr { color: #aa0000 } /* Generic.Error */
.highlight .gh { color: #333333 } /* Generic.Heading */
.highlight .gi { color: #000000; background-color: #ddffdd } /* Generic.Inserted */
.highlight .go { color: #888888 } /* Generic.Output */
.highlight .gp { color: #555555 } /* Generic.Prompt */
.highlight .gs { font-weight: bold } /* Generic.Strong */
.highlight .gu { color: #666666 } /* Generic.Subheading */
.highlight .gt { color: #aa0000 } /* Generic.Traceback */
.highlight .kc { color: #008800; font-weight: bold } /* Keyword.Constant */
.highlight .kd { color: #008800; font-weight: bold } /* Keyword.Declaration */
.highlight .kn { color: #008800; font-weight: bold } /* Keyword.Namespace */
.highlight .kp { color: #008800 } /* Keyword.Pseudo */
.highlight .kr { color: #008800; font-weight: bold } /* Keyword.Reserved */
.highlight .kt { color: #888888; font-weight: bold } /* Keyword.Type */
.highlight .m { color: #0000DD; font-weight: bold } /* Literal.Number */
.highlight .s { color: #dd2200; background-color: #fff0f0 } /* Literal.String */
.highlight .na { color: #336699 } /* Name.Attribute */
.highlight .nb { color: #003388 } /* Name.Builtin */
.highlight .nc { color: #bb0066; font-weight: bold } /* Name.Class */
.highlight .no { color: #003366; font-weight: bold } /* Name.Constant */
.highlight .nd { color: #555555 } /* Name.Decorator */
.highlight .ne { color: #bb0066; font-weight: bold } /* Name.Exception */
.highlight .nf { color: #0066bb; font-weight: bold } /* Name.Function */
.highlight .nl { color: #336699; font-style: italic } /* Name.Label */
.highlight .nn { color: #bb0066; font-weight: bold } /* Name.Namespace */
.highlight .py { color: #336699; font-weight: bold } /* Name.Property */
.highlight .nt { color: #bb0066; font-weight: bold } /* Name.Tag */
.highlight .nv { color: #336699 } /* Name.Variable */
.highlight .ow { color: #008800 } /* Operator.Word */
.highlight .w { color: #bbbbbb } /* Text.Whitespace */
.highlight .mb { color: #0000DD; font-weight: bold } /* Literal.Number.Bin */
.highlight .mf { color: #0000DD; font-weight: bold } /* Literal.Number.Float */
.highlight .mh { color: #0000DD; font-weight: bold } /* Literal.Number.Hex */
.highlight .mi { color: #0000DD; font-weight: bold } /* Literal.Number.Integer */
.highlight .mo { color: #0000DD; font-weight: bold } /* Literal.Number.Oct */
.highlight .sa { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Affix */
.highlight .sb { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Backtick */
.highlight .sc { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Char */
.highlight .dl { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Delimiter */
.highlight .sd { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Doc */
.highlight .s2 { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Double */
.highlight .se { color: #0044dd; background-color: #fff0f0 } /* Literal.String.Escape */
.highlight .sh { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Heredoc */
.highlight .si { color: #3333bb; background-color: #fff0f0 } /* Literal.String.Interpol */
.highlight .sx { color: #22bb22; background-color: #f0fff0 } /* Literal.String.Other */
.highlight .sr { color: #008800; background-color: #fff0ff } /* Literal.String.Regex */
.highlight .s1 { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Single */
.highlight .ss { color: #aa6600; background-color: #fff0f0 } /* Literal.String.Symbol */
.highlight .bp { color: #003388 } /* Name.Builtin.Pseudo */
.highlight .fm { color: #0066bb; font-weight: bold } /* Name.Function.Magic */
.highlight .vc { color: #336699 } /* Name.Variable.Class */
.highlight .vg { color: #dd7700 } /* Name.Variable.Global */
.highlight .vi { color: #3333bb } /* Name.Variable.Instance */
.highlight .vm { color: #336699 } /* Name.Variable.Magic */
.highlight .il { color: #0000DD; font-weight: bold } /* Literal.Number.Integer.Long */
/*		The portable font concept (!?*)
*/

/*	Line mode browser version:
*/
#ifndef HTFONT_H
#define HTFONT_H

typedef long int HTLMFont;	/* For now */

#define HT_NON_BREAK_SPACE ((char)1)	/* For now */
#define HT_EM_SPACE ((char)2) 		/* For now */


#define HT_FONT		0
#define HT_CAPITALS	1
#define HT_BOLD		2
#define HT_UNDERLINE	4
#define HT_INVERSE	8
#define HT_DOUBLE	0x10

#define HT_BLACK	0
#define HT_WHITE	1

#endif /* HTFONT_H */
ref='#n245'>245 246 247 248 249 250 251 252 253 254 255 256 257 258 259 260 261 262 263 264 265 266 267 268 269
# xxx also test on js

import std/genasts
import std/macros
from std/strformat import `&`
import ./mgenast

proc main =
  block:
    macro bar(x0: static Foo, x1: Foo, x2: Foo, xignored: Foo): untyped =
      let s0 = "not captured!"
      let s1 = "not captured!"
      let xignoredLocal = kfoo4

      # newLit optional:
      let x3 = newLit kfoo4
      let x3b = kfoo4

      result = genAstOpt({kDirtyTemplate}, s1=true, s2="asdf", x0, x1=x1, x2, x3, x3b):
        doAssert not declared(xignored)
        doAssert not declared(xignoredLocal)
        (s1, s2, s0, x0, x1, x2, x3, x3b)

    let s0 = "caller scope!"

    doAssert bar(kfoo1, kfoo2, kfoo3, kfoo4) ==
      (true, "asdf", "caller scope!", kfoo1, kfoo2, kfoo3, kfoo4, kfoo4)

  block:
    # doesn't have limitation mentioned in https://github.com/nim-lang/RFCs/issues/122#issue-401636535
    macro abc(name: untyped): untyped =
      result = genAst(name):
        type name = object

    abc(Bar)
    doAssert Bar.default == Bar()

  block:
    # backticks parser limitations / ambiguities not are an issue with `genAst`:
    # (#10326 #9745 are fixed but `quote do` still has underlying ambiguity issue
    # with backticks)
    type Foo = object
      a: int

    macro m1(): untyped =
      # result = quote do: # Error: undeclared identifier: 'a1'
      result = genAst:
        template `a1=`(x: var Foo, val: int) =
          x.a = val

    m1()
    var x0: Foo
    x0.a1 = 10
    doAssert x0 == Foo(a: 10)

  block:
    # avoids bug #7375
    macro fun(b: static[bool], b2: bool): untyped =
      result = newStmtList()
    macro foo(c: bool): untyped =
      var b = false
      result = genAst(b, c):
        fun(b, c)

    foo(true)

  block:
    # avoids bug #7589
    # since `==` works with genAst, the problem goes away
    macro foo2(): untyped =
      # result = quote do: # Error: '==' cannot be passed to a procvar
      result = genAst:
        `==`(3,4)
    doAssert not foo2()

  block:
    # avoids bug #7726
    # expressions such as `a.len` are just passed as arguments to `genAst`, and
    # caller scope is not polluted with definitions such as `let b = newLit a.len`
    macro foo(): untyped =
      let a = @[1, 2, 3, 4, 5]
      result = genAst(a, b = a.len): # shows 2 ways to get a.len
        (a.len, b)
    doAssert foo() == (5, 5)

  block:
    # avoids bug #9607
    proc fun1(info:LineInfo): string = "bar1"
    proc fun2(info:int): string = "bar2"

    macro bar2(args: varargs[untyped]): untyped =
      let info = args.lineInfoObj
      let fun1 = bindSym"fun1" # optional; we can remove this and also the
      # capture of fun1, as show in next example
      result = genAst(info, fun1):
        (fun1(info), fun2(info.line))
    doAssert bar2() == ("bar1", "bar2")

    macro bar3(args: varargs[untyped]): untyped =
      let info = args.lineInfoObj
      result = genAst(info):
        (fun1(info), fun2(info.line))
    doAssert bar3() == ("bar1", "bar2")

    macro bar(args: varargs[untyped]): untyped =
      let info = args.lineInfoObj
      let fun1 = bindSym"fun1"
      let fun2 = bindSym"fun2"
      result = genAstOpt({kDirtyTemplate}, info):
        (fun1(info), fun2(info.line))
    doAssert bar() == ("bar1", "bar2")

  block:
    # example from bug #7889 works
    # after changing method call syntax to regular call syntax; this is a
    # limitation described in bug #7085
    # note that `quote do` would also work after that change in this example.
    doAssert bindme2() == kfoo1
    doAssert bindme3() == kfoo1
    doAssert not compiles(bindme4()) # correctly gives Error: undeclared identifier: 'myLocalPriv'
    proc myLocalPriv2(): auto = kfoo2
    doAssert bindme5UseExpose() == kfoo1

    # example showing hijacking behavior when using `kDirtyTemplate`
    doAssert bindme5UseExposeFalse() == kfoo2
      # local `myLocalPriv2` hijacks symbol `mgenast.myLocalPriv2`. In most
      # use cases this is probably not what macro writer intends as it's
      # surprising; hence `kDirtyTemplate` is not the default.

    when nimvm: # disabled because `newStringStream` is used
      discard
    else:
      bindme6UseExpose()
      bindme6UseExposeFalse()

  block:
    macro mbar(x3: Foo, x3b: static Foo): untyped =
      var x1=kfoo3
      var x2=newLit kfoo3
      var x4=kfoo3
      var xLocal=kfoo3

      proc funLocal(): auto = kfoo4

      result = genAst(x1, x2, x3, x4):
        # local x1 overrides remote x1
        when false:
          # one advantage of using `kDirtyTemplate` is that these would hold:
          doAssert not declared xLocal
          doAssert not compiles(echo xLocal)
          # however, even without it, we at least correctly generate CT error
          # if trying to use un-captured symbol; this correctly gives:
          # Error: internal error: environment misses: xLocal
          echo xLocal

        proc foo1(): auto =
          # note that `funLocal` is captured implicitly, according to hygienic
          # template rules; with `kDirtyTemplate` it would not unless
          # captured in `genAst` capture list explicitly
          (a0: xRemote, a1: x1, a2: x2, a3: x3, a4: x4, a5: funLocal())

      return result

    proc main()=
      var xRemote=kfoo1
      var x1=kfoo2
      mbar(kfoo4, kfoo4)
      doAssert foo1() == (a0: kfoo1, a1: kfoo3, a2: kfoo3, a3: kfoo4, a4: kfoo3, a5: kfoo4)

    main()

  block:
    # With `kDirtyTemplate`, the example from #8220 works.
    # See https://nim-lang.github.io/Nim/strformat.html#limitations for
    # an explanation of why {.dirty.} is needed.
    macro foo(): untyped =
      result = genAstOpt({kDirtyTemplate}):
        let bar = "Hello, World"
        &"Let's interpolate {bar} in the string"
    doAssert foo() == "Let's interpolate Hello, World in the string"


  block: # nested application of genAst
    macro createMacro(name, obj, field: untyped): untyped =
      result = genAst(obj = newDotExpr(obj, field), lit = 10, name, field):
        # can't reuse `result` here, would clash
        macro name(arg: untyped): untyped =
          genAst(arg2=arg): # somehow `arg2` rename is needed
            (obj, astToStr(field), lit, arg2)

    var x = @[1, 2, 3]
    createMacro foo, x, len
    doAssert (foo 20) == (3, "len", 10, 20)

  block: # test with kNoNewLit
    macro bar(): untyped =
      let s1 = true
      template boo(x): untyped =
        fun(x)
      result = genAstOpt({kNoNewLit}, s1=newLit(s1), s1b=s1): (s1, s1b)
    doAssert bar() == (true, 1)

  block: # sanity check: check passing `{}` also works
    macro bar(): untyped =
      result = genAstOpt({}, s1=true): s1
    doAssert bar() == true

  block: # test passing function and type symbols
    proc z1(): auto = 41
    type Z4 = type(1'i8)
    macro bar(Z1: typedesc): untyped =
      proc z2(): auto = 42
      proc z3[T](a: T): auto = 43
      let Z2 = genAst():
        type(true)
      let z4 = genAst():
        proc myfun(): auto = 44
        myfun
      type Z3 = type(1'u8)
      result = genAst(z4, Z1, Z2):
        # z1, z2, z3, Z3, Z4 are captured automatically
        # z1, z2, z3 can optionally be specified in capture list
        (z1(), z2(), z3('a'), z4(), $Z1, $Z2, $Z3, $Z4)
    type Z1 = type('c')
    doAssert bar(Z1) == (41, 42, 43, 44, "char", "bool", "uint8", "int8")

  block: # fix bug #11986
    proc foo(): auto =
      var s = { 'a', 'b' }
      # var n = quote do: `s` # would print {97, 98}
      var n = genAst(s): s
      n.repr
    static: doAssert foo() == "{'a', 'b'}"

  block: # also from #11986
    macro foo(): untyped =
      var s = { 'a', 'b' }
      # quote do:
      #   let t = `s`
      #   $typeof(t) # set[range 0..65535(int)]
      genAst(s):
        let t = s
        $typeof(t)
    doAssert foo() == "set[char]"

  block:
    macro foo(): untyped =
      type Foo = object
      template baz2(a: int): untyped = a*10
      macro baz3(a: int): untyped = newLit 13
      result = newStmtList()

      result.add genAst(Foo, baz2, baz3) do: # shows you can pass types, templates etc
        var x: Foo
        $($typeof(x), baz2(3), baz3(4))

      let ret = genAst() do: # shows you don't have to, since they're inject'd
        var x: Foo
        $($typeof(x), baz2(3), baz3(4))
    doAssert foo() == """("Foo", 30, 13)"""

  block: # illustrates how symbol visiblity can be controlled precisely using `mixin`
    proc locafun1(): auto = "in locafun1 (caller scope)" # this will be used because of `mixin locafun1` => explicit hijacking is ok
    proc locafun2(): auto = "in locafun2 (caller scope)" # this won't be used => no hijacking
    proc locafun3(): auto = "in locafun3 (caller scope)"
    doAssert mixinExample() == ("in locafun1 (caller scope)", "in locafun2", "in locafun3 (caller scope)")

static: main()
main()