1#
2#
3#           The Nim Compiler
4#        (c) Copyright 2013 Andreas Rumpf
5#
6#    See the file "copying.txt", included in this
7#    distribution, for details about the copyright.
8#
9
10# included from cgen.nim
11
12when defined(nimCompilerStacktraceHints):
13  import std/stackframes
14
15proc getNullValueAuxT(p: BProc; orig, t: PType; obj, constOrNil: PNode,
16                      result: var Rope; count: var int;
17                      isConst: bool, info: TLineInfo)
18
19# -------------------------- constant expressions ------------------------
20
21proc rdSetElemLoc(conf: ConfigRef; a: TLoc, typ: PType): Rope
22
23proc int64Literal(i: BiggestInt): Rope =
24  if i > low(int64):
25    result = "IL64($1)" % [rope(i)]
26  else:
27    result = ~"(IL64(-9223372036854775807) - IL64(1))"
28
29proc uint64Literal(i: uint64): Rope = rope($i & "ULL")
30
31proc intLiteral(i: BiggestInt): Rope =
32  if i > low(int32) and i <= high(int32):
33    result = rope(i)
34  elif i == low(int32):
35    # Nim has the same bug for the same reasons :-)
36    result = ~"(-2147483647 -1)"
37  elif i > low(int64):
38    result = "IL64($1)" % [rope(i)]
39  else:
40    result = ~"(IL64(-9223372036854775807) - IL64(1))"
41
42proc intLiteral(i: Int128): Rope =
43  intLiteral(toInt64(i))
44
45proc genLiteral(p: BProc, n: PNode, ty: PType): Rope =
46  case n.kind
47  of nkCharLit..nkUInt64Lit:
48    var k: TTypeKind
49    if ty != nil:
50      k = skipTypes(ty, abstractVarRange).kind
51    else:
52      case n.kind
53      of nkCharLit: k = tyChar
54      of nkUInt64Lit: k = tyUInt64
55      of nkInt64Lit: k = tyInt64
56      else: k = tyNil # don't go into the case variant that uses 'ty'
57    case k
58    of tyChar, tyNil:
59      result = intLiteral(n.intVal)
60    of tyBool:
61      if n.intVal != 0: result = ~"NIM_TRUE"
62      else: result = ~"NIM_FALSE"
63    of tyInt64: result = int64Literal(n.intVal)
64    of tyUInt64: result = uint64Literal(uint64(n.intVal))
65    else:
66      result = "(($1) $2)" % [getTypeDesc(p.module,
67          ty), intLiteral(n.intVal)]
68  of nkNilLit:
69    let k = if ty == nil: tyPointer else: skipTypes(ty, abstractVarRange).kind
70    if k == tyProc and skipTypes(ty, abstractVarRange).callConv == ccClosure:
71      let id = nodeTableTestOrSet(p.module.dataCache, n, p.module.labels)
72      result = p.module.tmpBase & rope(id)
73      if id == p.module.labels:
74        # not found in cache:
75        inc(p.module.labels)
76        p.module.s[cfsData].addf(
77             "static NIM_CONST $1 $2 = {NIM_NIL,NIM_NIL};$n",
78             [getTypeDesc(p.module, ty), result])
79    elif k in {tyPointer, tyNil, tyProc}:
80      result = rope("NIM_NIL")
81    else:
82      result = "(($1) NIM_NIL)" % [getTypeDesc(p.module, ty)]
83  of nkStrLit..nkTripleStrLit:
84    let k = if ty == nil: tyString
85            else: skipTypes(ty, abstractVarRange + {tyStatic, tyUserTypeClass, tyUserTypeClassInst}).kind
86    case k
87    of tyNil:
88      result = genNilStringLiteral(p.module, n.info)
89    of tyString:
90      # with the new semantics for not 'nil' strings, we can map "" to nil and
91      # save tons of allocations:
92      if n.strVal.len == 0 and optSeqDestructors notin p.config.globalOptions:
93        result = genNilStringLiteral(p.module, n.info)
94      else:
95        result = genStringLiteral(p.module, n)
96    else:
97      result = makeCString(n.strVal)
98  of nkFloatLit, nkFloat64Lit:
99    if ty.kind == tyFloat32:
100      result = rope(n.floatVal.float32.toStrMaxPrecision)
101    else:
102      result = rope(n.floatVal.toStrMaxPrecision)
103  of nkFloat32Lit:
104    result = rope(n.floatVal.float32.toStrMaxPrecision)
105  else:
106    internalError(p.config, n.info, "genLiteral(" & $n.kind & ')')
107    result = nil
108
109proc genLiteral(p: BProc, n: PNode): Rope =
110  result = genLiteral(p, n, n.typ)
111
112proc bitSetToWord(s: TBitSet, size: int): BiggestUInt =
113  result = 0
114  for j in 0..<size:
115    if j < s.len: result = result or (BiggestUInt(s[j]) shl (j * 8))
116
117proc genRawSetData(cs: TBitSet, size: int): Rope =
118  if size > 8:
119    var res = "{\n"
120    for i in 0..<size:
121      res.add "0x"
122      res.add "0123456789abcdef"[cs[i] div 16]
123      res.add "0123456789abcdef"[cs[i] mod 16]
124      if i < size - 1:
125        # not last iteration
126        if i mod 8 == 7:
127          res.add ",\n"
128        else:
129          res.add ", "
130      else:
131        res.add "}\n"
132
133    result = rope(res)
134  else:
135    result = intLiteral(cast[BiggestInt](bitSetToWord(cs, size)))
136
137proc genSetNode(p: BProc, n: PNode): Rope =
138  var size = int(getSize(p.config, n.typ))
139  let cs = toBitSet(p.config, n)
140  if size > 8:
141    let id = nodeTableTestOrSet(p.module.dataCache, n, p.module.labels)
142    result = p.module.tmpBase & rope(id)
143    if id == p.module.labels:
144      # not found in cache:
145      inc(p.module.labels)
146      p.module.s[cfsData].addf("static NIM_CONST $1 $2 = $3;$n",
147           [getTypeDesc(p.module, n.typ), result, genRawSetData(cs, size)])
148  else:
149    result = genRawSetData(cs, size)
150
151proc getStorageLoc(n: PNode): TStorageLoc =
152  ## deadcode
153  case n.kind
154  of nkSym:
155    case n.sym.kind
156    of skParam, skTemp:
157      result = OnStack
158    of skVar, skForVar, skResult, skLet:
159      if sfGlobal in n.sym.flags: result = OnHeap
160      else: result = OnStack
161    of skConst:
162      if sfGlobal in n.sym.flags: result = OnHeap
163      else: result = OnUnknown
164    else: result = OnUnknown
165  of nkDerefExpr, nkHiddenDeref:
166    case n[0].typ.kind
167    of tyVar, tyLent: result = OnUnknown
168    of tyPtr: result = OnStack
169    of tyRef: result = OnHeap
170    else: doAssert(false, "getStorageLoc")
171  of nkBracketExpr, nkDotExpr, nkObjDownConv, nkObjUpConv:
172    result = getStorageLoc(n[0])
173  else: result = OnUnknown
174
175proc canMove(p: BProc, n: PNode; dest: TLoc): bool =
176  # for now we're conservative here:
177  if n.kind == nkBracket:
178    # This needs to be kept consistent with 'const' seq code
179    # generation!
180    if not isDeepConstExpr(n) or n.len == 0:
181      if skipTypes(n.typ, abstractVarRange).kind == tySequence:
182        return true
183  elif n.kind in nkStrKinds and n.strVal.len == 0:
184    # Empty strings are codegen'd as NIM_NIL so it's just a pointer copy
185    return true
186  result = n.kind in nkCallKinds
187  #if not result and dest.k == locTemp:
188  #  return true
189
190  #if result:
191  #  echo n.info, " optimized ", n
192  #  result = false
193
194proc genRefAssign(p: BProc, dest, src: TLoc) =
195  if (dest.storage == OnStack and p.config.selectedGC != gcGo) or not usesWriteBarrier(p.config):
196    linefmt(p, cpsStmts, "$1 = $2;$n", [rdLoc(dest), rdLoc(src)])
197  elif dest.storage == OnHeap:
198    linefmt(p, cpsStmts, "#asgnRef((void**) $1, $2);$n",
199            [addrLoc(p.config, dest), rdLoc(src)])
200  else:
201    linefmt(p, cpsStmts, "#unsureAsgnRef((void**) $1, $2);$n",
202            [addrLoc(p.config, dest), rdLoc(src)])
203
204proc asgnComplexity(n: PNode): int =
205  if n != nil:
206    case n.kind
207    of nkSym: result = 1
208    of nkRecCase:
209      # 'case objects' are too difficult to inline their assignment operation:
210      result = 100
211    of nkRecList:
212      for t in items(n):
213        result += asgnComplexity(t)
214    else: discard
215
216proc optAsgnLoc(a: TLoc, t: PType, field: Rope): TLoc =
217  assert field != nil
218  result.k = locField
219  result.storage = a.storage
220  result.lode = lodeTyp t
221  result.r = rdLoc(a) & "." & field
222
223proc genOptAsgnTuple(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
224  let newflags =
225    if src.storage == OnStatic:
226      flags + {needToCopy}
227    elif tfShallow in dest.t.flags:
228      flags - {needToCopy}
229    else:
230      flags
231  let t = skipTypes(dest.t, abstractInst).getUniqueType()
232  for i in 0..<t.len:
233    let t = t[i]
234    let field = "Field$1" % [i.rope]
235    genAssignment(p, optAsgnLoc(dest, t, field),
236                     optAsgnLoc(src, t, field), newflags)
237
238proc genOptAsgnObject(p: BProc, dest, src: TLoc, flags: TAssignmentFlags,
239                      t: PNode, typ: PType) =
240  if t == nil: return
241  let newflags =
242    if src.storage == OnStatic:
243      flags + {needToCopy}
244    elif tfShallow in dest.t.flags:
245      flags - {needToCopy}
246    else:
247      flags
248  case t.kind
249  of nkSym:
250    let field = t.sym
251    if field.loc.r == nil: fillObjectFields(p.module, typ)
252    genAssignment(p, optAsgnLoc(dest, field.typ, field.loc.r),
253                     optAsgnLoc(src, field.typ, field.loc.r), newflags)
254  of nkRecList:
255    for child in items(t): genOptAsgnObject(p, dest, src, newflags, child, typ)
256  else: discard
257
258proc genGenericAsgn(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
259  # Consider:
260  # type TMyFastString {.shallow.} = string
261  # Due to the implementation of pragmas this would end up to set the
262  # tfShallow flag for the built-in string type too! So we check only
263  # here for this flag, where it is reasonably safe to do so
264  # (for objects, etc.):
265  if optSeqDestructors in p.config.globalOptions:
266    linefmt(p, cpsStmts,
267        "$1 = $2;$n",
268        [rdLoc(dest), rdLoc(src)])
269  elif needToCopy notin flags or
270      tfShallow in skipTypes(dest.t, abstractVarRange).flags:
271    if (dest.storage == OnStack and p.config.selectedGC != gcGo) or not usesWriteBarrier(p.config):
272      linefmt(p, cpsStmts,
273           "#nimCopyMem((void*)$1, (NIM_CONST void*)$2, sizeof($3));$n",
274           [addrLoc(p.config, dest), addrLoc(p.config, src), rdLoc(dest)])
275    else:
276      linefmt(p, cpsStmts, "#genericShallowAssign((void*)$1, (void*)$2, $3);$n",
277              [addrLoc(p.config, dest), addrLoc(p.config, src), genTypeInfoV1(p.module, dest.t, dest.lode.info)])
278  else:
279    linefmt(p, cpsStmts, "#genericAssign((void*)$1, (void*)$2, $3);$n",
280            [addrLoc(p.config, dest), addrLoc(p.config, src), genTypeInfoV1(p.module, dest.t, dest.lode.info)])
281
282proc genOpenArrayConv(p: BProc; d: TLoc; a: TLoc) =
283  assert d.k != locNone
284  #  getTemp(p, d.t, d)
285
286  case a.t.skipTypes(abstractVar).kind
287  of tyOpenArray, tyVarargs:
288    if reifiedOpenArray(a.lode):
289      linefmt(p, cpsStmts, "$1.Field0 = $2.Field0; $1.Field1 = $2.Field1;$n",
290        [rdLoc(d), a.rdLoc])
291    else:
292      linefmt(p, cpsStmts, "$1.Field0 = $2; $1.Field1 = $2Len_0;$n",
293        [rdLoc(d), a.rdLoc])
294  of tySequence:
295    linefmt(p, cpsStmts, "$1.Field0 = $2$3; $1.Field1 = $4;$n",
296      [rdLoc(d), a.rdLoc, dataField(p), lenExpr(p, a)])
297  of tyArray:
298    linefmt(p, cpsStmts, "$1.Field0 = $2; $1.Field1 = $3;$n",
299      [rdLoc(d), rdLoc(a), rope(lengthOrd(p.config, a.t))])
300  of tyString:
301    let etyp = skipTypes(a.t, abstractInst)
302    if etyp.kind in {tyVar} and optSeqDestructors in p.config.globalOptions:
303      linefmt(p, cpsStmts, "#nimPrepareStrMutationV2($1);$n", [byRefLoc(p, a)])
304
305    linefmt(p, cpsStmts, "$1.Field0 = $2$3; $1.Field1 = $4;$n",
306      [rdLoc(d), a.rdLoc, dataField(p), lenExpr(p, a)])
307  else:
308    internalError(p.config, a.lode.info, "cannot handle " & $a.t.kind)
309
310proc genAssignment(p: BProc, dest, src: TLoc, flags: TAssignmentFlags) =
311  # This function replaces all other methods for generating
312  # the assignment operation in C.
313  if src.t != nil and src.t.kind == tyPtr:
314    # little HACK to support the new 'var T' as return type:
315    linefmt(p, cpsStmts, "$1 = $2;$n", [rdLoc(dest), rdLoc(src)])
316    return
317  let ty = skipTypes(dest.t, abstractRange + tyUserTypeClasses + {tyStatic})
318  case ty.kind
319  of tyRef:
320    genRefAssign(p, dest, src)
321  of tySequence:
322    if optSeqDestructors in p.config.globalOptions:
323      genGenericAsgn(p, dest, src, flags)
324    elif (needToCopy notin flags and src.storage != OnStatic) or canMove(p, src.lode, dest):
325      genRefAssign(p, dest, src)
326    else:
327      linefmt(p, cpsStmts, "#genericSeqAssign($1, $2, $3);$n",
328              [addrLoc(p.config, dest), rdLoc(src),
329              genTypeInfoV1(p.module, dest.t, dest.lode.info)])
330  of tyString:
331    if optSeqDestructors in p.config.globalOptions:
332      genGenericAsgn(p, dest, src, flags)
333    elif (needToCopy notin flags and src.storage != OnStatic) or canMove(p, src.lode, dest):
334      genRefAssign(p, dest, src)
335    else:
336      if (dest.storage == OnStack and p.config.selectedGC != gcGo) or not usesWriteBarrier(p.config):
337        linefmt(p, cpsStmts, "$1 = #copyString($2);$n", [dest.rdLoc, src.rdLoc])
338      elif dest.storage == OnHeap:
339        # we use a temporary to care for the dreaded self assignment:
340        var tmp: TLoc
341        getTemp(p, ty, tmp)
342        linefmt(p, cpsStmts, "$3 = $1; $1 = #copyStringRC1($2);$n",
343                [dest.rdLoc, src.rdLoc, tmp.rdLoc])
344        linefmt(p, cpsStmts, "if ($1) #nimGCunrefNoCycle($1);$n", [tmp.rdLoc])
345      else:
346        linefmt(p, cpsStmts, "#unsureAsgnRef((void**) $1, #copyString($2));$n",
347               [addrLoc(p.config, dest), rdLoc(src)])
348  of tyProc:
349    if containsGarbageCollectedRef(dest.t):
350      # optimize closure assignment:
351      let a = optAsgnLoc(dest, dest.t, "ClE_0".rope)
352      let b = optAsgnLoc(src, dest.t, "ClE_0".rope)
353      genRefAssign(p, a, b)
354      linefmt(p, cpsStmts, "$1.ClP_0 = $2.ClP_0;$n", [rdLoc(dest), rdLoc(src)])
355    else:
356      linefmt(p, cpsStmts, "$1 = $2;$n", [rdLoc(dest), rdLoc(src)])
357  of tyTuple:
358    if containsGarbageCollectedRef(dest.t):
359      if dest.t.len <= 4: genOptAsgnTuple(p, dest, src, flags)
360      else: genGenericAsgn(p, dest, src, flags)
361    else:
362      linefmt(p, cpsStmts, "$1 = $2;$n", [rdLoc(dest), rdLoc(src)])
363  of tyObject:
364    # XXX: check for subtyping?
365    if ty.isImportedCppType:
366      linefmt(p, cpsStmts, "$1 = $2;$n", [rdLoc(dest), rdLoc(src)])
367    elif not isObjLackingTypeField(ty):
368      genGenericAsgn(p, dest, src, flags)
369    elif containsGarbageCollectedRef(ty):
370      if ty[0].isNil and asgnComplexity(ty.n) <= 4:
371        discard getTypeDesc(p.module, ty)
372        internalAssert p.config, ty.n != nil
373        genOptAsgnObject(p, dest, src, flags, ty.n, ty)
374      else:
375        genGenericAsgn(p, dest, src, flags)
376    else:
377      linefmt(p, cpsStmts, "$1 = $2;$n", [rdLoc(dest), rdLoc(src)])
378  of tyArray:
379    if containsGarbageCollectedRef(dest.t) and p.config.selectedGC notin {gcArc, gcOrc, gcHooks}:
380      genGenericAsgn(p, dest, src, flags)
381    else:
382      linefmt(p, cpsStmts,
383           "#nimCopyMem((void*)$1, (NIM_CONST void*)$2, sizeof($3));$n",
384           [rdLoc(dest), rdLoc(src), getTypeDesc(p.module, dest.t)])
385  of tyOpenArray, tyVarargs:
386    # open arrays are always on the stack - really? What if a sequence is
387    # passed to an open array?
388    if reifiedOpenArray(dest.lode):
389      genOpenArrayConv(p, dest, src)
390    elif containsGarbageCollectedRef(dest.t):
391      linefmt(p, cpsStmts,     # XXX: is this correct for arrays?
392           "#genericAssignOpenArray((void*)$1, (void*)$2, $1Len_0, $3);$n",
393           [addrLoc(p.config, dest), addrLoc(p.config, src),
394           genTypeInfoV1(p.module, dest.t, dest.lode.info)])
395    else:
396      linefmt(p, cpsStmts,
397           # bug #4799, keep the nimCopyMem for a while
398           #"#nimCopyMem((void*)$1, (NIM_CONST void*)$2, sizeof($1[0])*$1Len_0);$n",
399           "$1 = $2;$n",
400           [rdLoc(dest), rdLoc(src)])
401  of tySet:
402    if mapSetType(p.config, ty) == ctArray:
403      linefmt(p, cpsStmts, "#nimCopyMem((void*)$1, (NIM_CONST void*)$2, $3);$n",
404              [rdLoc(dest), rdLoc(src), getSize(p.config, dest.t)])
405    else:
406      linefmt(p, cpsStmts, "$1 = $2;$n", [rdLoc(dest), rdLoc(src)])
407  of tyPtr, tyPointer, tyChar, tyBool, tyEnum, tyCstring,
408     tyInt..tyUInt64, tyRange, tyVar, tyLent, tyNil:
409    linefmt(p, cpsStmts, "$1 = $2;$n", [rdLoc(dest), rdLoc(src)])
410  else: internalError(p.config, "genAssignment: " & $ty.kind)
411
412  if optMemTracker in p.options and dest.storage in {OnHeap, OnUnknown}:
413    #writeStackTrace()
414    #echo p.currLineInfo, " requesting"
415    linefmt(p, cpsStmts, "#memTrackerWrite((void*)$1, $2, $3, $4);$n",
416            [addrLoc(p.config, dest), getSize(p.config, dest.t),
417            makeCString(toFullPath(p.config, p.currLineInfo)),
418            p.currLineInfo.safeLineNm])
419
420proc genDeepCopy(p: BProc; dest, src: TLoc) =
421  template addrLocOrTemp(a: TLoc): Rope =
422    if a.k == locExpr:
423      var tmp: TLoc
424      getTemp(p, a.t, tmp)
425      genAssignment(p, tmp, a, {})
426      addrLoc(p.config, tmp)
427    else:
428      addrLoc(p.config, a)
429
430  var ty = skipTypes(dest.t, abstractVarRange + {tyStatic})
431  case ty.kind
432  of tyPtr, tyRef, tyProc, tyTuple, tyObject, tyArray:
433    # XXX optimize this
434    linefmt(p, cpsStmts, "#genericDeepCopy((void*)$1, (void*)$2, $3);$n",
435            [addrLoc(p.config, dest), addrLocOrTemp(src),
436            genTypeInfoV1(p.module, dest.t, dest.lode.info)])
437  of tySequence, tyString:
438    if optTinyRtti in p.config.globalOptions:
439      linefmt(p, cpsStmts, "#genericDeepCopy((void*)$1, (void*)$2, $3);$n",
440              [addrLoc(p.config, dest), addrLocOrTemp(src),
441              genTypeInfoV1(p.module, dest.t, dest.lode.info)])
442    else:
443      linefmt(p, cpsStmts, "#genericSeqDeepCopy($1, $2, $3);$n",
444              [addrLoc(p.config, dest), rdLoc(src),
445              genTypeInfoV1(p.module, dest.t, dest.lode.info)])
446  of tyOpenArray, tyVarargs:
447    linefmt(p, cpsStmts,
448         "#genericDeepCopyOpenArray((void*)$1, (void*)$2, $1Len_0, $3);$n",
449         [addrLoc(p.config, dest), addrLocOrTemp(src),
450         genTypeInfoV1(p.module, dest.t, dest.lode.info)])
451  of tySet:
452    if mapSetType(p.config, ty) == ctArray:
453      linefmt(p, cpsStmts, "#nimCopyMem((void*)$1, (NIM_CONST void*)$2, $3);$n",
454              [rdLoc(dest), rdLoc(src), getSize(p.config, dest.t)])
455    else:
456      linefmt(p, cpsStmts, "$1 = $2;$n", [rdLoc(dest), rdLoc(src)])
457  of tyPointer, tyChar, tyBool, tyEnum, tyCstring,
458     tyInt..tyUInt64, tyRange, tyVar, tyLent:
459    linefmt(p, cpsStmts, "$1 = $2;$n", [rdLoc(dest), rdLoc(src)])
460  else: internalError(p.config, "genDeepCopy: " & $ty.kind)
461
462proc putLocIntoDest(p: BProc, d: var TLoc, s: TLoc) =
463  if d.k != locNone:
464    if lfNoDeepCopy in d.flags: genAssignment(p, d, s, {})
465    else: genAssignment(p, d, s, {needToCopy})
466  else:
467    d = s # ``d`` is free, so fill it with ``s``
468
469proc putDataIntoDest(p: BProc, d: var TLoc, n: PNode, r: Rope) =
470  var a: TLoc
471  if d.k != locNone:
472    # need to generate an assignment here
473    initLoc(a, locData, n, OnStatic)
474    a.r = r
475    if lfNoDeepCopy in d.flags: genAssignment(p, d, a, {})
476    else: genAssignment(p, d, a, {needToCopy})
477  else:
478    # we cannot call initLoc() here as that would overwrite
479    # the flags field!
480    d.k = locData
481    d.lode = n
482    d.r = r
483
484proc putIntoDest(p: BProc, d: var TLoc, n: PNode, r: Rope; s=OnUnknown) =
485  var a: TLoc
486  if d.k != locNone:
487    # need to generate an assignment here
488    initLoc(a, locExpr, n, s)
489    a.r = r
490    if lfNoDeepCopy in d.flags: genAssignment(p, d, a, {})
491    else: genAssignment(p, d, a, {needToCopy})
492  else:
493    # we cannot call initLoc() here as that would overwrite
494    # the flags field!
495    d.k = locExpr
496    d.lode = n
497    d.r = r
498
499proc binaryStmt(p: BProc, e: PNode, d: var TLoc, op: string) =
500  var a, b: TLoc
501  if d.k != locNone: internalError(p.config, e.info, "binaryStmt")
502  initLocExpr(p, e[1], a)
503  initLocExpr(p, e[2], b)
504  lineCg(p, cpsStmts, "$1 $2 $3;$n", [rdLoc(a), op, rdLoc(b)])
505
506proc binaryStmtAddr(p: BProc, e: PNode, d: var TLoc, cpname: string) =
507  var a, b: TLoc
508  if d.k != locNone: internalError(p.config, e.info, "binaryStmtAddr")
509  initLocExpr(p, e[1], a)
510  initLocExpr(p, e[2], b)
511  lineCg(p, cpsStmts, "#$1($2, $3);$n", [cpname, byRefLoc(p, a), rdLoc(b)])
512
513template unaryStmt(p: BProc, e: PNode, d: var TLoc, frmt: string) =
514  var a: TLoc
515  if d.k != locNone: internalError(p.config, e.info, "unaryStmt")
516  initLocExpr(p, e[1], a)
517  lineCg(p, cpsStmts, frmt, [rdLoc(a)])
518
519template binaryExpr(p: BProc, e: PNode, d: var TLoc, frmt: string) =
520  var a, b: TLoc
521  assert(e[1].typ != nil)
522  assert(e[2].typ != nil)
523  initLocExpr(p, e[1], a)
524  initLocExpr(p, e[2], b)
525  putIntoDest(p, d, e, ropecg(p.module, frmt, [rdLoc(a), rdLoc(b)]))
526
527template binaryExprChar(p: BProc, e: PNode, d: var TLoc, frmt: string) =
528  var a, b: TLoc
529  assert(e[1].typ != nil)
530  assert(e[2].typ != nil)
531  initLocExpr(p, e[1], a)
532  initLocExpr(p, e[2], b)
533  putIntoDest(p, d, e, ropecg(p.module, frmt, [a.rdCharLoc, b.rdCharLoc]))
534
535template unaryExpr(p: BProc, e: PNode, d: var TLoc, frmt: string) =
536  var a: TLoc
537  initLocExpr(p, e[1], a)
538  putIntoDest(p, d, e, ropecg(p.module, frmt, [rdLoc(a)]))
539
540template unaryExprChar(p: BProc, e: PNode, d: var TLoc, frmt: string) =
541  var a: TLoc
542  initLocExpr(p, e[1], a)
543  putIntoDest(p, d, e, ropecg(p.module, frmt, [rdCharLoc(a)]))
544
545template binaryArithOverflowRaw(p: BProc, t: PType, a, b: TLoc;
546                            cpname: string): Rope =
547  var size = getSize(p.config, t)
548  let storage = if size < p.config.target.intSize: rope("NI")
549                else: getTypeDesc(p.module, t)
550  var result = getTempName(p.module)
551  linefmt(p, cpsLocals, "$1 $2;$n", [storage, result])
552  lineCg(p, cpsStmts, "if (#$2($3, $4, &$1)) { #raiseOverflow(); $5};$n",
553      [result, cpname, rdCharLoc(a), rdCharLoc(b), raiseInstr(p)])
554  if size < p.config.target.intSize or t.kind in {tyRange, tyEnum}:
555    linefmt(p, cpsStmts, "if ($1 < $2 || $1 > $3){ #raiseOverflow(); $4}$n",
556            [result, intLiteral(firstOrd(p.config, t)), intLiteral(lastOrd(p.config, t)),
557            raiseInstr(p)])
558  result
559
560proc binaryArithOverflow(p: BProc, e: PNode, d: var TLoc, m: TMagic) =
561  const
562    prc: array[mAddI..mPred, string] = [
563      "nimAddInt", "nimSubInt",
564      "nimMulInt", "nimDivInt", "nimModInt",
565      "nimAddInt", "nimSubInt"
566    ]
567    prc64: array[mAddI..mPred, string] = [
568      "nimAddInt64", "nimSubInt64",
569      "nimMulInt64", "nimDivInt64", "nimModInt64",
570      "nimAddInt64", "nimSubInt64"
571    ]
572    opr: array[mAddI..mPred, string] = ["+", "-", "*", "/", "%", "+", "-"]
573  var a, b: TLoc
574  assert(e[1].typ != nil)
575  assert(e[2].typ != nil)
576  initLocExpr(p, e[1], a)
577  initLocExpr(p, e[2], b)
578  # skipping 'range' is correct here as we'll generate a proper range check
579  # later via 'chckRange'
580  let t = e.typ.skipTypes(abstractRange)
581  if optOverflowCheck notin p.options:
582    let res = "($1)($2 $3 $4)" % [getTypeDesc(p.module, e.typ), rdLoc(a), rope(opr[m]), rdLoc(b)]
583    putIntoDest(p, d, e, res)
584  else:
585    # we handle div by zero here so that we know that the compilerproc's
586    # result is only for overflows.
587    if m in {mDivI, mModI}:
588      linefmt(p, cpsStmts, "if ($1 == 0){ #raiseDivByZero(); $2}$n",
589              [rdLoc(b), raiseInstr(p)])
590
591    let res = binaryArithOverflowRaw(p, t, a, b,
592      if t.kind == tyInt64: prc64[m] else: prc[m])
593    putIntoDest(p, d, e, "($#)($#)" % [getTypeDesc(p.module, e.typ), res])
594
595proc unaryArithOverflow(p: BProc, e: PNode, d: var TLoc, m: TMagic) =
596  var
597    a: TLoc
598    t: PType
599  assert(e[1].typ != nil)
600  initLocExpr(p, e[1], a)
601  t = skipTypes(e.typ, abstractRange)
602  if optOverflowCheck in p.options:
603    linefmt(p, cpsStmts, "if ($1 == $2){ #raiseOverflow(); $3}$n",
604            [rdLoc(a), intLiteral(firstOrd(p.config, t)), raiseInstr(p)])
605  case m
606  of mUnaryMinusI:
607    putIntoDest(p, d, e, "((NI$2)-($1))" % [rdLoc(a), rope(getSize(p.config, t) * 8)])
608  of mUnaryMinusI64:
609    putIntoDest(p, d, e, "-($1)" % [rdLoc(a)])
610  of mAbsI:
611    putIntoDest(p, d, e, "($1 > 0? ($1) : -($1))" % [rdLoc(a)])
612  else:
613    assert(false, $m)
614
615proc binaryArith(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
616  var
617    a, b: TLoc
618    s, k: BiggestInt
619  assert(e[1].typ != nil)
620  assert(e[2].typ != nil)
621  initLocExpr(p, e[1], a)
622  initLocExpr(p, e[2], b)
623  # BUGFIX: cannot use result-type here, as it may be a boolean
624  s = max(getSize(p.config, a.t), getSize(p.config, b.t)) * 8
625  k = getSize(p.config, a.t) * 8
626
627  template applyFormat(frmt: untyped) =
628    putIntoDest(p, d, e, frmt % [
629      rdLoc(a), rdLoc(b), rope(s),
630      getSimpleTypeDesc(p.module, e.typ), rope(k)]
631    )
632
633  case op
634  of mAddF64: applyFormat("(($4)($1) + ($4)($2))")
635  of mSubF64: applyFormat("(($4)($1) - ($4)($2))")
636  of mMulF64: applyFormat("(($4)($1) * ($4)($2))")
637  of mDivF64: applyFormat("(($4)($1) / ($4)($2))")
638  of mShrI: applyFormat("($4)((NU$5)($1) >> (NU$3)($2))")
639  of mShlI: applyFormat("($4)((NU$3)($1) << (NU$3)($2))")
640  of mAshrI: applyFormat("($4)((NI$3)($1) >> (NU$3)($2))")
641  of mBitandI: applyFormat("($4)($1 & $2)")
642  of mBitorI: applyFormat("($4)($1 | $2)")
643  of mBitxorI: applyFormat("($4)($1 ^ $2)")
644  of mMinI: applyFormat("(($1 <= $2) ? $1 : $2)")
645  of mMaxI: applyFormat("(($1 >= $2) ? $1 : $2)")
646  of mAddU: applyFormat("($4)((NU$3)($1) + (NU$3)($2))")
647  of mSubU: applyFormat("($4)((NU$3)($1) - (NU$3)($2))")
648  of mMulU: applyFormat("($4)((NU$3)($1) * (NU$3)($2))")
649  of mDivU: applyFormat("($4)((NU$3)($1) / (NU$3)($2))")
650  of mModU: applyFormat("($4)((NU$3)($1) % (NU$3)($2))")
651  of mEqI: applyFormat("($1 == $2)")
652  of mLeI: applyFormat("($1 <= $2)")
653  of mLtI: applyFormat("($1 < $2)")
654  of mEqF64: applyFormat("($1 == $2)")
655  of mLeF64: applyFormat("($1 <= $2)")
656  of mLtF64: applyFormat("($1 < $2)")
657  of mLeU: applyFormat("((NU$3)($1) <= (NU$3)($2))")
658  of mLtU: applyFormat("((NU$3)($1) < (NU$3)($2))")
659  of mEqEnum: applyFormat("($1 == $2)")
660  of mLeEnum: applyFormat("($1 <= $2)")
661  of mLtEnum: applyFormat("($1 < $2)")
662  of mEqCh: applyFormat("((NU8)($1) == (NU8)($2))")
663  of mLeCh: applyFormat("((NU8)($1) <= (NU8)($2))")
664  of mLtCh: applyFormat("((NU8)($1) < (NU8)($2))")
665  of mEqB: applyFormat("($1 == $2)")
666  of mLeB: applyFormat("($1 <= $2)")
667  of mLtB: applyFormat("($1 < $2)")
668  of mEqRef: applyFormat("($1 == $2)")
669  of mLePtr: applyFormat("($1 <= $2)")
670  of mLtPtr: applyFormat("($1 < $2)")
671  of mXor: applyFormat("($1 != $2)")
672  else:
673    assert(false, $op)
674
675proc genEqProc(p: BProc, e: PNode, d: var TLoc) =
676  var a, b: TLoc
677  assert(e[1].typ != nil)
678  assert(e[2].typ != nil)
679  initLocExpr(p, e[1], a)
680  initLocExpr(p, e[2], b)
681  if a.t.skipTypes(abstractInstOwned).callConv == ccClosure:
682    putIntoDest(p, d, e,
683      "($1.ClP_0 == $2.ClP_0 && $1.ClE_0 == $2.ClE_0)" % [rdLoc(a), rdLoc(b)])
684  else:
685    putIntoDest(p, d, e, "($1 == $2)" % [rdLoc(a), rdLoc(b)])
686
687proc genIsNil(p: BProc, e: PNode, d: var TLoc) =
688  let t = skipTypes(e[1].typ, abstractRange)
689  if t.kind == tyProc and t.callConv == ccClosure:
690    unaryExpr(p, e, d, "($1.ClP_0 == 0)")
691  else:
692    unaryExpr(p, e, d, "($1 == 0)")
693
694proc unaryArith(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
695  var
696    a: TLoc
697    t: PType
698  assert(e[1].typ != nil)
699  initLocExpr(p, e[1], a)
700  t = skipTypes(e.typ, abstractRange)
701
702  template applyFormat(frmt: untyped) =
703    putIntoDest(p, d, e, frmt % [rdLoc(a), rope(getSize(p.config, t) * 8),
704                getSimpleTypeDesc(p.module, e.typ)])
705  case op
706  of mNot:
707    applyFormat("!($1)")
708  of mUnaryPlusI:
709    applyFormat("$1")
710  of mBitnotI:
711    applyFormat("($3)((NU$2) ~($1))")
712  of mUnaryPlusF64:
713    applyFormat("$1")
714  of mUnaryMinusF64:
715    applyFormat("-($1)")
716  else:
717    assert false, $op
718
719proc isCppRef(p: BProc; typ: PType): bool {.inline.} =
720  result = p.module.compileToCpp and
721      skipTypes(typ, abstractInstOwned).kind in {tyVar} and
722      tfVarIsPtr notin skipTypes(typ, abstractInstOwned).flags
723
724proc genDeref(p: BProc, e: PNode, d: var TLoc) =
725  let mt = mapType(p.config, e[0].typ, mapTypeChooser(e[0]))
726  if mt in {ctArray, ctPtrToArray} and lfEnforceDeref notin d.flags:
727    # XXX the amount of hacks for C's arrays is incredible, maybe we should
728    # simply wrap them in a struct? --> Losing auto vectorization then?
729    expr(p, e[0], d)
730    if e[0].typ.skipTypes(abstractInstOwned).kind == tyRef:
731      d.storage = OnHeap
732  else:
733    var a: TLoc
734    var typ = e[0].typ
735    if typ.kind in {tyUserTypeClass, tyUserTypeClassInst} and typ.isResolvedUserTypeClass:
736      typ = typ.lastSon
737    typ = typ.skipTypes(abstractInstOwned)
738    if typ.kind in {tyVar} and tfVarIsPtr notin typ.flags and p.module.compileToCpp and e[0].kind == nkHiddenAddr:
739      initLocExprSingleUse(p, e[0][0], d)
740      return
741    else:
742      initLocExprSingleUse(p, e[0], a)
743    if d.k == locNone:
744      # dest = *a;  <-- We do not know that 'dest' is on the heap!
745      # It is completely wrong to set 'd.storage' here, unless it's not yet
746      # been assigned to.
747      case typ.kind
748      of tyRef:
749        d.storage = OnHeap
750      of tyVar, tyLent:
751        d.storage = OnUnknown
752        if tfVarIsPtr notin typ.flags and p.module.compileToCpp and
753            e.kind == nkHiddenDeref:
754          putIntoDest(p, d, e, rdLoc(a), a.storage)
755          return
756      of tyPtr:
757        d.storage = OnUnknown         # BUGFIX!
758      else:
759        internalError(p.config, e.info, "genDeref " & $typ.kind)
760    elif p.module.compileToCpp:
761      if typ.kind in {tyVar} and tfVarIsPtr notin typ.flags and
762           e.kind == nkHiddenDeref:
763        putIntoDest(p, d, e, rdLoc(a), a.storage)
764        return
765    if mt == ctPtrToArray and lfEnforceDeref in d.flags:
766      # we lie about the type for better C interop: 'ptr array[3,T]' is
767      # translated to 'ptr T', but for deref'ing this produces wrong code.
768      # See tmissingderef. So we get rid of the deref instead. The codegen
769      # ends up using 'memcpy' for the array assignment,
770      # so the '&' and '*' cancel out:
771      putIntoDest(p, d, e, rdLoc(a), a.storage)
772    else:
773      putIntoDest(p, d, e, "(*$1)" % [rdLoc(a)], a.storage)
774
775proc cowBracket(p: BProc; n: PNode) =
776  if n.kind == nkBracketExpr and optSeqDestructors in p.config.globalOptions:
777    let strCandidate = n[0]
778    if strCandidate.typ.skipTypes(abstractInst).kind == tyString:
779      var a: TLoc
780      initLocExpr(p, strCandidate, a)
781      linefmt(p, cpsStmts, "#nimPrepareStrMutationV2($1);$n", [byRefLoc(p, a)])
782
783proc cow(p: BProc; n: PNode) {.inline.} =
784  if n.kind == nkHiddenAddr: cowBracket(p, n[0])
785
786proc genAddr(p: BProc, e: PNode, d: var TLoc) =
787  # careful  'addr(myptrToArray)' needs to get the ampersand:
788  if e[0].typ.skipTypes(abstractInstOwned).kind in {tyRef, tyPtr}:
789    var a: TLoc
790    initLocExpr(p, e[0], a)
791    putIntoDest(p, d, e, "&" & a.r, a.storage)
792    #Message(e.info, warnUser, "HERE NEW &")
793  elif mapType(p.config, e[0].typ, mapTypeChooser(e[0])) == ctArray or isCppRef(p, e.typ):
794    expr(p, e[0], d)
795  else:
796    var a: TLoc
797    initLocExpr(p, e[0], a)
798    putIntoDest(p, d, e, addrLoc(p.config, a), a.storage)
799
800template inheritLocation(d: var TLoc, a: TLoc) =
801  if d.k == locNone: d.storage = a.storage
802
803proc genRecordFieldAux(p: BProc, e: PNode, d, a: var TLoc) =
804  initLocExpr(p, e[0], a)
805  if e[1].kind != nkSym: internalError(p.config, e.info, "genRecordFieldAux")
806  d.inheritLocation(a)
807  discard getTypeDesc(p.module, a.t) # fill the record's fields.loc
808
809proc genTupleElem(p: BProc, e: PNode, d: var TLoc) =
810  var
811    a: TLoc
812    i: int
813  initLocExpr(p, e[0], a)
814  let tupType = a.t.skipTypes(abstractInst+{tyVar})
815  assert tupType.kind == tyTuple
816  d.inheritLocation(a)
817  discard getTypeDesc(p.module, a.t) # fill the record's fields.loc
818  var r = rdLoc(a)
819  case e[1].kind
820  of nkIntLit..nkUInt64Lit: i = int(e[1].intVal)
821  else: internalError(p.config, e.info, "genTupleElem")
822  r.addf(".Field$1", [rope(i)])
823  putIntoDest(p, d, e, r, a.storage)
824
825proc lookupFieldAgain(p: BProc, ty: PType; field: PSym; r: var Rope;
826                      resTyp: ptr PType = nil): PSym =
827  var ty = ty
828  assert r != nil
829  while ty != nil:
830    ty = ty.skipTypes(skipPtrs)
831    assert(ty.kind in {tyTuple, tyObject})
832    result = lookupInRecord(ty.n, field.name)
833    if result != nil:
834      if resTyp != nil: resTyp[] = ty
835      break
836    if not p.module.compileToCpp: r.add(".Sup")
837    ty = ty[0]
838  if result == nil: internalError(p.config, field.info, "genCheckedRecordField")
839
840proc genRecordField(p: BProc, e: PNode, d: var TLoc) =
841  var a: TLoc
842  genRecordFieldAux(p, e, d, a)
843  var r = rdLoc(a)
844  var f = e[1].sym
845  let ty = skipTypes(a.t, abstractInstOwned + tyUserTypeClasses)
846  if ty.kind == tyTuple:
847    # we found a unique tuple type which lacks field information
848    # so we use Field$i
849    r.addf(".Field$1", [rope(f.position)])
850    putIntoDest(p, d, e, r, a.storage)
851  else:
852    var rtyp: PType
853    let field = lookupFieldAgain(p, ty, f, r, addr rtyp)
854    if field.loc.r == nil and rtyp != nil: fillObjectFields(p.module, rtyp)
855    if field.loc.r == nil: internalError(p.config, e.info, "genRecordField 3 " & typeToString(ty))
856    r.addf(".$1", [field.loc.r])
857    putIntoDest(p, d, e, r, a.storage)
858
859proc genInExprAux(p: BProc, e: PNode, a, b, d: var TLoc)
860
861proc genFieldCheck(p: BProc, e: PNode, obj: Rope, field: PSym) =
862  var test, u, v: TLoc
863  for i in 1..<e.len:
864    var it = e[i]
865    assert(it.kind in nkCallKinds)
866    assert(it[0].kind == nkSym)
867    let op = it[0].sym
868    if op.magic == mNot: it = it[1]
869    let disc = it[2].skipConv
870    assert(disc.kind == nkSym)
871    initLoc(test, locNone, it, OnStack)
872    initLocExpr(p, it[1], u)
873    initLoc(v, locExpr, disc, OnUnknown)
874    v.r = obj
875    v.r.add(".")
876    v.r.add(disc.sym.loc.r)
877    genInExprAux(p, it, u, v, test)
878    var msg = ""
879    if optDeclaredLocs in p.config.globalOptions:
880      # xxx this should be controlled by a separate flag, and
881      # used for other similar defects so that location information is shown
882      # even without the expensive `--stacktrace`; binary size could be optimized
883      # by encoding the file names separately from `file(line:col)`, essentially
884      # passing around `TLineInfo` + the set of files in the project.
885      msg.add toFileLineCol(p.config, e.info) & " "
886    msg.add genFieldDefect(p.config, field.name.s, disc.sym)
887    let strLit = genStringLiteral(p.module, newStrNode(nkStrLit, msg))
888
889    ## discriminant check
890    template fun(code) = linefmt(p, cpsStmts, code, [rdLoc(test)])
891    if op.magic == mNot: fun("if ($1) ") else: fun("if (!($1)) ")
892
893    ## call raiseFieldError2 on failure
894    let discIndex = rdSetElemLoc(p.config, v, u.t)
895    if optTinyRtti in p.config.globalOptions:
896      # not sure how to use `genEnumToStr` here
897      if p.config.getStdlibVersion < (1,5,1):
898        const code = "{ #raiseFieldError($1); $2} $n"
899        linefmt(p, cpsStmts, code, [strLit, raiseInstr(p)])
900      else:
901        const code = "{ #raiseFieldError2($1, (NI)$3); $2} $n"
902        linefmt(p, cpsStmts, code, [strLit, raiseInstr(p), discIndex])
903    else:
904      # complication needed for signed types
905      let first = p.config.firstOrd(disc.sym.typ)
906      let firstLit = int64Literal(cast[int](first))
907      let discName = genTypeInfo(p.config, p.module, disc.sym.typ, e.info)
908      if p.config.getStdlibVersion < (1,5,1):
909        const code = "{ #raiseFieldError($1); $2} $n"
910        linefmt(p, cpsStmts, code, [strLit, raiseInstr(p)])
911      else:
912        const code = "{ #raiseFieldError2($1, #reprDiscriminant(((NI)$3) + (NI)$4, $5)); $2} $n"
913        linefmt(p, cpsStmts, code, [strLit, raiseInstr(p), discIndex, firstLit, discName])
914
915proc genCheckedRecordField(p: BProc, e: PNode, d: var TLoc) =
916  assert e[0].kind == nkDotExpr
917  if optFieldCheck in p.options:
918    var a: TLoc
919    genRecordFieldAux(p, e[0], d, a)
920    let ty = skipTypes(a.t, abstractInst + tyUserTypeClasses)
921    var r = rdLoc(a)
922    let f = e[0][1].sym
923    let field = lookupFieldAgain(p, ty, f, r)
924    if field.loc.r == nil: fillObjectFields(p.module, ty)
925    if field.loc.r == nil:
926      internalError(p.config, e.info, "genCheckedRecordField") # generate the checks:
927    genFieldCheck(p, e, r, field)
928    r.add(ropecg(p.module, ".$1", [field.loc.r]))
929    putIntoDest(p, d, e[0], r, a.storage)
930  else:
931    genRecordField(p, e[0], d)
932
933proc genUncheckedArrayElem(p: BProc, n, x, y: PNode, d: var TLoc) =
934  var a, b: TLoc
935  initLocExpr(p, x, a)
936  initLocExpr(p, y, b)
937  d.inheritLocation(a)
938  putIntoDest(p, d, n, ropecg(p.module, "$1[$2]", [rdLoc(a), rdCharLoc(b)]),
939              a.storage)
940
941proc genArrayElem(p: BProc, n, x, y: PNode, d: var TLoc) =
942  var a, b: TLoc
943  initLocExpr(p, x, a)
944  initLocExpr(p, y, b)
945  var ty = skipTypes(a.t, abstractVarRange + abstractPtrs + tyUserTypeClasses)
946  var first = intLiteral(firstOrd(p.config, ty))
947  # emit range check:
948  if optBoundsCheck in p.options and ty.kind != tyUncheckedArray:
949    if not isConstExpr(y):
950      # semantic pass has already checked for const index expressions
951      if firstOrd(p.config, ty) == 0 and lastOrd(p.config, ty) >= 0:
952        if (firstOrd(p.config, b.t) < firstOrd(p.config, ty)) or (lastOrd(p.config, b.t) > lastOrd(p.config, ty)):
953          linefmt(p, cpsStmts, "if ((NU)($1) > (NU)($2)){ #raiseIndexError2($1, $2); $3}$n",
954                  [rdCharLoc(b), intLiteral(lastOrd(p.config, ty)), raiseInstr(p)])
955      else:
956        linefmt(p, cpsStmts, "if ($1 < $2 || $1 > $3){ #raiseIndexError3($1, $2, $3); $4}$n",
957                [rdCharLoc(b), first, intLiteral(lastOrd(p.config, ty)), raiseInstr(p)])
958    else:
959      let idx = getOrdValue(y)
960      if idx < firstOrd(p.config, ty) or idx > lastOrd(p.config, ty):
961        localError(p.config, x.info, formatErrorIndexBound(idx, firstOrd(p.config, ty), lastOrd(p.config, ty)))
962  d.inheritLocation(a)
963  putIntoDest(p, d, n,
964              ropecg(p.module, "$1[($2)- $3]", [rdLoc(a), rdCharLoc(b), first]), a.storage)
965
966proc genCStringElem(p: BProc, n, x, y: PNode, d: var TLoc) =
967  var a, b: TLoc
968  initLocExpr(p, x, a)
969  initLocExpr(p, y, b)
970  inheritLocation(d, a)
971  putIntoDest(p, d, n,
972              ropecg(p.module, "$1[$2]", [rdLoc(a), rdCharLoc(b)]), a.storage)
973
974proc genBoundsCheck(p: BProc; arr, a, b: TLoc) =
975  let ty = skipTypes(arr.t, abstractVarRange)
976  case ty.kind
977  of tyOpenArray, tyVarargs:
978    if reifiedOpenArray(arr.lode):
979      linefmt(p, cpsStmts,
980        "if ($2-$1 != -1 && " &
981        "((NU)($1) >= (NU)($3.Field1) || (NU)($2) >= (NU)($3.Field1))){ #raiseIndexError(); $4}$n",
982        [rdLoc(a), rdLoc(b), rdLoc(arr), raiseInstr(p)])
983    else:
984      linefmt(p, cpsStmts,
985        "if ($2-$1 != -1 && " &
986        "((NU)($1) >= (NU)($3Len_0) || (NU)($2) >= (NU)($3Len_0))){ #raiseIndexError(); $4}$n",
987        [rdLoc(a), rdLoc(b), rdLoc(arr), raiseInstr(p)])
988  of tyArray:
989    let first = intLiteral(firstOrd(p.config, ty))
990    linefmt(p, cpsStmts,
991      "if ($2-$1 != -1 && " &
992      "($2-$1 < -1 || $1 < $3 || $1 > $4 || $2 < $3 || $2 > $4)){ #raiseIndexError(); $5}$n",
993      [rdCharLoc(a), rdCharLoc(b), first, intLiteral(lastOrd(p.config, ty)), raiseInstr(p)])
994  of tySequence, tyString:
995    linefmt(p, cpsStmts,
996      "if ($2-$1 != -1 && " &
997      "((NU)($1) >= (NU)$3 || (NU)($2) >= (NU)$3)){ #raiseIndexError(); $4}$n",
998      [rdLoc(a), rdLoc(b), lenExpr(p, arr), raiseInstr(p)])
999  else: discard
1000
1001proc genOpenArrayElem(p: BProc, n, x, y: PNode, d: var TLoc) =
1002  var a, b: TLoc
1003  initLocExpr(p, x, a)
1004  initLocExpr(p, y, b)
1005  if not reifiedOpenArray(x):
1006    # emit range check:
1007    if optBoundsCheck in p.options:
1008      linefmt(p, cpsStmts, "if ((NU)($1) >= (NU)($2Len_0)){ #raiseIndexError2($1,$2Len_0-1); $3}$n",
1009              [rdCharLoc(b), rdLoc(a), raiseInstr(p)]) # BUGFIX: ``>=`` and not ``>``!
1010    inheritLocation(d, a)
1011    putIntoDest(p, d, n,
1012                ropecg(p.module, "$1[$2]", [rdLoc(a), rdCharLoc(b)]), a.storage)
1013  else:
1014    if optBoundsCheck in p.options:
1015      linefmt(p, cpsStmts, "if ((NU)($1) >= (NU)($2.Field1)){ #raiseIndexError2($1,$2.Field1-1); $3}$n",
1016              [rdCharLoc(b), rdLoc(a), raiseInstr(p)]) # BUGFIX: ``>=`` and not ``>``!
1017    inheritLocation(d, a)
1018    putIntoDest(p, d, n,
1019                ropecg(p.module, "$1.Field0[$2]", [rdLoc(a), rdCharLoc(b)]), a.storage)
1020
1021proc genSeqElem(p: BProc, n, x, y: PNode, d: var TLoc) =
1022  var a, b: TLoc
1023  initLocExpr(p, x, a)
1024  initLocExpr(p, y, b)
1025  var ty = skipTypes(a.t, abstractVarRange)
1026  if ty.kind in {tyRef, tyPtr}:
1027    ty = skipTypes(ty.lastSon, abstractVarRange) # emit range check:
1028  if optBoundsCheck in p.options:
1029    linefmt(p, cpsStmts,
1030            "if ((NU)($1) >= (NU)$2){ #raiseIndexError2($1,$2-1); $3}$n",
1031            [rdCharLoc(b), lenExpr(p, a), raiseInstr(p)])
1032  if d.k == locNone: d.storage = OnHeap
1033  if skipTypes(a.t, abstractVar).kind in {tyRef, tyPtr}:
1034    a.r = ropecg(p.module, "(*$1)", [a.r])
1035
1036  if lfPrepareForMutation in d.flags and ty.kind == tyString and
1037      optSeqDestructors in p.config.globalOptions:
1038    linefmt(p, cpsStmts, "#nimPrepareStrMutationV2($1);$n", [byRefLoc(p, a)])
1039  putIntoDest(p, d, n,
1040              ropecg(p.module, "$1$3[$2]", [rdLoc(a), rdCharLoc(b), dataField(p)]), a.storage)
1041
1042proc genBracketExpr(p: BProc; n: PNode; d: var TLoc) =
1043  var ty = skipTypes(n[0].typ, abstractVarRange + tyUserTypeClasses)
1044  if ty.kind in {tyRef, tyPtr}: ty = skipTypes(ty.lastSon, abstractVarRange)
1045  case ty.kind
1046  of tyUncheckedArray: genUncheckedArrayElem(p, n, n[0], n[1], d)
1047  of tyArray: genArrayElem(p, n, n[0], n[1], d)
1048  of tyOpenArray, tyVarargs: genOpenArrayElem(p, n, n[0], n[1], d)
1049  of tySequence, tyString: genSeqElem(p, n, n[0], n[1], d)
1050  of tyCstring: genCStringElem(p, n, n[0], n[1], d)
1051  of tyTuple: genTupleElem(p, n, d)
1052  else: internalError(p.config, n.info, "expr(nkBracketExpr, " & $ty.kind & ')')
1053  discard getTypeDesc(p.module, n.typ)
1054
1055proc isSimpleExpr(n: PNode): bool =
1056  # calls all the way down --> can stay expression based
1057  case n.kind
1058  of nkCallKinds, nkDotExpr, nkPar, nkTupleConstr,
1059      nkObjConstr, nkBracket, nkCurly, nkHiddenDeref, nkDerefExpr, nkHiddenAddr,
1060      nkHiddenStdConv, nkHiddenSubConv, nkConv, nkAddr:
1061    for c in n:
1062      if not isSimpleExpr(c): return false
1063    result = true
1064  of nkStmtListExpr:
1065    for i in 0..<n.len-1:
1066      if n[i].kind notin {nkCommentStmt, nkEmpty}: return false
1067    result = isSimpleExpr(n.lastSon)
1068  else:
1069    if n.isAtom:
1070      result = true
1071
1072proc genAndOr(p: BProc, e: PNode, d: var TLoc, m: TMagic) =
1073  # how to generate code?
1074  #  'expr1 and expr2' becomes:
1075  #     result = expr1
1076  #     fjmp result, end
1077  #     result = expr2
1078  #  end:
1079  #  ... (result computed)
1080  # BUGFIX:
1081  #   a = b or a
1082  # used to generate:
1083  # a = b
1084  # if a: goto end
1085  # a = a
1086  # end:
1087  # now it generates:
1088  # tmp = b
1089  # if tmp: goto end
1090  # tmp = a
1091  # end:
1092  # a = tmp
1093  when false:
1094    #if isSimpleExpr(e) and p.module.compileToCpp:
1095    var tmpA, tmpB: TLoc
1096    #getTemp(p, e.typ, tmpA)
1097    #getTemp(p, e.typ, tmpB)
1098    initLocExprSingleUse(p, e[1], tmpA)
1099    initLocExprSingleUse(p, e[2], tmpB)
1100    tmpB.k = locExpr
1101    if m == mOr:
1102      tmpB.r = "((" & rdLoc(tmpA) & ")||(" & rdLoc(tmpB) & "))"
1103    else:
1104      tmpB.r = "((" & rdLoc(tmpA) & ")&&(" & rdLoc(tmpB) & "))"
1105    if d.k == locNone:
1106      d = tmpB
1107    else:
1108      genAssignment(p, d, tmpB, {})
1109  else:
1110    var
1111      L: TLabel
1112      tmp: TLoc
1113    getTemp(p, e.typ, tmp)      # force it into a temp!
1114    inc p.splitDecls
1115    expr(p, e[1], tmp)
1116    L = getLabel(p)
1117    if m == mOr:
1118      lineF(p, cpsStmts, "if ($1) goto $2;$n", [rdLoc(tmp), L])
1119    else:
1120      lineF(p, cpsStmts, "if (!($1)) goto $2;$n", [rdLoc(tmp), L])
1121    expr(p, e[2], tmp)
1122    fixLabel(p, L)
1123    if d.k == locNone:
1124      d = tmp
1125    else:
1126      genAssignment(p, d, tmp, {}) # no need for deep copying
1127    dec p.splitDecls
1128
1129proc genEcho(p: BProc, n: PNode) =
1130  # this unusual way of implementing it ensures that e.g. ``echo("hallo", 45)``
1131  # is threadsafe.
1132  internalAssert p.config, n.kind == nkBracket
1133  if p.config.target.targetOS == osGenode:
1134    # echo directly to the Genode LOG session
1135    var args: Rope = nil
1136    var a: TLoc
1137    for i, it in n.sons:
1138      if it.skipConv.kind == nkNilLit:
1139        args.add(", \"\"")
1140      elif n.len != 0:
1141        initLocExpr(p, it, a)
1142        if i > 0:
1143          args.add(", ")
1144        case detectStrVersion(p.module)
1145        of 2:
1146          args.add(ropecg(p.module, "Genode::Cstring($1.p->data, $1.len)", [a.rdLoc]))
1147        else:
1148          args.add(ropecg(p.module, "Genode::Cstring($1->data, $1->len)", [a.rdLoc]))
1149    p.module.includeHeader("<base/log.h>")
1150    p.module.includeHeader("<util/string.h>")
1151    linefmt(p, cpsStmts, """Genode::log($1);$n""", [args])
1152  else:
1153    if n.len == 0:
1154      linefmt(p, cpsStmts, "#echoBinSafe(NIM_NIL, $1);$n", [n.len])
1155    else:
1156      var a: TLoc
1157      initLocExpr(p, n, a)
1158      linefmt(p, cpsStmts, "#echoBinSafe($1, $2);$n", [a.rdLoc, n.len])
1159    when false:
1160      p.module.includeHeader("<stdio.h>")
1161      linefmt(p, cpsStmts, "printf($1$2);$n",
1162              makeCString(repeat("%s", n.len) & "\L"), [args])
1163      linefmt(p, cpsStmts, "fflush(stdout);$n", [])
1164
1165proc gcUsage(conf: ConfigRef; n: PNode) =
1166  if conf.selectedGC == gcNone: message(conf, n.info, warnGcMem, n.renderTree)
1167
1168proc strLoc(p: BProc; d: TLoc): Rope =
1169  if optSeqDestructors in p.config.globalOptions:
1170    result = byRefLoc(p, d)
1171  else:
1172    result = rdLoc(d)
1173
1174proc genStrConcat(p: BProc, e: PNode, d: var TLoc) =
1175  #   <Nim code>
1176  #   s = 'Hello ' & name & ', how do you feel?' & 'z'
1177  #
1178  #   <generated C code>
1179  #  {
1180  #    string tmp0;
1181  #    ...
1182  #    tmp0 = rawNewString(6 + 17 + 1 + s2->len);
1183  #    // we cannot generate s = rawNewString(...) here, because
1184  #    // ``s`` may be used on the right side of the expression
1185  #    appendString(tmp0, strlit_1);
1186  #    appendString(tmp0, name);
1187  #    appendString(tmp0, strlit_2);
1188  #    appendChar(tmp0, 'z');
1189  #    asgn(s, tmp0);
1190  #  }
1191  var a, tmp: TLoc
1192  getTemp(p, e.typ, tmp)
1193  var L = 0
1194  var appends: Rope = nil
1195  var lens: Rope = nil
1196  for i in 0..<e.len - 1:
1197    # compute the length expression:
1198    initLocExpr(p, e[i + 1], a)
1199    if skipTypes(e[i + 1].typ, abstractVarRange).kind == tyChar:
1200      inc(L)
1201      appends.add(ropecg(p.module, "#appendChar($1, $2);$n", [strLoc(p, tmp), rdLoc(a)]))
1202    else:
1203      if e[i + 1].kind in {nkStrLit..nkTripleStrLit}:
1204        inc(L, e[i + 1].strVal.len)
1205      else:
1206        lens.add(lenExpr(p, a))
1207        lens.add(" + ")
1208      appends.add(ropecg(p.module, "#appendString($1, $2);$n", [strLoc(p, tmp), rdLoc(a)]))
1209  linefmt(p, cpsStmts, "$1 = #rawNewString($2$3);$n", [tmp.r, lens, L])
1210  p.s(cpsStmts).add appends
1211  if d.k == locNone:
1212    d = tmp
1213  else:
1214    genAssignment(p, d, tmp, {}) # no need for deep copying
1215  gcUsage(p.config, e)
1216
1217proc genStrAppend(p: BProc, e: PNode, d: var TLoc) =
1218  #  <Nim code>
1219  #  s &= 'Hello ' & name & ', how do you feel?' & 'z'
1220  #  // BUG: what if s is on the left side too?
1221  #  <generated C code>
1222  #  {
1223  #    s = resizeString(s, 6 + 17 + 1 + name->len);
1224  #    appendString(s, strlit_1);
1225  #    appendString(s, name);
1226  #    appendString(s, strlit_2);
1227  #    appendChar(s, 'z');
1228  #  }
1229  var
1230    a, dest, call: TLoc
1231    appends, lens: Rope
1232  assert(d.k == locNone)
1233  var L = 0
1234  initLocExpr(p, e[1], dest)
1235  for i in 0..<e.len - 2:
1236    # compute the length expression:
1237    initLocExpr(p, e[i + 2], a)
1238    if skipTypes(e[i + 2].typ, abstractVarRange).kind == tyChar:
1239      inc(L)
1240      appends.add(ropecg(p.module, "#appendChar($1, $2);$n",
1241                        [strLoc(p, dest), rdLoc(a)]))
1242    else:
1243      if e[i + 2].kind in {nkStrLit..nkTripleStrLit}:
1244        inc(L, e[i + 2].strVal.len)
1245      else:
1246        lens.add(lenExpr(p, a))
1247        lens.add(" + ")
1248      appends.add(ropecg(p.module, "#appendString($1, $2);$n",
1249                        [strLoc(p, dest), rdLoc(a)]))
1250  if optSeqDestructors in p.config.globalOptions:
1251    linefmt(p, cpsStmts, "#prepareAdd($1, $2$3);$n",
1252            [byRefLoc(p, dest), lens, L])
1253  else:
1254    initLoc(call, locCall, e, OnHeap)
1255    call.r = ropecg(p.module, "#resizeString($1, $2$3)", [rdLoc(dest), lens, L])
1256    genAssignment(p, dest, call, {})
1257    gcUsage(p.config, e)
1258  p.s(cpsStmts).add appends
1259
1260proc genSeqElemAppend(p: BProc, e: PNode, d: var TLoc) =
1261  # seq &= x  -->
1262  #    seq = (typeof seq) incrSeq(&seq->Sup, sizeof(x));
1263  #    seq->data[seq->len-1] = x;
1264  var a, b, dest, tmpL, call: TLoc
1265  initLocExpr(p, e[1], a)
1266  initLocExpr(p, e[2], b)
1267  let seqType = skipTypes(e[1].typ, {tyVar})
1268  initLoc(call, locCall, e, OnHeap)
1269  if not p.module.compileToCpp:
1270    const seqAppendPattern = "($2) #incrSeqV3((TGenericSeq*)($1), $3)"
1271    call.r = ropecg(p.module, seqAppendPattern, [rdLoc(a),
1272      getTypeDesc(p.module, e[1].typ),
1273      genTypeInfoV1(p.module, seqType, e.info)])
1274  else:
1275    const seqAppendPattern = "($2) #incrSeqV3($1, $3)"
1276    call.r = ropecg(p.module, seqAppendPattern, [rdLoc(a),
1277      getTypeDesc(p.module, e[1].typ),
1278      genTypeInfoV1(p.module, seqType, e.info)])
1279  # emit the write barrier if required, but we can always move here, so
1280  # use 'genRefAssign' for the seq.
1281  genRefAssign(p, a, call)
1282  #if bt != b.t:
1283  #  echo "YES ", e.info, " new: ", typeToString(bt), " old: ", typeToString(b.t)
1284  initLoc(dest, locExpr, e[2], OnHeap)
1285  getIntTemp(p, tmpL)
1286  lineCg(p, cpsStmts, "$1 = $2->$3++;$n", [tmpL.r, rdLoc(a), lenField(p)])
1287  dest.r = ropecg(p.module, "$1$3[$2]", [rdLoc(a), tmpL.r, dataField(p)])
1288  genAssignment(p, dest, b, {needToCopy})
1289  gcUsage(p.config, e)
1290
1291proc genReset(p: BProc, n: PNode) =
1292  var a: TLoc
1293  initLocExpr(p, n[1], a)
1294  specializeReset(p, a)
1295  when false:
1296    linefmt(p, cpsStmts, "#genericReset((void*)$1, $2);$n",
1297            [addrLoc(p.config, a),
1298            genTypeInfoV1(p.module, skipTypes(a.t, {tyVar}), n.info)])
1299
1300proc genDefault(p: BProc; n: PNode; d: var TLoc) =
1301  if d.k == locNone: getTemp(p, n.typ, d, needsInit=true)
1302  else: resetLoc(p, d)
1303
1304proc rawGenNew(p: BProc, a: var TLoc, sizeExpr: Rope; needsInit: bool) =
1305  var sizeExpr = sizeExpr
1306  let typ = a.t
1307  var b: TLoc
1308  initLoc(b, locExpr, a.lode, OnHeap)
1309  let refType = typ.skipTypes(abstractInstOwned)
1310  assert refType.kind == tyRef
1311  let bt = refType.lastSon
1312  if sizeExpr.isNil:
1313    sizeExpr = "sizeof($1)" % [getTypeDesc(p.module, bt)]
1314
1315  if optTinyRtti in p.config.globalOptions:
1316    if needsInit:
1317      b.r = ropecg(p.module, "($1) #nimNewObj($2, NIM_ALIGNOF($3))",
1318          [getTypeDesc(p.module, typ), sizeExpr, getTypeDesc(p.module, bt)])
1319    else:
1320      b.r = ropecg(p.module, "($1) #nimNewObjUninit($2, NIM_ALIGNOF($3))",
1321          [getTypeDesc(p.module, typ), sizeExpr, getTypeDesc(p.module, bt)])
1322    genAssignment(p, a, b, {})
1323  else:
1324    let ti = genTypeInfoV1(p.module, typ, a.lode.info)
1325    let op = getAttachedOp(p.module.g.graph, bt, attachedDestructor)
1326    if op != nil and not isTrivialProc(p.module.g.graph, op):
1327      # the prototype of a destructor is ``=destroy(x: var T)`` and that of a
1328      # finalizer is: ``proc (x: ref T) {.nimcall.}``. We need to check the calling
1329      # convention at least:
1330      if op.typ == nil or op.typ.callConv != ccNimCall:
1331        localError(p.module.config, a.lode.info,
1332          "the destructor that is turned into a finalizer needs " &
1333          "to have the 'nimcall' calling convention")
1334      var f: TLoc
1335      initLocExpr(p, newSymNode(op), f)
1336      p.module.s[cfsTypeInit3].addf("$1->finalizer = (void*)$2;$n", [ti, rdLoc(f)])
1337
1338    if a.storage == OnHeap and usesWriteBarrier(p.config):
1339      if canFormAcycle(a.t):
1340        linefmt(p, cpsStmts, "if ($1) { #nimGCunrefRC1($1); $1 = NIM_NIL; }$n", [a.rdLoc])
1341      else:
1342        linefmt(p, cpsStmts, "if ($1) { #nimGCunrefNoCycle($1); $1 = NIM_NIL; }$n", [a.rdLoc])
1343      if p.config.selectedGC == gcGo:
1344        # newObjRC1() would clash with unsureAsgnRef() - which is used by gcGo to
1345        # implement the write barrier
1346        b.r = ropecg(p.module, "($1) #newObj($2, $3)", [getTypeDesc(p.module, typ), ti, sizeExpr])
1347        linefmt(p, cpsStmts, "#unsureAsgnRef((void**) $1, $2);$n",
1348                [addrLoc(p.config, a), b.rdLoc])
1349      else:
1350        # use newObjRC1 as an optimization
1351        b.r = ropecg(p.module, "($1) #newObjRC1($2, $3)", [getTypeDesc(p.module, typ), ti, sizeExpr])
1352        linefmt(p, cpsStmts, "$1 = $2;$n", [a.rdLoc, b.rdLoc])
1353    else:
1354      b.r = ropecg(p.module, "($1) #newObj($2, $3)", [getTypeDesc(p.module, typ), ti, sizeExpr])
1355      genAssignment(p, a, b, {})
1356  # set the object type:
1357  genObjectInit(p, cpsStmts, bt, a, constructRefObj)
1358
1359proc genNew(p: BProc, e: PNode) =
1360  var a: TLoc
1361  initLocExpr(p, e[1], a)
1362  # 'genNew' also handles 'unsafeNew':
1363  if e.len == 3:
1364    var se: TLoc
1365    initLocExpr(p, e[2], se)
1366    rawGenNew(p, a, se.rdLoc, needsInit = true)
1367  else:
1368    rawGenNew(p, a, nil, needsInit = true)
1369  gcUsage(p.config, e)
1370
1371proc genNewSeqAux(p: BProc, dest: TLoc, length: Rope; lenIsZero: bool) =
1372  let seqtype = skipTypes(dest.t, abstractVarRange)
1373  var call: TLoc
1374  initLoc(call, locExpr, dest.lode, OnHeap)
1375  if dest.storage == OnHeap and usesWriteBarrier(p.config):
1376    if canFormAcycle(dest.t):
1377      linefmt(p, cpsStmts, "if ($1) { #nimGCunrefRC1($1); $1 = NIM_NIL; }$n", [dest.rdLoc])
1378    else:
1379      linefmt(p, cpsStmts, "if ($1) { #nimGCunrefNoCycle($1); $1 = NIM_NIL; }$n", [dest.rdLoc])
1380    if not lenIsZero:
1381      if p.config.selectedGC == gcGo:
1382        # we need the write barrier
1383        call.r = ropecg(p.module, "($1) #newSeq($2, $3)", [getTypeDesc(p.module, seqtype),
1384              genTypeInfoV1(p.module, seqtype, dest.lode.info), length])
1385        linefmt(p, cpsStmts, "#unsureAsgnRef((void**) $1, $2);$n", [addrLoc(p.config, dest), call.rdLoc])
1386      else:
1387        call.r = ropecg(p.module, "($1) #newSeqRC1($2, $3)", [getTypeDesc(p.module, seqtype),
1388              genTypeInfoV1(p.module, seqtype, dest.lode.info), length])
1389        linefmt(p, cpsStmts, "$1 = $2;$n", [dest.rdLoc, call.rdLoc])
1390  else:
1391    if lenIsZero:
1392      call.r = rope"NIM_NIL"
1393    else:
1394      call.r = ropecg(p.module, "($1) #newSeq($2, $3)", [getTypeDesc(p.module, seqtype),
1395              genTypeInfoV1(p.module, seqtype, dest.lode.info), length])
1396    genAssignment(p, dest, call, {})
1397
1398proc genNewSeq(p: BProc, e: PNode) =
1399  var a, b: TLoc
1400  initLocExpr(p, e[1], a)
1401  initLocExpr(p, e[2], b)
1402  if optSeqDestructors in p.config.globalOptions:
1403    let seqtype = skipTypes(e[1].typ, abstractVarRange)
1404    linefmt(p, cpsStmts, "$1.len = $2; $1.p = ($4*) #newSeqPayload($2, sizeof($3), NIM_ALIGNOF($3));$n",
1405      [a.rdLoc, b.rdLoc,
1406       getTypeDesc(p.module, seqtype.lastSon),
1407       getSeqPayloadType(p.module, seqtype)])
1408  else:
1409    let lenIsZero = e[2].kind == nkIntLit and e[2].intVal == 0
1410    genNewSeqAux(p, a, b.rdLoc, lenIsZero)
1411    gcUsage(p.config, e)
1412
1413proc genNewSeqOfCap(p: BProc; e: PNode; d: var TLoc) =
1414  let seqtype = skipTypes(e.typ, abstractVarRange)
1415  var a: TLoc
1416  initLocExpr(p, e[1], a)
1417  if optSeqDestructors in p.config.globalOptions:
1418    if d.k == locNone: getTemp(p, e.typ, d, needsInit=false)
1419    linefmt(p, cpsStmts, "$1.len = 0; $1.p = ($4*) #newSeqPayload($2, sizeof($3), NIM_ALIGNOF($3));$n",
1420      [d.rdLoc, a.rdLoc, getTypeDesc(p.module, seqtype.lastSon),
1421      getSeqPayloadType(p.module, seqtype),
1422    ])
1423  else:
1424    putIntoDest(p, d, e, ropecg(p.module,
1425                "($1)#nimNewSeqOfCap($2, $3)", [
1426                getTypeDesc(p.module, seqtype),
1427                genTypeInfoV1(p.module, seqtype, e.info), a.rdLoc]))
1428    gcUsage(p.config, e)
1429
1430proc rawConstExpr(p: BProc, n: PNode; d: var TLoc) =
1431  let t = n.typ
1432  discard getTypeDesc(p.module, t) # so that any fields are initialized
1433  let id = nodeTableTestOrSet(p.module.dataCache, n, p.module.labels)
1434  fillLoc(d, locData, n, p.module.tmpBase & rope(id), OnStatic)
1435  if id == p.module.labels:
1436    # expression not found in the cache:
1437    inc(p.module.labels)
1438    p.module.s[cfsData].addf("static NIM_CONST $1 $2 = $3;$n",
1439          [getTypeDesc(p.module, t), d.r, genBracedInit(p, n, isConst = true, t)])
1440
1441proc handleConstExpr(p: BProc, n: PNode, d: var TLoc): bool =
1442  if d.k == locNone and n.len > ord(n.kind == nkObjConstr) and n.isDeepConstExpr:
1443    rawConstExpr(p, n, d)
1444    result = true
1445  else:
1446    result = false
1447
1448proc genObjConstr(p: BProc, e: PNode, d: var TLoc) =
1449  #echo renderTree e, " ", e.isDeepConstExpr
1450  # inheritance in C++ does not allow struct initialization so
1451  # we skip this step here:
1452  if not p.module.compileToCpp and optSeqDestructors notin p.config.globalOptions:
1453    # disabled optimization: it is wrong for C++ and now also
1454    # causes trouble for --gc:arc, see bug #13240
1455    #[
1456      var box: seq[Thing]
1457      for i in 0..3:
1458        box.add Thing(s1: "121") # pass by sink can mutate Thing.
1459    ]#
1460    if handleConstExpr(p, e, d): return
1461  var t = e.typ.skipTypes(abstractInstOwned)
1462  let isRef = t.kind == tyRef
1463
1464  # check if we need to construct the object in a temporary
1465  var useTemp =
1466        isRef or
1467        (d.k notin {locTemp,locLocalVar,locGlobalVar,locParam,locField}) or
1468        (isPartOf(d.lode, e) != arNo)
1469
1470  var tmp: TLoc
1471  var r: Rope
1472  if useTemp:
1473    getTemp(p, t, tmp)
1474    r = rdLoc(tmp)
1475    if isRef:
1476      rawGenNew(p, tmp, nil, needsInit = nfAllFieldsSet notin e.flags)
1477      t = t.lastSon.skipTypes(abstractInstOwned)
1478      r = "(*$1)" % [r]
1479      gcUsage(p.config, e)
1480    else:
1481      constructLoc(p, tmp)
1482  else:
1483    resetLoc(p, d)
1484    r = rdLoc(d)
1485  discard getTypeDesc(p.module, t)
1486  let ty = getUniqueType(t)
1487  for i in 1..<e.len:
1488    let it = e[i]
1489    var tmp2: TLoc
1490    tmp2.r = r
1491    let field = lookupFieldAgain(p, ty, it[0].sym, tmp2.r)
1492    if field.loc.r == nil: fillObjectFields(p.module, ty)
1493    if field.loc.r == nil: internalError(p.config, e.info, "genObjConstr")
1494    if it.len == 3 and optFieldCheck in p.options:
1495      genFieldCheck(p, it[2], r, field)
1496    tmp2.r.add(".")
1497    tmp2.r.add(field.loc.r)
1498    if useTemp:
1499      tmp2.k = locTemp
1500      tmp2.storage = if isRef: OnHeap else: OnStack
1501    else:
1502      tmp2.k = d.k
1503      tmp2.storage = if isRef: OnHeap else: d.storage
1504    tmp2.lode = it[1]
1505    expr(p, it[1], tmp2)
1506  if useTemp:
1507    if d.k == locNone:
1508      d = tmp
1509    else:
1510      genAssignment(p, d, tmp, {})
1511
1512proc lhsDoesAlias(a, b: PNode): bool =
1513  for y in b:
1514    if isPartOf(a, y) != arNo: return true
1515
1516proc genSeqConstr(p: BProc, n: PNode, d: var TLoc) =
1517  var arr, tmp: TLoc
1518  # bug #668
1519  let doesAlias = lhsDoesAlias(d.lode, n)
1520  let dest = if doesAlias: addr(tmp) else: addr(d)
1521  if doesAlias:
1522    getTemp(p, n.typ, tmp)
1523  elif d.k == locNone:
1524    getTemp(p, n.typ, d)
1525
1526  let l = intLiteral(n.len)
1527  if optSeqDestructors in p.config.globalOptions:
1528    let seqtype = n.typ
1529    linefmt(p, cpsStmts, "$1.len = $2; $1.p = ($4*) #newSeqPayload($2, sizeof($3), NIM_ALIGNOF($3));$n",
1530      [rdLoc dest[], l, getTypeDesc(p.module, seqtype.lastSon),
1531      getSeqPayloadType(p.module, seqtype)])
1532  else:
1533    # generate call to newSeq before adding the elements per hand:
1534    genNewSeqAux(p, dest[], l, n.len == 0)
1535  for i in 0..<n.len:
1536    initLoc(arr, locExpr, n[i], OnHeap)
1537    arr.r = ropecg(p.module, "$1$3[$2]", [rdLoc(dest[]), intLiteral(i), dataField(p)])
1538    arr.storage = OnHeap            # we know that sequences are on the heap
1539    expr(p, n[i], arr)
1540  gcUsage(p.config, n)
1541  if doesAlias:
1542    if d.k == locNone:
1543      d = tmp
1544    else:
1545      genAssignment(p, d, tmp, {})
1546
1547proc genArrToSeq(p: BProc, n: PNode, d: var TLoc) =
1548  var elem, a, arr: TLoc
1549  if n[1].kind == nkBracket:
1550    n[1].typ = n.typ
1551    genSeqConstr(p, n[1], d)
1552    return
1553  if d.k == locNone:
1554    getTemp(p, n.typ, d)
1555  # generate call to newSeq before adding the elements per hand:
1556  let L = toInt(lengthOrd(p.config, n[1].typ))
1557  if optSeqDestructors in p.config.globalOptions:
1558    let seqtype = n.typ
1559    linefmt(p, cpsStmts, "$1.len = $2; $1.p = ($4*) #newSeqPayload($2, sizeof($3), NIM_ALIGNOF($3));$n",
1560      [rdLoc d, L, getTypeDesc(p.module, seqtype.lastSon),
1561      getSeqPayloadType(p.module, seqtype)])
1562  else:
1563    genNewSeqAux(p, d, intLiteral(L), L == 0)
1564  initLocExpr(p, n[1], a)
1565  # bug #5007; do not produce excessive C source code:
1566  if L < 10:
1567    for i in 0..<L:
1568      initLoc(elem, locExpr, lodeTyp elemType(skipTypes(n.typ, abstractInst)), OnHeap)
1569      elem.r = ropecg(p.module, "$1$3[$2]", [rdLoc(d), intLiteral(i), dataField(p)])
1570      elem.storage = OnHeap # we know that sequences are on the heap
1571      initLoc(arr, locExpr, lodeTyp elemType(skipTypes(n[1].typ, abstractInst)), a.storage)
1572      arr.r = ropecg(p.module, "$1[$2]", [rdLoc(a), intLiteral(i)])
1573      genAssignment(p, elem, arr, {needToCopy})
1574  else:
1575    var i: TLoc
1576    getTemp(p, getSysType(p.module.g.graph, unknownLineInfo, tyInt), i)
1577    linefmt(p, cpsStmts, "for ($1 = 0; $1 < $2; $1++) {$n",  [i.r, L])
1578    initLoc(elem, locExpr, lodeTyp elemType(skipTypes(n.typ, abstractInst)), OnHeap)
1579    elem.r = ropecg(p.module, "$1$3[$2]", [rdLoc(d), rdLoc(i), dataField(p)])
1580    elem.storage = OnHeap # we know that sequences are on the heap
1581    initLoc(arr, locExpr, lodeTyp elemType(skipTypes(n[1].typ, abstractInst)), a.storage)
1582    arr.r = ropecg(p.module, "$1[$2]", [rdLoc(a), rdLoc(i)])
1583    genAssignment(p, elem, arr, {needToCopy})
1584    lineF(p, cpsStmts, "}$n", [])
1585
1586
1587proc genNewFinalize(p: BProc, e: PNode) =
1588  var
1589    a, b, f: TLoc
1590    refType, bt: PType
1591    ti: Rope
1592  refType = skipTypes(e[1].typ, abstractVarRange)
1593  initLocExpr(p, e[1], a)
1594  initLocExpr(p, e[2], f)
1595  initLoc(b, locExpr, a.lode, OnHeap)
1596  ti = genTypeInfo(p.config, p.module, refType, e.info)
1597  p.module.s[cfsTypeInit3].addf("$1->finalizer = (void*)$2;$n", [ti, rdLoc(f)])
1598  b.r = ropecg(p.module, "($1) #newObj($2, sizeof($3))", [
1599      getTypeDesc(p.module, refType),
1600      ti, getTypeDesc(p.module, skipTypes(refType.lastSon, abstractRange))])
1601  genAssignment(p, a, b, {})  # set the object type:
1602  bt = skipTypes(refType.lastSon, abstractRange)
1603  genObjectInit(p, cpsStmts, bt, a, constructRefObj)
1604  gcUsage(p.config, e)
1605
1606proc genOfHelper(p: BProc; dest: PType; a: Rope; info: TLineInfo): Rope =
1607  if optTinyRtti in p.config.globalOptions:
1608    result = ropecg(p.module, "#isObj($1.m_type, $2)",
1609      [a, genTypeInfo2Name(p.module, dest)])
1610  else:
1611    # unfortunately 'genTypeInfoV1' sets tfObjHasKids as a side effect, so we
1612    # have to call it here first:
1613    let ti = genTypeInfoV1(p.module, dest, info)
1614    if tfFinal in dest.flags or (objHasKidsValid in p.module.flags and
1615                                tfObjHasKids notin dest.flags):
1616      result = "$1.m_type == $2" % [a, ti]
1617    else:
1618      discard cgsym(p.module, "TNimType")
1619      inc p.module.labels
1620      let cache = "Nim_OfCheck_CACHE" & p.module.labels.rope
1621      p.module.s[cfsVars].addf("static TNimType* $#[2];$n", [cache])
1622      result = ropecg(p.module, "#isObjWithCache($#.m_type, $#, $#)", [a, ti, cache])
1623    when false:
1624      # former version:
1625      result = ropecg(p.module, "#isObj($1.m_type, $2)",
1626                    [a, genTypeInfoV1(p.module, dest, info)])
1627
1628proc genOf(p: BProc, x: PNode, typ: PType, d: var TLoc) =
1629  var a: TLoc
1630  initLocExpr(p, x, a)
1631  var dest = skipTypes(typ, typedescPtrs)
1632  var r = rdLoc(a)
1633  var nilCheck: Rope = nil
1634  var t = skipTypes(a.t, abstractInstOwned)
1635  while t.kind in {tyVar, tyLent, tyPtr, tyRef}:
1636    if t.kind notin {tyVar, tyLent}: nilCheck = r
1637    if t.kind notin {tyVar, tyLent} or not p.module.compileToCpp:
1638      r = ropecg(p.module, "(*$1)", [r])
1639    t = skipTypes(t.lastSon, typedescInst+{tyOwned})
1640  discard getTypeDesc(p.module, t)
1641  if not p.module.compileToCpp:
1642    while t.kind == tyObject and t[0] != nil:
1643      r.add(~".Sup")
1644      t = skipTypes(t[0], skipPtrs)
1645  if isObjLackingTypeField(t):
1646    globalError(p.config, x.info,
1647      "no 'of' operator available for pure objects")
1648  if nilCheck != nil:
1649    r = ropecg(p.module, "(($1) && ($2))", [nilCheck, genOfHelper(p, dest, r, x.info)])
1650  else:
1651    r = ropecg(p.module, "($1)", [genOfHelper(p, dest, r, x.info)])
1652  putIntoDest(p, d, x, r, a.storage)
1653
1654proc genOf(p: BProc, n: PNode, d: var TLoc) =
1655  genOf(p, n[1], n[2].typ, d)
1656
1657proc genRepr(p: BProc, e: PNode, d: var TLoc) =
1658  if optTinyRtti in p.config.globalOptions:
1659    localError(p.config, e.info, "'repr' is not available for --newruntime")
1660  var a: TLoc
1661  initLocExpr(p, e[1], a)
1662  var t = skipTypes(e[1].typ, abstractVarRange)
1663  case t.kind
1664  of tyInt..tyInt64, tyUInt..tyUInt64:
1665    putIntoDest(p, d, e,
1666                ropecg(p.module, "#reprInt((NI64)$1)", [rdLoc(a)]), a.storage)
1667  of tyFloat..tyFloat128:
1668    putIntoDest(p, d, e, ropecg(p.module, "#reprFloat($1)", [rdLoc(a)]), a.storage)
1669  of tyBool:
1670    putIntoDest(p, d, e, ropecg(p.module, "#reprBool($1)", [rdLoc(a)]), a.storage)
1671  of tyChar:
1672    putIntoDest(p, d, e, ropecg(p.module, "#reprChar($1)", [rdLoc(a)]), a.storage)
1673  of tyEnum, tyOrdinal:
1674    putIntoDest(p, d, e,
1675                ropecg(p.module, "#reprEnum((NI)$1, $2)", [
1676                rdLoc(a), genTypeInfoV1(p.module, t, e.info)]), a.storage)
1677  of tyString:
1678    putIntoDest(p, d, e, ropecg(p.module, "#reprStr($1)", [rdLoc(a)]), a.storage)
1679  of tySet:
1680    putIntoDest(p, d, e, ropecg(p.module, "#reprSet($1, $2)", [
1681                addrLoc(p.config, a), genTypeInfoV1(p.module, t, e.info)]), a.storage)
1682  of tyOpenArray, tyVarargs:
1683    var b: TLoc
1684    case skipTypes(a.t, abstractVarRange).kind
1685    of tyOpenArray, tyVarargs:
1686      putIntoDest(p, b, e, "$1, $1Len_0" % [rdLoc(a)], a.storage)
1687    of tyString, tySequence:
1688      putIntoDest(p, b, e,
1689                  "$1$3, $2" % [rdLoc(a), lenExpr(p, a), dataField(p)], a.storage)
1690    of tyArray:
1691      putIntoDest(p, b, e,
1692                  "$1, $2" % [rdLoc(a), rope(lengthOrd(p.config, a.t))], a.storage)
1693    else: internalError(p.config, e[0].info, "genRepr()")
1694    putIntoDest(p, d, e,
1695        ropecg(p.module, "#reprOpenArray($1, $2)", [rdLoc(b),
1696        genTypeInfoV1(p.module, elemType(t), e.info)]), a.storage)
1697  of tyCstring, tyArray, tyRef, tyPtr, tyPointer, tyNil, tySequence:
1698    putIntoDest(p, d, e,
1699                ropecg(p.module, "#reprAny($1, $2)", [
1700                rdLoc(a), genTypeInfoV1(p.module, t, e.info)]), a.storage)
1701  of tyEmpty, tyVoid:
1702    localError(p.config, e.info, "'repr' doesn't support 'void' type")
1703  else:
1704    putIntoDest(p, d, e, ropecg(p.module, "#reprAny($1, $2)",
1705                              [addrLoc(p.config, a), genTypeInfoV1(p.module, t, e.info)]),
1706                               a.storage)
1707  gcUsage(p.config, e)
1708
1709proc rdMType(p: BProc; a: TLoc; nilCheck: var Rope; enforceV1 = false): Rope =
1710  result = rdLoc(a)
1711  var t = skipTypes(a.t, abstractInst)
1712  while t.kind in {tyVar, tyLent, tyPtr, tyRef}:
1713    if t.kind notin {tyVar, tyLent}: nilCheck = result
1714    if t.kind notin {tyVar, tyLent} or not p.module.compileToCpp:
1715      result = "(*$1)" % [result]
1716    t = skipTypes(t.lastSon, abstractInst)
1717  discard getTypeDesc(p.module, t)
1718  if not p.module.compileToCpp:
1719    while t.kind == tyObject and t[0] != nil:
1720      result.add(".Sup")
1721      t = skipTypes(t[0], skipPtrs)
1722  result.add ".m_type"
1723  if optTinyRtti in p.config.globalOptions and enforceV1:
1724    result.add "->typeInfoV1"
1725
1726proc genGetTypeInfo(p: BProc, e: PNode, d: var TLoc) =
1727  discard cgsym(p.module, "TNimType")
1728  let t = e[1].typ
1729  # ordinary static type information
1730  putIntoDest(p, d, e, genTypeInfoV1(p.module, t, e.info))
1731
1732proc genGetTypeInfoV2(p: BProc, e: PNode, d: var TLoc) =
1733  let t = e[1].typ
1734  if isFinal(t) or e[0].sym.name.s != "getDynamicTypeInfo":
1735    # ordinary static type information
1736    putIntoDest(p, d, e, genTypeInfoV2(p.module, t, e.info))
1737  else:
1738    var a: TLoc
1739    initLocExpr(p, e[1], a)
1740    var nilCheck = Rope(nil)
1741    # use the dynamic type stored at offset 0:
1742    putIntoDest(p, d, e, rdMType(p, a, nilCheck))
1743
1744proc genAccessTypeField(p: BProc; e: PNode; d: var TLoc) =
1745  var a: TLoc
1746  initLocExpr(p, e[1], a)
1747  var nilCheck = Rope(nil)
1748  # use the dynamic type stored at offset 0:
1749  putIntoDest(p, d, e, rdMType(p, a, nilCheck))
1750
1751template genDollar(p: BProc, n: PNode, d: var TLoc, frmt: string) =
1752  var a: TLoc
1753  initLocExpr(p, n[1], a)
1754  a.r = ropecg(p.module, frmt, [rdLoc(a)])
1755  a.flags.excl lfIndirect # this flag should not be propagated here (not just for HCR)
1756  if d.k == locNone: getTemp(p, n.typ, d)
1757  genAssignment(p, d, a, {})
1758  gcUsage(p.config, n)
1759
1760proc genArrayLen(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
1761  var a = e[1]
1762  if a.kind == nkHiddenAddr: a = a[0]
1763  var typ = skipTypes(a.typ, abstractVar + tyUserTypeClasses)
1764  case typ.kind
1765  of tyOpenArray, tyVarargs:
1766    # Bug #9279, len(toOpenArray()) has to work:
1767    if a.kind in nkCallKinds and a[0].kind == nkSym and a[0].sym.magic == mSlice:
1768      # magic: pass slice to openArray:
1769      var b, c: TLoc
1770      initLocExpr(p, a[2], b)
1771      initLocExpr(p, a[3], c)
1772      if op == mHigh:
1773        putIntoDest(p, d, e, ropecg(p.module, "($2)-($1)", [rdLoc(b), rdLoc(c)]))
1774      else:
1775        putIntoDest(p, d, e, ropecg(p.module, "($2)-($1)+1", [rdLoc(b), rdLoc(c)]))
1776    else:
1777      if not reifiedOpenArray(a):
1778        if op == mHigh: unaryExpr(p, e, d, "($1Len_0-1)")
1779        else: unaryExpr(p, e, d, "$1Len_0")
1780      else:
1781        if op == mHigh: unaryExpr(p, e, d, "($1.Field1-1)")
1782        else: unaryExpr(p, e, d, "$1.Field1")
1783  of tyCstring:
1784    if op == mHigh: unaryExpr(p, e, d, "($1 ? (#nimCStrLen($1)-1) : -1)")
1785    else: unaryExpr(p, e, d, "($1 ? #nimCStrLen($1) : 0)")
1786  of tyString:
1787    var a: TLoc
1788    initLocExpr(p, e[1], a)
1789    var x = lenExpr(p, a)
1790    if op == mHigh: x = "($1-1)" % [x]
1791    putIntoDest(p, d, e, x)
1792  of tySequence:
1793    # we go through a temporary here because people write bullshit code.
1794    var a, tmp: TLoc
1795    initLocExpr(p, e[1], a)
1796    getIntTemp(p, tmp)
1797    var x = lenExpr(p, a)
1798    if op == mHigh: x = "($1-1)" % [x]
1799    lineCg(p, cpsStmts, "$1 = $2;$n", [tmp.r, x])
1800    putIntoDest(p, d, e, tmp.r)
1801  of tyArray:
1802    # YYY: length(sideeffect) is optimized away incorrectly?
1803    if op == mHigh: putIntoDest(p, d, e, rope(lastOrd(p.config, typ)))
1804    else: putIntoDest(p, d, e, rope(lengthOrd(p.config, typ)))
1805  else: internalError(p.config, e.info, "genArrayLen()")
1806
1807proc makePtrType(baseType: PType; idgen: IdGenerator): PType =
1808  result = newType(tyPtr, nextTypeId idgen, baseType.owner)
1809  addSonSkipIntLit(result, baseType, idgen)
1810
1811proc makeAddr(n: PNode; idgen: IdGenerator): PNode =
1812  if n.kind == nkHiddenAddr:
1813    result = n
1814  else:
1815    result = newTree(nkHiddenAddr, n)
1816    result.typ = makePtrType(n.typ, idgen)
1817
1818proc genSetLengthSeq(p: BProc, e: PNode, d: var TLoc) =
1819  if optSeqDestructors in p.config.globalOptions:
1820    e[1] = makeAddr(e[1], p.module.idgen)
1821    genCall(p, e, d)
1822    return
1823  var a, b, call: TLoc
1824  assert(d.k == locNone)
1825  var x = e[1]
1826  if x.kind in {nkAddr, nkHiddenAddr}: x = x[0]
1827  initLocExpr(p, x, a)
1828  initLocExpr(p, e[2], b)
1829  let t = skipTypes(e[1].typ, {tyVar})
1830
1831  initLoc(call, locCall, e, OnHeap)
1832  if not p.module.compileToCpp:
1833    const setLenPattern = "($3) #setLengthSeqV2(&($1)->Sup, $4, $2)"
1834    call.r = ropecg(p.module, setLenPattern, [
1835      rdLoc(a), rdLoc(b), getTypeDesc(p.module, t),
1836      genTypeInfoV1(p.module, t.skipTypes(abstractInst), e.info)])
1837
1838  else:
1839    const setLenPattern = "($3) #setLengthSeqV2($1, $4, $2)"
1840    call.r = ropecg(p.module, setLenPattern, [
1841      rdLoc(a), rdLoc(b), getTypeDesc(p.module, t),
1842      genTypeInfoV1(p.module, t.skipTypes(abstractInst), e.info)])
1843
1844  genAssignment(p, a, call, {})
1845  gcUsage(p.config, e)
1846
1847proc genSetLengthStr(p: BProc, e: PNode, d: var TLoc) =
1848  if optSeqDestructors in p.config.globalOptions:
1849    binaryStmtAddr(p, e, d, "setLengthStrV2")
1850  else:
1851    var a, b, call: TLoc
1852    if d.k != locNone: internalError(p.config, e.info, "genSetLengthStr")
1853    initLocExpr(p, e[1], a)
1854    initLocExpr(p, e[2], b)
1855
1856    initLoc(call, locCall, e, OnHeap)
1857    call.r = ropecg(p.module, "#setLengthStr($1, $2)", [
1858        rdLoc(a), rdLoc(b)])
1859    genAssignment(p, a, call, {})
1860    gcUsage(p.config, e)
1861
1862proc genSwap(p: BProc, e: PNode, d: var TLoc) =
1863  # swap(a, b) -->
1864  # temp = a
1865  # a = b
1866  # b = temp
1867  cowBracket(p, e[1])
1868  cowBracket(p, e[2])
1869  var a, b, tmp: TLoc
1870  getTemp(p, skipTypes(e[1].typ, abstractVar), tmp)
1871  initLocExpr(p, e[1], a) # eval a
1872  initLocExpr(p, e[2], b) # eval b
1873  genAssignment(p, tmp, a, {})
1874  genAssignment(p, a, b, {})
1875  genAssignment(p, b, tmp, {})
1876
1877proc rdSetElemLoc(conf: ConfigRef; a: TLoc, typ: PType): Rope =
1878  # read a location of an set element; it may need a subtraction operation
1879  # before the set operation
1880  result = rdCharLoc(a)
1881  let setType = typ.skipTypes(abstractPtrs)
1882  assert(setType.kind == tySet)
1883  if firstOrd(conf, setType) != 0:
1884    result = "($1- $2)" % [result, rope(firstOrd(conf, setType))]
1885
1886proc fewCmps(conf: ConfigRef; s: PNode): bool =
1887  # this function estimates whether it is better to emit code
1888  # for constructing the set or generating a bunch of comparisons directly
1889  if s.kind != nkCurly: return false
1890  if (getSize(conf, s.typ) <= conf.target.intSize) and (nfAllConst in s.flags):
1891    result = false            # it is better to emit the set generation code
1892  elif elemType(s.typ).kind in {tyInt, tyInt16..tyInt64}:
1893    result = true             # better not emit the set if int is basetype!
1894  else:
1895    result = s.len <= 8  # 8 seems to be a good value
1896
1897template binaryExprIn(p: BProc, e: PNode, a, b, d: var TLoc, frmt: string) =
1898  putIntoDest(p, d, e, frmt % [rdLoc(a), rdSetElemLoc(p.config, b, a.t)])
1899
1900proc genInExprAux(p: BProc, e: PNode, a, b, d: var TLoc) =
1901  case int(getSize(p.config, skipTypes(e[1].typ, abstractVar)))
1902  of 1: binaryExprIn(p, e, a, b, d, "(($1 &((NU8)1<<((NU)($2)&7U)))!=0)")
1903  of 2: binaryExprIn(p, e, a, b, d, "(($1 &((NU16)1<<((NU)($2)&15U)))!=0)")
1904  of 4: binaryExprIn(p, e, a, b, d, "(($1 &((NU32)1<<((NU)($2)&31U)))!=0)")
1905  of 8: binaryExprIn(p, e, a, b, d, "(($1 &((NU64)1<<((NU)($2)&63U)))!=0)")
1906  else: binaryExprIn(p, e, a, b, d, "(($1[(NU)($2)>>3] &(1U<<((NU)($2)&7U)))!=0)")
1907
1908template binaryStmtInExcl(p: BProc, e: PNode, d: var TLoc, frmt: string) =
1909  var a, b: TLoc
1910  assert(d.k == locNone)
1911  initLocExpr(p, e[1], a)
1912  initLocExpr(p, e[2], b)
1913  lineF(p, cpsStmts, frmt, [rdLoc(a), rdSetElemLoc(p.config, b, a.t)])
1914
1915proc genInOp(p: BProc, e: PNode, d: var TLoc) =
1916  var a, b, x, y: TLoc
1917  if (e[1].kind == nkCurly) and fewCmps(p.config, e[1]):
1918    # a set constructor but not a constant set:
1919    # do not emit the set, but generate a bunch of comparisons; and if we do
1920    # so, we skip the unnecessary range check: This is a semantical extension
1921    # that code now relies on. :-/ XXX
1922    let ea = if e[2].kind in {nkChckRange, nkChckRange64}:
1923               e[2][0]
1924             else:
1925               e[2]
1926    initLocExpr(p, ea, a)
1927    initLoc(b, locExpr, e, OnUnknown)
1928    if e[1].len > 0:
1929      b.r = rope("(")
1930      for i in 0..<e[1].len:
1931        let it = e[1][i]
1932        if it.kind == nkRange:
1933          initLocExpr(p, it[0], x)
1934          initLocExpr(p, it[1], y)
1935          b.r.addf("$1 >= $2 && $1 <= $3",
1936               [rdCharLoc(a), rdCharLoc(x), rdCharLoc(y)])
1937        else:
1938          initLocExpr(p, it, x)
1939          b.r.addf("$1 == $2", [rdCharLoc(a), rdCharLoc(x)])
1940        if i < e[1].len - 1: b.r.add(" || ")
1941      b.r.add(")")
1942    else:
1943      # handle the case of an empty set
1944      b.r = rope("0")
1945    putIntoDest(p, d, e, b.r)
1946  else:
1947    assert(e[1].typ != nil)
1948    assert(e[2].typ != nil)
1949    initLocExpr(p, e[1], a)
1950    initLocExpr(p, e[2], b)
1951    genInExprAux(p, e, a, b, d)
1952
1953proc genSetOp(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
1954  const
1955    lookupOpr: array[mLeSet..mMinusSet, string] = [
1956      "for ($1 = 0; $1 < $2; $1++) { $n" &
1957      "  $3 = (($4[$1] & ~ $5[$1]) == 0);$n" &
1958      "  if (!$3) break;}$n",
1959      "for ($1 = 0; $1 < $2; $1++) { $n" &
1960      "  $3 = (($4[$1] & ~ $5[$1]) == 0);$n" &
1961      "  if (!$3) break;}$n" &
1962      "if ($3) $3 = (#nimCmpMem($4, $5, $2) != 0);$n",
1963      "&",
1964      "|",
1965      "& ~"]
1966  var a, b, i: TLoc
1967  var setType = skipTypes(e[1].typ, abstractVar)
1968  var size = int(getSize(p.config, setType))
1969  case size
1970  of 1, 2, 4, 8:
1971    case op
1972    of mIncl:
1973      case size
1974      of 1: binaryStmtInExcl(p, e, d, "$1 |= ((NU8)1)<<(($2) & 7);$n")
1975      of 2: binaryStmtInExcl(p, e, d, "$1 |= ((NU16)1)<<(($2) & 15);$n")
1976      of 4: binaryStmtInExcl(p, e, d, "$1 |= ((NU32)1)<<(($2) & 31);$n")
1977      of 8: binaryStmtInExcl(p, e, d, "$1 |= ((NU64)1)<<(($2) & 63);$n")
1978      else: assert(false, $size)
1979    of mExcl:
1980      case size
1981      of 1: binaryStmtInExcl(p, e, d, "$1 &= ~(((NU8)1) << (($2) & 7));$n")
1982      of 2: binaryStmtInExcl(p, e, d, "$1 &= ~(((NU16)1) << (($2) & 15));$n")
1983      of 4: binaryStmtInExcl(p, e, d, "$1 &= ~(((NU32)1) << (($2) & 31));$n")
1984      of 8: binaryStmtInExcl(p, e, d, "$1 &= ~(((NU64)1) << (($2) & 63));$n")
1985      else: assert(false, $size)
1986    of mCard:
1987      if size <= 4: unaryExprChar(p, e, d, "#countBits32($1)")
1988      else: unaryExprChar(p, e, d, "#countBits64($1)")
1989    of mLtSet: binaryExprChar(p, e, d, "((($1 & ~ $2)==0)&&($1 != $2))")
1990    of mLeSet: binaryExprChar(p, e, d, "(($1 & ~ $2)==0)")
1991    of mEqSet: binaryExpr(p, e, d, "($1 == $2)")
1992    of mMulSet: binaryExpr(p, e, d, "($1 & $2)")
1993    of mPlusSet: binaryExpr(p, e, d, "($1 | $2)")
1994    of mMinusSet: binaryExpr(p, e, d, "($1 & ~ $2)")
1995    of mInSet:
1996      genInOp(p, e, d)
1997    else: internalError(p.config, e.info, "genSetOp()")
1998  else:
1999    case op
2000    of mIncl: binaryStmtInExcl(p, e, d, "$1[(NU)($2)>>3] |=(1U<<($2&7U));$n")
2001    of mExcl: binaryStmtInExcl(p, e, d, "$1[(NU)($2)>>3] &= ~(1U<<($2&7U));$n")
2002    of mCard:
2003      var a: TLoc
2004      initLocExpr(p, e[1], a)
2005      putIntoDest(p, d, e, ropecg(p.module, "#cardSet($1, $2)", [rdCharLoc(a), size]))
2006    of mLtSet, mLeSet:
2007      getTemp(p, getSysType(p.module.g.graph, unknownLineInfo, tyInt), i) # our counter
2008      initLocExpr(p, e[1], a)
2009      initLocExpr(p, e[2], b)
2010      if d.k == locNone: getTemp(p, getSysType(p.module.g.graph, unknownLineInfo, tyBool), d)
2011      if op == mLtSet:
2012        linefmt(p, cpsStmts, lookupOpr[mLtSet],
2013           [rdLoc(i), size, rdLoc(d), rdLoc(a), rdLoc(b)])
2014      else:
2015        linefmt(p, cpsStmts, lookupOpr[mLeSet],
2016           [rdLoc(i), size, rdLoc(d), rdLoc(a), rdLoc(b)])
2017    of mEqSet:
2018      var a, b: TLoc
2019      assert(e[1].typ != nil)
2020      assert(e[2].typ != nil)
2021      initLocExpr(p, e[1], a)
2022      initLocExpr(p, e[2], b)
2023      putIntoDest(p, d, e, ropecg(p.module, "(#nimCmpMem($1, $2, $3)==0)", [a.rdCharLoc, b.rdCharLoc, size]))
2024    of mMulSet, mPlusSet, mMinusSet:
2025      # we inline the simple for loop for better code generation:
2026      getTemp(p, getSysType(p.module.g.graph, unknownLineInfo, tyInt), i) # our counter
2027      initLocExpr(p, e[1], a)
2028      initLocExpr(p, e[2], b)
2029      if d.k == locNone: getTemp(p, setType, d)
2030      lineF(p, cpsStmts,
2031           "for ($1 = 0; $1 < $2; $1++) $n" &
2032           "  $3[$1] = $4[$1] $6 $5[$1];$n", [
2033          rdLoc(i), rope(size), rdLoc(d), rdLoc(a), rdLoc(b),
2034          rope(lookupOpr[op])])
2035    of mInSet: genInOp(p, e, d)
2036    else: internalError(p.config, e.info, "genSetOp")
2037
2038proc genOrd(p: BProc, e: PNode, d: var TLoc) =
2039  unaryExprChar(p, e, d, "$1")
2040
2041proc genSomeCast(p: BProc, e: PNode, d: var TLoc) =
2042  const
2043    ValueTypes = {tyTuple, tyObject, tyArray, tyOpenArray, tyVarargs, tyUncheckedArray}
2044  # we use whatever C gives us. Except if we have a value-type, we need to go
2045  # through its address:
2046  var a: TLoc
2047  initLocExpr(p, e[1], a)
2048  let etyp = skipTypes(e.typ, abstractRange+{tyOwned})
2049  let srcTyp = skipTypes(e[1].typ, abstractRange)
2050  if etyp.kind in ValueTypes and lfIndirect notin a.flags:
2051    putIntoDest(p, d, e, "(*($1*) ($2))" %
2052        [getTypeDesc(p.module, e.typ), addrLoc(p.config, a)], a.storage)
2053  elif etyp.kind == tyProc and etyp.callConv == ccClosure and srcTyp.callConv != ccClosure:
2054    putIntoDest(p, d, e, "(($1) ($2))" %
2055        [getClosureType(p.module, etyp, clHalfWithEnv), rdCharLoc(a)], a.storage)
2056  else:
2057    # C++ does not like direct casts from pointer to shorter integral types
2058    if srcTyp.kind in {tyPtr, tyPointer} and etyp.kind in IntegralTypes:
2059      putIntoDest(p, d, e, "(($1) (ptrdiff_t) ($2))" %
2060          [getTypeDesc(p.module, e.typ), rdCharLoc(a)], a.storage)
2061    elif optSeqDestructors in p.config.globalOptions and etyp.kind in {tySequence, tyString}:
2062      putIntoDest(p, d, e, "(*($1*) (&$2))" %
2063          [getTypeDesc(p.module, e.typ), rdCharLoc(a)], a.storage)
2064    elif etyp.kind == tyBool and srcTyp.kind in IntegralTypes:
2065      putIntoDest(p, d, e, "(($1) != 0)" % [rdCharLoc(a)], a.storage)
2066    else:
2067      putIntoDest(p, d, e, "(($1) ($2))" %
2068          [getTypeDesc(p.module, e.typ), rdCharLoc(a)], a.storage)
2069
2070proc genCast(p: BProc, e: PNode, d: var TLoc) =
2071  const ValueTypes = {tyFloat..tyFloat128, tyTuple, tyObject, tyArray}
2072  let
2073    destt = skipTypes(e.typ, abstractRange)
2074    srct = skipTypes(e[1].typ, abstractRange)
2075  if destt.kind in ValueTypes or srct.kind in ValueTypes:
2076    # 'cast' and some float type involved? --> use a union.
2077    inc(p.labels)
2078    var lbl = p.labels.rope
2079    var tmp: TLoc
2080    tmp.r = "LOC$1.source" % [lbl]
2081    linefmt(p, cpsLocals, "union { $1 source; $2 dest; } LOC$3;$n",
2082      [getTypeDesc(p.module, e[1].typ), getTypeDesc(p.module, e.typ), lbl])
2083    tmp.k = locExpr
2084    tmp.lode = lodeTyp srct
2085    tmp.storage = OnStack
2086    tmp.flags = {}
2087    expr(p, e[1], tmp)
2088    putIntoDest(p, d, e, "LOC$#.dest" % [lbl], tmp.storage)
2089  else:
2090    # I prefer the shorter cast version for pointer types -> generate less
2091    # C code; plus it's the right thing to do for closures:
2092    genSomeCast(p, e, d)
2093
2094proc genRangeChck(p: BProc, n: PNode, d: var TLoc) =
2095  var a: TLoc
2096  var dest = skipTypes(n.typ, abstractVar)
2097  initLocExpr(p, n[0], a)
2098  if optRangeCheck notin p.options or (dest.kind in {tyUInt..tyUInt64} and
2099      checkUnsignedConversions notin p.config.legacyFeatures):
2100    discard "no need to generate a check because it was disabled"
2101  else:
2102    let n0t = n[0].typ
2103
2104    # emit range check:
2105    if n0t.kind in {tyUInt, tyUInt64}:
2106      linefmt(p, cpsStmts, "if ($1 > ($6)($3)){ #raiseRangeErrorNoArgs(); $5}$n",
2107        [rdCharLoc(a), genLiteral(p, n[1], dest), genLiteral(p, n[2], dest),
2108        raiser, raiseInstr(p), getTypeDesc(p.module, n0t)])
2109    else:
2110      let raiser =
2111        case skipTypes(n.typ, abstractVarRange).kind
2112        of tyUInt..tyUInt64, tyChar: "raiseRangeErrorU"
2113        of tyFloat..tyFloat128: "raiseRangeErrorF"
2114        else: "raiseRangeErrorI"
2115      discard cgsym(p.module, raiser)
2116
2117      let boundaryCast =
2118        if n0t.skipTypes(abstractVarRange).kind in {tyUInt, tyUInt32, tyUInt64} or
2119            (n0t.sym != nil and sfSystemModule in n0t.sym.owner.flags and n0t.sym.name.s == "csize"):
2120          "(NI64)"
2121        else:
2122          ""
2123      linefmt(p, cpsStmts, "if ($6($1) < $2 || $6($1) > $3){ $4($1, $2, $3); $5}$n",
2124        [rdCharLoc(a), genLiteral(p, n[1], dest), genLiteral(p, n[2], dest),
2125        raiser, raiseInstr(p), boundaryCast])
2126  putIntoDest(p, d, n, "(($1) ($2))" %
2127      [getTypeDesc(p.module, dest), rdCharLoc(a)], a.storage)
2128
2129proc genConv(p: BProc, e: PNode, d: var TLoc) =
2130  let destType = e.typ.skipTypes({tyVar, tyLent, tyGenericInst, tyAlias, tySink})
2131  if sameBackendType(destType, e[1].typ):
2132    expr(p, e[1], d)
2133  else:
2134    genSomeCast(p, e, d)
2135
2136proc convStrToCStr(p: BProc, n: PNode, d: var TLoc) =
2137  var a: TLoc
2138  initLocExpr(p, n[0], a)
2139  putIntoDest(p, d, n,
2140              ropecg(p.module, "#nimToCStringConv($1)", [rdLoc(a)]),
2141#                "($1 ? $1->data : (NCSTRING)\"\")" % [a.rdLoc],
2142              a.storage)
2143
2144proc convCStrToStr(p: BProc, n: PNode, d: var TLoc) =
2145  var a: TLoc
2146  initLocExpr(p, n[0], a)
2147  putIntoDest(p, d, n,
2148              ropecg(p.module, "#cstrToNimstr($1)", [rdLoc(a)]),
2149              a.storage)
2150  gcUsage(p.config, n)
2151
2152proc genStrEquals(p: BProc, e: PNode, d: var TLoc) =
2153  var x: TLoc
2154  var a = e[1]
2155  var b = e[2]
2156  if a.kind in {nkStrLit..nkTripleStrLit} and a.strVal == "":
2157    initLocExpr(p, e[2], x)
2158    putIntoDest(p, d, e,
2159      ropecg(p.module, "($1 == 0)", [lenExpr(p, x)]))
2160  elif b.kind in {nkStrLit..nkTripleStrLit} and b.strVal == "":
2161    initLocExpr(p, e[1], x)
2162    putIntoDest(p, d, e,
2163      ropecg(p.module, "($1 == 0)", [lenExpr(p, x)]))
2164  else:
2165    binaryExpr(p, e, d, "#eqStrings($1, $2)")
2166
2167proc binaryFloatArith(p: BProc, e: PNode, d: var TLoc, m: TMagic) =
2168  if {optNaNCheck, optInfCheck} * p.options != {}:
2169    const opr: array[mAddF64..mDivF64, string] = ["+", "-", "*", "/"]
2170    var a, b: TLoc
2171    assert(e[1].typ != nil)
2172    assert(e[2].typ != nil)
2173    initLocExpr(p, e[1], a)
2174    initLocExpr(p, e[2], b)
2175    putIntoDest(p, d, e, ropecg(p.module, "(($4)($2) $1 ($4)($3))",
2176                              [opr[m], rdLoc(a), rdLoc(b),
2177                              getSimpleTypeDesc(p.module, e[1].typ)]))
2178    if optNaNCheck in p.options:
2179      linefmt(p, cpsStmts, "if ($1 != $1){ #raiseFloatInvalidOp(); $2}$n", [rdLoc(d), raiseInstr(p)])
2180    if optInfCheck in p.options:
2181      linefmt(p, cpsStmts, "if ($1 != 0.0 && $1*0.5 == $1) { #raiseFloatOverflow($1); $2}$n", [rdLoc(d), raiseInstr(p)])
2182  else:
2183    binaryArith(p, e, d, m)
2184
2185proc skipAddr(n: PNode): PNode =
2186  result = if n.kind in {nkAddr, nkHiddenAddr}: n[0] else: n
2187
2188proc genWasMoved(p: BProc; n: PNode) =
2189  var a: TLoc
2190  let n1 = n[1].skipAddr
2191  if p.withinBlockLeaveActions > 0 and notYetAlive(n1):
2192    discard
2193  else:
2194    initLocExpr(p, n1, a)
2195    resetLoc(p, a)
2196    #linefmt(p, cpsStmts, "#nimZeroMem((void*)$1, sizeof($2));$n",
2197    #  [addrLoc(p.config, a), getTypeDesc(p.module, a.t)])
2198
2199proc genMove(p: BProc; n: PNode; d: var TLoc) =
2200  var a: TLoc
2201  initLocExpr(p, n[1].skipAddr, a)
2202  if n.len == 4:
2203    # generated by liftdestructors:
2204    var src: TLoc
2205    initLocExpr(p, n[2], src)
2206    linefmt(p, cpsStmts, "if ($1.p != $2.p) {", [rdLoc(a), rdLoc(src)])
2207    genStmts(p, n[3])
2208    linefmt(p, cpsStmts, "}$n$1.len = $2.len; $1.p = $2.p;$n", [rdLoc(a), rdLoc(src)])
2209  else:
2210    if d.k == locNone: getTemp(p, n.typ, d)
2211    genAssignment(p, d, a, {})
2212    resetLoc(p, a)
2213
2214proc genDestroy(p: BProc; n: PNode) =
2215  if optSeqDestructors in p.config.globalOptions:
2216    let arg = n[1].skipAddr
2217    let t = arg.typ.skipTypes(abstractInst)
2218    case t.kind
2219    of tyString:
2220      var a: TLoc
2221      initLocExpr(p, arg, a)
2222      if optThreads in p.config.globalOptions:
2223        linefmt(p, cpsStmts, "if ($1.p && !($1.p->cap & NIM_STRLIT_FLAG)) {$n" &
2224          " #deallocShared($1.p);$n" &
2225          "}$n", [rdLoc(a)])
2226      else:
2227        linefmt(p, cpsStmts, "if ($1.p && !($1.p->cap & NIM_STRLIT_FLAG)) {$n" &
2228          " #dealloc($1.p);$n" &
2229          "}$n", [rdLoc(a)])
2230    of tySequence:
2231      var a: TLoc
2232      initLocExpr(p, arg, a)
2233      linefmt(p, cpsStmts, "if ($1.p && !($1.p->cap & NIM_STRLIT_FLAG)) {$n" &
2234        " #alignedDealloc($1.p, NIM_ALIGNOF($2));$n" &
2235        "}$n",
2236        [rdLoc(a), getTypeDesc(p.module, t.lastSon)])
2237    else: discard "nothing to do"
2238  else:
2239    let t = n[1].typ.skipTypes(abstractVar)
2240    let op = getAttachedOp(p.module.g.graph, t, attachedDestructor)
2241    if op != nil and getBody(p.module.g.graph, op).len != 0:
2242      internalError(p.config, n.info, "destructor turned out to be not trivial")
2243    discard "ignore calls to the default destructor"
2244
2245proc genDispose(p: BProc; n: PNode) =
2246  when false:
2247    let elemType = n[1].typ.skipTypes(abstractVar).lastSon
2248
2249    var a: TLoc
2250    initLocExpr(p, n[1].skipAddr, a)
2251
2252    if isFinal(elemType):
2253      if elemType.destructor != nil:
2254        var destroyCall = newNodeI(nkCall, n.info)
2255        genStmts(p, destroyCall)
2256      lineFmt(p, cpsStmts, "#nimRawDispose($1, NIM_ALIGNOF($2))", [rdLoc(a), getTypeDesc(p.module, elemType)])
2257    else:
2258      # ``nimRawDisposeVirtual`` calls the ``finalizer`` which is the same as the
2259      # destructor, but it uses the runtime type. Afterwards the memory is freed:
2260      lineCg(p, cpsStmts, ["#nimDestroyAndDispose($#)", rdLoc(a)])
2261
2262proc genSlice(p: BProc; e: PNode; d: var TLoc) =
2263  let (x, y) = genOpenArraySlice(p, e, e.typ, e.typ.lastSon)
2264  if d.k == locNone: getTemp(p, e.typ, d)
2265  linefmt(p, cpsStmts, "$1.Field0 = $2; $1.Field1 = $3;$n", [rdLoc(d), x, y])
2266  when false:
2267    localError(p.config, e.info, "invalid context for 'toOpenArray'; " &
2268      "'toOpenArray' is only valid within a call expression")
2269
2270proc genEnumToStr(p: BProc, e: PNode, d: var TLoc) =
2271  let t = e[1].typ.skipTypes(abstractInst+{tyRange})
2272  let toStrProc = getToStringProc(p.module.g.graph, t)
2273  # XXX need to modify this logic for IC.
2274  var n = copyTree(e)
2275  n[0] = newSymNode(toStrProc)
2276  expr(p, n, d)
2277
2278proc genMagicExpr(p: BProc, e: PNode, d: var TLoc, op: TMagic) =
2279  case op
2280  of mOr, mAnd: genAndOr(p, e, d, op)
2281  of mNot..mUnaryMinusF64: unaryArith(p, e, d, op)
2282  of mUnaryMinusI..mAbsI: unaryArithOverflow(p, e, d, op)
2283  of mAddF64..mDivF64: binaryFloatArith(p, e, d, op)
2284  of mShrI..mXor: binaryArith(p, e, d, op)
2285  of mEqProc: genEqProc(p, e, d)
2286  of mAddI..mPred: binaryArithOverflow(p, e, d, op)
2287  of mRepr: genRepr(p, e, d)
2288  of mGetTypeInfo: genGetTypeInfo(p, e, d)
2289  of mGetTypeInfoV2: genGetTypeInfoV2(p, e, d)
2290  of mSwap: genSwap(p, e, d)
2291  of mInc, mDec:
2292    const opr: array[mInc..mDec, string] = ["+=", "-="]
2293    const fun64: array[mInc..mDec, string] = ["nimAddInt64", "nimSubInt64"]
2294    const fun: array[mInc..mDec, string] = ["nimAddInt","nimSubInt"]
2295    let underlying = skipTypes(e[1].typ, {tyGenericInst, tyAlias, tySink, tyVar, tyLent, tyRange, tyDistinct})
2296    if optOverflowCheck notin p.options or underlying.kind in {tyUInt..tyUInt64}:
2297      binaryStmt(p, e, d, opr[op])
2298    else:
2299      var a, b: TLoc
2300      assert(e[1].typ != nil)
2301      assert(e[2].typ != nil)
2302      initLocExpr(p, e[1], a)
2303      initLocExpr(p, e[2], b)
2304
2305      let ranged = skipTypes(e[1].typ, {tyGenericInst, tyAlias, tySink, tyVar, tyLent, tyDistinct})
2306      let res = binaryArithOverflowRaw(p, ranged, a, b,
2307        if underlying.kind == tyInt64: fun64[op] else: fun[op])
2308
2309      putIntoDest(p, a, e[1], "($#)($#)" % [
2310        getTypeDesc(p.module, ranged), res])
2311
2312  of mConStrStr: genStrConcat(p, e, d)
2313  of mAppendStrCh:
2314    if optSeqDestructors in p.config.globalOptions:
2315      binaryStmtAddr(p, e, d, "nimAddCharV1")
2316    else:
2317      var dest, b, call: TLoc
2318      initLoc(call, locCall, e, OnHeap)
2319      initLocExpr(p, e[1], dest)
2320      initLocExpr(p, e[2], b)
2321      call.r = ropecg(p.module, "#addChar($1, $2)", [rdLoc(dest), rdLoc(b)])
2322      genAssignment(p, dest, call, {})
2323  of mAppendStrStr: genStrAppend(p, e, d)
2324  of mAppendSeqElem:
2325    if optSeqDestructors in p.config.globalOptions:
2326      e[1] = makeAddr(e[1], p.module.idgen)
2327      genCall(p, e, d)
2328    else:
2329      genSeqElemAppend(p, e, d)
2330  of mEqStr: genStrEquals(p, e, d)
2331  of mLeStr: binaryExpr(p, e, d, "(#cmpStrings($1, $2) <= 0)")
2332  of mLtStr: binaryExpr(p, e, d, "(#cmpStrings($1, $2) < 0)")
2333  of mIsNil: genIsNil(p, e, d)
2334  of mIntToStr: genDollar(p, e, d, "#nimIntToStr($1)")
2335  of mInt64ToStr: genDollar(p, e, d, "#nimInt64ToStr($1)")
2336  of mBoolToStr: genDollar(p, e, d, "#nimBoolToStr($1)")
2337  of mCharToStr: genDollar(p, e, d, "#nimCharToStr($1)")
2338  of mFloatToStr:
2339    if e[1].typ.skipTypes(abstractInst).kind == tyFloat32:
2340      genDollar(p, e, d, "#nimFloat32ToStr($1)")
2341    else:
2342      genDollar(p, e, d, "#nimFloatToStr($1)")
2343  of mCStrToStr: genDollar(p, e, d, "#cstrToNimstr($1)")
2344  of mStrToStr, mUnown: expr(p, e[1], d)
2345  of mIsolate, mFinished: genCall(p, e, d)
2346  of mEnumToStr:
2347    if optTinyRtti in p.config.globalOptions:
2348      genEnumToStr(p, e, d)
2349    else:
2350      genRepr(p, e, d)
2351  of mOf: genOf(p, e, d)
2352  of mNew: genNew(p, e)
2353  of mNewFinalize:
2354    if optTinyRtti in p.config.globalOptions:
2355      var a: TLoc
2356      initLocExpr(p, e[1], a)
2357      rawGenNew(p, a, nil, needsInit = true)
2358      gcUsage(p.config, e)
2359    else:
2360      genNewFinalize(p, e)
2361  of mNewSeq:
2362    if optSeqDestructors in p.config.globalOptions:
2363      e[1] = makeAddr(e[1], p.module.idgen)
2364      genCall(p, e, d)
2365    else:
2366      genNewSeq(p, e)
2367  of mNewSeqOfCap: genNewSeqOfCap(p, e, d)
2368  of mSizeOf:
2369    let t = e[1].typ.skipTypes({tyTypeDesc})
2370    putIntoDest(p, d, e, "((NI)sizeof($1))" % [getTypeDesc(p.module, t, skVar)])
2371  of mAlignOf:
2372    let t = e[1].typ.skipTypes({tyTypeDesc})
2373    putIntoDest(p, d, e, "((NI)NIM_ALIGNOF($1))" % [getTypeDesc(p.module, t, skVar)])
2374  of mOffsetOf:
2375    var dotExpr: PNode
2376    if e[1].kind == nkDotExpr:
2377      dotExpr = e[1]
2378    elif e[1].kind == nkCheckedFieldExpr:
2379      dotExpr = e[1][0]
2380    else:
2381      internalError(p.config, e.info, "unknown ast")
2382    let t = dotExpr[0].typ.skipTypes({tyTypeDesc})
2383    let tname = getTypeDesc(p.module, t, skVar)
2384    let member =
2385      if t.kind == tyTuple:
2386        "Field" & rope(dotExpr[1].sym.position)
2387      else: dotExpr[1].sym.loc.r
2388    putIntoDest(p,d,e, "((NI)offsetof($1, $2))" % [tname, member])
2389  of mChr: genSomeCast(p, e, d)
2390  of mOrd: genOrd(p, e, d)
2391  of mLengthArray, mHigh, mLengthStr, mLengthSeq, mLengthOpenArray:
2392    genArrayLen(p, e, d, op)
2393  of mGCref: unaryStmt(p, e, d, "if ($1) { #nimGCref($1); }$n")
2394  of mGCunref: unaryStmt(p, e, d, "if ($1) { #nimGCunref($1); }$n")
2395  of mSetLengthStr: genSetLengthStr(p, e, d)
2396  of mSetLengthSeq: genSetLengthSeq(p, e, d)
2397  of mIncl, mExcl, mCard, mLtSet, mLeSet, mEqSet, mMulSet, mPlusSet, mMinusSet,
2398     mInSet:
2399    genSetOp(p, e, d, op)
2400  of mNewString, mNewStringOfCap, mExit, mParseBiggestFloat:
2401    var opr = e[0].sym
2402    # Why would anyone want to set nodecl to one of these hardcoded magics?
2403    # - not sure, and it wouldn't work if the symbol behind the magic isn't
2404    #   somehow forward-declared from some other usage, but it is *possible*
2405    if lfNoDecl notin opr.loc.flags:
2406      let prc = magicsys.getCompilerProc(p.module.g.graph, $opr.loc.r)
2407      assert prc != nil, $opr.loc.r
2408      # HACK:
2409      # Explicitly add this proc as declared here so the cgsym call doesn't
2410      # add a forward declaration - without this we could end up with the same
2411      # 2 forward declarations. That happens because the magic symbol and the original
2412      # one that shall be used have different ids (even though a call to one is
2413      # actually a call to the other) so checking into m.declaredProtos with the 2 different ids doesn't work.
2414      # Why would 2 identical forward declarations be a problem?
2415      # - in the case of hot code-reloading we generate function pointers instead
2416      #   of forward declarations and in C++ it is an error to redefine a global
2417      let wasDeclared = containsOrIncl(p.module.declaredProtos, prc.id)
2418      # Make the function behind the magic get actually generated - this will
2419      # not lead to a forward declaration! The genCall will lead to one.
2420      discard cgsym(p.module, $opr.loc.r)
2421      # make sure we have pointer-initialising code for hot code reloading
2422      if not wasDeclared and p.hcrOn:
2423        p.module.s[cfsDynLibInit].addf("\t$1 = ($2) hcrGetProc($3, \"$1\");$n",
2424             [mangleDynLibProc(prc), getTypeDesc(p.module, prc.loc.t), getModuleDllPath(p.module, prc)])
2425    genCall(p, e, d)
2426  of mDefault: genDefault(p, e, d)
2427  of mReset: genReset(p, e)
2428  of mEcho: genEcho(p, e[1].skipConv)
2429  of mArrToSeq: genArrToSeq(p, e, d)
2430  of mNLen..mNError, mSlurp..mQuoteAst:
2431    localError(p.config, e.info, strutils.`%`(errXMustBeCompileTime, e[0].sym.name.s))
2432  of mSpawn:
2433    when defined(leanCompiler):
2434      p.config.quitOrRaise "compiler built without support for the 'spawn' statement"
2435    else:
2436      let n = spawn.wrapProcForSpawn(p.module.g.graph, p.module.idgen, p.module.module, e, e.typ, nil, nil)
2437      expr(p, n, d)
2438  of mParallel:
2439    when defined(leanCompiler):
2440      p.config.quitOrRaise "compiler built without support for the 'parallel' statement"
2441    else:
2442      let n = semparallel.liftParallel(p.module.g.graph, p.module.idgen, p.module.module, e)
2443      expr(p, n, d)
2444  of mDeepCopy:
2445    if p.config.selectedGC in {gcArc, gcOrc} and optEnableDeepCopy notin p.config.globalOptions:
2446      localError(p.config, e.info,
2447        "for --gc:arc|orc 'deepcopy' support has to be enabled with --deepcopy:on")
2448
2449    var a, b: TLoc
2450    let x = if e[1].kind in {nkAddr, nkHiddenAddr}: e[1][0] else: e[1]
2451    initLocExpr(p, x, a)
2452    initLocExpr(p, e[2], b)
2453    genDeepCopy(p, a, b)
2454  of mDotDot, mEqCString: genCall(p, e, d)
2455  of mWasMoved: genWasMoved(p, e)
2456  of mMove: genMove(p, e, d)
2457  of mDestroy: genDestroy(p, e)
2458  of mAccessEnv: unaryExpr(p, e, d, "$1.ClE_0")
2459  of mAccessTypeField: genAccessTypeField(p, e, d)
2460  of mSlice: genSlice(p, e, d)
2461  of mTrace: discard "no code to generate"
2462  else:
2463    when defined(debugMagics):
2464      echo p.prc.name.s, " ", p.prc.id, " ", p.prc.flags, " ", p.prc.ast[genericParamsPos].kind
2465    internalError(p.config, e.info, "genMagicExpr: " & $op)
2466
2467proc genSetConstr(p: BProc, e: PNode, d: var TLoc) =
2468  # example: { a..b, c, d, e, f..g }
2469  # we have to emit an expression of the form:
2470  # nimZeroMem(tmp, sizeof(tmp)); inclRange(tmp, a, b); incl(tmp, c);
2471  # incl(tmp, d); incl(tmp, e); inclRange(tmp, f, g);
2472  var
2473    a, b, idx: TLoc
2474  if nfAllConst in e.flags:
2475    putIntoDest(p, d, e, genSetNode(p, e))
2476  else:
2477    if d.k == locNone: getTemp(p, e.typ, d)
2478    if getSize(p.config, e.typ) > 8:
2479      # big set:
2480      linefmt(p, cpsStmts, "#nimZeroMem($1, sizeof($2));$n",
2481          [rdLoc(d), getTypeDesc(p.module, e.typ)])
2482      for it in e.sons:
2483        if it.kind == nkRange:
2484          getTemp(p, getSysType(p.module.g.graph, unknownLineInfo, tyInt), idx) # our counter
2485          initLocExpr(p, it[0], a)
2486          initLocExpr(p, it[1], b)
2487          lineF(p, cpsStmts, "for ($1 = $3; $1 <= $4; $1++) $n" &
2488              "$2[(NU)($1)>>3] |=(1U<<((NU)($1)&7U));$n", [rdLoc(idx), rdLoc(d),
2489              rdSetElemLoc(p.config, a, e.typ), rdSetElemLoc(p.config, b, e.typ)])
2490        else:
2491          initLocExpr(p, it, a)
2492          lineF(p, cpsStmts, "$1[(NU)($2)>>3] |=(1U<<((NU)($2)&7U));$n",
2493               [rdLoc(d), rdSetElemLoc(p.config, a, e.typ)])
2494    else:
2495      # small set
2496      var ts = "NU" & $(getSize(p.config, e.typ) * 8)
2497      lineF(p, cpsStmts, "$1 = 0;$n", [rdLoc(d)])
2498      for it in e.sons:
2499        if it.kind == nkRange:
2500          getTemp(p, getSysType(p.module.g.graph, unknownLineInfo, tyInt), idx) # our counter
2501          initLocExpr(p, it[0], a)
2502          initLocExpr(p, it[1], b)
2503          lineF(p, cpsStmts, "for ($1 = $3; $1 <= $4; $1++) $n" &
2504              "$2 |=(($5)(1)<<(($1)%(sizeof($5)*8)));$n", [
2505              rdLoc(idx), rdLoc(d), rdSetElemLoc(p.config, a, e.typ),
2506              rdSetElemLoc(p.config, b, e.typ), rope(ts)])
2507        else:
2508          initLocExpr(p, it, a)
2509          lineF(p, cpsStmts,
2510               "$1 |=(($3)(1)<<(($2)%(sizeof($3)*8)));$n",
2511               [rdLoc(d), rdSetElemLoc(p.config, a, e.typ), rope(ts)])
2512
2513proc genTupleConstr(p: BProc, n: PNode, d: var TLoc) =
2514  var rec: TLoc
2515  if not handleConstExpr(p, n, d):
2516    let t = n.typ
2517    discard getTypeDesc(p.module, t) # so that any fields are initialized
2518    if d.k == locNone: getTemp(p, t, d)
2519    for i in 0..<n.len:
2520      var it = n[i]
2521      if it.kind == nkExprColonExpr: it = it[1]
2522      initLoc(rec, locExpr, it, d.storage)
2523      rec.r = "$1.Field$2" % [rdLoc(d), rope(i)]
2524      rec.flags.incl(lfEnforceDeref)
2525      expr(p, it, rec)
2526
2527proc isConstClosure(n: PNode): bool {.inline.} =
2528  result = n[0].kind == nkSym and isRoutine(n[0].sym) and
2529      n[1].kind == nkNilLit
2530
2531proc genClosure(p: BProc, n: PNode, d: var TLoc) =
2532  assert n.kind in {nkPar, nkTupleConstr, nkClosure}
2533
2534  if isConstClosure(n):
2535    inc(p.module.labels)
2536    var tmp = "CNSTCLOSURE" & rope(p.module.labels)
2537    p.module.s[cfsData].addf("static NIM_CONST $1 $2 = $3;$n",
2538        [getTypeDesc(p.module, n.typ), tmp, genBracedInit(p, n, isConst = true, n.typ)])
2539    putIntoDest(p, d, n, tmp, OnStatic)
2540  else:
2541    var tmp, a, b: TLoc
2542    initLocExpr(p, n[0], a)
2543    initLocExpr(p, n[1], b)
2544    if n[0].skipConv.kind == nkClosure:
2545      internalError(p.config, n.info, "closure to closure created")
2546    # tasyncawait.nim breaks with this optimization:
2547    when false:
2548      if d.k != locNone:
2549        linefmt(p, cpsStmts, "$1.ClP_0 = $2; $1.ClE_0 = $3;$n",
2550                [d.rdLoc, a.rdLoc, b.rdLoc])
2551    else:
2552      getTemp(p, n.typ, tmp)
2553      linefmt(p, cpsStmts, "$1.ClP_0 = $2; $1.ClE_0 = $3;$n",
2554              [tmp.rdLoc, a.rdLoc, b.rdLoc])
2555      putLocIntoDest(p, d, tmp)
2556
2557proc genArrayConstr(p: BProc, n: PNode, d: var TLoc) =
2558  var arr: TLoc
2559  if not handleConstExpr(p, n, d):
2560    if d.k == locNone: getTemp(p, n.typ, d)
2561    for i in 0..<n.len:
2562      initLoc(arr, locExpr, lodeTyp elemType(skipTypes(n.typ, abstractInst)), d.storage)
2563      arr.r = "$1[$2]" % [rdLoc(d), intLiteral(i)]
2564      expr(p, n[i], arr)
2565
2566proc genComplexConst(p: BProc, sym: PSym, d: var TLoc) =
2567  requestConstImpl(p, sym)
2568  assert((sym.loc.r != nil) and (sym.loc.t != nil))
2569  putLocIntoDest(p, d, sym.loc)
2570
2571template genStmtListExprImpl(exprOrStmt) {.dirty.} =
2572  #let hasNimFrame = magicsys.getCompilerProc("nimFrame") != nil
2573  let hasNimFrame = p.prc != nil and
2574      sfSystemModule notin p.module.module.flags and
2575      optStackTrace in p.prc.options
2576  var frameName: Rope = nil
2577  for i in 0..<n.len - 1:
2578    let it = n[i]
2579    if it.kind == nkComesFrom:
2580      if hasNimFrame and frameName == nil:
2581        inc p.labels
2582        frameName = "FR" & rope(p.labels) & "_"
2583        let theMacro = it[0].sym
2584        add p.s(cpsStmts), initFrameNoDebug(p, frameName,
2585           makeCString theMacro.name.s,
2586           quotedFilename(p.config, theMacro.info), it.info.line.int)
2587    else:
2588      genStmts(p, it)
2589  if n.len > 0: exprOrStmt
2590  if frameName != nil:
2591    p.s(cpsStmts).add deinitFrameNoDebug(p, frameName)
2592
2593proc genStmtListExpr(p: BProc, n: PNode, d: var TLoc) =
2594  genStmtListExprImpl:
2595    expr(p, n[^1], d)
2596
2597proc genStmtList(p: BProc, n: PNode) =
2598  genStmtListExprImpl:
2599    genStmts(p, n[^1])
2600
2601from parampatterns import isLValue
2602
2603proc upConv(p: BProc, n: PNode, d: var TLoc) =
2604  var a: TLoc
2605  initLocExpr(p, n[0], a)
2606  let dest = skipTypes(n.typ, abstractPtrs)
2607  if optObjCheck in p.options and not isObjLackingTypeField(dest):
2608    var nilCheck = Rope(nil)
2609    let r = rdMType(p, a, nilCheck)
2610    let checkFor = if optTinyRtti in p.config.globalOptions:
2611                     genTypeInfo2Name(p.module, dest)
2612                   else:
2613                     genTypeInfoV1(p.module, dest, n.info)
2614    if nilCheck != nil:
2615      linefmt(p, cpsStmts, "if ($1 && !#isObj($2, $3)){ #raiseObjectConversionError(); $4}$n",
2616              [nilCheck, r, checkFor, raiseInstr(p)])
2617    else:
2618      linefmt(p, cpsStmts, "if (!#isObj($1, $2)){ #raiseObjectConversionError(); $3}$n",
2619              [r, checkFor, raiseInstr(p)])
2620  if n[0].typ.kind != tyObject:
2621    if n.isLValue:
2622      putIntoDest(p, d, n,
2623                "(*(($1*) (&($2))))" % [getTypeDesc(p.module, n.typ), rdLoc(a)], a.storage)
2624    else:
2625      putIntoDest(p, d, n,
2626                "(($1) ($2))" % [getTypeDesc(p.module, n.typ), rdLoc(a)], a.storage)
2627  else:
2628    putIntoDest(p, d, n, "(*($1*) ($2))" %
2629                        [getTypeDesc(p.module, dest), addrLoc(p.config, a)], a.storage)
2630
2631proc downConv(p: BProc, n: PNode, d: var TLoc) =
2632  var arg = n[0]
2633  while arg.kind == nkObjDownConv: arg = arg[0]
2634
2635  let dest = skipTypes(n.typ, abstractPtrs)
2636  let src = skipTypes(arg.typ, abstractPtrs)
2637  discard getTypeDesc(p.module, src)
2638  let isRef = skipTypes(arg.typ, abstractInstOwned).kind in {tyRef, tyPtr, tyVar, tyLent}
2639  if isRef and d.k == locNone and n.typ.skipTypes(abstractInstOwned).kind in {tyRef, tyPtr} and n.isLValue:
2640    # it can happen that we end up generating '&&x->Sup' here, so we pack
2641    # the '&x->Sup' into a temporary and then those address is taken
2642    # (see bug #837). However sometimes using a temporary is not correct:
2643    # init(TFigure(my)) # where it is passed to a 'var TFigure'. We test
2644    # this by ensuring the destination is also a pointer:
2645    var a: TLoc
2646    initLocExpr(p, arg, a)
2647    putIntoDest(p, d, n,
2648              "(*(($1*) (&($2))))" % [getTypeDesc(p.module, n.typ), rdLoc(a)], a.storage)
2649  elif p.module.compileToCpp:
2650    # C++ implicitly downcasts for us
2651    expr(p, arg, d)
2652  else:
2653    var a: TLoc
2654    initLocExpr(p, arg, a)
2655    var r = rdLoc(a) & (if isRef: "->Sup" else: ".Sup")
2656    for i in 2..abs(inheritanceDiff(dest, src)): r.add(".Sup")
2657    putIntoDest(p, d, n, if isRef: "&" & r else: r, a.storage)
2658
2659proc exprComplexConst(p: BProc, n: PNode, d: var TLoc) =
2660  let t = n.typ
2661  discard getTypeDesc(p.module, t) # so that any fields are initialized
2662  let id = nodeTableTestOrSet(p.module.dataCache, n, p.module.labels)
2663  let tmp = p.module.tmpBase & rope(id)
2664
2665  if id == p.module.labels:
2666    # expression not found in the cache:
2667    inc(p.module.labels)
2668    p.module.s[cfsData].addf("static NIM_CONST $1 $2 = $3;$n",
2669         [getTypeDesc(p.module, t, skConst), tmp, genBracedInit(p, n, isConst = true, t)])
2670
2671  if d.k == locNone:
2672    fillLoc(d, locData, n, tmp, OnStatic)
2673  else:
2674    putDataIntoDest(p, d, n, tmp)
2675    # This fixes bug #4551, but we really need better dataflow
2676    # analysis to make this 100% safe.
2677    if t.kind notin {tySequence, tyString}:
2678      d.storage = OnStatic
2679
2680proc genConstSetup(p: BProc; sym: PSym): bool =
2681  let m = p.module
2682  useHeader(m, sym)
2683  if sym.loc.k == locNone:
2684    fillLoc(sym.loc, locData, sym.ast, mangleName(p.module, sym), OnStatic)
2685  if m.hcrOn: incl(sym.loc.flags, lfIndirect)
2686  result = lfNoDecl notin sym.loc.flags
2687
2688proc genConstHeader(m, q: BModule; p: BProc, sym: PSym) =
2689  if sym.loc.r == nil:
2690    if not genConstSetup(p, sym): return
2691  assert(sym.loc.r != nil, $sym.name.s & $sym.itemId)
2692  if m.hcrOn:
2693    m.s[cfsVars].addf("static $1* $2;$n", [getTypeDesc(m, sym.loc.t, skVar), sym.loc.r]);
2694    m.initProc.procSec(cpsLocals).addf(
2695      "\t$1 = ($2*)hcrGetGlobal($3, \"$1\");$n", [sym.loc.r,
2696      getTypeDesc(m, sym.loc.t, skVar), getModuleDllPath(q, sym)])
2697  else:
2698    let headerDecl = "extern NIM_CONST $1 $2;$n" %
2699        [getTypeDesc(m, sym.loc.t, skVar), sym.loc.r]
2700    m.s[cfsData].add(headerDecl)
2701    if sfExportc in sym.flags and p.module.g.generatedHeader != nil:
2702      p.module.g.generatedHeader.s[cfsData].add(headerDecl)
2703
2704proc genConstDefinition(q: BModule; p: BProc; sym: PSym) =
2705  # add a suffix for hcr - will later init the global pointer with this data
2706  let actualConstName = if q.hcrOn: sym.loc.r & "_const" else: sym.loc.r
2707  q.s[cfsData].addf("N_LIB_PRIVATE NIM_CONST $1 $2 = $3;$n",
2708      [getTypeDesc(q, sym.typ), actualConstName,
2709      genBracedInit(q.initProc, sym.ast, isConst = true, sym.typ)])
2710  if q.hcrOn:
2711    # generate the global pointer with the real name
2712    q.s[cfsVars].addf("static $1* $2;$n", [getTypeDesc(q, sym.loc.t, skVar), sym.loc.r])
2713    # register it (but ignore the boolean result of hcrRegisterGlobal)
2714    q.initProc.procSec(cpsLocals).addf(
2715      "\thcrRegisterGlobal($1, \"$2\", sizeof($3), NULL, (void**)&$2);$n",
2716      [getModuleDllPath(q, sym), sym.loc.r, rdLoc(sym.loc)])
2717    # always copy over the contents of the actual constant with the _const
2718    # suffix ==> this means that the constant is reloadable & updatable!
2719    q.initProc.procSec(cpsLocals).add(ropecg(q,
2720      "\t#nimCopyMem((void*)$1, (NIM_CONST void*)&$2, sizeof($3));$n",
2721      [sym.loc.r, actualConstName, rdLoc(sym.loc)]))
2722
2723proc genConstStmt(p: BProc, n: PNode) =
2724  # This code is only used in the new DCE implementation.
2725  assert useAliveDataFromDce in p.module.flags
2726  let m = p.module
2727  for it in n:
2728    if it[0].kind == nkSym:
2729      let sym = it[0].sym
2730      if not isSimpleConst(sym.typ) and sym.itemId.item in m.alive and genConstSetup(p, sym):
2731        genConstDefinition(m, p, sym)
2732
2733proc expr(p: BProc, n: PNode, d: var TLoc) =
2734  when defined(nimCompilerStacktraceHints):
2735    setFrameMsg p.config$n.info & " " & $n.kind
2736  p.currLineInfo = n.info
2737
2738  case n.kind
2739  of nkSym:
2740    var sym = n.sym
2741    case sym.kind
2742    of skMethod:
2743      if useAliveDataFromDce in p.module.flags or {sfDispatcher, sfForward} * sym.flags != {}:
2744        # we cannot produce code for the dispatcher yet:
2745        fillProcLoc(p.module, n)
2746        genProcPrototype(p.module, sym)
2747      else:
2748        genProc(p.module, sym)
2749      putLocIntoDest(p, d, sym.loc)
2750    of skProc, skConverter, skIterator, skFunc:
2751      #if sym.kind == skIterator:
2752      #  echo renderTree(sym.getBody, {renderIds})
2753      if sfCompileTime in sym.flags:
2754        localError(p.config, n.info, "request to generate code for .compileTime proc: " &
2755           sym.name.s)
2756      if useAliveDataFromDce in p.module.flags and sym.typ.callConv != ccInline:
2757        fillProcLoc(p.module, n)
2758        genProcPrototype(p.module, sym)
2759      else:
2760        genProc(p.module, sym)
2761      if sym.loc.r == nil or sym.loc.lode == nil:
2762        internalError(p.config, n.info, "expr: proc not init " & sym.name.s)
2763      putLocIntoDest(p, d, sym.loc)
2764    of skConst:
2765      if isSimpleConst(sym.typ):
2766        putIntoDest(p, d, n, genLiteral(p, sym.ast, sym.typ), OnStatic)
2767      elif useAliveDataFromDce in p.module.flags:
2768        genConstHeader(p.module, p.module, p, sym)
2769        assert((sym.loc.r != nil) and (sym.loc.t != nil))
2770        putLocIntoDest(p, d, sym.loc)
2771      else:
2772        genComplexConst(p, sym, d)
2773    of skEnumField:
2774      # we never reach this case - as of the time of this comment,
2775      # skEnumField is folded to an int in semfold.nim, but this code
2776      # remains for robustness
2777      putIntoDest(p, d, n, rope(sym.position))
2778    of skVar, skForVar, skResult, skLet:
2779      if {sfGlobal, sfThread} * sym.flags != {}:
2780        genVarPrototype(p.module, n)
2781        if sfCompileTime in sym.flags:
2782          genSingleVar(p, sym, n, astdef(sym))
2783
2784      if sym.loc.r == nil or sym.loc.t == nil:
2785        #echo "FAILED FOR PRCO ", p.prc.name.s
2786        #echo renderTree(p.prc.ast, {renderIds})
2787        internalError p.config, n.info, "expr: var not init " & sym.name.s & "_" & $sym.id
2788      if sfThread in sym.flags:
2789        accessThreadLocalVar(p, sym)
2790        if emulatedThreadVars(p.config):
2791          putIntoDest(p, d, sym.loc.lode, "NimTV_->" & sym.loc.r)
2792        else:
2793          putLocIntoDest(p, d, sym.loc)
2794      else:
2795        putLocIntoDest(p, d, sym.loc)
2796    of skTemp:
2797      when false:
2798        # this is more harmful than helpful.
2799        if sym.loc.r == nil:
2800          # we now support undeclared 'skTemp' variables for easier
2801          # transformations in other parts of the compiler:
2802          assignLocalVar(p, n)
2803      if sym.loc.r == nil or sym.loc.t == nil:
2804        #echo "FAILED FOR PRCO ", p.prc.name.s
2805        #echo renderTree(p.prc.ast, {renderIds})
2806        internalError(p.config, n.info, "expr: temp not init " & sym.name.s & "_" & $sym.id)
2807      putLocIntoDest(p, d, sym.loc)
2808    of skParam:
2809      if sym.loc.r == nil or sym.loc.t == nil:
2810        # echo "FAILED FOR PRCO ", p.prc.name.s
2811        # debug p.prc.typ.n
2812        # echo renderTree(p.prc.ast, {renderIds})
2813        internalError(p.config, n.info, "expr: param not init " & sym.name.s & "_" & $sym.id)
2814      putLocIntoDest(p, d, sym.loc)
2815    else: internalError(p.config, n.info, "expr(" & $sym.kind & "); unknown symbol")
2816  of nkNilLit:
2817    if not isEmptyType(n.typ):
2818      putIntoDest(p, d, n, genLiteral(p, n))
2819  of nkStrLit..nkTripleStrLit:
2820    putDataIntoDest(p, d, n, genLiteral(p, n))
2821  of nkIntLit..nkUInt64Lit,
2822     nkFloatLit..nkFloat128Lit, nkCharLit:
2823    putIntoDest(p, d, n, genLiteral(p, n))
2824  of nkCall, nkHiddenCallConv, nkInfix, nkPrefix, nkPostfix, nkCommand,
2825     nkCallStrLit:
2826    genLineDir(p, n) # may be redundant, it is generated in fixupCall as well
2827    let op = n[0]
2828    if n.typ.isNil:
2829      # discard the value:
2830      var a: TLoc
2831      if op.kind == nkSym and op.sym.magic != mNone:
2832        genMagicExpr(p, n, a, op.sym.magic)
2833      else:
2834        genCall(p, n, a)
2835    else:
2836      # load it into 'd':
2837      if op.kind == nkSym and op.sym.magic != mNone:
2838        genMagicExpr(p, n, d, op.sym.magic)
2839      else:
2840        genCall(p, n, d)
2841  of nkCurly:
2842    if isDeepConstExpr(n) and n.len != 0:
2843      putIntoDest(p, d, n, genSetNode(p, n))
2844    else:
2845      genSetConstr(p, n, d)
2846  of nkBracket:
2847    if isDeepConstExpr(n) and n.len != 0:
2848      exprComplexConst(p, n, d)
2849    elif skipTypes(n.typ, abstractVarRange).kind == tySequence:
2850      genSeqConstr(p, n, d)
2851    else:
2852      genArrayConstr(p, n, d)
2853  of nkPar, nkTupleConstr:
2854    if n.typ != nil and n.typ.kind == tyProc and n.len == 2:
2855      genClosure(p, n, d)
2856    elif isDeepConstExpr(n) and n.len != 0:
2857      exprComplexConst(p, n, d)
2858    else:
2859      genTupleConstr(p, n, d)
2860  of nkObjConstr: genObjConstr(p, n, d)
2861  of nkCast: genCast(p, n, d)
2862  of nkHiddenStdConv, nkHiddenSubConv, nkConv: genConv(p, n, d)
2863  of nkHiddenAddr, nkAddr: genAddr(p, n, d)
2864  of nkBracketExpr: genBracketExpr(p, n, d)
2865  of nkDerefExpr, nkHiddenDeref: genDeref(p, n, d)
2866  of nkDotExpr: genRecordField(p, n, d)
2867  of nkCheckedFieldExpr: genCheckedRecordField(p, n, d)
2868  of nkBlockExpr, nkBlockStmt: genBlock(p, n, d)
2869  of nkStmtListExpr: genStmtListExpr(p, n, d)
2870  of nkStmtList: genStmtList(p, n)
2871  of nkIfExpr, nkIfStmt: genIf(p, n, d)
2872  of nkWhen:
2873    # This should be a "when nimvm" node.
2874    expr(p, n[1][0], d)
2875  of nkObjDownConv: downConv(p, n, d)
2876  of nkObjUpConv: upConv(p, n, d)
2877  of nkChckRangeF, nkChckRange64, nkChckRange: genRangeChck(p, n, d)
2878  of nkStringToCString: convStrToCStr(p, n, d)
2879  of nkCStringToString: convCStrToStr(p, n, d)
2880  of nkLambdaKinds:
2881    var sym = n[namePos].sym
2882    genProc(p.module, sym)
2883    if sym.loc.r == nil or sym.loc.lode == nil:
2884      internalError(p.config, n.info, "expr: proc not init " & sym.name.s)
2885    putLocIntoDest(p, d, sym.loc)
2886  of nkClosure: genClosure(p, n, d)
2887
2888  of nkEmpty: discard
2889  of nkWhileStmt: genWhileStmt(p, n)
2890  of nkVarSection, nkLetSection: genVarStmt(p, n)
2891  of nkConstSection:
2892    if useAliveDataFromDce in p.module.flags:
2893      genConstStmt(p, n)
2894    # else: consts generated lazily on use
2895  of nkForStmt: internalError(p.config, n.info, "for statement not eliminated")
2896  of nkCaseStmt: genCase(p, n, d)
2897  of nkReturnStmt: genReturnStmt(p, n)
2898  of nkBreakStmt: genBreakStmt(p, n)
2899  of nkAsgn:
2900    cow(p, n[1])
2901    if nfPreventCg notin n.flags:
2902      genAsgn(p, n, fastAsgn=false)
2903  of nkFastAsgn:
2904    cow(p, n[1])
2905    if nfPreventCg notin n.flags:
2906      # transf is overly aggressive with 'nkFastAsgn', so we work around here.
2907      # See tests/run/tcnstseq3 for an example that would fail otherwise.
2908      genAsgn(p, n, fastAsgn=p.prc != nil)
2909  of nkDiscardStmt:
2910    let ex = n[0]
2911    if ex.kind != nkEmpty:
2912      genLineDir(p, n)
2913      var a: TLoc
2914      initLocExprSingleUse(p, ex, a)
2915      line(p, cpsStmts, "(void)(" & a.r & ");\L")
2916  of nkAsmStmt: genAsmStmt(p, n)
2917  of nkTryStmt, nkHiddenTryStmt:
2918    case p.config.exc
2919    of excGoto:
2920      genTryGoto(p, n, d)
2921    of excCpp:
2922      genTryCpp(p, n, d)
2923    else:
2924      genTrySetjmp(p, n, d)
2925  of nkRaiseStmt: genRaiseStmt(p, n)
2926  of nkTypeSection:
2927    # we have to emit the type information for object types here to support
2928    # separate compilation:
2929    genTypeSection(p.module, n)
2930  of nkCommentStmt, nkIteratorDef, nkIncludeStmt,
2931     nkImportStmt, nkImportExceptStmt, nkExportStmt, nkExportExceptStmt,
2932     nkFromStmt, nkTemplateDef, nkMacroDef, nkStaticStmt:
2933    discard
2934  of nkPragma: genPragma(p, n)
2935  of nkPragmaBlock: expr(p, n.lastSon, d)
2936  of nkProcDef, nkFuncDef, nkMethodDef, nkConverterDef:
2937    if n[genericParamsPos].kind == nkEmpty:
2938      var prc = n[namePos].sym
2939      if useAliveDataFromDce in p.module.flags:
2940        if p.module.alive.contains(prc.itemId.item) and prc.magic in {mNone, mIsolate, mFinished}:
2941          genProc(p.module, prc)
2942      elif prc.skipGenericOwner.kind == skModule and sfCompileTime notin prc.flags:
2943        if ({sfExportc, sfCompilerProc} * prc.flags == {sfExportc}) or
2944            (sfExportc in prc.flags and lfExportLib in prc.loc.flags) or
2945            (prc.kind == skMethod):
2946          # due to a bug/limitation in the lambda lifting, unused inner procs
2947          # are not transformed correctly. We work around this issue (#411) here
2948          # by ensuring it's no inner proc (owner is a module).
2949          # Generate proc even if empty body, bugfix #11651.
2950          genProc(p.module, prc)
2951  of nkParForStmt: genParForStmt(p, n)
2952  of nkState: genState(p, n)
2953  of nkGotoState:
2954    # simply never set it back to 0 here from here on...
2955    inc p.splitDecls
2956    genGotoState(p, n)
2957  of nkBreakState: genBreakState(p, n, d)
2958  of nkMixinStmt, nkBindStmt: discard
2959  else: internalError(p.config, n.info, "expr(" & $n.kind & "); unknown node kind")
2960
2961proc genNamedConstExpr(p: BProc, n: PNode; isConst: bool): Rope =
2962  if n.kind == nkExprColonExpr: result = genBracedInit(p, n[1], isConst, n[0].typ)
2963  else: result = genBracedInit(p, n, isConst, n.typ)
2964
2965proc getDefaultValue(p: BProc; typ: PType; info: TLineInfo): Rope =
2966  var t = skipTypes(typ, abstractRange+{tyOwned}-{tyTypeDesc})
2967  case t.kind
2968  of tyBool: result = rope"NIM_FALSE"
2969  of tyEnum, tyChar, tyInt..tyInt64, tyUInt..tyUInt64: result = rope"0"
2970  of tyFloat..tyFloat128: result = rope"0.0"
2971  of tyCstring, tyVar, tyLent, tyPointer, tyPtr, tyUntyped,
2972     tyTyped, tyTypeDesc, tyStatic, tyRef, tyNil:
2973    result = rope"NIM_NIL"
2974  of tyString, tySequence:
2975    if optSeqDestructors in p.config.globalOptions:
2976      result = rope"{0, NIM_NIL}"
2977    else:
2978      result = rope"NIM_NIL"
2979  of tyProc:
2980    if t.callConv != ccClosure:
2981      result = rope"NIM_NIL"
2982    else:
2983      result = rope"{NIM_NIL, NIM_NIL}"
2984  of tyObject:
2985    var count = 0
2986    result.add "{"
2987    getNullValueAuxT(p, t, t, t.n, nil, result, count, true, info)
2988    result.add "}"
2989  of tyTuple:
2990    result = rope"{"
2991    for i in 0..<t.len:
2992      if i > 0: result.add ", "
2993      result.add getDefaultValue(p, t[i], info)
2994    result.add "}"
2995  of tyArray:
2996    result = rope"{"
2997    for i in 0..<toInt(lengthOrd(p.config, t.sons[0])):
2998      if i > 0: result.add ", "
2999      result.add getDefaultValue(p, t.sons[1], info)
3000    result.add "}"
3001    #result = rope"{}"
3002  of tyOpenArray, tyVarargs:
3003    result = rope"{NIM_NIL, 0}"
3004  of tySet:
3005    if mapSetType(p.config, t) == ctArray: result = rope"{}"
3006    else: result = rope"0"
3007  else:
3008    globalError(p.config, info, "cannot create null element for: " & $t.kind)
3009
3010proc caseObjDefaultBranch(obj: PNode; branch: Int128): int =
3011  for i in 1 ..< obj.len:
3012    for j in 0 .. obj[i].len - 2:
3013      if obj[i][j].kind == nkRange:
3014        let x = getOrdValue(obj[i][j][0])
3015        let y = getOrdValue(obj[i][j][1])
3016        if branch >= x and branch <= y:
3017          return i
3018      elif getOrdValue(obj[i][j]) == branch:
3019        return i
3020    if obj[i].len == 1:
3021      # else branch
3022      return i
3023  assert(false, "unreachable")
3024
3025proc getNullValueAux(p: BProc; t: PType; obj, constOrNil: PNode,
3026                     result: var Rope; count: var int;
3027                     isConst: bool, info: TLineInfo) =
3028  case obj.kind
3029  of nkRecList:
3030    for it in obj.sons:
3031      getNullValueAux(p, t, it, constOrNil, result, count, isConst, info)
3032  of nkRecCase:
3033    getNullValueAux(p, t, obj[0], constOrNil, result, count, isConst, info)
3034    if count > 0: result.add ", "
3035    var branch = Zero
3036    if constOrNil != nil:
3037      ## find kind value, default is zero if not specified
3038      for i in 1..<constOrNil.len:
3039        if constOrNil[i].kind == nkExprColonExpr:
3040          if constOrNil[i][0].sym.name.id == obj[0].sym.name.id:
3041            branch = getOrdValue(constOrNil[i][1])
3042            break
3043        elif i == obj[0].sym.position:
3044          branch = getOrdValue(constOrNil[i])
3045          break
3046
3047    let selectedBranch = caseObjDefaultBranch(obj, branch)
3048    result.add "{"
3049    var countB = 0
3050    let b = lastSon(obj[selectedBranch])
3051    # designated initilization is the only way to init non first element of unions
3052    # branches are allowed to have no members (b.len == 0), in this case they don't need initializer
3053    if b.kind == nkRecList and b.len > 0:
3054      result.add "._" & mangleRecFieldName(p.module, obj[0].sym) & "_" & $selectedBranch & " = {"
3055      getNullValueAux(p, t,  b, constOrNil, result, countB, isConst, info)
3056      result.add "}"
3057    elif b.kind == nkSym:
3058      result.add "." & mangleRecFieldName(p.module, b.sym) & " = "
3059      getNullValueAux(p, t,  b, constOrNil, result, countB, isConst, info)
3060    result.add "}"
3061
3062  of nkSym:
3063    if count > 0: result.add ", "
3064    inc count
3065    let field = obj.sym
3066    if constOrNil != nil:
3067      for i in 1..<constOrNil.len:
3068        if constOrNil[i].kind == nkExprColonExpr:
3069          if constOrNil[i][0].sym.name.id == field.name.id:
3070            result.add genBracedInit(p, constOrNil[i][1], isConst, field.typ)
3071            return
3072        elif i == field.position:
3073          result.add genBracedInit(p, constOrNil[i], isConst, field.typ)
3074          return
3075    # not found, produce default value:
3076    result.add getDefaultValue(p, field.typ, info)
3077  else:
3078    localError(p.config, info, "cannot create null element for: " & $obj)
3079
3080proc getNullValueAuxT(p: BProc; orig, t: PType; obj, constOrNil: PNode,
3081                      result: var Rope; count: var int;
3082                      isConst: bool, info: TLineInfo) =
3083  var base = t[0]
3084  let oldRes = result
3085  let oldcount = count
3086  if base != nil:
3087    result.add "{"
3088    base = skipTypes(base, skipPtrs)
3089    getNullValueAuxT(p, orig, base, base.n, constOrNil, result, count, isConst, info)
3090    result.add "}"
3091  elif not isObjLackingTypeField(t):
3092    if optTinyRtti in p.config.globalOptions:
3093      result.add genTypeInfoV2(p.module, orig, obj.info)
3094    else:
3095      result.add genTypeInfoV1(p.module, orig, obj.info)
3096    inc count
3097  getNullValueAux(p, t, obj, constOrNil, result, count, isConst, info)
3098  # do not emit '{}' as that is not valid C:
3099  if oldcount == count: result = oldRes
3100
3101proc genConstObjConstr(p: BProc; n: PNode; isConst: bool): Rope =
3102  result = nil
3103  let t = n.typ.skipTypes(abstractInstOwned)
3104  var count = 0
3105  #if not isObjLackingTypeField(t) and not p.module.compileToCpp:
3106  #  result.addf("{$1}", [genTypeInfo(p.module, t)])
3107  #  inc count
3108  if t.kind == tyObject:
3109    getNullValueAuxT(p, t, t, t.n, n, result, count, isConst, n.info)
3110  result = "{$1}$n" % [result]
3111
3112proc genConstSimpleList(p: BProc, n: PNode; isConst: bool): Rope =
3113  result = rope("{")
3114  for i in 0..<n.len:
3115    let it = n[i]
3116    if i > 0: result.add ",\n"
3117    if it.kind == nkExprColonExpr: result.add genBracedInit(p, it[1], isConst, it[0].typ)
3118    else: result.add genBracedInit(p, it, isConst, it.typ)
3119  result.add("}\n")
3120
3121proc genConstTuple(p: BProc, n: PNode; isConst: bool; tup: PType): Rope =
3122  result = rope("{")
3123  for i in 0..<n.len:
3124    let it = n[i]
3125    if i > 0: result.add ",\n"
3126    if it.kind == nkExprColonExpr: result.add genBracedInit(p, it[1], isConst, tup[i])
3127    else: result.add genBracedInit(p, it, isConst, tup[i])
3128  result.add("}\n")
3129
3130proc genConstSeq(p: BProc, n: PNode, t: PType; isConst: bool): Rope =
3131  var data = "{{$1, $1 | NIM_STRLIT_FLAG}" % [n.len.rope]
3132  let base = t.skipTypes(abstractInst)[0]
3133  if n.len > 0:
3134    # array part needs extra curlies:
3135    data.add(", {")
3136    for i in 0..<n.len:
3137      if i > 0: data.addf(",$n", [])
3138      data.add genBracedInit(p, n[i], isConst, base)
3139    data.add("}")
3140  data.add("}")
3141
3142  result = getTempName(p.module)
3143
3144  appcg(p.module, cfsData,
3145        "static $5 struct {$n" &
3146        "  #TGenericSeq Sup;$n" &
3147        "  $1 data[$2];$n" &
3148        "} $3 = $4;$n", [
3149        getTypeDesc(p.module, base), n.len, result, data,
3150        if isConst: "NIM_CONST" else: ""])
3151
3152  result = "(($1)&$2)" % [getTypeDesc(p.module, t), result]
3153
3154proc genConstSeqV2(p: BProc, n: PNode, t: PType; isConst: bool): Rope =
3155  let base = t.skipTypes(abstractInst)[0]
3156  var data = rope"{"
3157  for i in 0..<n.len:
3158    if i > 0: data.addf(",$n", [])
3159    data.add genBracedInit(p, n[i], isConst, base)
3160  data.add("}")
3161
3162  let payload = getTempName(p.module)
3163
3164  appcg(p.module, cfsData,
3165    "static $5 struct {$n" &
3166    "  NI cap; $1 data[$2];$n" &
3167    "} $3 = {$2 | NIM_STRLIT_FLAG, $4};$n", [
3168    getTypeDesc(p.module, base), n.len, payload, data,
3169    if isConst: "const" else: ""])
3170  result = "{$1, ($2*)&$3}" % [rope(n.len), getSeqPayloadType(p.module, t), payload]
3171
3172proc genBracedInit(p: BProc, n: PNode; isConst: bool; optionalType: PType): Rope =
3173  case n.kind
3174  of nkHiddenStdConv, nkHiddenSubConv:
3175    result = genBracedInit(p, n[1], isConst, n.typ)
3176  else:
3177    var ty = tyNone
3178    var typ: PType = nil
3179    if optionalType == nil:
3180      if n.kind in nkStrKinds:
3181        ty = tyString
3182      else:
3183        internalError(p.config, n.info, "node has no type")
3184    else:
3185      typ = skipTypes(optionalType, abstractInstOwned + {tyStatic})
3186      ty = typ.kind
3187    case ty
3188    of tySet:
3189      let cs = toBitSet(p.config, n)
3190      result = genRawSetData(cs, int(getSize(p.config, n.typ)))
3191    of tySequence:
3192      if optSeqDestructors in p.config.globalOptions:
3193        result = genConstSeqV2(p, n, typ, isConst)
3194      else:
3195        result = genConstSeq(p, n, typ, isConst)
3196    of tyProc:
3197      if typ.callConv == ccClosure and n.safeLen > 1 and n[1].kind == nkNilLit:
3198        # n.kind could be: nkClosure, nkTupleConstr and maybe others; `n.safeLen`
3199        # guards against the case of `nkSym`, refs bug #14340.
3200        # Conversion: nimcall -> closure.
3201        # this hack fixes issue that nkNilLit is expanded to {NIM_NIL,NIM_NIL}
3202        # this behaviour is needed since closure_var = nil must be
3203        # expanded to {NIM_NIL,NIM_NIL}
3204        # in VM closures are initialized with nkPar(nkNilLit, nkNilLit)
3205        # leading to duplicate code like this:
3206        # "{NIM_NIL,NIM_NIL}, {NIM_NIL,NIM_NIL}"
3207        if n[0].kind == nkNilLit:
3208          result = ~"{NIM_NIL,NIM_NIL}"
3209        else:
3210          var d: TLoc
3211          initLocExpr(p, n[0], d)
3212          result = "{(($1) $2),NIM_NIL}" % [getClosureType(p.module, typ, clHalfWithEnv), rdLoc(d)]
3213      else:
3214        var d: TLoc
3215        initLocExpr(p, n, d)
3216        result = rdLoc(d)
3217    of tyArray, tyVarargs:
3218      result = genConstSimpleList(p, n, isConst)
3219    of tyTuple:
3220      result = genConstTuple(p, n, isConst, typ)
3221    of tyOpenArray:
3222      if n.kind != nkBracket:
3223        internalError(p.config, n.info, "const openArray expression is not an array construction")
3224
3225      let data = genConstSimpleList(p, n, isConst)
3226
3227      let payload = getTempName(p.module)
3228      let ctype = getTypeDesc(p.module, typ[0])
3229      let arrLen = n.len
3230      appcg(p.module, cfsData,
3231        "static $5 $1 $3[$2] = $4;$n", [
3232        ctype, arrLen, payload, data,
3233        if isConst: "const" else: ""])
3234      result = "{($1*)&$2, $3}" % [ctype, payload, rope arrLen]
3235
3236    of tyObject:
3237      result = genConstObjConstr(p, n, isConst)
3238    of tyString, tyCstring:
3239      if optSeqDestructors in p.config.globalOptions and n.kind != nkNilLit and ty == tyString:
3240        result = genStringLiteralV2Const(p.module, n, isConst)
3241      else:
3242        var d: TLoc
3243        initLocExpr(p, n, d)
3244        result = rdLoc(d)
3245    else:
3246      var d: TLoc
3247      initLocExpr(p, n, d)
3248      result = rdLoc(d)
3249