summary refs log tree commit diff stats
path: root/tests/stdlib/tmacros.nim
blob: 64a474743b6fa8dd66091c9117c7efc3f7d283fd (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
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
#[
xxx macros tests need to be reorganized to makes sure each API is tested once
See also:
  tests/macros/tdumpast.nim for treeRepr + friends
]#

import std/macros

block: # hasArgOfName
  macro m(u: untyped): untyped =
    for name in ["s","i","j","k","b","xs","ys"]:
      doAssert hasArgOfName(params u,name)
    doAssert not hasArgOfName(params u,"nonexistent")

  proc p(s: string; i,j,k: int; b: bool; xs,ys: seq[int] = @[]) {.m.} = discard

block: # bug #17454
  proc f(v: NimNode): string {.raises: [].} = $v

block: # unpackVarargs
  block:
    proc bar1(a: varargs[int]): string =
      for ai in a: result.add " " & $ai
    proc bar2(a: varargs[int]) =
      let s1 = bar1(a)
      let s2 = unpackVarargs(bar1, a) # `unpackVarargs` makes no difference here
      doAssert s1 == s2
    bar2(1, 2, 3)
    bar2(1)
    bar2()

  block:
    template call1(fun: typed; args: varargs[untyped]): untyped =
      unpackVarargs(fun, args)
    template call2(fun: typed; args: varargs[untyped]): untyped =
      # fun(args) # works except for last case with empty `args`, pending bug #9996
      when varargsLen(args) > 0: fun(args)
      else: fun()

    proc fn1(a = 0, b = 1) = discard (a, b)

    call1(fn1)
    call1(fn1, 10)
    call1(fn1, 10, 11)

    call2(fn1)
    call2(fn1, 10)
    call2(fn1, 10, 11)

  block:
    template call1(fun: typed; args: varargs[typed]): untyped =
      unpackVarargs(fun, args)
    template call2(fun: typed; args: varargs[typed]): untyped =
      # xxx this would give a confusing error message:
      # required type for a: varargs[typed] [varargs] but expression '[10]' is of type: varargs[typed] [varargs]
      when varargsLen(args) > 0: fun(args)
      else: fun()
    macro toString(a: varargs[typed, `$`]): string =
      var msg = genSym(nskVar, "msg")
      result = newStmtList()
      result.add quote do:
        var `msg` = ""
      for ai in a:
        result.add quote do: `msg`.add $`ai`
      result.add quote do: `msg`
    doAssert call1(toString) == ""
    doAssert call1(toString, 10) == "10"
    doAssert call1(toString, 10, 11) == "1011"

block: # SameType
  type
    A = int
    B = distinct int
    C = object
    Generic[T, Y] = object
  macro isSameType(a, b: typed): untyped =
    newLit(sameType(a, b))

  static:
    assert Generic[int, int].isSameType(Generic[int, int])
    assert Generic[A, string].isSameType(Generic[int, string])
    assert not Generic[A, string].isSameType(Generic[B, string])
    assert not Generic[int, string].isSameType(Generic[int, int])
    assert isSameType(int, A)
    assert isSameType(10, 20)
    assert isSameType("Hello", "world")
    assert not isSameType("Hello", cstring"world")
    assert not isSameType(int, B)
    assert not isSameType(int, Generic[int, int])
    assert not isSameType(C, string)
    assert not isSameType(C, int)


  #[
    # compiler sameType fails for the following, read more in `types.nim`'s `sameTypeAux`.
    type
      D[T] = C
      G[T] = T
    static:
      assert isSameType(D[int], C)
      assert isSameType(D[int], D[float])
      assert isSameType(G[float](1.0), float(1.0))
      assert isSameType(float(1.0), G[float](1.0))
  ]#

  type Tensor[T] = object
    data: T

  macro testTensorInt(x: typed): untyped =
    let
      tensorIntType = getTypeInst(Tensor[int])[1]
      xTyp = x.getTypeInst
    
    newLit(xTyp.sameType(tensorIntType))

  var
    x: Tensor[int]
    x1 = Tensor[float]()
    x2 = Tensor[A]()
    x3 = Tensor[B]()

  static: 
    assert testTensorInt(x)
    assert not testTensorInt(x1)
    assert testTensorInt(x2)
    assert not testTensorInt(x3)