vmgen.nim 73 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863186418651866186718681869187018711872187318741875187618771878187918801881188218831884188518861887188818891890189118921893189418951896189718981899190019011902190319041905190619071908190919101911191219131914191519161917191819191920192119221923192419251926192719281929193019311932193319341935193619371938193919401941194219431944194519461947194819491950195119521953195419551956195719581959196019611962196319641965196619671968196919701971197219731974197519761977197819791980198119821983198419851986198719881989199019911992199319941995199619971998199920002001200220032004200520062007200820092010201120122013201420152016201720182019202020212022202320242025202620272028202920302031203220332034203520362037203820392040204120422043204420452046204720482049205020512052205320542055205620572058205920602061206220632064206520662067206820692070207120722073207420752076207720782079208020812082208320842085208620872088208920902091209220932094209520962097209820992100210121022103210421052106210721082109211021112112211321142115211621172118211921202121212221232124212521262127212821292130213121322133213421352136213721382139214021412142214321442145214621472148214921502151215221532154215521562157215821592160216121622163216421652166216721682169217021712172217321742175217621772178217921802181218221832184218521862187218821892190
  1. #
  2. #
  3. # The Nim Compiler
  4. # (c) Copyright 2015 Andreas Rumpf
  5. #
  6. # See the file "copying.txt", included in this
  7. # distribution, for details about the copyright.
  8. #
  9. ## This module implements the code generator for the VM.
  10. # Important things to remember:
  11. # - The VM does not distinguish between definitions ('var x = y') and
  12. # assignments ('x = y'). For simple data types that fit into a register
  13. # this doesn't matter. However it matters for strings and other complex
  14. # types that use the 'node' field; the reason is that slots are
  15. # re-used in a register based VM. Example:
  16. #
  17. # .. code-block:: nim
  18. # let s = a & b # no matter what, create fresh node
  19. # s = a & b # no matter what, keep the node
  20. #
  21. # Also *stores* into non-temporary memory need to perform deep copies:
  22. # a.b = x.y
  23. # We used to generate opcAsgn for the *load* of 'x.y' but this is clearly
  24. # wrong! We need to produce opcAsgn (the copy) for the *store*. This also
  25. # solves the opcLdConst vs opcAsgnConst issue. Of course whether we need
  26. # this copy depends on the involved types.
  27. import
  28. strutils, ast, astalgo, types, msgs, renderer, vmdef,
  29. trees, intsets, magicsys, options, lowerings, lineinfos, transf
  30. import platform
  31. from os import splitFile
  32. when hasFFI:
  33. import evalffi
  34. type
  35. TGenFlag = enum
  36. gfNode # Affects how variables are loaded - always loads as rkNode
  37. gfNodeAddr # Affects how variables are loaded - always loads as rkNodeAddr
  38. TGenFlags = set[TGenFlag]
  39. proc debugInfo(c: PCtx; info: TLineInfo): string =
  40. result = toFilename(c.config, info).splitFile.name & ":" & $info.line
  41. proc codeListing(c: PCtx, result: var string, start=0; last = -1) =
  42. # first iteration: compute all necessary labels:
  43. var jumpTargets = initIntSet()
  44. let last = if last < 0: c.code.len-1 else: min(last, c.code.len-1)
  45. for i in start..last:
  46. let x = c.code[i]
  47. if x.opcode in relativeJumps:
  48. jumpTargets.incl(i+x.regBx-wordExcess)
  49. # for debugging purposes
  50. var i = start
  51. while i <= last:
  52. if i in jumpTargets: result.addf("L$1:\n", i)
  53. let x = c.code[i]
  54. result.add($i)
  55. let opc = opcode(x)
  56. if opc in {opcConv, opcCast}:
  57. let y = c.code[i+1]
  58. let z = c.code[i+2]
  59. result.addf("\t$#\tr$#, r$#, $#, $#", ($opc).substr(3), x.regA, x.regB,
  60. c.types[y.regBx-wordExcess].typeToString,
  61. c.types[z.regBx-wordExcess].typeToString)
  62. inc i, 2
  63. elif opc < firstABxInstr:
  64. result.addf("\t$#\tr$#, r$#, r$#", ($opc).substr(3), x.regA,
  65. x.regB, x.regC)
  66. elif opc in relativeJumps:
  67. result.addf("\t$#\tr$#, L$#", ($opc).substr(3), x.regA,
  68. i+x.regBx-wordExcess)
  69. elif opc in {opcLdConst, opcAsgnConst}:
  70. let idx = x.regBx-wordExcess
  71. result.addf("\t$#\tr$#, $# ($#)", ($opc).substr(3), x.regA,
  72. c.constants[idx].renderTree, $idx)
  73. elif opc in {opcMarshalLoad, opcMarshalStore}:
  74. let y = c.code[i+1]
  75. result.addf("\t$#\tr$#, r$#, $#", ($opc).substr(3), x.regA, x.regB,
  76. c.types[y.regBx-wordExcess].typeToString)
  77. inc i
  78. else:
  79. result.addf("\t$#\tr$#, $#", ($opc).substr(3), x.regA, x.regBx-wordExcess)
  80. result.add("\t#")
  81. result.add(debugInfo(c, c.debug[i]))
  82. result.add("\n")
  83. inc i
  84. proc echoCode*(c: PCtx; start=0; last = -1) {.deprecated.} =
  85. var buf = ""
  86. codeListing(c, buf, start, last)
  87. echo buf
  88. proc gABC(ctx: PCtx; n: PNode; opc: TOpcode; a, b, c: TRegister = 0) =
  89. ## Takes the registers `b` and `c`, applies the operation `opc` to them, and
  90. ## stores the result into register `a`
  91. ## The node is needed for debug information
  92. assert opc.ord < 255
  93. let ins = (opc.uint32 or (a.uint32 shl 8'u32) or
  94. (b.uint32 shl 16'u32) or
  95. (c.uint32 shl 24'u32)).TInstr
  96. when false:
  97. if ctx.code.len == 43:
  98. writeStackTrace()
  99. echo "generating ", opc
  100. ctx.code.add(ins)
  101. ctx.debug.add(n.info)
  102. proc gABI(c: PCtx; n: PNode; opc: TOpcode; a, b: TRegister; imm: BiggestInt) =
  103. # Takes the `b` register and the immediate `imm`, appies the operation `opc`,
  104. # and stores the output value into `a`.
  105. # `imm` is signed and must be within [-128, 127]
  106. if imm >= -128 and imm <= 127:
  107. let ins = (opc.uint32 or (a.uint32 shl 8'u32) or
  108. (b.uint32 shl 16'u32) or
  109. (imm+byteExcess).uint32 shl 24'u32).TInstr
  110. c.code.add(ins)
  111. c.debug.add(n.info)
  112. else:
  113. localError(c.config, n.info,
  114. "VM: immediate value does not fit into an int8")
  115. proc gABx(c: PCtx; n: PNode; opc: TOpcode; a: TRegister = 0; bx: int) =
  116. # Applies `opc` to `bx` and stores it into register `a`
  117. # `bx` must be signed and in the range [-32768, 32767]
  118. when false:
  119. if c.code.len == 43:
  120. writeStackTrace()
  121. echo "generating ", opc
  122. if bx >= -32768 and bx <= 32767:
  123. let ins = (opc.uint32 or a.uint32 shl 8'u32 or
  124. (bx+wordExcess).uint32 shl 16'u32).TInstr
  125. c.code.add(ins)
  126. c.debug.add(n.info)
  127. else:
  128. localError(c.config, n.info,
  129. "VM: immediate value does not fit into an int16")
  130. proc xjmp(c: PCtx; n: PNode; opc: TOpcode; a: TRegister = 0): TPosition =
  131. #assert opc in {opcJmp, opcFJmp, opcTJmp}
  132. result = TPosition(c.code.len)
  133. gABx(c, n, opc, a, 0)
  134. proc genLabel(c: PCtx): TPosition =
  135. result = TPosition(c.code.len)
  136. #c.jumpTargets.incl(c.code.len)
  137. proc jmpBack(c: PCtx, n: PNode, p = TPosition(0)) =
  138. let dist = p.int - c.code.len
  139. internalAssert(c.config, -0x7fff < dist and dist < 0x7fff)
  140. gABx(c, n, opcJmpBack, 0, dist)
  141. proc patch(c: PCtx, p: TPosition) =
  142. # patch with current index
  143. let p = p.int
  144. let diff = c.code.len - p
  145. #c.jumpTargets.incl(c.code.len)
  146. internalAssert(c.config, -0x7fff < diff and diff < 0x7fff)
  147. let oldInstr = c.code[p]
  148. # opcode and regA stay the same:
  149. c.code[p] = ((oldInstr.uint32 and 0xffff'u32).uint32 or
  150. uint32(diff+wordExcess) shl 16'u32).TInstr
  151. proc getSlotKind(t: PType): TSlotKind =
  152. case t.skipTypes(abstractRange-{tyTypeDesc}).kind
  153. of tyBool, tyChar, tyEnum, tyOrdinal, tyInt..tyInt64, tyUInt..tyUInt64:
  154. slotTempInt
  155. of tyString, tyCString:
  156. slotTempStr
  157. of tyFloat..tyFloat128:
  158. slotTempFloat
  159. else:
  160. slotTempComplex
  161. const
  162. HighRegisterPressure = 40
  163. proc bestEffort(c: PCtx): TLineInfo =
  164. if c.prc != nil and c.prc.sym != nil:
  165. c.prc.sym.info
  166. else:
  167. c.module.info
  168. proc getTemp(cc: PCtx; tt: PType): TRegister =
  169. let typ = tt.skipTypesOrNil({tyStatic})
  170. let c = cc.prc
  171. # we prefer the same slot kind here for efficiency. Unfortunately for
  172. # discardable return types we may not know the desired type. This can happen
  173. # for e.g. mNAdd[Multiple]:
  174. let k = if typ.isNil: slotTempComplex else: typ.getSlotKind
  175. for i in 0 .. c.maxSlots-1:
  176. if c.slots[i].kind == k and not c.slots[i].inUse:
  177. c.slots[i].inUse = true
  178. return TRegister(i)
  179. # if register pressure is high, we re-use more aggressively:
  180. if c.maxSlots >= HighRegisterPressure and false:
  181. for i in 0 .. c.maxSlots-1:
  182. if not c.slots[i].inUse:
  183. c.slots[i] = (inUse: true, kind: k)
  184. return TRegister(i)
  185. if c.maxSlots >= high(TRegister):
  186. globalError(cc.config, cc.bestEffort, "VM problem: too many registers required")
  187. result = TRegister(c.maxSlots)
  188. c.slots[c.maxSlots] = (inUse: true, kind: k)
  189. inc c.maxSlots
  190. proc freeTemp(c: PCtx; r: TRegister) =
  191. let c = c.prc
  192. if c.slots[r].kind in {slotSomeTemp..slotTempComplex}: c.slots[r].inUse = false
  193. proc getTempRange(cc: PCtx; n: int; kind: TSlotKind): TRegister =
  194. # if register pressure is high, we re-use more aggressively:
  195. let c = cc.prc
  196. if c.maxSlots >= HighRegisterPressure or c.maxSlots+n >= high(TRegister):
  197. for i in 0 .. c.maxSlots-n:
  198. if not c.slots[i].inUse:
  199. block search:
  200. for j in i+1 .. i+n-1:
  201. if c.slots[j].inUse: break search
  202. result = TRegister(i)
  203. for k in result .. result+n-1: c.slots[k] = (inUse: true, kind: kind)
  204. return
  205. if c.maxSlots+n >= high(TRegister):
  206. globalError(cc.config, cc.bestEffort, "VM problem: too many registers required")
  207. result = TRegister(c.maxSlots)
  208. inc c.maxSlots, n
  209. for k in result .. result+n-1: c.slots[k] = (inUse: true, kind: kind)
  210. proc freeTempRange(c: PCtx; start: TRegister, n: int) =
  211. for i in start .. start+n-1: c.freeTemp(TRegister(i))
  212. template withTemp(tmp, typ, body: untyped) {.dirty.} =
  213. var tmp = getTemp(c, typ)
  214. body
  215. c.freeTemp(tmp)
  216. proc popBlock(c: PCtx; oldLen: int) =
  217. for f in c.prc.blocks[oldLen].fixups:
  218. c.patch(f)
  219. c.prc.blocks.setLen(oldLen)
  220. template withBlock(labl: PSym; body: untyped) {.dirty.} =
  221. var oldLen {.gensym.} = c.prc.blocks.len
  222. c.prc.blocks.add TBlock(label: labl, fixups: @[])
  223. body
  224. popBlock(c, oldLen)
  225. proc gen(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags = {})
  226. proc gen(c: PCtx; n: PNode; dest: TRegister; flags: TGenFlags = {}) =
  227. var d: TDest = dest
  228. gen(c, n, d, flags)
  229. #internalAssert c.config, d == dest # issue #7407
  230. proc gen(c: PCtx; n: PNode; flags: TGenFlags = {}) =
  231. var tmp: TDest = -1
  232. gen(c, n, tmp, flags)
  233. #if n.typ.isEmptyType: InternalAssert tmp < 0
  234. proc genx(c: PCtx; n: PNode; flags: TGenFlags = {}): TRegister =
  235. var tmp: TDest = -1
  236. gen(c, n, tmp, flags)
  237. #internalAssert c.config, tmp >= 0 # 'nim check' does not like this internalAssert.
  238. if tmp >= 0:
  239. result = TRegister(tmp)
  240. proc clearDest(c: PCtx; n: PNode; dest: var TDest) {.inline.} =
  241. # stmt is different from 'void' in meta programming contexts.
  242. # So we only set dest to -1 if 'void':
  243. if dest >= 0 and (n.typ.isNil or n.typ.kind == tyVoid):
  244. c.freeTemp(dest)
  245. dest = -1
  246. proc isNotOpr(n: PNode): bool =
  247. n.kind in nkCallKinds and n.sons[0].kind == nkSym and
  248. n.sons[0].sym.magic == mNot
  249. proc isTrue(n: PNode): bool =
  250. n.kind == nkSym and n.sym.kind == skEnumField and n.sym.position != 0 or
  251. n.kind == nkIntLit and n.intVal != 0
  252. proc genWhile(c: PCtx; n: PNode) =
  253. # L1:
  254. # cond, tmp
  255. # fjmp tmp, L2
  256. # body
  257. # jmp L1
  258. # L2:
  259. let L1 = c.genLabel
  260. withBlock(nil):
  261. if isTrue(n.sons[0]):
  262. c.gen(n.sons[1])
  263. c.jmpBack(n, L1)
  264. elif isNotOpr(n.sons[0]):
  265. var tmp = c.genx(n.sons[0].sons[1])
  266. let L2 = c.xjmp(n, opcTJmp, tmp)
  267. c.freeTemp(tmp)
  268. c.gen(n.sons[1])
  269. c.jmpBack(n, L1)
  270. c.patch(L2)
  271. else:
  272. var tmp = c.genx(n.sons[0])
  273. let L2 = c.xjmp(n, opcFJmp, tmp)
  274. c.freeTemp(tmp)
  275. c.gen(n.sons[1])
  276. c.jmpBack(n, L1)
  277. c.patch(L2)
  278. proc genBlock(c: PCtx; n: PNode; dest: var TDest) =
  279. withBlock(n.sons[0].sym):
  280. c.gen(n.sons[1], dest)
  281. c.clearDest(n, dest)
  282. proc genBreak(c: PCtx; n: PNode) =
  283. let L1 = c.xjmp(n, opcJmp)
  284. if n.sons[0].kind == nkSym:
  285. #echo cast[int](n.sons[0].sym)
  286. for i in countdown(c.prc.blocks.len-1, 0):
  287. if c.prc.blocks[i].label == n.sons[0].sym:
  288. c.prc.blocks[i].fixups.add L1
  289. return
  290. globalError(c.config, n.info, "VM problem: cannot find 'break' target")
  291. else:
  292. c.prc.blocks[c.prc.blocks.high].fixups.add L1
  293. proc genIf(c: PCtx, n: PNode; dest: var TDest) =
  294. # if (!expr1) goto L1;
  295. # thenPart
  296. # goto LEnd
  297. # L1:
  298. # if (!expr2) goto L2;
  299. # thenPart2
  300. # goto LEnd
  301. # L2:
  302. # elsePart
  303. # Lend:
  304. if dest < 0 and not isEmptyType(n.typ): dest = getTemp(c, n.typ)
  305. var endings: seq[TPosition] = @[]
  306. for i in countup(0, len(n) - 1):
  307. var it = n.sons[i]
  308. if it.len == 2:
  309. withTemp(tmp, it.sons[0].typ):
  310. var elsePos: TPosition
  311. if isNotOpr(it.sons[0]):
  312. c.gen(it.sons[0].sons[1], tmp)
  313. elsePos = c.xjmp(it.sons[0].sons[1], opcTJmp, tmp) # if true
  314. else:
  315. c.gen(it.sons[0], tmp)
  316. elsePos = c.xjmp(it.sons[0], opcFJmp, tmp) # if false
  317. c.clearDest(n, dest)
  318. c.gen(it.sons[1], dest) # then part
  319. if i < sonsLen(n)-1:
  320. endings.add(c.xjmp(it.sons[1], opcJmp, 0))
  321. c.patch(elsePos)
  322. else:
  323. c.clearDest(n, dest)
  324. c.gen(it.sons[0], dest)
  325. for endPos in endings: c.patch(endPos)
  326. c.clearDest(n, dest)
  327. proc genAndOr(c: PCtx; n: PNode; opc: TOpcode; dest: var TDest) =
  328. # asgn dest, a
  329. # tjmp|fjmp L1
  330. # asgn dest, b
  331. # L1:
  332. if dest < 0: dest = getTemp(c, n.typ)
  333. c.gen(n.sons[1], dest)
  334. let L1 = c.xjmp(n, opc, dest)
  335. c.gen(n.sons[2], dest)
  336. c.patch(L1)
  337. proc canonValue*(n: PNode): PNode =
  338. result = n
  339. proc rawGenLiteral(c: PCtx; n: PNode): int =
  340. result = c.constants.len
  341. #assert(n.kind != nkCall)
  342. n.flags.incl nfAllConst
  343. c.constants.add n.canonValue
  344. internalAssert c.config, result < 0x7fff
  345. proc sameConstant*(a, b: PNode): bool =
  346. result = false
  347. if a == b:
  348. result = true
  349. elif a != nil and b != nil and a.kind == b.kind:
  350. case a.kind
  351. of nkSym: result = a.sym == b.sym
  352. of nkIdent: result = a.ident.id == b.ident.id
  353. of nkCharLit..nkUInt64Lit: result = a.intVal == b.intVal
  354. of nkFloatLit..nkFloat64Lit: result = a.floatVal == b.floatVal
  355. of nkStrLit..nkTripleStrLit: result = a.strVal == b.strVal
  356. of nkType, nkNilLit: result = a.typ == b.typ
  357. of nkEmpty: result = true
  358. else:
  359. if sonsLen(a) == sonsLen(b):
  360. for i in countup(0, sonsLen(a) - 1):
  361. if not sameConstant(a.sons[i], b.sons[i]): return
  362. result = true
  363. proc genLiteral(c: PCtx; n: PNode): int =
  364. # types do not matter here:
  365. for i in 0 ..< c.constants.len:
  366. if sameConstant(c.constants[i], n): return i
  367. result = rawGenLiteral(c, n)
  368. proc unused(c: PCtx; n: PNode; x: TDest) {.inline.} =
  369. if x >= 0:
  370. #debug(n)
  371. globalError(c.config, n.info, "not unused")
  372. proc genCase(c: PCtx; n: PNode; dest: var TDest) =
  373. # if (!expr1) goto L1;
  374. # thenPart
  375. # goto LEnd
  376. # L1:
  377. # if (!expr2) goto L2;
  378. # thenPart2
  379. # goto LEnd
  380. # L2:
  381. # elsePart
  382. # Lend:
  383. if not isEmptyType(n.typ):
  384. if dest < 0: dest = getTemp(c, n.typ)
  385. else:
  386. unused(c, n, dest)
  387. var endings: seq[TPosition] = @[]
  388. withTemp(tmp, n.sons[0].typ):
  389. c.gen(n.sons[0], tmp)
  390. # branch tmp, codeIdx
  391. # fjmp elseLabel
  392. for i in 1 ..< n.len:
  393. let it = n.sons[i]
  394. if it.len == 1:
  395. # else stmt:
  396. c.gen(it.sons[0], dest)
  397. else:
  398. let b = rawGenLiteral(c, it)
  399. c.gABx(it, opcBranch, tmp, b)
  400. let elsePos = c.xjmp(it.lastSon, opcFJmp, tmp)
  401. c.gen(it.lastSon, dest)
  402. if i < sonsLen(n)-1:
  403. endings.add(c.xjmp(it.lastSon, opcJmp, 0))
  404. c.patch(elsePos)
  405. c.clearDest(n, dest)
  406. for endPos in endings: c.patch(endPos)
  407. proc genType(c: PCtx; typ: PType): int =
  408. for i, t in c.types:
  409. if sameType(t, typ): return i
  410. result = c.types.len
  411. c.types.add(typ)
  412. internalAssert(c.config, result <= 0x7fff)
  413. proc genTry(c: PCtx; n: PNode; dest: var TDest) =
  414. if dest < 0 and not isEmptyType(n.typ): dest = getTemp(c, n.typ)
  415. var endings: seq[TPosition] = @[]
  416. let elsePos = c.xjmp(n, opcTry, 0)
  417. c.gen(n.sons[0], dest)
  418. c.clearDest(n, dest)
  419. c.patch(elsePos)
  420. for i in 1 ..< n.len:
  421. let it = n.sons[i]
  422. if it.kind != nkFinally:
  423. var blen = len(it)
  424. # first opcExcept contains the end label of the 'except' block:
  425. let endExcept = c.xjmp(it, opcExcept, 0)
  426. for j in countup(0, blen - 2):
  427. assert(it.sons[j].kind == nkType)
  428. let typ = it.sons[j].typ.skipTypes(abstractPtrs-{tyTypeDesc})
  429. c.gABx(it, opcExcept, 0, c.genType(typ))
  430. if blen == 1:
  431. # general except section:
  432. c.gABx(it, opcExcept, 0, 0)
  433. c.gen(it.lastSon, dest)
  434. c.clearDest(n, dest)
  435. if i < sonsLen(n)-1:
  436. endings.add(c.xjmp(it, opcJmp, 0))
  437. c.patch(endExcept)
  438. for endPos in endings: c.patch(endPos)
  439. let fin = lastSon(n)
  440. # we always generate an 'opcFinally' as that pops the safepoint
  441. # from the stack
  442. c.gABx(fin, opcFinally, 0, 0)
  443. if fin.kind == nkFinally:
  444. c.gen(fin.sons[0])
  445. c.clearDest(n, dest)
  446. c.gABx(fin, opcFinallyEnd, 0, 0)
  447. proc genRaise(c: PCtx; n: PNode) =
  448. let dest = genx(c, n.sons[0])
  449. c.gABC(n, opcRaise, dest)
  450. c.freeTemp(dest)
  451. proc genReturn(c: PCtx; n: PNode) =
  452. if n.sons[0].kind != nkEmpty:
  453. gen(c, n.sons[0])
  454. c.gABC(n, opcRet)
  455. proc genLit(c: PCtx; n: PNode; dest: var TDest) =
  456. # opcLdConst is now always valid. We produce the necessary copy in the
  457. # assignments now:
  458. #var opc = opcLdConst
  459. if dest < 0: dest = c.getTemp(n.typ)
  460. #elif c.prc.slots[dest].kind == slotFixedVar: opc = opcAsgnConst
  461. let lit = genLiteral(c, n)
  462. c.gABx(n, opcLdConst, dest, lit)
  463. proc genCall(c: PCtx; n: PNode; dest: var TDest) =
  464. # it can happen that due to inlining we have a 'n' that should be
  465. # treated as a constant (see issue #537).
  466. #if n.typ != nil and n.typ.sym != nil and n.typ.sym.magic == mPNimrodNode:
  467. # genLit(c, n, dest)
  468. # return
  469. if dest < 0 and not isEmptyType(n.typ): dest = getTemp(c, n.typ)
  470. let x = c.getTempRange(n.len, slotTempUnknown)
  471. # varargs need 'opcSetType' for the FFI support:
  472. let fntyp = skipTypes(n.sons[0].typ, abstractInst)
  473. for i in 0..<n.len:
  474. #if i > 0 and i < sonsLen(fntyp):
  475. # let paramType = fntyp.n.sons[i]
  476. # if paramType.typ.isCompileTimeOnly: continue
  477. var r: TRegister = x+i
  478. c.gen(n.sons[i], r)
  479. if i >= fntyp.len:
  480. internalAssert c.config, tfVarargs in fntyp.flags
  481. c.gABx(n, opcSetType, r, c.genType(n.sons[i].typ))
  482. if dest < 0:
  483. c.gABC(n, opcIndCall, 0, x, n.len)
  484. else:
  485. c.gABC(n, opcIndCallAsgn, dest, x, n.len)
  486. c.freeTempRange(x, n.len)
  487. template isGlobal(s: PSym): bool = sfGlobal in s.flags and s.kind != skForVar
  488. proc isGlobal(n: PNode): bool = n.kind == nkSym and isGlobal(n.sym)
  489. proc needsAsgnPatch(n: PNode): bool =
  490. n.kind in {nkBracketExpr, nkDotExpr, nkCheckedFieldExpr,
  491. nkDerefExpr, nkHiddenDeref} or (n.kind == nkSym and n.sym.isGlobal)
  492. proc genField(c: PCtx; n: PNode): TRegister =
  493. if n.kind != nkSym or n.sym.kind != skField:
  494. globalError(c.config, n.info, "no field symbol")
  495. let s = n.sym
  496. if s.position > high(result):
  497. globalError(c.config, n.info,
  498. "too large offset! cannot generate code for: " & s.name.s)
  499. result = s.position
  500. proc genIndex(c: PCtx; n: PNode; arr: PType): TRegister =
  501. if arr.skipTypes(abstractInst).kind == tyArray and (let x = firstOrd(c.config, arr);
  502. x != 0):
  503. let tmp = c.genx(n)
  504. # freeing the temporary here means we can produce: regA = regA - Imm
  505. c.freeTemp(tmp)
  506. result = c.getTemp(n.typ)
  507. c.gABI(n, opcSubImmInt, result, tmp, x.int)
  508. else:
  509. result = c.genx(n)
  510. proc genCheckedObjAccessAux(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags)
  511. proc genAsgnPatch(c: PCtx; le: PNode, value: TRegister) =
  512. case le.kind
  513. of nkBracketExpr:
  514. let dest = c.genx(le.sons[0], {gfNode})
  515. let idx = c.genIndex(le.sons[1], le.sons[0].typ)
  516. c.gABC(le, opcWrArr, dest, idx, value)
  517. c.freeTemp(dest)
  518. c.freeTemp(idx)
  519. of nkCheckedFieldExpr:
  520. var objR: TDest = -1
  521. genCheckedObjAccessAux(c, le, objR, {gfNode})
  522. let idx = genField(c, le[0].sons[1])
  523. c.gABC(le[0], opcWrObj, objR, idx, value)
  524. c.freeTemp(objR)
  525. of nkDotExpr:
  526. let dest = c.genx(le.sons[0], {gfNode})
  527. let idx = genField(c, le.sons[1])
  528. c.gABC(le, opcWrObj, dest, idx, value)
  529. c.freeTemp(dest)
  530. of nkDerefExpr, nkHiddenDeref:
  531. let dest = c.genx(le.sons[0], {gfNode})
  532. c.gABC(le, opcWrDeref, dest, 0, value)
  533. c.freeTemp(dest)
  534. of nkSym:
  535. if le.sym.isGlobal:
  536. let dest = c.genx(le, {gfNodeAddr})
  537. c.gABC(le, opcWrDeref, dest, 0, value)
  538. c.freeTemp(dest)
  539. else:
  540. discard
  541. proc genNew(c: PCtx; n: PNode) =
  542. let dest = if needsAsgnPatch(n.sons[1]): c.getTemp(n.sons[1].typ)
  543. else: c.genx(n.sons[1])
  544. # we use the ref's base type here as the VM conflates 'ref object'
  545. # and 'object' since internally we already have a pointer.
  546. c.gABx(n, opcNew, dest,
  547. c.genType(n.sons[1].typ.skipTypes(abstractVar-{tyTypeDesc}).sons[0]))
  548. c.genAsgnPatch(n.sons[1], dest)
  549. c.freeTemp(dest)
  550. proc genNewSeq(c: PCtx; n: PNode) =
  551. let t = n.sons[1].typ
  552. let dest = if needsAsgnPatch(n.sons[1]): c.getTemp(t)
  553. else: c.genx(n.sons[1])
  554. let tmp = c.genx(n.sons[2])
  555. c.gABx(n, opcNewSeq, dest, c.genType(t.skipTypes(
  556. abstractVar-{tyTypeDesc})))
  557. c.gABx(n, opcNewSeq, tmp, 0)
  558. c.freeTemp(tmp)
  559. c.genAsgnPatch(n.sons[1], dest)
  560. c.freeTemp(dest)
  561. proc genNewSeqOfCap(c: PCtx; n: PNode; dest: var TDest) =
  562. let t = n.typ
  563. let tmp = c.getTemp(n.sons[1].typ)
  564. c.gABx(n, opcLdNull, dest, c.genType(t))
  565. c.gABx(n, opcLdImmInt, tmp, 0)
  566. c.gABx(n, opcNewSeq, dest, c.genType(t.skipTypes(
  567. abstractVar-{tyTypeDesc})))
  568. c.gABx(n, opcNewSeq, tmp, 0)
  569. c.freeTemp(tmp)
  570. proc genUnaryABC(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
  571. let tmp = c.genx(n.sons[1])
  572. if dest < 0: dest = c.getTemp(n.typ)
  573. c.gABC(n, opc, dest, tmp)
  574. c.freeTemp(tmp)
  575. proc genUnaryABI(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode; imm: BiggestInt=0) =
  576. let tmp = c.genx(n.sons[1])
  577. if dest < 0: dest = c.getTemp(n.typ)
  578. c.gABI(n, opc, dest, tmp, imm)
  579. c.freeTemp(tmp)
  580. proc genBinaryABC(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
  581. let
  582. tmp = c.genx(n.sons[1])
  583. tmp2 = c.genx(n.sons[2])
  584. if dest < 0: dest = c.getTemp(n.typ)
  585. c.gABC(n, opc, dest, tmp, tmp2)
  586. c.freeTemp(tmp)
  587. c.freeTemp(tmp2)
  588. proc genBinaryABCD(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
  589. let
  590. tmp = c.genx(n.sons[1])
  591. tmp2 = c.genx(n.sons[2])
  592. tmp3 = c.genx(n.sons[3])
  593. if dest < 0: dest = c.getTemp(n.typ)
  594. c.gABC(n, opc, dest, tmp, tmp2)
  595. c.gABC(n, opc, tmp3)
  596. c.freeTemp(tmp)
  597. c.freeTemp(tmp2)
  598. c.freeTemp(tmp3)
  599. proc genNarrow(c: PCtx; n: PNode; dest: TDest) =
  600. let t = skipTypes(n.typ, abstractVar-{tyTypeDesc})
  601. # uint is uint64 in the VM, we we only need to mask the result for
  602. # other unsigned types:
  603. if t.kind in {tyUInt8..tyUInt32} or (t.kind == tyUInt and t.size < 8):
  604. c.gABC(n, opcNarrowU, dest, TRegister(t.size*8))
  605. elif t.kind in {tyInt8..tyInt32} or (t.kind == tyInt and t.size < 8):
  606. c.gABC(n, opcNarrowS, dest, TRegister(t.size*8))
  607. proc genNarrowU(c: PCtx; n: PNode; dest: TDest) =
  608. let t = skipTypes(n.typ, abstractVar-{tyTypeDesc})
  609. # uint is uint64 in the VM, we we only need to mask the result for
  610. # other unsigned types:
  611. if t.kind in {tyUInt8..tyUInt32, tyInt8..tyInt32} or
  612. (t.kind in {tyUInt, tyInt} and t.size < 8):
  613. c.gABC(n, opcNarrowU, dest, TRegister(t.size*8))
  614. proc genBinaryABCnarrow(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
  615. genBinaryABC(c, n, dest, opc)
  616. genNarrow(c, n, dest)
  617. proc genBinaryABCnarrowU(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
  618. genBinaryABC(c, n, dest, opc)
  619. genNarrowU(c, n, dest)
  620. proc genSetType(c: PCtx; n: PNode; dest: TRegister) =
  621. let t = skipTypes(n.typ, abstractInst-{tyTypeDesc})
  622. if t.kind == tySet:
  623. c.gABx(n, opcSetType, dest, c.genType(t))
  624. proc genBinarySet(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
  625. let
  626. tmp = c.genx(n.sons[1])
  627. tmp2 = c.genx(n.sons[2])
  628. if dest < 0: dest = c.getTemp(n.typ)
  629. c.genSetType(n.sons[1], tmp)
  630. c.genSetType(n.sons[2], tmp2)
  631. c.gABC(n, opc, dest, tmp, tmp2)
  632. c.freeTemp(tmp)
  633. c.freeTemp(tmp2)
  634. proc genBinaryStmt(c: PCtx; n: PNode; opc: TOpcode) =
  635. let
  636. dest = c.genx(n.sons[1])
  637. tmp = c.genx(n.sons[2])
  638. c.gABC(n, opc, dest, tmp, 0)
  639. c.freeTemp(tmp)
  640. proc genBinaryStmtVar(c: PCtx; n: PNode; opc: TOpcode) =
  641. var x = n.sons[1]
  642. if x.kind in {nkAddr, nkHiddenAddr}: x = x.sons[0]
  643. let
  644. dest = c.genx(x)
  645. tmp = c.genx(n.sons[2])
  646. c.gABC(n, opc, dest, tmp, 0)
  647. #c.genAsgnPatch(n.sons[1], dest)
  648. c.freeTemp(tmp)
  649. proc genUnaryStmt(c: PCtx; n: PNode; opc: TOpcode) =
  650. let tmp = c.genx(n.sons[1])
  651. c.gABC(n, opc, tmp, 0, 0)
  652. c.freeTemp(tmp)
  653. proc genVarargsABC(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
  654. if dest < 0: dest = getTemp(c, n.typ)
  655. var x = c.getTempRange(n.len-1, slotTempStr)
  656. for i in 1..n.len-1:
  657. var r: TRegister = x+i-1
  658. c.gen(n.sons[i], r)
  659. c.gABC(n, opc, dest, x, n.len-1)
  660. c.freeTempRange(x, n.len)
  661. proc isInt8Lit(n: PNode): bool =
  662. if n.kind in {nkCharLit..nkUInt64Lit}:
  663. result = n.intVal >= low(int8) and n.intVal <= high(int8)
  664. proc isInt16Lit(n: PNode): bool =
  665. if n.kind in {nkCharLit..nkUInt64Lit}:
  666. result = n.intVal >= low(int16) and n.intVal <= high(int16)
  667. proc genAddSubInt(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) =
  668. if n.sons[2].isInt8Lit:
  669. let tmp = c.genx(n.sons[1])
  670. if dest < 0: dest = c.getTemp(n.typ)
  671. c.gABI(n, succ(opc), dest, tmp, n.sons[2].intVal)
  672. c.freeTemp(tmp)
  673. else:
  674. genBinaryABC(c, n, dest, opc)
  675. c.genNarrow(n, dest)
  676. proc genConv(c: PCtx; n, arg: PNode; dest: var TDest; opc=opcConv) =
  677. if n.typ.kind == arg.typ.kind and arg.typ.kind == tyProc:
  678. # don't do anything for lambda lifting conversions:
  679. gen(c, arg, dest)
  680. return
  681. let tmp = c.genx(arg)
  682. if dest < 0: dest = c.getTemp(n.typ)
  683. c.gABC(n, opc, dest, tmp)
  684. c.gABx(n, opc, 0, genType(c, n.typ.skipTypes({tyStatic})))
  685. c.gABx(n, opc, 0, genType(c, arg.typ.skipTypes({tyStatic})))
  686. c.freeTemp(tmp)
  687. proc genCard(c: PCtx; n: PNode; dest: var TDest) =
  688. let tmp = c.genx(n.sons[1])
  689. if dest < 0: dest = c.getTemp(n.typ)
  690. c.genSetType(n.sons[1], tmp)
  691. c.gABC(n, opcCard, dest, tmp)
  692. c.freeTemp(tmp)
  693. proc genCastIntFloat(c: PCtx; n: PNode; dest: var TDest) =
  694. const allowedIntegers = {tyInt..tyInt64, tyUInt..tyUInt64, tyChar}
  695. var signedIntegers = {tyInt8..tyInt32}
  696. var unsignedIntegers = {tyUInt8..tyUInt32, tyChar}
  697. let src = n.sons[1].typ.skipTypes(abstractRange)#.kind
  698. let dst = n.sons[0].typ.skipTypes(abstractRange)#.kind
  699. let src_size = getSize(c.config, src)
  700. let dst_size = getSize(c.config, dst)
  701. if c.config.target.intSize < 8:
  702. signedIntegers.incl(tyInt)
  703. unsignedIntegers.incl(tyUInt)
  704. if src_size == dst_size and src.kind in allowedIntegers and
  705. dst.kind in allowedIntegers:
  706. let tmp = c.genx(n.sons[1])
  707. var tmp2 = c.getTemp(n.sons[1].typ)
  708. let tmp3 = c.getTemp(n.sons[1].typ)
  709. if dest < 0: dest = c.getTemp(n[0].typ)
  710. proc mkIntLit(ival: int): int =
  711. result = genLiteral(c, newIntTypeNode(nkIntLit, ival, getSysType(c.graph, n.info, tyInt)))
  712. if src.kind in unsignedIntegers and dst.kind in signedIntegers:
  713. # cast unsigned to signed integer of same size
  714. # signedVal = (unsignedVal xor offset) -% offset
  715. let offset = 1 shl (src_size * 8 - 1)
  716. c.gABx(n, opcLdConst, tmp2, mkIntLit(offset))
  717. c.gABC(n, opcBitxorInt, tmp3, tmp, tmp2)
  718. c.gABC(n, opcSubInt, dest, tmp3, tmp2)
  719. elif src.kind in signedIntegers and dst.kind in unsignedIntegers:
  720. # cast signed to unsigned integer of same size
  721. # unsignedVal = (offset +% signedVal +% 1) and offset
  722. let offset = (1 shl (src_size * 8)) - 1
  723. c.gABx(n, opcLdConst, tmp2, mkIntLit(offset))
  724. c.gABx(n, opcLdConst, dest, mkIntLit(offset+1))
  725. c.gABC(n, opcAddu, tmp3, tmp, dest)
  726. c.gABC(n, opcNarrowU, tmp3, TRegister(src_size*8))
  727. c.gABC(n, opcBitandInt, dest, tmp3, tmp2)
  728. else:
  729. c.gABC(n, opcAsgnInt, dest, tmp)
  730. c.freeTemp(tmp)
  731. c.freeTemp(tmp2)
  732. c.freeTemp(tmp3)
  733. elif src_size == dst_size and src.kind in allowedIntegers and
  734. dst.kind in {tyFloat, tyFloat32, tyFloat64}:
  735. let tmp = c.genx(n[1])
  736. if dest < 0: dest = c.getTemp(n[0].typ)
  737. if dst.kind == tyFloat32:
  738. c.gABC(n, opcAsgnFloat32FromInt, dest, tmp)
  739. else:
  740. c.gABC(n, opcAsgnFloat64FromInt, dest, tmp)
  741. c.freeTemp(tmp)
  742. elif src_size == dst_size and src.kind in {tyFloat, tyFloat32, tyFloat64} and
  743. dst.kind in allowedIntegers:
  744. let tmp = c.genx(n[1])
  745. if dest < 0: dest = c.getTemp(n[0].typ)
  746. if src.kind == tyFloat32:
  747. c.gABC(n, opcAsgnIntFromFloat32, dest, tmp)
  748. else:
  749. c.gABC(n, opcAsgnIntFromFloat64, dest, tmp)
  750. c.freeTemp(tmp)
  751. else:
  752. globalError(c.config, n.info, "VM is only allowed to 'cast' between integers and/or floats of same size")
  753. proc genVoidABC(c: PCtx, n: PNode, dest: TDest, opcode: TOpcode) =
  754. unused(c, n, dest)
  755. var
  756. tmp1 = c.genx(n[1])
  757. tmp2 = c.genx(n[2])
  758. tmp3 = c.genx(n[3])
  759. c.gABC(n, opcode, tmp1, tmp2, tmp3)
  760. c.freeTemp(tmp1)
  761. c.freeTemp(tmp2)
  762. c.freeTemp(tmp3)
  763. proc genBindSym(c: PCtx; n: PNode; dest: var TDest) =
  764. # nah, cannot use c.config.features because sempass context
  765. # can have local experimental switch
  766. # if dynamicBindSym notin c.config.features:
  767. if n.len == 2: # hmm, reliable?
  768. # bindSym with static input
  769. if n[1].kind in {nkClosedSymChoice, nkOpenSymChoice, nkSym}:
  770. let idx = c.genLiteral(n[1])
  771. if dest < 0: dest = c.getTemp(n.typ)
  772. c.gABx(n, opcNBindSym, dest, idx)
  773. else:
  774. localError(c.config, n.info, "invalid bindSym usage")
  775. else:
  776. # experimental bindSym
  777. if dest < 0: dest = c.getTemp(n.typ)
  778. let x = c.getTempRange(n.len, slotTempUnknown)
  779. # callee symbol
  780. var tmp0 = TDest(x)
  781. c.genLit(n.sons[0], tmp0)
  782. # original parameters
  783. for i in 1..<n.len-2:
  784. var r = TRegister(x+i)
  785. c.gen(n.sons[i], r)
  786. # info node
  787. var tmp1 = TDest(x+n.len-2)
  788. c.genLit(n.sons[^2], tmp1)
  789. # payload idx
  790. var tmp2 = TDest(x+n.len-1)
  791. c.genLit(n.sons[^1], tmp2)
  792. c.gABC(n, opcNDynBindSym, dest, x, n.len)
  793. c.freeTempRange(x, n.len)
  794. proc genMagic(c: PCtx; n: PNode; dest: var TDest; m: TMagic) =
  795. case m
  796. of mAnd: c.genAndOr(n, opcFJmp, dest)
  797. of mOr: c.genAndOr(n, opcTJmp, dest)
  798. of mUnaryLt:
  799. let tmp = c.genx(n.sons[1])
  800. if dest < 0: dest = c.getTemp(n.typ)
  801. c.gABI(n, opcSubImmInt, dest, tmp, 1)
  802. c.freeTemp(tmp)
  803. of mPred, mSubI:
  804. c.genAddSubInt(n, dest, opcSubInt)
  805. of mSucc, mAddI:
  806. c.genAddSubInt(n, dest, opcAddInt)
  807. of mInc, mDec:
  808. unused(c, n, dest)
  809. let opc = if m == mInc: opcAddInt else: opcSubInt
  810. let d = c.genx(n.sons[1])
  811. if n.sons[2].isInt8Lit:
  812. c.gABI(n, succ(opc), d, d, n.sons[2].intVal)
  813. else:
  814. let tmp = c.genx(n.sons[2])
  815. c.gABC(n, opc, d, d, tmp)
  816. c.freeTemp(tmp)
  817. c.genNarrow(n.sons[1], d)
  818. c.genAsgnPatch(n.sons[1], d)
  819. c.freeTemp(d)
  820. of mOrd, mChr, mArrToSeq: c.gen(n.sons[1], dest)
  821. of mNew, mNewFinalize:
  822. unused(c, n, dest)
  823. c.genNew(n)
  824. of mNewSeq:
  825. unused(c, n, dest)
  826. c.genNewSeq(n)
  827. of mNewSeqOfCap: c.genNewSeqOfCap(n, dest)
  828. of mNewString:
  829. genUnaryABC(c, n, dest, opcNewStr)
  830. # XXX buggy
  831. of mNewStringOfCap:
  832. # we ignore the 'cap' argument and translate it as 'newString(0)'.
  833. # eval n.sons[1] for possible side effects:
  834. c.freeTemp(c.genx(n.sons[1]))
  835. var tmp = c.getTemp(n.sons[1].typ)
  836. c.gABx(n, opcLdImmInt, tmp, 0)
  837. if dest < 0: dest = c.getTemp(n.typ)
  838. c.gABC(n, opcNewStr, dest, tmp)
  839. c.freeTemp(tmp)
  840. # XXX buggy
  841. of mLengthOpenArray, mLengthArray, mLengthSeq, mXLenSeq:
  842. genUnaryABI(c, n, dest, opcLenSeq)
  843. of mLengthStr, mXLenStr:
  844. genUnaryABI(c, n, dest, opcLenStr)
  845. of mIncl, mExcl:
  846. unused(c, n, dest)
  847. var d = c.genx(n.sons[1])
  848. var tmp = c.genx(n.sons[2])
  849. c.genSetType(n.sons[1], d)
  850. c.gABC(n, if m == mIncl: opcIncl else: opcExcl, d, tmp)
  851. c.freeTemp(d)
  852. c.freeTemp(tmp)
  853. of mCard: genCard(c, n, dest)
  854. of mMulI: genBinaryABCnarrow(c, n, dest, opcMulInt)
  855. of mDivI: genBinaryABCnarrow(c, n, dest, opcDivInt)
  856. of mModI: genBinaryABCnarrow(c, n, dest, opcModInt)
  857. of mAddF64: genBinaryABC(c, n, dest, opcAddFloat)
  858. of mSubF64: genBinaryABC(c, n, dest, opcSubFloat)
  859. of mMulF64: genBinaryABC(c, n, dest, opcMulFloat)
  860. of mDivF64: genBinaryABC(c, n, dest, opcDivFloat)
  861. of mShrI:
  862. # the idea here is to narrow type if needed before executing right shift
  863. # inlined modified: genNarrowU(c, n, dest)
  864. let t = skipTypes(n.typ, abstractVar-{tyTypeDesc})
  865. # uint is uint64 in the VM, we we only need to mask the result for
  866. # other unsigned types:
  867. let tmp = c.genx(n.sons[1])
  868. if t.kind in {tyUInt8..tyUInt32, tyInt8..tyInt32}:
  869. c.gABC(n, opcNarrowU, tmp, TRegister(t.size*8))
  870. # inlined modified: genBinaryABC(c, n, dest, opcShrInt)
  871. let tmp2 = c.genx(n.sons[2])
  872. if dest < 0: dest = c.getTemp(n.typ)
  873. c.gABC(n, opcShrInt, dest, tmp, tmp2)
  874. c.freeTemp(tmp)
  875. c.freeTemp(tmp2)
  876. of mShlI: genBinaryABCnarrowU(c, n, dest, opcShlInt)
  877. of mAshrI: genBinaryABCnarrow(c, n, dest, opcAshrInt)
  878. of mBitandI: genBinaryABCnarrowU(c, n, dest, opcBitandInt)
  879. of mBitorI: genBinaryABCnarrowU(c, n, dest, opcBitorInt)
  880. of mBitxorI: genBinaryABCnarrowU(c, n, dest, opcBitxorInt)
  881. of mAddU: genBinaryABCnarrowU(c, n, dest, opcAddu)
  882. of mSubU: genBinaryABCnarrowU(c, n, dest, opcSubu)
  883. of mMulU: genBinaryABCnarrowU(c, n, dest, opcMulu)
  884. of mDivU: genBinaryABCnarrowU(c, n, dest, opcDivu)
  885. of mModU: genBinaryABCnarrowU(c, n, dest, opcModu)
  886. of mEqI, mEqB, mEqEnum, mEqCh:
  887. genBinaryABC(c, n, dest, opcEqInt)
  888. of mLeI, mLeEnum, mLeCh, mLeB:
  889. genBinaryABC(c, n, dest, opcLeInt)
  890. of mLtI, mLtEnum, mLtCh, mLtB:
  891. genBinaryABC(c, n, dest, opcLtInt)
  892. of mEqF64: genBinaryABC(c, n, dest, opcEqFloat)
  893. of mLeF64: genBinaryABC(c, n, dest, opcLeFloat)
  894. of mLtF64: genBinaryABC(c, n, dest, opcLtFloat)
  895. of mLePtr, mLeU, mLeU64: genBinaryABC(c, n, dest, opcLeu)
  896. of mLtPtr, mLtU, mLtU64: genBinaryABC(c, n, dest, opcLtu)
  897. of mEqProc, mEqRef, mEqUntracedRef:
  898. genBinaryABC(c, n, dest, opcEqRef)
  899. of mXor: genBinaryABCnarrowU(c, n, dest, opcXor)
  900. of mNot: genUnaryABC(c, n, dest, opcNot)
  901. of mUnaryMinusI, mUnaryMinusI64:
  902. genUnaryABC(c, n, dest, opcUnaryMinusInt)
  903. genNarrow(c, n, dest)
  904. of mUnaryMinusF64: genUnaryABC(c, n, dest, opcUnaryMinusFloat)
  905. of mUnaryPlusI, mUnaryPlusF64: gen(c, n.sons[1], dest)
  906. of mBitnotI:
  907. genUnaryABC(c, n, dest, opcBitnotInt)
  908. genNarrowU(c, n, dest)
  909. of mToFloat, mToBiggestFloat, mToInt,
  910. mToBiggestInt, mCharToStr, mBoolToStr, mIntToStr, mInt64ToStr,
  911. mFloatToStr, mCStrToStr, mStrToStr, mEnumToStr:
  912. genConv(c, n, n.sons[1], dest)
  913. of mZe8ToI, mZe8ToI64, mZe16ToI, mZe16ToI64, mZe32ToI64, mZeIToI64:
  914. #genNarrowU modified
  915. let t = skipTypes(n.sons[1].typ, abstractVar-{tyTypeDesc})
  916. let tmp = c.genx(n.sons[1])
  917. c.gABC(n, opcNarrowU, tmp, TRegister(t.size*8))
  918. # assign result to dest register
  919. if dest < 0: dest = c.getTemp(n.typ)
  920. c.gABC(n, opcAsgnInt, dest, tmp)
  921. c.freeTemp(tmp)
  922. of mToU8, mToU16, mToU32:
  923. let t = skipTypes(n.typ, abstractVar-{tyTypeDesc})
  924. var tmp = c.genx(n.sons[1])
  925. if dest < 0: dest = c.getTemp(n.typ)
  926. c.gABC(n, opcToNarrowInt, dest, tmp, TRegister(t.size*8))
  927. c.freeTemp(tmp)
  928. of mEqStr, mEqCString: genBinaryABC(c, n, dest, opcEqStr)
  929. of mLeStr: genBinaryABC(c, n, dest, opcLeStr)
  930. of mLtStr: genBinaryABC(c, n, dest, opcLtStr)
  931. of mEqSet: genBinarySet(c, n, dest, opcEqSet)
  932. of mLeSet: genBinarySet(c, n, dest, opcLeSet)
  933. of mLtSet: genBinarySet(c, n, dest, opcLtSet)
  934. of mMulSet: genBinarySet(c, n, dest, opcMulSet)
  935. of mPlusSet: genBinarySet(c, n, dest, opcPlusSet)
  936. of mMinusSet: genBinarySet(c, n, dest, opcMinusSet)
  937. of mSymDiffSet: genBinarySet(c, n, dest, opcSymdiffSet)
  938. of mConStrStr: genVarargsABC(c, n, dest, opcConcatStr)
  939. of mInSet: genBinarySet(c, n, dest, opcContainsSet)
  940. of mRepr: genUnaryABC(c, n, dest, opcRepr)
  941. of mExit:
  942. unused(c, n, dest)
  943. var tmp = c.genx(n.sons[1])
  944. c.gABC(n, opcQuit, tmp)
  945. c.freeTemp(tmp)
  946. of mSetLengthStr, mSetLengthSeq:
  947. unused(c, n, dest)
  948. var d = c.genx(n.sons[1])
  949. var tmp = c.genx(n.sons[2])
  950. c.gABC(n, if m == mSetLengthStr: opcSetLenStr else: opcSetLenSeq, d, tmp)
  951. c.genAsgnPatch(n.sons[1], d)
  952. c.freeTemp(tmp)
  953. of mSwap:
  954. unused(c, n, dest)
  955. c.gen(lowerSwap(c.graph, n, if c.prc == nil: c.module else: c.prc.sym))
  956. of mIsNil: genUnaryABC(c, n, dest, opcIsNil)
  957. of mCopyStr:
  958. if dest < 0: dest = c.getTemp(n.typ)
  959. var
  960. tmp1 = c.genx(n.sons[1])
  961. tmp2 = c.genx(n.sons[2])
  962. tmp3 = c.getTemp(n.sons[2].typ)
  963. c.gABC(n, opcLenStr, tmp3, tmp1)
  964. c.gABC(n, opcSubStr, dest, tmp1, tmp2)
  965. c.gABC(n, opcSubStr, tmp3)
  966. c.freeTemp(tmp1)
  967. c.freeTemp(tmp2)
  968. c.freeTemp(tmp3)
  969. of mCopyStrLast:
  970. if dest < 0: dest = c.getTemp(n.typ)
  971. var
  972. tmp1 = c.genx(n.sons[1])
  973. tmp2 = c.genx(n.sons[2])
  974. tmp3 = c.genx(n.sons[3])
  975. c.gABC(n, opcSubStr, dest, tmp1, tmp2)
  976. c.gABC(n, opcSubStr, tmp3)
  977. c.freeTemp(tmp1)
  978. c.freeTemp(tmp2)
  979. c.freeTemp(tmp3)
  980. of mParseBiggestFloat:
  981. if dest < 0: dest = c.getTemp(n.typ)
  982. var d2: TRegister
  983. # skip 'nkHiddenAddr':
  984. let d2AsNode = n.sons[2].sons[0]
  985. if needsAsgnPatch(d2AsNode):
  986. d2 = c.getTemp(getSysType(c.graph, n.info, tyFloat))
  987. else:
  988. d2 = c.genx(d2AsNode)
  989. var
  990. tmp1 = c.genx(n.sons[1])
  991. tmp3 = c.genx(n.sons[3])
  992. c.gABC(n, opcParseFloat, dest, tmp1, d2)
  993. c.gABC(n, opcParseFloat, tmp3)
  994. c.freeTemp(tmp1)
  995. c.freeTemp(tmp3)
  996. c.genAsgnPatch(d2AsNode, d2)
  997. c.freeTemp(d2)
  998. of mReset:
  999. unused(c, n, dest)
  1000. var d = c.genx(n.sons[1])
  1001. c.gABC(n, opcReset, d)
  1002. of mOf, mIs:
  1003. if dest < 0: dest = c.getTemp(n.typ)
  1004. var tmp = c.genx(n.sons[1])
  1005. var idx = c.getTemp(getSysType(c.graph, n.info, tyInt))
  1006. var typ = n.sons[2].typ
  1007. if m == mOf: typ = typ.skipTypes(abstractPtrs-{tyTypeDesc})
  1008. c.gABx(n, opcLdImmInt, idx, c.genType(typ))
  1009. c.gABC(n, if m == mOf: opcOf else: opcIs, dest, tmp, idx)
  1010. c.freeTemp(tmp)
  1011. c.freeTemp(idx)
  1012. of mHigh:
  1013. if dest < 0: dest = c.getTemp(n.typ)
  1014. let tmp = c.genx(n.sons[1])
  1015. case n.sons[1].typ.skipTypes(abstractVar-{tyTypeDesc}).kind:
  1016. of tyString, tyCString:
  1017. c.gABI(n, opcLenStr, dest, tmp, 1)
  1018. else:
  1019. c.gABI(n, opcLenSeq, dest, tmp, 1)
  1020. c.freeTemp(tmp)
  1021. of mEcho:
  1022. unused(c, n, dest)
  1023. let n = n[1].skipConv
  1024. let x = c.getTempRange(n.len, slotTempUnknown)
  1025. internalAssert c.config, n.kind == nkBracket
  1026. for i in 0..<n.len:
  1027. var r: TRegister = x+i
  1028. c.gen(n.sons[i], r)
  1029. c.gABC(n, opcEcho, x, n.len)
  1030. c.freeTempRange(x, n.len)
  1031. of mAppendStrCh:
  1032. unused(c, n, dest)
  1033. genBinaryStmtVar(c, n, opcAddStrCh)
  1034. of mAppendStrStr:
  1035. unused(c, n, dest)
  1036. genBinaryStmtVar(c, n, opcAddStrStr)
  1037. of mAppendSeqElem:
  1038. unused(c, n, dest)
  1039. genBinaryStmtVar(c, n, opcAddSeqElem)
  1040. of mParseExprToAst:
  1041. genUnaryABC(c, n, dest, opcParseExprToAst)
  1042. of mParseStmtToAst:
  1043. genUnaryABC(c, n, dest, opcParseStmtToAst)
  1044. of mTypeTrait:
  1045. let tmp = c.genx(n.sons[1])
  1046. if dest < 0: dest = c.getTemp(n.typ)
  1047. c.gABx(n, opcSetType, tmp, c.genType(n.sons[1].typ))
  1048. c.gABC(n, opcTypeTrait, dest, tmp)
  1049. c.freeTemp(tmp)
  1050. of mSlurp: genUnaryABC(c, n, dest, opcSlurp)
  1051. of mStaticExec: genBinaryABCD(c, n, dest, opcGorge)
  1052. of mNLen: genUnaryABI(c, n, dest, opcLenSeq, nimNodeFlag)
  1053. of mGetImpl: genUnaryABC(c, n, dest, opcGetImpl)
  1054. of mGetImplTransf: genUnaryABC(c, n, dest, opcGetImplTransf)
  1055. of mSymOwner: genUnaryABC(c, n, dest, opcSymOwner)
  1056. of mNChild: genBinaryABC(c, n, dest, opcNChild)
  1057. of mNSetChild: genVoidABC(c, n, dest, opcNSetChild)
  1058. of mNDel: genVoidABC(c, n, dest, opcNDel)
  1059. of mNAdd: genBinaryABC(c, n, dest, opcNAdd)
  1060. of mNAddMultiple: genBinaryABC(c, n, dest, opcNAddMultiple)
  1061. of mNKind: genUnaryABC(c, n, dest, opcNKind)
  1062. of mNSymKind: genUnaryABC(c, n, dest, opcNSymKind)
  1063. of mNccValue: genUnaryABC(c, n, dest, opcNccValue)
  1064. of mNccInc: genBinaryABC(c, n, dest, opcNccInc)
  1065. of mNcsAdd: genBinaryABC(c, n, dest, opcNcsAdd)
  1066. of mNcsIncl: genBinaryABC(c, n, dest, opcNcsIncl)
  1067. of mNcsLen: genUnaryABC(c, n, dest, opcNcsLen)
  1068. of mNcsAt: genBinaryABC(c, n, dest, opcNcsAt)
  1069. of mNctPut: genVoidABC(c, n, dest, opcNctPut)
  1070. of mNctLen: genUnaryABC(c, n, dest, opcNctLen)
  1071. of mNctGet: genBinaryABC(c, n, dest, opcNctGet)
  1072. of mNctHasNext: genBinaryABC(c, n, dest, opcNctHasNext)
  1073. of mNctNext: genBinaryABC(c, n, dest, opcNctNext)
  1074. of mNIntVal: genUnaryABC(c, n, dest, opcNIntVal)
  1075. of mNFloatVal: genUnaryABC(c, n, dest, opcNFloatVal)
  1076. of mNSymbol: genUnaryABC(c, n, dest, opcNSymbol)
  1077. of mNIdent: genUnaryABC(c, n, dest, opcNIdent)
  1078. of mNGetType:
  1079. let tmp = c.genx(n.sons[1])
  1080. if dest < 0: dest = c.getTemp(n.typ)
  1081. let rc = case n[0].sym.name.s:
  1082. of "getType": 0
  1083. of "typeKind": 1
  1084. of "getTypeInst": 2
  1085. else: 3 # "getTypeImpl"
  1086. c.gABC(n, opcNGetType, dest, tmp, rc)
  1087. c.freeTemp(tmp)
  1088. #genUnaryABC(c, n, dest, opcNGetType)
  1089. of mNStrVal: genUnaryABC(c, n, dest, opcNStrVal)
  1090. of mNSetIntVal:
  1091. unused(c, n, dest)
  1092. genBinaryStmt(c, n, opcNSetIntVal)
  1093. of mNSetFloatVal:
  1094. unused(c, n, dest)
  1095. genBinaryStmt(c, n, opcNSetFloatVal)
  1096. of mNSetSymbol:
  1097. unused(c, n, dest)
  1098. genBinaryStmt(c, n, opcNSetSymbol)
  1099. of mNSetIdent:
  1100. unused(c, n, dest)
  1101. genBinaryStmt(c, n, opcNSetIdent)
  1102. of mNSetType:
  1103. unused(c, n, dest)
  1104. genBinaryStmt(c, n, opcNSetType)
  1105. of mNSetStrVal:
  1106. unused(c, n, dest)
  1107. genBinaryStmt(c, n, opcNSetStrVal)
  1108. of mNNewNimNode: genBinaryABC(c, n, dest, opcNNewNimNode)
  1109. of mNCopyNimNode: genUnaryABC(c, n, dest, opcNCopyNimNode)
  1110. of mNCopyNimTree: genUnaryABC(c, n, dest, opcNCopyNimTree)
  1111. of mNBindSym: genBindSym(c, n, dest)
  1112. of mStrToIdent: genUnaryABC(c, n, dest, opcStrToIdent)
  1113. of mEqIdent: genBinaryABC(c, n, dest, opcEqIdent)
  1114. of mEqNimrodNode: genBinaryABC(c, n, dest, opcEqNimNode)
  1115. of mSameNodeType: genBinaryABC(c, n, dest, opcSameNodeType)
  1116. of mNLineInfo:
  1117. case n[0].sym.name.s
  1118. of "getFile": genUnaryABI(c, n, dest, opcNGetLineInfo, 0)
  1119. of "getLine": genUnaryABI(c, n, dest, opcNGetLineInfo, 1)
  1120. of "getColumn": genUnaryABI(c, n, dest, opcNGetLineInfo, 2)
  1121. of "copyLineInfo":
  1122. internalAssert c.config, n.len == 3
  1123. unused(c, n, dest)
  1124. genBinaryStmt(c, n, opcNSetLineInfo)
  1125. else: internalAssert c.config, false
  1126. of mNHint:
  1127. unused(c, n, dest)
  1128. genBinaryStmt(c, n, opcNHint)
  1129. of mNWarning:
  1130. unused(c, n, dest)
  1131. genBinaryStmt(c, n, opcNWarning)
  1132. of mNError:
  1133. if n.len <= 1:
  1134. # query error condition:
  1135. c.gABC(n, opcQueryErrorFlag, dest)
  1136. else:
  1137. # setter
  1138. unused(c, n, dest)
  1139. genBinaryStmt(c, n, opcNError)
  1140. of mNCallSite:
  1141. if dest < 0: dest = c.getTemp(n.typ)
  1142. c.gABC(n, opcCallSite, dest)
  1143. of mNGenSym: genBinaryABC(c, n, dest, opcGenSym)
  1144. of mMinI, mMaxI, mAbsF64, mMinF64, mMaxF64, mAbsI,
  1145. mDotDot:
  1146. c.genCall(n, dest)
  1147. of mExpandToAst:
  1148. if n.len != 2:
  1149. globalError(c.config, n.info, "expandToAst requires 1 argument")
  1150. let arg = n.sons[1]
  1151. if arg.kind in nkCallKinds:
  1152. #if arg[0].kind != nkSym or arg[0].sym.kind notin {skTemplate, skMacro}:
  1153. # "ExpandToAst: expanded symbol is no macro or template"
  1154. if dest < 0: dest = c.getTemp(n.typ)
  1155. c.genCall(arg, dest)
  1156. # do not call clearDest(n, dest) here as getAst has a meta-type as such
  1157. # produces a value
  1158. else:
  1159. globalError(c.config, n.info, "expandToAst requires a call expression")
  1160. of mSizeOf, mAlignOf:
  1161. globalError(c.config, n.info, "cannot evaluate 'sizeof/alignof' because its type is not defined completely")
  1162. of mRunnableExamples:
  1163. discard "just ignore any call to runnableExamples"
  1164. else:
  1165. # mGCref, mGCunref,
  1166. globalError(c.config, n.info, "cannot generate code for: " & $m)
  1167. proc genMarshalLoad(c: PCtx, n: PNode, dest: var TDest) =
  1168. ## Signature: proc to*[T](data: string): T
  1169. if dest < 0: dest = c.getTemp(n.typ)
  1170. var tmp = c.genx(n.sons[1])
  1171. c.gABC(n, opcMarshalLoad, dest, tmp)
  1172. c.gABx(n, opcMarshalLoad, 0, c.genType(n.typ))
  1173. c.freeTemp(tmp)
  1174. proc genMarshalStore(c: PCtx, n: PNode, dest: var TDest) =
  1175. ## Signature: proc `$$`*[T](x: T): string
  1176. if dest < 0: dest = c.getTemp(n.typ)
  1177. var tmp = c.genx(n.sons[1])
  1178. c.gABC(n, opcMarshalStore, dest, tmp)
  1179. c.gABx(n, opcMarshalStore, 0, c.genType(n.sons[1].typ))
  1180. c.freeTemp(tmp)
  1181. const
  1182. atomicTypes = {tyBool, tyChar,
  1183. tyExpr, tyStmt, tyTypeDesc, tyStatic,
  1184. tyEnum,
  1185. tyOrdinal,
  1186. tyRange,
  1187. tyProc,
  1188. tyPointer, tyOpenArray,
  1189. tyString, tyCString,
  1190. tyInt, tyInt8, tyInt16, tyInt32, tyInt64,
  1191. tyFloat, tyFloat32, tyFloat64, tyFloat128,
  1192. tyUInt, tyUInt8, tyUInt16, tyUInt32, tyUInt64}
  1193. proc fitsRegister*(t: PType): bool =
  1194. assert t != nil
  1195. t.skipTypes(abstractInst-{tyTypeDesc}).kind in {
  1196. tyRange, tyEnum, tyBool, tyInt..tyUInt64, tyChar}
  1197. proc unneededIndirection(n: PNode): bool =
  1198. n.typ.skipTypes(abstractInst-{tyTypeDesc}).kind == tyRef
  1199. proc canElimAddr(n: PNode): PNode =
  1200. case n.sons[0].kind
  1201. of nkObjUpConv, nkObjDownConv, nkChckRange, nkChckRangeF, nkChckRange64:
  1202. var m = n.sons[0].sons[0]
  1203. if m.kind in {nkDerefExpr, nkHiddenDeref}:
  1204. # addr ( nkConv ( deref ( x ) ) ) --> nkConv(x)
  1205. result = copyNode(n.sons[0])
  1206. result.add m.sons[0]
  1207. of nkHiddenStdConv, nkHiddenSubConv, nkConv:
  1208. var m = n.sons[0].sons[1]
  1209. if m.kind in {nkDerefExpr, nkHiddenDeref}:
  1210. # addr ( nkConv ( deref ( x ) ) ) --> nkConv(x)
  1211. result = copyNode(n.sons[0])
  1212. result.add m.sons[0]
  1213. else:
  1214. if n.sons[0].kind in {nkDerefExpr, nkHiddenDeref}:
  1215. # addr ( deref ( x )) --> x
  1216. result = n.sons[0].sons[0]
  1217. proc genAddr(c: PCtx, n: PNode, dest: var TDest, flags: TGenFlags) =
  1218. if (let m = canElimAddr(n); m != nil):
  1219. gen(c, m, dest, flags)
  1220. return
  1221. let af = if n[0].kind in {nkBracketExpr, nkDotExpr, nkCheckedFieldExpr}: {gfNode}
  1222. else: {gfNodeAddr}
  1223. let newflags = flags-{gfNode, gfNodeAddr}+af
  1224. if isGlobal(n.sons[0]):
  1225. gen(c, n.sons[0], dest, flags+af)
  1226. else:
  1227. let tmp = c.genx(n.sons[0], newflags)
  1228. if dest < 0: dest = c.getTemp(n.typ)
  1229. if c.prc.slots[tmp].kind >= slotTempUnknown:
  1230. gABC(c, n, opcAddrNode, dest, tmp)
  1231. # hack ahead; in order to fix bug #1781 we mark the temporary as
  1232. # permanent, so that it's not used for anything else:
  1233. c.prc.slots[tmp].kind = slotTempPerm
  1234. # XXX this is still a hack
  1235. #message(n.info, warnUser, "suspicious opcode used")
  1236. else:
  1237. gABC(c, n, opcAddrReg, dest, tmp)
  1238. c.freeTemp(tmp)
  1239. proc genDeref(c: PCtx, n: PNode, dest: var TDest, flags: TGenFlags) =
  1240. if unneededIndirection(n.sons[0]):
  1241. gen(c, n.sons[0], dest, flags)
  1242. if {gfNodeAddr, gfNode} * flags == {} and fitsRegister(n.typ):
  1243. c.gABC(n, opcNodeToReg, dest, dest)
  1244. else:
  1245. let tmp = c.genx(n.sons[0], flags)
  1246. if dest < 0: dest = c.getTemp(n.typ)
  1247. gABC(c, n, opcLdDeref, dest, tmp)
  1248. assert n.typ != nil
  1249. if {gfNodeAddr, gfNode} * flags == {} and fitsRegister(n.typ):
  1250. c.gABC(n, opcNodeToReg, dest, dest)
  1251. proc whichAsgnOpc(n: PNode): TOpcode =
  1252. case n.typ.skipTypes(abstractRange-{tyTypeDesc}).kind
  1253. of tyBool, tyChar, tyEnum, tyOrdinal, tyInt..tyInt64, tyUInt..tyUInt64:
  1254. opcAsgnInt
  1255. of tyString, tyCString:
  1256. opcAsgnStr
  1257. of tyFloat..tyFloat128:
  1258. opcAsgnFloat
  1259. of tyRef, tyNil, tyVar, tyLent, tyPtr:
  1260. opcAsgnRef
  1261. else:
  1262. opcAsgnComplex
  1263. proc whichAsgnOpc(n: PNode; opc: TOpcode): TOpcode = opc
  1264. proc genAsgn(c: PCtx; dest: TDest; ri: PNode; requiresCopy: bool) =
  1265. let tmp = c.genx(ri)
  1266. assert dest >= 0
  1267. gABC(c, ri, whichAsgnOpc(ri), dest, tmp, 1-ord(requiresCopy))
  1268. c.freeTemp(tmp)
  1269. proc setSlot(c: PCtx; v: PSym) =
  1270. # XXX generate type initialization here?
  1271. if v.position == 0:
  1272. if c.prc.maxSlots == 0: c.prc.maxSlots = 1
  1273. if c.prc.maxSlots >= high(TRegister):
  1274. globalError(c.config, v.info, "cannot generate code; too many registers required")
  1275. v.position = c.prc.maxSlots
  1276. c.prc.slots[v.position] = (inUse: true,
  1277. kind: if v.kind == skLet: slotFixedLet else: slotFixedVar)
  1278. inc c.prc.maxSlots
  1279. proc cannotEval(c: PCtx; n: PNode) {.noinline.} =
  1280. globalError(c.config, n.info, "cannot evaluate at compile time: " &
  1281. n.renderTree)
  1282. proc isOwnedBy(a, b: PSym): bool =
  1283. var a = a.owner
  1284. while a != nil and a.kind != skModule:
  1285. if a == b: return true
  1286. a = a.owner
  1287. proc getOwner(c: PCtx): PSym =
  1288. result = c.prc.sym
  1289. if result.isNil: result = c.module
  1290. proc checkCanEval(c: PCtx; n: PNode) =
  1291. # we need to ensure that we don't evaluate 'x' here:
  1292. # proc foo() = var x ...
  1293. let s = n.sym
  1294. if {sfCompileTime, sfGlobal} <= s.flags: return
  1295. if s.kind in {skVar, skTemp, skLet, skParam, skResult} and
  1296. not s.isOwnedBy(c.prc.sym) and s.owner != c.module and c.mode != emRepl:
  1297. cannotEval(c, n)
  1298. elif s.kind in {skProc, skFunc, skConverter, skMethod,
  1299. skIterator} and sfForward in s.flags:
  1300. cannotEval(c, n)
  1301. proc isTemp(c: PCtx; dest: TDest): bool =
  1302. result = dest >= 0 and c.prc.slots[dest].kind >= slotTempUnknown
  1303. template needsAdditionalCopy(n): untyped =
  1304. not c.isTemp(dest) and not fitsRegister(n.typ)
  1305. proc genAdditionalCopy(c: PCtx; n: PNode; opc: TOpcode;
  1306. dest, idx, value: TRegister) =
  1307. var cc = c.getTemp(n.typ)
  1308. c.gABC(n, whichAsgnOpc(n), cc, value, 0)
  1309. c.gABC(n, opc, dest, idx, cc)
  1310. c.freeTemp(cc)
  1311. proc preventFalseAlias(c: PCtx; n: PNode; opc: TOpcode;
  1312. dest, idx, value: TRegister) =
  1313. # opcLdObj et al really means "load address". We sometimes have to create a
  1314. # copy in order to not introduce false aliasing:
  1315. # mylocal = a.b # needs a copy of the data!
  1316. assert n.typ != nil
  1317. if needsAdditionalCopy(n):
  1318. genAdditionalCopy(c, n, opc, dest, idx, value)
  1319. else:
  1320. c.gABC(n, opc, dest, idx, value)
  1321. proc genAsgn(c: PCtx; le, ri: PNode; requiresCopy: bool) =
  1322. case le.kind
  1323. of nkBracketExpr:
  1324. let dest = c.genx(le.sons[0], {gfNode})
  1325. let idx = c.genIndex(le.sons[1], le.sons[0].typ)
  1326. let tmp = c.genx(ri)
  1327. if le.sons[0].typ.skipTypes(abstractVarRange-{tyTypeDesc}).kind in {
  1328. tyString, tyCString}:
  1329. c.preventFalseAlias(le, opcWrStrIdx, dest, idx, tmp)
  1330. else:
  1331. c.preventFalseAlias(le, opcWrArr, dest, idx, tmp)
  1332. c.freeTemp(tmp)
  1333. of nkCheckedFieldExpr:
  1334. var objR: TDest = -1
  1335. genCheckedObjAccessAux(c, le, objR, {gfNode})
  1336. let idx = genField(c, le[0].sons[1])
  1337. let tmp = c.genx(ri)
  1338. c.preventFalseAlias(le[0], opcWrObj, objR, idx, tmp)
  1339. c.freeTemp(tmp)
  1340. c.freeTemp(objR)
  1341. of nkDotExpr:
  1342. let dest = c.genx(le.sons[0], {gfNode})
  1343. let idx = genField(c, le.sons[1])
  1344. let tmp = c.genx(ri)
  1345. c.preventFalseAlias(le, opcWrObj, dest, idx, tmp)
  1346. c.freeTemp(tmp)
  1347. of nkDerefExpr, nkHiddenDeref:
  1348. let dest = c.genx(le.sons[0], {gfNode})
  1349. let tmp = c.genx(ri)
  1350. c.preventFalseAlias(le, opcWrDeref, dest, 0, tmp)
  1351. c.freeTemp(tmp)
  1352. of nkSym:
  1353. let s = le.sym
  1354. checkCanEval(c, le)
  1355. if s.isGlobal:
  1356. withTemp(tmp, le.typ):
  1357. c.gen(le, tmp, {gfNodeAddr})
  1358. let val = c.genx(ri)
  1359. c.preventFalseAlias(le, opcWrDeref, tmp, 0, val)
  1360. c.freeTemp(val)
  1361. else:
  1362. if s.kind == skForVar: c.setSlot s
  1363. internalAssert c.config, s.position > 0 or (s.position == 0 and
  1364. s.kind in {skParam,skResult})
  1365. var dest: TRegister = s.position + ord(s.kind == skParam)
  1366. assert le.typ != nil
  1367. if needsAdditionalCopy(le) and s.kind in {skResult, skVar, skParam}:
  1368. var cc = c.getTemp(le.typ)
  1369. gen(c, ri, cc)
  1370. c.gABC(le, whichAsgnOpc(le), dest, cc, 1)
  1371. c.freeTemp(cc)
  1372. else:
  1373. gen(c, ri, dest)
  1374. else:
  1375. let dest = c.genx(le, {gfNodeAddr})
  1376. genAsgn(c, dest, ri, requiresCopy)
  1377. proc genTypeLit(c: PCtx; t: PType; dest: var TDest) =
  1378. var n = newNode(nkType)
  1379. n.typ = t
  1380. genLit(c, n, dest)
  1381. proc importcSym(c: PCtx; info: TLineInfo; s: PSym) =
  1382. when hasFFI:
  1383. if allowFFI in c.features:
  1384. c.globals.add(importcSymbol(s))
  1385. s.position = c.globals.len
  1386. else:
  1387. localError(c.config, info, "VM is not allowed to 'importc'")
  1388. else:
  1389. localError(c.config, info,
  1390. "cannot 'importc' variable at compile time")
  1391. proc getNullValue*(typ: PType, info: TLineInfo; conf: ConfigRef): PNode
  1392. proc genGlobalInit(c: PCtx; n: PNode; s: PSym) =
  1393. c.globals.add(getNullValue(s.typ, n.info, c.config))
  1394. s.position = c.globals.len
  1395. # This is rather hard to support, due to the laziness of the VM code
  1396. # generator. See tests/compile/tmacro2 for why this is necessary:
  1397. # var decls{.compileTime.}: seq[NimNode] = @[]
  1398. let dest = c.getTemp(s.typ)
  1399. c.gABx(n, opcLdGlobal, dest, s.position)
  1400. if s.ast != nil:
  1401. let tmp = c.genx(s.ast)
  1402. c.genAdditionalCopy(n, opcWrDeref, dest, 0, tmp)
  1403. c.freeTemp(dest)
  1404. c.freeTemp(tmp)
  1405. proc genRdVar(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags) =
  1406. # gfNodeAddr and gfNode are mutually exclusive
  1407. assert card(flags * {gfNodeAddr, gfNode}) < 2
  1408. let s = n.sym
  1409. if s.isGlobal:
  1410. if sfCompileTime in s.flags or c.mode == emRepl:
  1411. discard
  1412. elif s.position == 0:
  1413. cannotEval(c, n)
  1414. if s.position == 0:
  1415. if sfImportc in s.flags: c.importcSym(n.info, s)
  1416. else: genGlobalInit(c, n, s)
  1417. if dest < 0: dest = c.getTemp(n.typ)
  1418. assert s.typ != nil
  1419. if gfNodeAddr in flags:
  1420. c.gABx(n, opcLdGlobalAddr, dest, s.position)
  1421. elif fitsRegister(s.typ) and gfNode notin flags:
  1422. var cc = c.getTemp(n.typ)
  1423. c.gABx(n, opcLdGlobal, cc, s.position)
  1424. c.gABC(n, opcNodeToReg, dest, cc)
  1425. c.freeTemp(cc)
  1426. else:
  1427. c.gABx(n, opcLdGlobal, dest, s.position)
  1428. else:
  1429. if s.kind == skForVar and c.mode == emRepl: c.setSlot(s)
  1430. if s.position > 0 or (s.position == 0 and
  1431. s.kind in {skParam,skResult}):
  1432. if dest < 0:
  1433. dest = s.position + ord(s.kind == skParam)
  1434. internalAssert(c.config, c.prc.slots[dest].kind < slotSomeTemp)
  1435. else:
  1436. # we need to generate an assignment:
  1437. genAsgn(c, dest, n, c.prc.slots[dest].kind >= slotSomeTemp)
  1438. else:
  1439. # see tests/t99bott for an example that triggers it:
  1440. cannotEval(c, n)
  1441. template needsRegLoad(): untyped =
  1442. {gfNode, gfNodeAddr} * flags == {} and
  1443. fitsRegister(n.typ.skipTypes({tyVar, tyLent, tyStatic}))
  1444. proc genArrAccess2(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode;
  1445. flags: TGenFlags) =
  1446. let a = c.genx(n.sons[0], flags)
  1447. let b = c.genIndex(n.sons[1], n.sons[0].typ)
  1448. if dest < 0: dest = c.getTemp(n.typ)
  1449. if needsRegLoad():
  1450. var cc = c.getTemp(n.typ)
  1451. c.gABC(n, opc, cc, a, b)
  1452. c.gABC(n, opcNodeToReg, dest, cc)
  1453. c.freeTemp(cc)
  1454. else:
  1455. #message(n.info, warnUser, "argh")
  1456. #echo "FLAGS ", flags, " ", fitsRegister(n.typ), " ", typeToString(n.typ)
  1457. c.gABC(n, opc, dest, a, b)
  1458. c.freeTemp(a)
  1459. c.freeTemp(b)
  1460. proc genObjAccess(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags) =
  1461. let a = c.genx(n.sons[0], flags)
  1462. let b = genField(c, n.sons[1])
  1463. if dest < 0: dest = c.getTemp(n.typ)
  1464. if needsRegLoad():
  1465. var cc = c.getTemp(n.typ)
  1466. c.gABC(n, opcLdObj, cc, a, b)
  1467. c.gABC(n, opcNodeToReg, dest, cc)
  1468. c.freeTemp(cc)
  1469. else:
  1470. c.gABC(n, opcLdObj, dest, a, b)
  1471. c.freeTemp(a)
  1472. proc genCheckedObjAccessAux(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags) =
  1473. internalAssert c.config, n.kind == nkCheckedFieldExpr
  1474. # nkDotExpr to access the requested field
  1475. let accessExpr = n[0]
  1476. # nkCall to check if the discriminant is valid
  1477. var checkExpr = n[1]
  1478. let negCheck = checkExpr[0].sym.magic == mNot
  1479. if negCheck:
  1480. checkExpr = checkExpr[^1]
  1481. # Discriminant symbol
  1482. let disc = checkExpr[2]
  1483. internalAssert c.config, disc.sym.kind == skField
  1484. # Load the object in `dest`
  1485. c.gen(accessExpr[0], dest, flags)
  1486. # Load the discriminant
  1487. var discVal = c.getTemp(disc.typ)
  1488. c.gABC(n, opcLdObj, discVal, dest, genField(c, disc))
  1489. # Check if its value is contained in the supplied set
  1490. let setLit = c.genx(checkExpr[1])
  1491. var rs = c.getTemp(getSysType(c.graph, n.info, tyBool))
  1492. c.gABC(n, opcContainsSet, rs, setLit, discVal)
  1493. c.freeTemp(setLit)
  1494. # If the check fails let the user know
  1495. let L1 = c.xjmp(n, if negCheck: opcFJmp else: opcTJmp, rs)
  1496. c.freeTemp(rs)
  1497. # Not ideal but will do for the moment
  1498. c.gABC(n, opcQuit)
  1499. c.patch(L1)
  1500. proc genCheckedObjAccess(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags) =
  1501. var objR: TDest = -1
  1502. genCheckedObjAccessAux(c, n, objR, flags)
  1503. let accessExpr = n[0]
  1504. # Field symbol
  1505. var field = accessExpr[1]
  1506. internalAssert c.config, field.sym.kind == skField
  1507. # Load the content now
  1508. if dest < 0: dest = c.getTemp(n.typ)
  1509. let fieldPos = genField(c, field)
  1510. if needsRegLoad():
  1511. var cc = c.getTemp(accessExpr.typ)
  1512. c.gABC(n, opcLdObj, cc, objR, fieldPos)
  1513. c.gABC(n, opcNodeToReg, dest, cc)
  1514. c.freeTemp(cc)
  1515. else:
  1516. c.gABC(n, opcLdObj, dest, objR, fieldPos)
  1517. c.freeTemp(objR)
  1518. proc genArrAccess(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags) =
  1519. let arrayType = n.sons[0].typ.skipTypes(abstractVarRange-{tyTypeDesc}).kind
  1520. if arrayType in {tyString, tyCString}:
  1521. genArrAccess2(c, n, dest, opcLdStrIdx, {})
  1522. elif arrayType == tyTypeDesc:
  1523. c.genTypeLit(n.typ, dest)
  1524. else:
  1525. genArrAccess2(c, n, dest, opcLdArr, flags)
  1526. proc getNullValueAux(obj: PNode, result: PNode; conf: ConfigRef) =
  1527. case obj.kind
  1528. of nkRecList:
  1529. for i in countup(0, sonsLen(obj) - 1): getNullValueAux(obj.sons[i], result, conf)
  1530. of nkRecCase:
  1531. getNullValueAux(obj.sons[0], result, conf)
  1532. for i in countup(1, sonsLen(obj) - 1):
  1533. getNullValueAux(lastSon(obj.sons[i]), result, conf)
  1534. of nkSym:
  1535. let field = newNodeI(nkExprColonExpr, result.info)
  1536. field.add(obj)
  1537. field.add(getNullValue(obj.sym.typ, result.info, conf))
  1538. addSon(result, field)
  1539. else: globalError(conf, result.info, "cannot create null element for: " & $obj)
  1540. proc getNullValue(typ: PType, info: TLineInfo; conf: ConfigRef): PNode =
  1541. var t = skipTypes(typ, abstractRange+{tyStatic}-{tyTypeDesc})
  1542. case t.kind
  1543. of tyBool, tyEnum, tyChar, tyInt..tyInt64:
  1544. result = newNodeIT(nkIntLit, info, t)
  1545. of tyUInt..tyUInt64:
  1546. result = newNodeIT(nkUIntLit, info, t)
  1547. of tyFloat..tyFloat128:
  1548. result = newNodeIT(nkFloatLit, info, t)
  1549. of tyCString, tyString:
  1550. result = newNodeIT(nkStrLit, info, t)
  1551. result.strVal = ""
  1552. of tyVar, tyLent, tyPointer, tyPtr, tyExpr,
  1553. tyStmt, tyTypeDesc, tyRef, tyNil:
  1554. result = newNodeIT(nkNilLit, info, t)
  1555. of tyProc:
  1556. if t.callConv != ccClosure:
  1557. result = newNodeIT(nkNilLit, info, t)
  1558. else:
  1559. result = newNodeIT(nkTupleConstr, info, t)
  1560. result.add(newNodeIT(nkNilLit, info, t))
  1561. result.add(newNodeIT(nkNilLit, info, t))
  1562. of tyObject:
  1563. result = newNodeIT(nkObjConstr, info, t)
  1564. result.add(newNodeIT(nkEmpty, info, t))
  1565. # initialize inherited fields:
  1566. var base = t.sons[0]
  1567. while base != nil:
  1568. getNullValueAux(skipTypes(base, skipPtrs).n, result, conf)
  1569. base = base.sons[0]
  1570. getNullValueAux(t.n, result, conf)
  1571. of tyArray:
  1572. result = newNodeIT(nkBracket, info, t)
  1573. for i in countup(0, int(lengthOrd(conf, t)) - 1):
  1574. addSon(result, getNullValue(elemType(t), info, conf))
  1575. of tyTuple:
  1576. result = newNodeIT(nkTupleConstr, info, t)
  1577. for i in countup(0, sonsLen(t) - 1):
  1578. addSon(result, getNullValue(t.sons[i], info, conf))
  1579. of tySet:
  1580. result = newNodeIT(nkCurly, info, t)
  1581. of tyOpt:
  1582. result = newNodeIT(nkNilLit, info, t)
  1583. of tySequence:
  1584. result = newNodeIT(nkBracket, info, t)
  1585. else:
  1586. globalError(conf, info, "cannot create null element for: " & $t.kind)
  1587. result = newNodeI(nkEmpty, info)
  1588. proc ldNullOpcode(t: PType): TOpcode =
  1589. assert t != nil
  1590. if fitsRegister(t): opcLdNullReg else: opcLdNull
  1591. proc genVarSection(c: PCtx; n: PNode) =
  1592. for a in n:
  1593. if a.kind == nkCommentStmt: continue
  1594. #assert(a.sons[0].kind == nkSym) can happen for transformed vars
  1595. if a.kind == nkVarTuple:
  1596. for i in 0 .. a.len-3:
  1597. if not a[i].sym.isGlobal: setSlot(c, a[i].sym)
  1598. checkCanEval(c, a[i])
  1599. c.gen(lowerTupleUnpacking(c.graph, a, c.getOwner))
  1600. elif a.sons[0].kind == nkSym:
  1601. let s = a.sons[0].sym
  1602. checkCanEval(c, a.sons[0])
  1603. if s.isGlobal:
  1604. if s.position == 0:
  1605. if sfImportc in s.flags: c.importcSym(a.info, s)
  1606. else:
  1607. let sa = getNullValue(s.typ, a.info, c.config)
  1608. #if s.ast.isNil: getNullValue(s.typ, a.info)
  1609. #else: canonValue(s.ast)
  1610. assert sa.kind != nkCall
  1611. c.globals.add(sa)
  1612. s.position = c.globals.len
  1613. if a.sons[2].kind != nkEmpty:
  1614. let tmp = c.genx(a.sons[0], {gfNodeAddr})
  1615. let val = c.genx(a.sons[2])
  1616. c.genAdditionalCopy(a.sons[2], opcWrDeref, tmp, 0, val)
  1617. c.freeTemp(val)
  1618. c.freeTemp(tmp)
  1619. else:
  1620. setSlot(c, s)
  1621. if a.sons[2].kind == nkEmpty:
  1622. c.gABx(a, ldNullOpcode(s.typ), s.position, c.genType(s.typ))
  1623. else:
  1624. assert s.typ != nil
  1625. if not fitsRegister(s.typ):
  1626. c.gABx(a, ldNullOpcode(s.typ), s.position, c.genType(s.typ))
  1627. let le = a.sons[0]
  1628. assert le.typ != nil
  1629. if not fitsRegister(le.typ) and s.kind in {skResult, skVar, skParam}:
  1630. var cc = c.getTemp(le.typ)
  1631. gen(c, a.sons[2], cc)
  1632. c.gABC(le, whichAsgnOpc(le), s.position.TRegister, cc, 1)
  1633. c.freeTemp(cc)
  1634. else:
  1635. gen(c, a.sons[2], s.position.TRegister)
  1636. else:
  1637. # assign to a.sons[0]; happens for closures
  1638. if a.sons[2].kind == nkEmpty:
  1639. let tmp = genx(c, a.sons[0])
  1640. c.gABx(a, ldNullOpcode(a[0].typ), tmp, c.genType(a.sons[0].typ))
  1641. c.freeTemp(tmp)
  1642. else:
  1643. genAsgn(c, a.sons[0], a.sons[2], true)
  1644. proc genArrayConstr(c: PCtx, n: PNode, dest: var TDest) =
  1645. if dest < 0: dest = c.getTemp(n.typ)
  1646. c.gABx(n, opcLdNull, dest, c.genType(n.typ))
  1647. let intType = getSysType(c.graph, n.info, tyInt)
  1648. let seqType = n.typ.skipTypes(abstractVar-{tyTypeDesc})
  1649. if seqType.kind == tySequence:
  1650. var tmp = c.getTemp(intType)
  1651. c.gABx(n, opcLdImmInt, tmp, n.len)
  1652. c.gABx(n, opcNewSeq, dest, c.genType(seqType))
  1653. c.gABx(n, opcNewSeq, tmp, 0)
  1654. c.freeTemp(tmp)
  1655. if n.len > 0:
  1656. var tmp = getTemp(c, intType)
  1657. c.gABx(n, opcLdNullReg, tmp, c.genType(intType))
  1658. for x in n:
  1659. let a = c.genx(x)
  1660. c.preventFalseAlias(n, whichAsgnOpc(x, opcWrArr), dest, tmp, a)
  1661. c.gABI(n, opcAddImmInt, tmp, tmp, 1)
  1662. c.freeTemp(a)
  1663. c.freeTemp(tmp)
  1664. proc genSetConstr(c: PCtx, n: PNode, dest: var TDest) =
  1665. if dest < 0: dest = c.getTemp(n.typ)
  1666. c.gABx(n, opcLdNull, dest, c.genType(n.typ))
  1667. for x in n:
  1668. if x.kind == nkRange:
  1669. let a = c.genx(x.sons[0])
  1670. let b = c.genx(x.sons[1])
  1671. c.gABC(n, opcInclRange, dest, a, b)
  1672. c.freeTemp(b)
  1673. c.freeTemp(a)
  1674. else:
  1675. let a = c.genx(x)
  1676. c.gABC(n, opcIncl, dest, a)
  1677. c.freeTemp(a)
  1678. proc genObjConstr(c: PCtx, n: PNode, dest: var TDest) =
  1679. if dest < 0: dest = c.getTemp(n.typ)
  1680. let t = n.typ.skipTypes(abstractRange-{tyTypeDesc})
  1681. if t.kind == tyRef:
  1682. c.gABx(n, opcNew, dest, c.genType(t.sons[0]))
  1683. else:
  1684. c.gABx(n, opcLdNull, dest, c.genType(n.typ))
  1685. for i in 1..<n.len:
  1686. let it = n.sons[i]
  1687. if it.kind == nkExprColonExpr and it.sons[0].kind == nkSym:
  1688. let idx = genField(c, it.sons[0])
  1689. let tmp = c.genx(it.sons[1])
  1690. c.preventFalseAlias(it.sons[1], whichAsgnOpc(it.sons[1], opcWrObj),
  1691. dest, idx, tmp)
  1692. c.freeTemp(tmp)
  1693. else:
  1694. globalError(c.config, n.info, "invalid object constructor")
  1695. proc genTupleConstr(c: PCtx, n: PNode, dest: var TDest) =
  1696. if dest < 0: dest = c.getTemp(n.typ)
  1697. c.gABx(n, opcLdNull, dest, c.genType(n.typ))
  1698. # XXX x = (x.old, 22) produces wrong code ... stupid self assignments
  1699. for i in 0..<n.len:
  1700. let it = n.sons[i]
  1701. if it.kind == nkExprColonExpr:
  1702. let idx = genField(c, it.sons[0])
  1703. let tmp = c.genx(it.sons[1])
  1704. c.preventFalseAlias(it.sons[1], whichAsgnOpc(it.sons[1], opcWrObj),
  1705. dest, idx, tmp)
  1706. c.freeTemp(tmp)
  1707. else:
  1708. let tmp = c.genx(it)
  1709. c.preventFalseAlias(it, whichAsgnOpc(it, opcWrObj), dest, i.TRegister, tmp)
  1710. c.freeTemp(tmp)
  1711. proc genProc*(c: PCtx; s: PSym): int
  1712. proc matches(s: PSym; x: string): bool =
  1713. let y = x.split('.')
  1714. var s = s
  1715. var L = y.len-1
  1716. while L >= 0:
  1717. if s == nil or (y[L].cmpIgnoreStyle(s.name.s) != 0 and y[L] != "*"):
  1718. return false
  1719. s = s.owner
  1720. dec L
  1721. result = true
  1722. proc matches(s: PSym; y: varargs[string]): bool =
  1723. var s = s
  1724. var L = y.len-1
  1725. while L >= 0:
  1726. if s == nil or (y[L].cmpIgnoreStyle(s.name.s) != 0 and y[L] != "*"):
  1727. return false
  1728. s = if sfFromGeneric in s.flags: s.owner.owner else: s.owner
  1729. dec L
  1730. result = true
  1731. proc procIsCallback(c: PCtx; s: PSym): bool =
  1732. if s.offset < -1: return true
  1733. var i = -2
  1734. for key, value in items(c.callbacks):
  1735. if s.matches(key):
  1736. doAssert s.offset == -1
  1737. s.offset = i
  1738. return true
  1739. dec i
  1740. proc gen(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags = {}) =
  1741. case n.kind
  1742. of nkSym:
  1743. let s = n.sym
  1744. checkCanEval(c, n)
  1745. case s.kind
  1746. of skVar, skForVar, skTemp, skLet, skParam, skResult:
  1747. genRdVar(c, n, dest, flags)
  1748. of skProc, skFunc, skConverter, skMacro, skTemplate, skMethod, skIterator:
  1749. # 'skTemplate' is only allowed for 'getAst' support:
  1750. if procIsCallback(c, s): discard
  1751. elif sfImportc in s.flags: c.importcSym(n.info, s)
  1752. genLit(c, n, dest)
  1753. of skConst:
  1754. let constVal = if s.ast != nil: s.ast else: s.typ.n
  1755. gen(c, constVal, dest)
  1756. of skEnumField:
  1757. # we never reach this case - as of the time of this comment,
  1758. # skEnumField is folded to an int in semfold.nim, but this code
  1759. # remains for robustness
  1760. if dest < 0: dest = c.getTemp(n.typ)
  1761. if s.position >= low(int16) and s.position <= high(int16):
  1762. c.gABx(n, opcLdImmInt, dest, s.position)
  1763. else:
  1764. var lit = genLiteral(c, newIntNode(nkIntLit, s.position))
  1765. c.gABx(n, opcLdConst, dest, lit)
  1766. of skType:
  1767. genTypeLit(c, s.typ, dest)
  1768. of skGenericParam:
  1769. if c.prc.sym != nil and c.prc.sym.kind == skMacro:
  1770. genRdVar(c, n, dest, flags)
  1771. else:
  1772. globalError(c.config, n.info, "cannot generate code for: " & s.name.s)
  1773. else:
  1774. globalError(c.config, n.info, "cannot generate code for: " & s.name.s)
  1775. of nkCallKinds:
  1776. if n.sons[0].kind == nkSym:
  1777. let s = n.sons[0].sym
  1778. if s.magic != mNone:
  1779. genMagic(c, n, dest, s.magic)
  1780. elif s.kind == skMethod:
  1781. localError(c.config, n.info, "cannot call method " & s.name.s &
  1782. " at compile time")
  1783. elif matches(s, "stdlib", "marshal", "to"):
  1784. # XXX marshal load&store should not be opcodes, but use the
  1785. # general callback mechanisms.
  1786. genMarshalLoad(c, n, dest)
  1787. elif matches(s, "stdlib", "marshal", "$$"):
  1788. genMarshalStore(c, n, dest)
  1789. else:
  1790. genCall(c, n, dest)
  1791. clearDest(c, n, dest)
  1792. else:
  1793. genCall(c, n, dest)
  1794. clearDest(c, n, dest)
  1795. of nkCharLit..nkInt64Lit:
  1796. if isInt16Lit(n):
  1797. if dest < 0: dest = c.getTemp(n.typ)
  1798. c.gABx(n, opcLdImmInt, dest, n.intVal.int)
  1799. else:
  1800. genLit(c, n, dest)
  1801. of nkUIntLit..pred(nkNilLit): genLit(c, n, dest)
  1802. of nkNilLit:
  1803. if not n.typ.isEmptyType: genLit(c, getNullValue(n.typ, n.info, c.config), dest)
  1804. else: unused(c, n, dest)
  1805. of nkAsgn, nkFastAsgn:
  1806. unused(c, n, dest)
  1807. genAsgn(c, n.sons[0], n.sons[1], n.kind == nkAsgn)
  1808. of nkDotExpr: genObjAccess(c, n, dest, flags)
  1809. of nkCheckedFieldExpr: genCheckedObjAccess(c, n, dest, flags)
  1810. of nkBracketExpr: genArrAccess(c, n, dest, flags)
  1811. of nkDerefExpr, nkHiddenDeref: genDeref(c, n, dest, flags)
  1812. of nkAddr, nkHiddenAddr: genAddr(c, n, dest, flags)
  1813. of nkIfStmt, nkIfExpr: genIf(c, n, dest)
  1814. of nkWhenStmt:
  1815. # This is "when nimvm" node. Chose the first branch.
  1816. gen(c, n.sons[0].sons[1], dest)
  1817. of nkCaseStmt: genCase(c, n, dest)
  1818. of nkWhileStmt:
  1819. unused(c, n, dest)
  1820. genWhile(c, n)
  1821. of nkBlockExpr, nkBlockStmt: genBlock(c, n, dest)
  1822. of nkReturnStmt:
  1823. unused(c, n, dest)
  1824. genReturn(c, n)
  1825. of nkRaiseStmt:
  1826. genRaise(c, n)
  1827. of nkBreakStmt:
  1828. unused(c, n, dest)
  1829. genBreak(c, n)
  1830. of nkTryStmt: genTry(c, n, dest)
  1831. of nkStmtList:
  1832. #unused(c, n, dest)
  1833. # XXX Fix this bug properly, lexim triggers it
  1834. for x in n: gen(c, x)
  1835. of nkStmtListExpr:
  1836. let L = n.len-1
  1837. for i in 0 ..< L: gen(c, n.sons[i])
  1838. gen(c, n.sons[L], dest, flags)
  1839. of nkPragmaBlock:
  1840. gen(c, n.lastSon, dest, flags)
  1841. of nkDiscardStmt:
  1842. unused(c, n, dest)
  1843. gen(c, n.sons[0])
  1844. of nkHiddenStdConv, nkHiddenSubConv, nkConv:
  1845. genConv(c, n, n.sons[1], dest)
  1846. of nkObjDownConv:
  1847. genConv(c, n, n.sons[0], dest)
  1848. of nkVarSection, nkLetSection:
  1849. unused(c, n, dest)
  1850. genVarSection(c, n)
  1851. of declarativeDefs, nkMacroDef:
  1852. unused(c, n, dest)
  1853. of nkLambdaKinds:
  1854. #let s = n.sons[namePos].sym
  1855. #discard genProc(c, s)
  1856. genLit(c, newSymNode(n.sons[namePos].sym), dest)
  1857. of nkChckRangeF, nkChckRange64, nkChckRange:
  1858. let
  1859. tmp0 = c.genx(n.sons[0])
  1860. tmp1 = c.genx(n.sons[1])
  1861. tmp2 = c.genx(n.sons[2])
  1862. c.gABC(n, opcRangeChck, tmp0, tmp1, tmp2)
  1863. c.freeTemp(tmp1)
  1864. c.freeTemp(tmp2)
  1865. if dest >= 0:
  1866. gABC(c, n, whichAsgnOpc(n), dest, tmp0, 1)
  1867. c.freeTemp(tmp0)
  1868. else:
  1869. dest = tmp0
  1870. of nkEmpty, nkCommentStmt, nkTypeSection, nkConstSection, nkPragma,
  1871. nkTemplateDef, nkIncludeStmt, nkImportStmt, nkFromStmt, nkExportStmt:
  1872. unused(c, n, dest)
  1873. of nkStringToCString, nkCStringToString:
  1874. gen(c, n.sons[0], dest)
  1875. of nkBracket: genArrayConstr(c, n, dest)
  1876. of nkCurly: genSetConstr(c, n, dest)
  1877. of nkObjConstr: genObjConstr(c, n, dest)
  1878. of nkPar, nkClosure, nkTupleConstr: genTupleConstr(c, n, dest)
  1879. of nkCast:
  1880. if allowCast in c.features:
  1881. genConv(c, n, n.sons[1], dest, opcCast)
  1882. else:
  1883. genCastIntFloat(c, n, dest)
  1884. of nkTypeOfExpr:
  1885. genTypeLit(c, n.typ, dest)
  1886. of nkComesFrom:
  1887. discard "XXX to implement for better stack traces"
  1888. else:
  1889. globalError(c.config, n.info, "cannot generate VM code for " & $n)
  1890. proc removeLastEof(c: PCtx) =
  1891. let last = c.code.len-1
  1892. if last >= 0 and c.code[last].opcode == opcEof:
  1893. # overwrite last EOF:
  1894. assert c.code.len == c.debug.len
  1895. c.code.setLen(last)
  1896. c.debug.setLen(last)
  1897. proc genStmt*(c: PCtx; n: PNode): int =
  1898. c.removeLastEof
  1899. result = c.code.len
  1900. var d: TDest = -1
  1901. c.gen(n, d)
  1902. c.gABC(n, opcEof)
  1903. if d >= 0:
  1904. globalError(c.config, n.info, "VM problem: dest register is set")
  1905. proc genExpr*(c: PCtx; n: PNode, requiresValue = true): int =
  1906. c.removeLastEof
  1907. result = c.code.len
  1908. var d: TDest = -1
  1909. c.gen(n, d)
  1910. if d < 0:
  1911. if requiresValue:
  1912. globalError(c.config, n.info, "VM problem: dest register is not set")
  1913. d = 0
  1914. c.gABC(n, opcEof, d)
  1915. #echo renderTree(n)
  1916. #c.echoCode(result)
  1917. proc genParams(c: PCtx; params: PNode) =
  1918. # res.sym.position is already 0
  1919. c.prc.slots[0] = (inUse: true, kind: slotFixedVar)
  1920. for i in 1..<params.len:
  1921. c.prc.slots[i] = (inUse: true, kind: slotFixedLet)
  1922. c.prc.maxSlots = max(params.len, 1)
  1923. proc finalJumpTarget(c: PCtx; pc, diff: int) =
  1924. internalAssert(c.config, -0x7fff < diff and diff < 0x7fff)
  1925. let oldInstr = c.code[pc]
  1926. # opcode and regA stay the same:
  1927. c.code[pc] = ((oldInstr.uint32 and 0xffff'u32).uint32 or
  1928. uint32(diff+wordExcess) shl 16'u32).TInstr
  1929. proc genGenericParams(c: PCtx; gp: PNode) =
  1930. var base = c.prc.maxSlots
  1931. for i in 0..<gp.len:
  1932. var param = gp.sons[i].sym
  1933. param.position = base + i # XXX: fix this earlier; make it consistent with templates
  1934. c.prc.slots[base + i] = (inUse: true, kind: slotFixedLet)
  1935. c.prc.maxSlots = base + gp.len
  1936. proc optimizeJumps(c: PCtx; start: int) =
  1937. const maxIterations = 10
  1938. for i in start ..< c.code.len:
  1939. let opc = c.code[i].opcode
  1940. case opc
  1941. of opcTJmp, opcFJmp:
  1942. var reg = c.code[i].regA
  1943. var d = i + c.code[i].jmpDiff
  1944. for iters in countdown(maxIterations, 0):
  1945. case c.code[d].opcode
  1946. of opcJmp, opcJmpBack:
  1947. d = d + c.code[d].jmpDiff
  1948. of opcTJmp, opcFJmp:
  1949. if c.code[d].regA != reg: break
  1950. # tjmp x, 23
  1951. # ...
  1952. # tjmp x, 12
  1953. # -- we know 'x' is true, and so can jump to 12+13:
  1954. if c.code[d].opcode == opc:
  1955. d = d + c.code[d].jmpDiff
  1956. else:
  1957. # tjmp x, 23
  1958. # fjmp x, 22
  1959. # We know 'x' is true so skip to the next instruction:
  1960. d = d + 1
  1961. else: break
  1962. if d != i + c.code[i].jmpDiff:
  1963. c.finalJumpTarget(i, d - i)
  1964. of opcJmp, opcJmpBack:
  1965. var d = i + c.code[i].jmpDiff
  1966. var iters = maxIterations
  1967. while c.code[d].opcode == opcJmp and iters > 0:
  1968. d = d + c.code[d].jmpDiff
  1969. dec iters
  1970. if c.code[d].opcode == opcRet:
  1971. # optimize 'jmp to ret' to 'ret' here
  1972. c.code[i] = c.code[d]
  1973. elif d != i + c.code[i].jmpDiff:
  1974. c.finalJumpTarget(i, d - i)
  1975. else: discard
  1976. proc genProc(c: PCtx; s: PSym): int =
  1977. var x = s.ast.sons[miscPos]
  1978. if x.kind == nkEmpty or x[0].kind == nkEmpty:
  1979. #if s.name.s == "outterMacro" or s.name.s == "innerProc":
  1980. # echo "GENERATING CODE FOR ", s.name.s
  1981. let last = c.code.len-1
  1982. var eofInstr: TInstr
  1983. if last >= 0 and c.code[last].opcode == opcEof:
  1984. eofInstr = c.code[last]
  1985. c.code.setLen(last)
  1986. c.debug.setLen(last)
  1987. #c.removeLastEof
  1988. result = c.code.len+1 # skip the jump instruction
  1989. if x.kind == nkEmpty:
  1990. x = newTree(nkBracket, newIntNode(nkIntLit, result), x)
  1991. else:
  1992. x.sons[0] = newIntNode(nkIntLit, result)
  1993. s.ast.sons[miscPos] = x
  1994. # thanks to the jmp we can add top level statements easily and also nest
  1995. # procs easily:
  1996. let body = transformBody(c.graph, s, cache = not isCompileTimeProc(s),
  1997. noDestructors = true)
  1998. let procStart = c.xjmp(body, opcJmp, 0)
  1999. var p = PProc(blocks: @[], sym: s)
  2000. let oldPrc = c.prc
  2001. c.prc = p
  2002. # iterate over the parameters and allocate space for them:
  2003. genParams(c, s.typ.n)
  2004. # allocate additional space for any generically bound parameters
  2005. if s.kind == skMacro and
  2006. sfImmediate notin s.flags and
  2007. s.ast[genericParamsPos].kind != nkEmpty:
  2008. genGenericParams(c, s.ast[genericParamsPos])
  2009. if tfCapturesEnv in s.typ.flags:
  2010. #let env = s.ast.sons[paramsPos].lastSon.sym
  2011. #assert env.position == 2
  2012. c.prc.slots[c.prc.maxSlots] = (inUse: true, kind: slotFixedLet)
  2013. inc c.prc.maxSlots
  2014. gen(c, body)
  2015. # generate final 'return' statement:
  2016. c.gABC(body, opcRet)
  2017. c.patch(procStart)
  2018. c.gABC(body, opcEof, eofInstr.regA)
  2019. c.optimizeJumps(result)
  2020. s.offset = c.prc.maxSlots
  2021. #if s.name.s == "calc":
  2022. # echo renderTree(body)
  2023. # c.echoCode(result)
  2024. c.prc = oldPrc
  2025. else:
  2026. c.prc.maxSlots = s.offset
  2027. result = x[0].intVal.int