ccgexprs.nim 112 KB

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