ast.nim 79 KB

12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970717273747576777879808182838485868788899091929394959697989910010110210310410510610710810911011111211311411511611711811912012112212312412512612712812913013113213313413513613713813914014114214314414514614714814915015115215315415515615715815916016116216316416516616716816917017117217317417517617717817918018118218318418518618718818919019119219319419519619719819920020120220320420520620720820921021121221321421521621721821922022122222322422522622722822923023123223323423523623723823924024124224324424524624724824925025125225325425525625725825926026126226326426526626726826927027127227327427527627727827928028128228328428528628728828929029129229329429529629729829930030130230330430530630730830931031131231331431531631731831932032132232332432532632732832933033133233333433533633733833934034134234334434534634734834935035135235335435535635735835936036136236336436536636736836937037137237337437537637737837938038138238338438538638738838939039139239339439539639739839940040140240340440540640740840941041141241341441541641741841942042142242342442542642742842943043143243343443543643743843944044144244344444544644744844945045145245345445545645745845946046146246346446546646746846947047147247347447547647747847948048148248348448548648748848949049149249349449549649749849950050150250350450550650750850951051151251351451551651751851952052152252352452552652752852953053153253353453553653753853954054154254354454554654754854955055155255355455555655755855956056156256356456556656756856957057157257357457557657757857958058158258358458558658758858959059159259359459559659759859960060160260360460560660760860961061161261361461561661761861962062162262362462562662762862963063163263363463563663763863964064164264364464564664764864965065165265365465565665765865966066166266366466566666766866967067167267367467567667767867968068168268368468568668768868969069169269369469569669769869970070170270370470570670770870971071171271371471571671771871972072172272372472572672772872973073173273373473573673773873974074174274374474574674774874975075175275375475575675775875976076176276376476576676776876977077177277377477577677777877978078178278378478578678778878979079179279379479579679779879980080180280380480580680780880981081181281381481581681781881982082182282382482582682782882983083183283383483583683783883984084184284384484584684784884985085185285385485585685785885986086186286386486586686786886987087187287387487587687787887988088188288388488588688788888989089189289389489589689789889990090190290390490590690790890991091191291391491591691791891992092192292392492592692792892993093193293393493593693793893994094194294394494594694794894995095195295395495595695795895996096196296396496596696796896997097197297397497597697797897998098198298398498598698798898999099199299399499599699799899910001001100210031004100510061007100810091010101110121013101410151016101710181019102010211022102310241025102610271028102910301031103210331034103510361037103810391040104110421043104410451046104710481049105010511052105310541055105610571058105910601061106210631064106510661067106810691070107110721073107410751076107710781079108010811082108310841085108610871088108910901091109210931094109510961097109810991100110111021103110411051106110711081109111011111112111311141115111611171118111911201121112211231124112511261127112811291130113111321133113411351136113711381139114011411142114311441145114611471148114911501151115211531154115511561157115811591160116111621163116411651166116711681169117011711172117311741175117611771178117911801181118211831184118511861187118811891190119111921193119411951196119711981199120012011202120312041205120612071208120912101211121212131214121512161217121812191220122112221223122412251226122712281229123012311232123312341235123612371238123912401241124212431244124512461247124812491250125112521253125412551256125712581259126012611262126312641265126612671268126912701271127212731274127512761277127812791280128112821283128412851286128712881289129012911292129312941295129612971298129913001301130213031304130513061307130813091310131113121313131413151316131713181319132013211322132313241325132613271328132913301331133213331334133513361337133813391340134113421343134413451346134713481349135013511352135313541355135613571358135913601361136213631364136513661367136813691370137113721373137413751376137713781379138013811382138313841385138613871388138913901391139213931394139513961397139813991400140114021403140414051406140714081409141014111412141314141415141614171418141914201421142214231424142514261427142814291430143114321433143414351436143714381439144014411442144314441445144614471448144914501451145214531454145514561457145814591460146114621463146414651466146714681469147014711472147314741475147614771478147914801481148214831484148514861487148814891490149114921493149414951496149714981499150015011502150315041505150615071508150915101511151215131514151515161517151815191520152115221523152415251526152715281529153015311532153315341535153615371538153915401541154215431544154515461547154815491550155115521553155415551556155715581559156015611562156315641565156615671568156915701571157215731574157515761577157815791580158115821583158415851586158715881589159015911592159315941595159615971598159916001601160216031604160516061607160816091610161116121613161416151616161716181619162016211622162316241625162616271628162916301631163216331634163516361637163816391640164116421643164416451646164716481649165016511652165316541655165616571658165916601661166216631664166516661667166816691670167116721673167416751676167716781679168016811682168316841685168616871688168916901691169216931694169516961697169816991700170117021703170417051706170717081709171017111712171317141715171617171718171917201721172217231724172517261727172817291730173117321733173417351736173717381739174017411742174317441745174617471748174917501751175217531754175517561757175817591760176117621763176417651766176717681769177017711772177317741775177617771778177917801781178217831784178517861787178817891790179117921793179417951796179717981799180018011802180318041805180618071808180918101811181218131814181518161817181818191820182118221823182418251826182718281829183018311832183318341835183618371838183918401841184218431844184518461847184818491850185118521853185418551856185718581859186018611862186318641865186618671868186918701871187218731874187518761877187818791880188118821883188418851886188718881889189018911892189318941895189618971898189919001901190219031904190519061907190819091910191119121913191419151916191719181919192019211922192319241925192619271928192919301931193219331934193519361937193819391940194119421943194419451946194719481949195019511952195319541955195619571958195919601961196219631964196519661967196819691970197119721973197419751976197719781979198019811982198319841985198619871988198919901991199219931994199519961997199819992000200120022003200420052006200720082009201020112012201320142015201620172018201920202021202220232024202520262027202820292030203120322033203420352036203720382039204020412042204320442045204620472048204920502051205220532054205520562057205820592060206120622063206420652066206720682069207020712072207320742075207620772078207920802081208220832084208520862087208820892090209120922093209420952096209720982099210021012102210321042105210621072108210921102111211221132114211521162117211821192120212121222123212421252126212721282129213021312132213321342135213621372138213921402141214221432144214521462147
  1. #
  2. #
  3. # The Nim Compiler
  4. # (c) Copyright 2015 Andreas Rumpf
  5. #
  6. # See the file "copying.txt", included in this
  7. # distribution, for details about the copyright.
  8. #
  9. # abstract syntax tree + symbol table
  10. import
  11. lineinfos, options, ropes, idents, int128, wordrecg
  12. import std/[tables, hashes]
  13. from std/strutils import toLowerAscii
  14. when defined(nimPreviewSlimSystem):
  15. import std/assertions
  16. export int128
  17. import nodekinds
  18. export nodekinds
  19. type
  20. TCallingConvention* = enum
  21. ccNimCall = "nimcall" # nimcall, also the default
  22. ccStdCall = "stdcall" # procedure is stdcall
  23. ccCDecl = "cdecl" # cdecl
  24. ccSafeCall = "safecall" # safecall
  25. ccSysCall = "syscall" # system call
  26. ccInline = "inline" # proc should be inlined
  27. ccNoInline = "noinline" # proc should not be inlined
  28. ccFastCall = "fastcall" # fastcall (pass parameters in registers)
  29. ccThisCall = "thiscall" # thiscall (parameters are pushed right-to-left)
  30. ccClosure = "closure" # proc has a closure
  31. ccNoConvention = "noconv" # needed for generating proper C procs sometimes
  32. ccMember = "member" # proc is a (cpp) member
  33. TNodeKinds* = set[TNodeKind]
  34. type
  35. TSymFlag* = enum # 63 flags!
  36. sfUsed, # read access of sym (for warnings) or simply used
  37. sfExported, # symbol is exported from module
  38. sfFromGeneric, # symbol is instantiation of a generic; this is needed
  39. # for symbol file generation; such symbols should always
  40. # be written into the ROD file
  41. sfGlobal, # symbol is at global scope
  42. sfForward, # symbol is forward declared
  43. sfWasForwarded, # symbol had a forward declaration
  44. # (implies it's too dangerous to patch its type signature)
  45. sfImportc, # symbol is external; imported
  46. sfExportc, # symbol is exported (under a specified name)
  47. sfMangleCpp, # mangle as cpp (combines with `sfExportc`)
  48. sfVolatile, # variable is volatile
  49. sfRegister, # variable should be placed in a register
  50. sfPure, # object is "pure" that means it has no type-information
  51. # enum is "pure", its values need qualified access
  52. # variable is "pure"; it's an explicit "global"
  53. sfNoSideEffect, # proc has no side effects
  54. sfSideEffect, # proc may have side effects; cannot prove it has none
  55. sfMainModule, # module is the main module
  56. sfSystemModule, # module is the system module
  57. sfNoReturn, # proc never returns (an exit proc)
  58. sfAddrTaken, # the variable's address is taken (ex- or implicitly);
  59. # *OR*: a proc is indirectly called (used as first class)
  60. sfCompilerProc, # proc is a compiler proc, that is a C proc that is
  61. # needed for the code generator
  62. sfEscapes # param escapes
  63. # currently unimplemented
  64. sfDiscriminant, # field is a discriminant in a record/object
  65. sfRequiresInit, # field must be initialized during construction
  66. sfDeprecated, # symbol is deprecated
  67. sfExplain, # provide more diagnostics when this symbol is used
  68. sfError, # usage of symbol should trigger a compile-time error
  69. sfShadowed, # a symbol that was shadowed in some inner scope
  70. sfThread, # proc will run as a thread
  71. # variable is a thread variable
  72. sfCppNonPod, # tells compiler to treat such types as non-pod's, so that
  73. # `thread_local` is used instead of `__thread` for
  74. # {.threadvar.} + `--threads`. Only makes sense for importcpp types.
  75. # This has a performance impact so isn't set by default.
  76. sfCompileTime, # proc can be evaluated at compile time
  77. sfConstructor, # proc is a C++ constructor
  78. sfDispatcher, # copied method symbol is the dispatcher
  79. # deprecated and unused, except for the con
  80. sfBorrow, # proc is borrowed
  81. sfInfixCall, # symbol needs infix call syntax in target language;
  82. # for interfacing with C++, JS
  83. sfNamedParamCall, # symbol needs named parameter call syntax in target
  84. # language; for interfacing with Objective C
  85. sfDiscardable, # returned value may be discarded implicitly
  86. sfOverridden, # proc is overridden
  87. sfCallsite # A flag for template symbols to tell the
  88. # compiler it should use line information from
  89. # the calling side of the macro, not from the
  90. # implementation.
  91. sfGenSym # symbol is 'gensym'ed; do not add to symbol table
  92. sfNonReloadable # symbol will be left as-is when hot code reloading is on -
  93. # meaning that it won't be renamed and/or changed in any way
  94. sfGeneratedOp # proc is a generated '='; do not inject destructors in it
  95. # variable is generated closure environment; requires early
  96. # destruction for --newruntime.
  97. sfTemplateParam # symbol is a template parameter
  98. sfCursor # variable/field is a cursor, see RFC 177 for details
  99. sfInjectDestructors # whether the proc needs the 'injectdestructors' transformation
  100. sfNeverRaises # proc can never raise an exception, not even OverflowDefect
  101. # or out-of-memory
  102. sfSystemRaisesDefect # proc in the system can raise defects
  103. sfUsedInFinallyOrExcept # symbol is used inside an 'except' or 'finally'
  104. sfSingleUsedTemp # For temporaries that we know will only be used once
  105. sfNoalias # 'noalias' annotation, means C's 'restrict'
  106. # for templates and macros, means cannot be called
  107. # as a lone symbol (cannot use alias syntax)
  108. sfEffectsDelayed # an 'effectsDelayed' parameter
  109. sfGeneratedType # A anonymous generic type that is generated by the compiler for
  110. # objects that do not have generic parameters in case one of the
  111. # object fields has one.
  112. #
  113. # This is disallowed but can cause the typechecking to go into
  114. # an infinite loop, this flag is used as a sentinel to stop it.
  115. sfVirtual # proc is a C++ virtual function
  116. sfByCopy # param is marked as pass bycopy
  117. sfMember # proc is a C++ member of a type
  118. sfCodegenDecl # type, proc, global or proc param is marked as codegenDecl
  119. sfWasGenSym # symbol was 'gensym'ed
  120. sfForceLift # variable has to be lifted into closure environment
  121. sfDirty # template is not hygienic (old styled template) module,
  122. # compiled from a dirty-buffer
  123. sfCustomPragma # symbol is custom pragma template
  124. sfBase, # a base method
  125. sfGoto # var is used for 'goto' code generation
  126. sfAnon, # symbol name that was generated by the compiler
  127. # the compiler will avoid printing such names
  128. # in user messages.
  129. sfAllUntyped # macro or template is immediately expanded in a generic context
  130. sfTemplateRedefinition # symbol is a redefinition of an earlier template
  131. TSymFlags* = set[TSymFlag]
  132. const
  133. sfNoInit* = sfMainModule # don't generate code to init the variable
  134. sfNoForward* = sfRegister
  135. # forward declarations are not required (per module)
  136. sfReorder* = sfForward
  137. # reordering pass is enabled
  138. sfCompileToCpp* = sfInfixCall # compile the module as C++ code
  139. sfCompileToObjc* = sfNamedParamCall # compile the module as Objective-C code
  140. sfExperimental* = sfOverridden # module uses the .experimental switch
  141. sfWrittenTo* = sfBorrow # param is assigned to
  142. # currently unimplemented
  143. sfCppMember* = { sfVirtual, sfMember, sfConstructor } # proc is a C++ member, meaning it will be attached to the type definition
  144. const
  145. # getting ready for the future expr/stmt merge
  146. nkWhen* = nkWhenStmt
  147. nkWhenExpr* = nkWhenStmt
  148. nkEffectList* = nkArgList
  149. # hacks ahead: an nkEffectList is a node with 4 children:
  150. exceptionEffects* = 0 # exceptions at position 0
  151. requiresEffects* = 1 # 'requires' annotation
  152. ensuresEffects* = 2 # 'ensures' annotation
  153. tagEffects* = 3 # user defined tag ('gc', 'time' etc.)
  154. pragmasEffects* = 4 # not an effect, but a slot for pragmas in proc type
  155. forbiddenEffects* = 5 # list of illegal effects
  156. effectListLen* = 6 # list of effects list
  157. nkLastBlockStmts* = {nkRaiseStmt, nkReturnStmt, nkBreakStmt, nkContinueStmt}
  158. # these must be last statements in a block
  159. type
  160. TTypeKind* = enum # order is important!
  161. # Don't forget to change hti.nim if you make a change here
  162. # XXX put this into an include file to avoid this issue!
  163. # several types are no longer used (guess which), but a
  164. # spot in the sequence is kept for backwards compatibility
  165. # (apparently something with bootstrapping)
  166. # if you need to add a type, they can apparently be reused
  167. tyNone, tyBool, tyChar,
  168. tyEmpty, tyAlias, tyNil, tyUntyped, tyTyped, tyTypeDesc,
  169. tyGenericInvocation, # ``T[a, b]`` for types to invoke
  170. tyGenericBody, # ``T[a, b, body]`` last parameter is the body
  171. tyGenericInst, # ``T[a, b, realInstance]`` instantiated generic type
  172. # realInstance will be a concrete type like tyObject
  173. # unless this is an instance of a generic alias type.
  174. # then realInstance will be the tyGenericInst of the
  175. # completely (recursively) resolved alias.
  176. tyGenericParam, # ``a`` in the above patterns
  177. tyDistinct,
  178. tyEnum,
  179. tyOrdinal, # integer types (including enums and boolean)
  180. tyArray,
  181. tyObject,
  182. tyTuple,
  183. tySet,
  184. tyRange,
  185. tyPtr, tyRef,
  186. tyVar,
  187. tySequence,
  188. tyProc,
  189. tyPointer, tyOpenArray,
  190. tyString, tyCstring, tyForward,
  191. tyInt, tyInt8, tyInt16, tyInt32, tyInt64, # signed integers
  192. tyFloat, tyFloat32, tyFloat64, tyFloat128,
  193. tyUInt, tyUInt8, tyUInt16, tyUInt32, tyUInt64,
  194. tyOwned, tySink, tyLent,
  195. tyVarargs,
  196. tyUncheckedArray
  197. # An array with boundaries [0,+∞]
  198. tyError # used as erroneous type (for idetools)
  199. # as an erroneous node should match everything
  200. tyBuiltInTypeClass
  201. # Type such as the catch-all object, tuple, seq, etc
  202. tyUserTypeClass
  203. # the body of a user-defined type class
  204. tyUserTypeClassInst
  205. # Instance of a parametric user-defined type class.
  206. # Structured similarly to tyGenericInst.
  207. # tyGenericInst represents concrete types, while
  208. # this is still a "generic param" that will bind types
  209. # and resolves them during sigmatch and instantiation.
  210. tyCompositeTypeClass
  211. # Type such as seq[Number]
  212. # The notes for tyUserTypeClassInst apply here as well
  213. # sons[0]: the original expression used by the user.
  214. # sons[1]: fully expanded and instantiated meta type
  215. # (potentially following aliases)
  216. tyInferred
  217. # In the initial state `base` stores a type class constraining
  218. # the types that can be inferred. After a candidate type is
  219. # selected, it's stored in `last`. Between `base` and `last`
  220. # there may be 0, 2 or more types that were also considered as
  221. # possible candidates in the inference process (i.e. last will
  222. # be updated to store a type best conforming to all candidates)
  223. tyAnd, tyOr, tyNot
  224. # boolean type classes such as `string|int`,`not seq`,
  225. # `Sortable and Enumable`, etc
  226. tyAnything
  227. # a type class matching any type
  228. tyStatic
  229. # a value known at compile type (the underlying type is .base)
  230. tyFromExpr
  231. # This is a type representing an expression that depends
  232. # on generic parameters (the expression is stored in t.n)
  233. # It will be converted to a real type only during generic
  234. # instantiation and prior to this it has the potential to
  235. # be any type.
  236. tyConcept
  237. # new style concept.
  238. tyVoid
  239. # now different from tyEmpty, hurray!
  240. tyIterable
  241. static:
  242. # remind us when TTypeKind stops to fit in a single 64-bit word
  243. # assert TTypeKind.high.ord <= 63
  244. discard
  245. const
  246. tyPureObject* = tyTuple
  247. GcTypeKinds* = {tyRef, tySequence, tyString}
  248. tyTypeClasses* = {tyBuiltInTypeClass, tyCompositeTypeClass,
  249. tyUserTypeClass, tyUserTypeClassInst, tyConcept,
  250. tyAnd, tyOr, tyNot, tyAnything}
  251. tyMetaTypes* = {tyGenericParam, tyTypeDesc, tyUntyped} + tyTypeClasses
  252. tyUserTypeClasses* = {tyUserTypeClass, tyUserTypeClassInst}
  253. # consider renaming as `tyAbstractVarRange`
  254. abstractVarRange* = {tyGenericInst, tyRange, tyVar, tyDistinct, tyOrdinal,
  255. tyTypeDesc, tyAlias, tyInferred, tySink, tyOwned}
  256. abstractInst* = {tyGenericInst, tyDistinct, tyOrdinal, tyTypeDesc, tyAlias,
  257. tyInferred, tySink, tyOwned} # xxx what about tyStatic?
  258. type
  259. TTypeKinds* = set[TTypeKind]
  260. TNodeFlag* = enum
  261. nfNone,
  262. nfBase2, # nfBase10 is default, so not needed
  263. nfBase8,
  264. nfBase16,
  265. nfAllConst, # used to mark complex expressions constant; easy to get rid of
  266. # but unfortunately it has measurable impact for compilation
  267. # efficiency
  268. nfTransf, # node has been transformed
  269. nfNoRewrite # node should not be transformed anymore
  270. nfSem # node has been checked for semantics
  271. nfLL # node has gone through lambda lifting
  272. nfDotField # the call can use a dot operator
  273. nfDotSetter # the call can use a setter dot operarator
  274. nfExplicitCall # x.y() was used instead of x.y
  275. nfExprCall # this is an attempt to call a regular expression
  276. nfIsRef # this node is a 'ref' node; used for the VM
  277. nfIsPtr # this node is a 'ptr' node; used for the VM
  278. nfPreventCg # this node should be ignored by the codegen
  279. nfBlockArg # this a stmtlist appearing in a call (e.g. a do block)
  280. nfFromTemplate # a top-level node returned from a template
  281. nfDefaultParam # an automatically inserter default parameter
  282. nfDefaultRefsParam # a default param value references another parameter
  283. # the flag is applied to proc default values and to calls
  284. nfExecuteOnReload # A top-level statement that will be executed during reloads
  285. nfLastRead # this node is a last read
  286. nfFirstWrite # this node is a first write
  287. nfHasComment # node has a comment
  288. nfSkipFieldChecking # node skips field visable checking
  289. nfDisabledOpenSym # temporary: node should be nkOpenSym but cannot
  290. # because openSym experimental switch is disabled
  291. # gives warning instead
  292. TNodeFlags* = set[TNodeFlag]
  293. TTypeFlag* = enum # keep below 32 for efficiency reasons (now: 47)
  294. tfVarargs, # procedure has C styled varargs
  295. # tyArray type represeting a varargs list
  296. tfNoSideEffect, # procedure type does not allow side effects
  297. tfFinal, # is the object final?
  298. tfInheritable, # is the object inheritable?
  299. tfHasOwned, # type contains an 'owned' type and must be moved
  300. tfEnumHasHoles, # enum cannot be mapped into a range
  301. tfShallow, # type can be shallow copied on assignment
  302. tfThread, # proc type is marked as ``thread``; alias for ``gcsafe``
  303. tfFromGeneric, # type is an instantiation of a generic; this is needed
  304. # because for instantiations of objects, structural
  305. # type equality has to be used
  306. tfUnresolved, # marks unresolved typedesc/static params: e.g.
  307. # proc foo(T: typedesc, list: seq[T]): var T
  308. # proc foo(L: static[int]): array[L, int]
  309. # can be attached to ranges to indicate that the range
  310. # can be attached to generic procs with free standing
  311. # type parameters: e.g. proc foo[T]()
  312. # depends on unresolved static params.
  313. tfResolved # marks a user type class, after it has been bound to a
  314. # concrete type (lastSon becomes the concrete type)
  315. tfRetType, # marks return types in proc (used to detect type classes
  316. # used as return types for return type inference)
  317. tfCapturesEnv, # whether proc really captures some environment
  318. tfByCopy, # pass object/tuple by copy (C backend)
  319. tfByRef, # pass object/tuple by reference (C backend)
  320. tfIterator, # type is really an iterator, not a tyProc
  321. tfPartial, # type is declared as 'partial'
  322. tfNotNil, # type cannot be 'nil'
  323. tfRequiresInit, # type contains a "not nil" constraint somewhere or
  324. # a `requiresInit` field, so the default zero init
  325. # is not appropriate
  326. tfNeedsFullInit, # object type marked with {.requiresInit.}
  327. # all fields must be initialized
  328. tfVarIsPtr, # 'var' type is translated like 'ptr' even in C++ mode
  329. tfHasMeta, # type contains "wildcard" sub-types such as generic params
  330. # or other type classes
  331. tfHasGCedMem, # type contains GC'ed memory
  332. tfPacked
  333. tfHasStatic
  334. tfGenericTypeParam
  335. tfImplicitTypeParam
  336. tfInferrableStatic
  337. tfConceptMatchedTypeSym
  338. tfExplicit # for typedescs, marks types explicitly prefixed with the
  339. # `type` operator (e.g. type int)
  340. tfWildcard # consider a proc like foo[T, I](x: Type[T, I])
  341. # T and I here can bind to both typedesc and static types
  342. # before this is determined, we'll consider them to be a
  343. # wildcard type.
  344. tfHasAsgn # type has overloaded assignment operator
  345. tfBorrowDot # distinct type borrows '.'
  346. tfTriggersCompileTime # uses the NimNode type which make the proc
  347. # implicitly '.compiletime'
  348. tfRefsAnonObj # used for 'ref object' and 'ptr object'
  349. tfCovariant # covariant generic param mimicking a ptr type
  350. tfWeakCovariant # covariant generic param mimicking a seq/array type
  351. tfContravariant # contravariant generic param
  352. tfCheckedForDestructor # type was checked for having a destructor.
  353. # If it has one, t.destructor is not nil.
  354. tfAcyclic # object type was annotated as .acyclic
  355. tfIncompleteStruct # treat this type as if it had sizeof(pointer)
  356. tfCompleteStruct
  357. # (for importc types); type is fully specified, allowing to compute
  358. # sizeof, alignof, offsetof at CT
  359. tfExplicitCallConv
  360. tfIsConstructor
  361. tfEffectSystemWorkaround
  362. tfIsOutParam
  363. tfSendable
  364. tfImplicitStatic
  365. TTypeFlags* = set[TTypeFlag]
  366. TSymKind* = enum # the different symbols (start with the prefix sk);
  367. # order is important for the documentation generator!
  368. skUnknown, # unknown symbol: used for parsing assembler blocks
  369. # and first phase symbol lookup in generics
  370. skConditional, # symbol for the preprocessor (may become obsolete)
  371. skDynLib, # symbol represents a dynamic library; this is used
  372. # internally; it does not exist in Nim code
  373. skParam, # a parameter
  374. skGenericParam, # a generic parameter; eq in ``proc x[eq=`==`]()``
  375. skTemp, # a temporary variable (introduced by compiler)
  376. skModule, # module identifier
  377. skType, # a type
  378. skVar, # a variable
  379. skLet, # a 'let' symbol
  380. skConst, # a constant
  381. skResult, # special 'result' variable
  382. skProc, # a proc
  383. skFunc, # a func
  384. skMethod, # a method
  385. skIterator, # an iterator
  386. skConverter, # a type converter
  387. skMacro, # a macro
  388. skTemplate, # a template; currently also misused for user-defined
  389. # pragmas
  390. skField, # a field in a record or object
  391. skEnumField, # an identifier in an enum
  392. skForVar, # a for loop variable
  393. skLabel, # a label (for block statement)
  394. skStub, # symbol is a stub and not yet loaded from the ROD
  395. # file (it is loaded on demand, which may
  396. # mean: never)
  397. skPackage, # symbol is a package (used for canonicalization)
  398. TSymKinds* = set[TSymKind]
  399. const
  400. routineKinds* = {skProc, skFunc, skMethod, skIterator,
  401. skConverter, skMacro, skTemplate}
  402. ExportableSymKinds* = {skVar, skLet, skConst, skType, skEnumField, skStub} + routineKinds
  403. tfUnion* = tfNoSideEffect
  404. tfGcSafe* = tfThread
  405. tfObjHasKids* = tfEnumHasHoles
  406. tfReturnsNew* = tfInheritable
  407. tfNonConstExpr* = tfExplicitCallConv
  408. ## tyFromExpr where the expression shouldn't be evaluated as a static value
  409. tfGenericHasDestructor* = tfExplicitCallConv
  410. ## tyGenericBody where an instance has a generated destructor
  411. skError* = skUnknown
  412. var
  413. eqTypeFlags* = {tfIterator, tfNotNil, tfVarIsPtr, tfGcSafe, tfNoSideEffect, tfIsOutParam}
  414. ## type flags that are essential for type equality.
  415. ## This is now a variable because for emulation of version:1.0 we
  416. ## might exclude {tfGcSafe, tfNoSideEffect}.
  417. type
  418. TMagic* = enum # symbols that require compiler magic:
  419. mNone,
  420. mDefined, mDeclared, mDeclaredInScope, mCompiles, mArrGet, mArrPut, mAsgn,
  421. mLow, mHigh, mSizeOf, mAlignOf, mOffsetOf, mTypeTrait,
  422. mIs, mOf, mAddr, mType, mTypeOf,
  423. mPlugin, mEcho, mShallowCopy, mSlurp, mStaticExec, mStatic,
  424. mParseExprToAst, mParseStmtToAst, mExpandToAst, mQuoteAst,
  425. mInc, mDec, mOrd,
  426. mNew, mNewFinalize, mNewSeq, mNewSeqOfCap,
  427. mLengthOpenArray, mLengthStr, mLengthArray, mLengthSeq,
  428. mIncl, mExcl, mCard, mChr,
  429. mGCref, mGCunref,
  430. mAddI, mSubI, mMulI, mDivI, mModI,
  431. mSucc, mPred,
  432. mAddF64, mSubF64, mMulF64, mDivF64,
  433. mShrI, mShlI, mAshrI, mBitandI, mBitorI, mBitxorI,
  434. mMinI, mMaxI,
  435. mAddU, mSubU, mMulU, mDivU, mModU,
  436. mEqI, mLeI, mLtI,
  437. mEqF64, mLeF64, mLtF64,
  438. mLeU, mLtU,
  439. mEqEnum, mLeEnum, mLtEnum,
  440. mEqCh, mLeCh, mLtCh,
  441. mEqB, mLeB, mLtB,
  442. mEqRef, mLePtr, mLtPtr,
  443. mXor, mEqCString, mEqProc,
  444. mUnaryMinusI, mUnaryMinusI64, mAbsI, mNot,
  445. mUnaryPlusI, mBitnotI,
  446. mUnaryPlusF64, mUnaryMinusF64,
  447. mCharToStr, mBoolToStr,
  448. mCStrToStr,
  449. mStrToStr, mEnumToStr,
  450. mAnd, mOr,
  451. mImplies, mIff, mExists, mForall, mOld,
  452. mEqStr, mLeStr, mLtStr,
  453. mEqSet, mLeSet, mLtSet, mMulSet, mPlusSet, mMinusSet, mXorSet,
  454. mConStrStr, mSlice,
  455. mDotDot, # this one is only necessary to give nice compile time warnings
  456. mFields, mFieldPairs, mOmpParFor,
  457. mAppendStrCh, mAppendStrStr, mAppendSeqElem,
  458. mInSet, mRepr, mExit,
  459. mSetLengthStr, mSetLengthSeq,
  460. mIsPartOf, mAstToStr, mParallel,
  461. mSwap, mIsNil, mArrToSeq, mOpenArrayToSeq,
  462. mNewString, mNewStringOfCap, mParseBiggestFloat,
  463. mMove, mEnsureMove, mWasMoved, mDup, mDestroy, mTrace,
  464. mDefault, mUnown, mFinished, mIsolate, mAccessEnv, mAccessTypeField,
  465. mArray, mOpenArray, mRange, mSet, mSeq, mVarargs,
  466. mRef, mPtr, mVar, mDistinct, mVoid, mTuple,
  467. mOrdinal, mIterableType,
  468. mInt, mInt8, mInt16, mInt32, mInt64,
  469. mUInt, mUInt8, mUInt16, mUInt32, mUInt64,
  470. mFloat, mFloat32, mFloat64, mFloat128,
  471. mBool, mChar, mString, mCstring,
  472. mPointer, mNil, mExpr, mStmt, mTypeDesc,
  473. mVoidType, mPNimrodNode, mSpawn, mDeepCopy,
  474. mIsMainModule, mCompileDate, mCompileTime, mProcCall,
  475. mCpuEndian, mHostOS, mHostCPU, mBuildOS, mBuildCPU, mAppType,
  476. mCompileOption, mCompileOptionArg,
  477. mNLen, mNChild, mNSetChild, mNAdd, mNAddMultiple, mNDel,
  478. mNKind, mNSymKind,
  479. mNccValue, mNccInc, mNcsAdd, mNcsIncl, mNcsLen, mNcsAt,
  480. mNctPut, mNctLen, mNctGet, mNctHasNext, mNctNext,
  481. mNIntVal, mNFloatVal, mNSymbol, mNIdent, mNGetType, mNStrVal, mNSetIntVal,
  482. mNSetFloatVal, mNSetSymbol, mNSetIdent, mNSetStrVal, mNLineInfo,
  483. mNNewNimNode, mNCopyNimNode, mNCopyNimTree, mStrToIdent, mNSigHash, mNSizeOf,
  484. mNBindSym, mNCallSite,
  485. mEqIdent, mEqNimrodNode, mSameNodeType, mGetImpl, mNGenSym,
  486. mNHint, mNWarning, mNError,
  487. mInstantiationInfo, mGetTypeInfo, mGetTypeInfoV2,
  488. mNimvm, mIntDefine, mStrDefine, mBoolDefine, mGenericDefine, mRunnableExamples,
  489. mException, mBuiltinType, mSymOwner, mUncheckedArray, mGetImplTransf,
  490. mSymIsInstantiationOf, mNodeId, mPrivateAccess, mZeroDefault
  491. const
  492. # things that we can evaluate safely at compile time, even if not asked for it:
  493. ctfeWhitelist* = {mNone, mSucc,
  494. mPred, mInc, mDec, mOrd, mLengthOpenArray,
  495. mLengthStr, mLengthArray, mLengthSeq,
  496. mArrGet, mArrPut, mAsgn, mDestroy,
  497. mIncl, mExcl, mCard, mChr,
  498. mAddI, mSubI, mMulI, mDivI, mModI,
  499. mAddF64, mSubF64, mMulF64, mDivF64,
  500. mShrI, mShlI, mBitandI, mBitorI, mBitxorI,
  501. mMinI, mMaxI,
  502. mAddU, mSubU, mMulU, mDivU, mModU,
  503. mEqI, mLeI, mLtI,
  504. mEqF64, mLeF64, mLtF64,
  505. mLeU, mLtU,
  506. mEqEnum, mLeEnum, mLtEnum,
  507. mEqCh, mLeCh, mLtCh,
  508. mEqB, mLeB, mLtB,
  509. mEqRef, mEqProc, mLePtr, mLtPtr, mEqCString, mXor,
  510. mUnaryMinusI, mUnaryMinusI64, mAbsI, mNot, mUnaryPlusI, mBitnotI,
  511. mUnaryPlusF64, mUnaryMinusF64,
  512. mCharToStr, mBoolToStr,
  513. mCStrToStr,
  514. mStrToStr, mEnumToStr,
  515. mAnd, mOr,
  516. mEqStr, mLeStr, mLtStr,
  517. mEqSet, mLeSet, mLtSet, mMulSet, mPlusSet, mMinusSet, mXorSet,
  518. mConStrStr, mAppendStrCh, mAppendStrStr, mAppendSeqElem,
  519. mInSet, mRepr, mOpenArrayToSeq}
  520. generatedMagics* = {mNone, mIsolate, mFinished, mOpenArrayToSeq}
  521. ## magics that are generated as normal procs in the backend
  522. type
  523. ItemId* = object
  524. module*: int32
  525. item*: int32
  526. proc `$`*(x: ItemId): string =
  527. "(module: " & $x.module & ", item: " & $x.item & ")"
  528. proc `==`*(a, b: ItemId): bool {.inline.} =
  529. a.item == b.item and a.module == b.module
  530. proc hash*(x: ItemId): Hash =
  531. var h: Hash = hash(x.module)
  532. h = h !& hash(x.item)
  533. result = !$h
  534. type
  535. PNode* = ref TNode
  536. TNodeSeq* = seq[PNode]
  537. PType* = ref TType
  538. PSym* = ref TSym
  539. TNode*{.final, acyclic.} = object # on a 32bit machine, this takes 32 bytes
  540. when defined(useNodeIds):
  541. id*: int
  542. typField: PType
  543. info*: TLineInfo
  544. flags*: TNodeFlags
  545. case kind*: TNodeKind
  546. of nkCharLit..nkUInt64Lit:
  547. intVal*: BiggestInt
  548. of nkFloatLit..nkFloat128Lit:
  549. floatVal*: BiggestFloat
  550. of nkStrLit..nkTripleStrLit:
  551. strVal*: string
  552. of nkSym:
  553. sym*: PSym
  554. of nkIdent:
  555. ident*: PIdent
  556. else:
  557. sons*: TNodeSeq
  558. when defined(nimsuggest):
  559. endInfo*: TLineInfo
  560. TStrTable* = object # a table[PIdent] of PSym
  561. counter*: int
  562. data*: seq[PSym]
  563. # -------------- backend information -------------------------------
  564. TLocKind* = enum
  565. locNone, # no location
  566. locTemp, # temporary location
  567. locLocalVar, # location is a local variable
  568. locGlobalVar, # location is a global variable
  569. locParam, # location is a parameter
  570. locField, # location is a record field
  571. locExpr, # "location" is really an expression
  572. locProc, # location is a proc (an address of a procedure)
  573. locData, # location is a constant
  574. locCall, # location is a call expression
  575. locOther # location is something other
  576. TLocFlag* = enum
  577. lfIndirect, # backend introduced a pointer
  578. lfNoDeepCopy, # no need for a deep copy
  579. lfNoDecl, # do not declare it in C
  580. lfDynamicLib, # link symbol to dynamic library
  581. lfExportLib, # export symbol for dynamic library generation
  582. lfHeader, # include header file for symbol
  583. lfImportCompilerProc, # ``importc`` of a compilerproc
  584. lfSingleUse # no location yet and will only be used once
  585. lfEnforceDeref # a copyMem is required to dereference if this a
  586. # ptr array due to C array limitations.
  587. # See #1181, #6422, #11171
  588. lfPrepareForMutation # string location is about to be mutated (V2)
  589. TStorageLoc* = enum
  590. OnUnknown, # location is unknown (stack, heap or static)
  591. OnStatic, # in a static section
  592. OnStack, # location is on hardware stack
  593. OnHeap # location is on heap or global
  594. # (reference counting needed)
  595. TLocFlags* = set[TLocFlag]
  596. TLoc* = object
  597. k*: TLocKind # kind of location
  598. storage*: TStorageLoc
  599. flags*: TLocFlags # location's flags
  600. lode*: PNode # Node where the location came from; can be faked
  601. snippet*: Rope # C code snippet of location (code generators)
  602. # ---------------- end of backend information ------------------------------
  603. TLibKind* = enum
  604. libHeader, libDynamic
  605. TLib* = object # also misused for headers!
  606. # keep in sync with PackedLib
  607. kind*: TLibKind
  608. generated*: bool # needed for the backends:
  609. isOverridden*: bool
  610. name*: Rope
  611. path*: PNode # can be a string literal!
  612. CompilesId* = int ## id that is used for the caching logic within
  613. ## ``system.compiles``. See the seminst module.
  614. TInstantiation* = object
  615. sym*: PSym
  616. concreteTypes*: seq[PType]
  617. compilesId*: CompilesId
  618. PInstantiation* = ref TInstantiation
  619. TScope* {.acyclic.} = object
  620. depthLevel*: int
  621. symbols*: TStrTable
  622. parent*: PScope
  623. allowPrivateAccess*: seq[PSym] # # enable access to private fields
  624. PScope* = ref TScope
  625. PLib* = ref TLib
  626. TSym* {.acyclic.} = object # Keep in sync with PackedSym
  627. itemId*: ItemId
  628. # proc and type instantiations are cached in the generic symbol
  629. case kind*: TSymKind
  630. of routineKinds:
  631. #procInstCache*: seq[PInstantiation]
  632. gcUnsafetyReason*: PSym # for better error messages regarding gcsafe
  633. transformedBody*: PNode # cached body after transf pass
  634. of skLet, skVar, skField, skForVar:
  635. guard*: PSym
  636. bitsize*: int
  637. alignment*: int # for alignment
  638. else: nil
  639. magic*: TMagic
  640. typ*: PType
  641. name*: PIdent
  642. info*: TLineInfo
  643. when defined(nimsuggest):
  644. endInfo*: TLineInfo
  645. hasUserSpecifiedType*: bool # used for determining whether to display inlay type hints
  646. ownerField: PSym
  647. flags*: TSymFlags
  648. ast*: PNode # syntax tree of proc, iterator, etc.:
  649. # the whole proc including header; this is used
  650. # for easy generation of proper error messages
  651. # for variant record fields the discriminant
  652. # expression
  653. # for modules, it's a placeholder for compiler
  654. # generated code that will be appended to the
  655. # module after the sem pass (see appendToModule)
  656. options*: TOptions
  657. position*: int # used for many different things:
  658. # for enum fields its position;
  659. # for fields its offset
  660. # for parameters its position (starting with 0)
  661. # for a conditional:
  662. # 1 iff the symbol is defined, else 0
  663. # (or not in symbol table)
  664. # for modules, an unique index corresponding
  665. # to the module's fileIdx
  666. # for variables a slot index for the evaluator
  667. offset*: int32 # offset of record field
  668. disamb*: int32 # disambiguation number; the basic idea is that
  669. # `<procname>__<module>_<disamb>` is unique
  670. loc*: TLoc
  671. annex*: PLib # additional fields (seldom used, so we use a
  672. # reference to another object to save space)
  673. when hasFFI:
  674. cname*: string # resolved C declaration name in importc decl, e.g.:
  675. # proc fun() {.importc: "$1aux".} => cname = funaux
  676. constraint*: PNode # additional constraints like 'lit|result'; also
  677. # misused for the codegenDecl and virtual pragmas in the hope
  678. # it won't cause problems
  679. # for skModule the string literal to output for
  680. # deprecated modules.
  681. instantiatedFrom*: PSym # for instances, the generic symbol where it came from.
  682. when defined(nimsuggest):
  683. allUsages*: seq[TLineInfo]
  684. TTypeSeq* = seq[PType]
  685. TTypeAttachedOp* = enum ## as usual, order is important here
  686. attachedWasMoved,
  687. attachedDestructor,
  688. attachedAsgn,
  689. attachedDup,
  690. attachedSink,
  691. attachedTrace,
  692. attachedDeepCopy
  693. TType* {.acyclic.} = object # \
  694. # types are identical iff they have the
  695. # same id; there may be multiple copies of a type
  696. # in memory!
  697. # Keep in sync with PackedType
  698. itemId*: ItemId
  699. kind*: TTypeKind # kind of type
  700. callConv*: TCallingConvention # for procs
  701. flags*: TTypeFlags # flags of the type
  702. sons: TTypeSeq # base types, etc.
  703. n*: PNode # node for types:
  704. # for range types a nkRange node
  705. # for record types a nkRecord node
  706. # for enum types a list of symbols
  707. # if kind == tyInt: it is an 'int literal(x)' type
  708. # for procs and tyGenericBody, it's the
  709. # formal param list
  710. # for concepts, the concept body
  711. # else: unused
  712. ownerField: PSym # the 'owner' of the type
  713. sym*: PSym # types have the sym associated with them
  714. # it is used for converting types to strings
  715. size*: BiggestInt # the size of the type in bytes
  716. # -1 means that the size is unkwown
  717. align*: int16 # the type's alignment requirements
  718. paddingAtEnd*: int16 #
  719. loc*: TLoc
  720. typeInst*: PType # for generic instantiations the tyGenericInst that led to this
  721. # type.
  722. uniqueId*: ItemId # due to a design mistake, we need to keep the real ID here as it
  723. # is required by the --incremental:on mode.
  724. TPair* = object
  725. key*, val*: RootRef
  726. TPairSeq* = seq[TPair]
  727. TNodePair* = object
  728. h*: Hash # because it is expensive to compute!
  729. key*: PNode
  730. val*: int
  731. TNodePairSeq* = seq[TNodePair]
  732. TNodeTable* = object # the same as table[PNode] of int;
  733. # nodes are compared by structure!
  734. counter*: int
  735. data*: TNodePairSeq
  736. TObjectSeq* = seq[RootRef]
  737. TObjectSet* = object
  738. counter*: int
  739. data*: TObjectSeq
  740. TImplication* = enum
  741. impUnknown, impNo, impYes
  742. template nodeId(n: PNode): int = cast[int](n)
  743. template typ*(n: PNode): PType =
  744. n.typField
  745. proc owner*(s: PSym|PType): PSym {.inline.} =
  746. result = s.ownerField
  747. proc setOwner*(s: PSym|PType, owner: PSym) {.inline.} =
  748. s.ownerField = owner
  749. type Gconfig = object
  750. # we put comments in a side channel to avoid increasing `sizeof(TNode)`, which
  751. # reduces memory usage given that `PNode` is the most allocated type by far.
  752. comments: Table[int, string] # nodeId => comment
  753. useIc*: bool
  754. var gconfig {.threadvar.}: Gconfig
  755. proc setUseIc*(useIc: bool) = gconfig.useIc = useIc
  756. proc comment*(n: PNode): string =
  757. if nfHasComment in n.flags and not gconfig.useIc:
  758. # IC doesn't track comments, see `packed_ast`, so this could fail
  759. result = gconfig.comments[n.nodeId]
  760. else:
  761. result = ""
  762. proc `comment=`*(n: PNode, a: string) =
  763. let id = n.nodeId
  764. if a.len > 0:
  765. # if needed, we could periodically cleanup gconfig.comments when its size increases,
  766. # to ensure only live nodes (and with nfHasComment) have an entry in gconfig.comments;
  767. # for compiling compiler, the waste is very small:
  768. # num calls to newNodeImpl: 14984160 (num of PNode allocations)
  769. # size of gconfig.comments: 33585
  770. # num of nodes with comments that were deleted and hence wasted: 3081
  771. n.flags.incl nfHasComment
  772. gconfig.comments[id] = a
  773. elif nfHasComment in n.flags:
  774. n.flags.excl nfHasComment
  775. gconfig.comments.del(id)
  776. # BUGFIX: a module is overloadable so that a proc can have the
  777. # same name as an imported module. This is necessary because of
  778. # the poor naming choices in the standard library.
  779. const
  780. OverloadableSyms* = {skProc, skFunc, skMethod, skIterator,
  781. skConverter, skModule, skTemplate, skMacro, skEnumField}
  782. GenericTypes*: TTypeKinds = {tyGenericInvocation, tyGenericBody,
  783. tyGenericParam}
  784. StructuralEquivTypes*: TTypeKinds = {tyNil, tyTuple, tyArray,
  785. tySet, tyRange, tyPtr, tyRef, tyVar, tyLent, tySequence, tyProc, tyOpenArray,
  786. tyVarargs}
  787. ConcreteTypes*: TTypeKinds = { # types of the expr that may occur in::
  788. # var x = expr
  789. tyBool, tyChar, tyEnum, tyArray, tyObject,
  790. tySet, tyTuple, tyRange, tyPtr, tyRef, tyVar, tyLent, tySequence, tyProc,
  791. tyPointer,
  792. tyOpenArray, tyString, tyCstring, tyInt..tyInt64, tyFloat..tyFloat128,
  793. tyUInt..tyUInt64}
  794. IntegralTypes* = {tyBool, tyChar, tyEnum, tyInt..tyInt64,
  795. tyFloat..tyFloat128, tyUInt..tyUInt64} # weird name because it contains tyFloat
  796. ConstantDataTypes*: TTypeKinds = {tyArray, tySet,
  797. tyTuple, tySequence}
  798. NilableTypes*: TTypeKinds = {tyPointer, tyCstring, tyRef, tyPtr,
  799. tyProc, tyError} # TODO
  800. PtrLikeKinds*: TTypeKinds = {tyPointer, tyPtr} # for VM
  801. PersistentNodeFlags*: TNodeFlags = {nfBase2, nfBase8, nfBase16,
  802. nfDotSetter, nfDotField,
  803. nfIsRef, nfIsPtr, nfPreventCg, nfLL,
  804. nfFromTemplate, nfDefaultRefsParam,
  805. nfExecuteOnReload, nfLastRead,
  806. nfFirstWrite, nfSkipFieldChecking,
  807. nfDisabledOpenSym}
  808. namePos* = 0
  809. patternPos* = 1 # empty except for term rewriting macros
  810. genericParamsPos* = 2
  811. paramsPos* = 3
  812. pragmasPos* = 4
  813. miscPos* = 5 # used for undocumented and hacky stuff
  814. bodyPos* = 6 # position of body; use rodread.getBody() instead!
  815. resultPos* = 7
  816. dispatcherPos* = 8
  817. nfAllFieldsSet* = nfBase2
  818. nkIdentKinds* = {nkIdent, nkSym, nkAccQuoted, nkOpenSymChoice,
  819. nkClosedSymChoice, nkOpenSym}
  820. nkPragmaCallKinds* = {nkExprColonExpr, nkCall, nkCallStrLit}
  821. nkLiterals* = {nkCharLit..nkTripleStrLit}
  822. nkFloatLiterals* = {nkFloatLit..nkFloat128Lit}
  823. nkLambdaKinds* = {nkLambda, nkDo}
  824. declarativeDefs* = {nkProcDef, nkFuncDef, nkMethodDef, nkIteratorDef, nkConverterDef}
  825. routineDefs* = declarativeDefs + {nkMacroDef, nkTemplateDef}
  826. procDefs* = nkLambdaKinds + declarativeDefs
  827. callableDefs* = nkLambdaKinds + routineDefs
  828. nkSymChoices* = {nkClosedSymChoice, nkOpenSymChoice}
  829. nkStrKinds* = {nkStrLit..nkTripleStrLit}
  830. skLocalVars* = {skVar, skLet, skForVar, skParam, skResult}
  831. skProcKinds* = {skProc, skFunc, skTemplate, skMacro, skIterator,
  832. skMethod, skConverter}
  833. defaultSize = -1
  834. defaultAlignment = -1
  835. defaultOffset* = -1
  836. proc getPIdent*(a: PNode): PIdent {.inline.} =
  837. ## Returns underlying `PIdent` for `{nkSym, nkIdent}`, or `nil`.
  838. case a.kind
  839. of nkSym: a.sym.name
  840. of nkIdent: a.ident
  841. of nkOpenSymChoice, nkClosedSymChoice: a.sons[0].sym.name
  842. of nkOpenSym: getPIdent(a.sons[0])
  843. else: nil
  844. const
  845. moduleShift = when defined(cpu32): 20 else: 24
  846. template id*(a: PType | PSym): int =
  847. let x = a
  848. (x.itemId.module.int shl moduleShift) + x.itemId.item.int
  849. type
  850. IdGenerator* = ref object # unfortunately, we really need the 'shared mutable' aspect here.
  851. module*: int32
  852. symId*: int32
  853. typeId*: int32
  854. sealed*: bool
  855. disambTable*: CountTable[PIdent]
  856. const
  857. PackageModuleId* = -3'i32
  858. proc idGeneratorFromModule*(m: PSym): IdGenerator =
  859. assert m.kind == skModule
  860. result = IdGenerator(module: m.itemId.module, symId: m.itemId.item, typeId: 0, disambTable: initCountTable[PIdent]())
  861. proc idGeneratorForPackage*(nextIdWillBe: int32): IdGenerator =
  862. result = IdGenerator(module: PackageModuleId, symId: nextIdWillBe - 1'i32, typeId: 0, disambTable: initCountTable[PIdent]())
  863. proc nextSymId(x: IdGenerator): ItemId {.inline.} =
  864. assert(not x.sealed)
  865. inc x.symId
  866. result = ItemId(module: x.module, item: x.symId)
  867. proc nextTypeId*(x: IdGenerator): ItemId {.inline.} =
  868. assert(not x.sealed)
  869. inc x.typeId
  870. result = ItemId(module: x.module, item: x.typeId)
  871. when false:
  872. proc nextId*(x: IdGenerator): ItemId {.inline.} =
  873. inc x.item
  874. result = x[]
  875. when false:
  876. proc storeBack*(dest: var IdGenerator; src: IdGenerator) {.inline.} =
  877. assert dest.ItemId.module == src.ItemId.module
  878. if dest.ItemId.item > src.ItemId.item:
  879. echo dest.ItemId.item, " ", src.ItemId.item, " ", src.ItemId.module
  880. assert dest.ItemId.item <= src.ItemId.item
  881. dest = src
  882. var ggDebug* {.deprecated.}: bool ## convenience switch for trying out things
  883. proc isCallExpr*(n: PNode): bool =
  884. result = n.kind in nkCallKinds
  885. proc discardSons*(father: PNode)
  886. proc len*(n: PNode): int {.inline.} =
  887. result = n.sons.len
  888. proc safeLen*(n: PNode): int {.inline.} =
  889. ## works even for leaves.
  890. if n.kind in {nkNone..nkNilLit}: result = 0
  891. else: result = n.len
  892. proc safeArrLen*(n: PNode): int {.inline.} =
  893. ## works for array-like objects (strings passed as openArray in VM).
  894. if n.kind in {nkStrLit..nkTripleStrLit}: result = n.strVal.len
  895. elif n.kind in {nkNone..nkFloat128Lit}: result = 0
  896. else: result = n.len
  897. proc add*(father, son: PNode) =
  898. assert son != nil
  899. father.sons.add(son)
  900. proc addAllowNil*(father, son: PNode) {.inline.} =
  901. father.sons.add(son)
  902. template `[]`*(n: PNode, i: int): PNode = n.sons[i]
  903. template `[]=`*(n: PNode, i: int; x: PNode) = n.sons[i] = x
  904. template `[]`*(n: PNode, i: BackwardsIndex): PNode = n[n.len - i.int]
  905. template `[]=`*(n: PNode, i: BackwardsIndex; x: PNode) = n[n.len - i.int] = x
  906. proc add*(father, son: PType) =
  907. assert son != nil
  908. father.sons.add(son)
  909. proc addAllowNil*(father, son: PType) {.inline.} =
  910. father.sons.add(son)
  911. template `[]`*(n: PType, i: int): PType = n.sons[i]
  912. template `[]=`*(n: PType, i: int; x: PType) = n.sons[i] = x
  913. template `[]`*(n: PType, i: BackwardsIndex): PType = n[n.len - i.int]
  914. template `[]=`*(n: PType, i: BackwardsIndex; x: PType) = n[n.len - i.int] = x
  915. proc getDeclPragma*(n: PNode): PNode =
  916. ## return the `nkPragma` node for declaration `n`, or `nil` if no pragma was found.
  917. ## Currently only supports routineDefs + {nkTypeDef}.
  918. case n.kind
  919. of routineDefs:
  920. if n[pragmasPos].kind != nkEmpty: result = n[pragmasPos]
  921. else: result = nil
  922. of nkTypeDef:
  923. #[
  924. type F3*{.deprecated: "x3".} = int
  925. TypeSection
  926. TypeDef
  927. PragmaExpr
  928. Postfix
  929. Ident "*"
  930. Ident "F3"
  931. Pragma
  932. ExprColonExpr
  933. Ident "deprecated"
  934. StrLit "x3"
  935. Empty
  936. Ident "int"
  937. ]#
  938. if n[0].kind == nkPragmaExpr:
  939. result = n[0][1]
  940. else:
  941. result = nil
  942. else:
  943. # support as needed for `nkIdentDefs` etc.
  944. result = nil
  945. if result != nil:
  946. assert result.kind == nkPragma, $(result.kind, n.kind)
  947. proc extractPragma*(s: PSym): PNode =
  948. ## gets the pragma node of routine/type/var/let/const symbol `s`
  949. if s.kind in routineKinds: # bug #24167
  950. if s.ast[pragmasPos] != nil and s.ast[pragmasPos].kind != nkEmpty:
  951. result = s.ast[pragmasPos]
  952. else:
  953. result = nil
  954. elif s.kind in {skType, skVar, skLet, skConst}:
  955. if s.ast != nil and s.ast.len > 0:
  956. if s.ast[0].kind == nkPragmaExpr and s.ast[0].len > 1:
  957. # s.ast = nkTypedef / nkPragmaExpr / [nkSym, nkPragma]
  958. result = s.ast[0][1]
  959. else:
  960. result = nil
  961. else:
  962. result = nil
  963. else:
  964. result = nil
  965. assert result == nil or result.kind == nkPragma
  966. proc skipPragmaExpr*(n: PNode): PNode =
  967. ## if pragma expr, give the node the pragmas are applied to,
  968. ## otherwise give node itself
  969. if n.kind == nkPragmaExpr:
  970. result = n[0]
  971. else:
  972. result = n
  973. proc setInfoRecursive*(n: PNode, info: TLineInfo) =
  974. ## set line info recursively
  975. if n != nil:
  976. for i in 0..<n.safeLen: setInfoRecursive(n[i], info)
  977. n.info = info
  978. when defined(useNodeIds):
  979. const nodeIdToDebug* = -1 # 2322968
  980. var gNodeId: int
  981. template newNodeImpl(info2) =
  982. result = PNode(kind: kind, info: info2)
  983. when false:
  984. # this would add overhead, so we skip it; it results in a small amount of leaked entries
  985. # for old PNode that gets re-allocated at the same address as a PNode that
  986. # has `nfHasComment` set (and an entry in that table). Only `nfHasComment`
  987. # should be used to test whether a PNode has a comment; gconfig.comments
  988. # can contain extra entries for deleted PNode's with comments.
  989. gconfig.comments.del(cast[int](result))
  990. template setIdMaybe() =
  991. when defined(useNodeIds):
  992. result.id = gNodeId
  993. if result.id == nodeIdToDebug:
  994. echo "KIND ", result.kind
  995. writeStackTrace()
  996. inc gNodeId
  997. proc newNode*(kind: TNodeKind): PNode =
  998. ## new node with unknown line info, no type, and no children
  999. newNodeImpl(unknownLineInfo)
  1000. setIdMaybe()
  1001. proc newNodeI*(kind: TNodeKind, info: TLineInfo): PNode =
  1002. ## new node with line info, no type, and no children
  1003. newNodeImpl(info)
  1004. setIdMaybe()
  1005. proc newNodeI*(kind: TNodeKind, info: TLineInfo, children: int): PNode =
  1006. ## new node with line info, type, and children
  1007. newNodeImpl(info)
  1008. if children > 0:
  1009. newSeq(result.sons, children)
  1010. setIdMaybe()
  1011. proc newNodeIT*(kind: TNodeKind, info: TLineInfo, typ: PType): PNode =
  1012. ## new node with line info, type, and no children
  1013. result = newNode(kind)
  1014. result.info = info
  1015. result.typ() = typ
  1016. proc newNode*(kind: TNodeKind, info: TLineInfo): PNode =
  1017. ## new node with line info, no type, and no children
  1018. newNodeImpl(info)
  1019. setIdMaybe()
  1020. proc newAtom*(ident: PIdent, info: TLineInfo): PNode =
  1021. result = newNode(nkIdent, info)
  1022. result.ident = ident
  1023. proc newAtom*(kind: TNodeKind, intVal: BiggestInt, info: TLineInfo): PNode =
  1024. result = newNode(kind, info)
  1025. result.intVal = intVal
  1026. proc newAtom*(kind: TNodeKind, floatVal: BiggestFloat, info: TLineInfo): PNode =
  1027. result = newNode(kind, info)
  1028. result.floatVal = floatVal
  1029. proc newAtom*(kind: TNodeKind; strVal: sink string; info: TLineInfo): PNode =
  1030. result = newNode(kind, info)
  1031. result.strVal = strVal
  1032. proc newTree*(kind: TNodeKind; info: TLineInfo; children: varargs[PNode]): PNode =
  1033. result = newNodeI(kind, info)
  1034. if children.len > 0:
  1035. result.info = children[0].info
  1036. result.sons = @children
  1037. proc newTree*(kind: TNodeKind; children: varargs[PNode]): PNode =
  1038. result = newNode(kind)
  1039. if children.len > 0:
  1040. result.info = children[0].info
  1041. result.sons = @children
  1042. proc newTreeI*(kind: TNodeKind; info: TLineInfo; children: varargs[PNode]): PNode =
  1043. result = newNodeI(kind, info)
  1044. if children.len > 0:
  1045. result.info = children[0].info
  1046. result.sons = @children
  1047. proc newTreeIT*(kind: TNodeKind; info: TLineInfo; typ: PType; children: varargs[PNode]): PNode =
  1048. result = newNodeIT(kind, info, typ)
  1049. if children.len > 0:
  1050. result.info = children[0].info
  1051. result.sons = @children
  1052. template previouslyInferred*(t: PType): PType =
  1053. if t.sons.len > 1: t.last else: nil
  1054. when false:
  1055. import tables, strutils
  1056. var x: CountTable[string]
  1057. addQuitProc proc () {.noconv.} =
  1058. for k, v in pairs(x):
  1059. echo k
  1060. echo v
  1061. proc newSym*(symKind: TSymKind, name: PIdent, idgen: IdGenerator; owner: PSym,
  1062. info: TLineInfo; options: TOptions = {}): PSym =
  1063. # generates a symbol and initializes the hash field too
  1064. assert not name.isNil
  1065. let id = nextSymId idgen
  1066. result = PSym(name: name, kind: symKind, flags: {}, info: info, itemId: id,
  1067. options: options, ownerField: owner, offset: defaultOffset,
  1068. disamb: getOrDefault(idgen.disambTable, name).int32)
  1069. idgen.disambTable.inc name
  1070. when false:
  1071. if id.module == 48 and id.item == 39:
  1072. writeStackTrace()
  1073. echo "kind ", symKind, " ", name.s
  1074. if owner != nil: echo owner.name.s
  1075. proc astdef*(s: PSym): PNode =
  1076. # get only the definition (initializer) portion of the ast
  1077. if s.ast != nil and s.ast.kind in {nkIdentDefs, nkConstDef}:
  1078. s.ast[2]
  1079. else:
  1080. s.ast
  1081. proc isMetaType*(t: PType): bool =
  1082. return t.kind in tyMetaTypes or
  1083. (t.kind == tyStatic and t.n == nil) or
  1084. tfHasMeta in t.flags
  1085. proc isUnresolvedStatic*(t: PType): bool =
  1086. return t.kind == tyStatic and t.n == nil
  1087. proc linkTo*(t: PType, s: PSym): PType {.discardable.} =
  1088. t.sym = s
  1089. s.typ = t
  1090. result = t
  1091. proc linkTo*(s: PSym, t: PType): PSym {.discardable.} =
  1092. t.sym = s
  1093. s.typ = t
  1094. result = s
  1095. template fileIdx*(c: PSym): FileIndex =
  1096. # XXX: this should be used only on module symbols
  1097. c.position.FileIndex
  1098. template filename*(c: PSym): string =
  1099. # XXX: this should be used only on module symbols
  1100. c.position.FileIndex.toFilename
  1101. proc appendToModule*(m: PSym, n: PNode) =
  1102. ## The compiler will use this internally to add nodes that will be
  1103. ## appended to the module after the sem pass
  1104. if m.ast == nil:
  1105. m.ast = newNode(nkStmtList)
  1106. m.ast.sons = @[n]
  1107. else:
  1108. assert m.ast.kind == nkStmtList
  1109. m.ast.sons.add(n)
  1110. const # for all kind of hash tables:
  1111. GrowthFactor* = 2 # must be power of 2, > 0
  1112. StartSize* = 8 # must be power of 2, > 0
  1113. proc copyStrTable*(dest: var TStrTable, src: TStrTable) =
  1114. dest.counter = src.counter
  1115. setLen(dest.data, src.data.len)
  1116. for i in 0..high(src.data): dest.data[i] = src.data[i]
  1117. proc copyObjectSet*(dest: var TObjectSet, src: TObjectSet) =
  1118. dest.counter = src.counter
  1119. setLen(dest.data, src.data.len)
  1120. for i in 0..high(src.data): dest.data[i] = src.data[i]
  1121. proc discardSons*(father: PNode) =
  1122. father.sons = @[]
  1123. proc withInfo*(n: PNode, info: TLineInfo): PNode =
  1124. n.info = info
  1125. return n
  1126. proc newIdentNode*(ident: PIdent, info: TLineInfo): PNode =
  1127. result = newNode(nkIdent)
  1128. result.ident = ident
  1129. result.info = info
  1130. proc newSymNode*(sym: PSym): PNode =
  1131. result = newNode(nkSym)
  1132. result.sym = sym
  1133. result.typ() = sym.typ
  1134. result.info = sym.info
  1135. proc newSymNode*(sym: PSym, info: TLineInfo): PNode =
  1136. result = newNode(nkSym)
  1137. result.sym = sym
  1138. result.typ() = sym.typ
  1139. result.info = info
  1140. proc newOpenSym*(n: PNode): PNode {.inline.} =
  1141. result = newTreeI(nkOpenSym, n.info, n)
  1142. proc newIntNode*(kind: TNodeKind, intVal: BiggestInt): PNode =
  1143. result = newNode(kind)
  1144. result.intVal = intVal
  1145. proc newIntNode*(kind: TNodeKind, intVal: Int128): PNode =
  1146. result = newNode(kind)
  1147. result.intVal = castToInt64(intVal)
  1148. proc lastSon*(n: PNode): PNode {.inline.} = n.sons[^1]
  1149. template setLastSon*(n: PNode, s: PNode) = n.sons[^1] = s
  1150. template firstSon*(n: PNode): PNode = n.sons[0]
  1151. template secondSon*(n: PNode): PNode = n.sons[1]
  1152. template hasSon*(n: PNode): bool = n.len > 0
  1153. template has2Sons*(n: PNode): bool = n.len > 1
  1154. proc replaceFirstSon*(n, newson: PNode) {.inline.} =
  1155. n.sons[0] = newson
  1156. proc replaceSon*(n: PNode; i: int; newson: PNode) {.inline.} =
  1157. n.sons[i] = newson
  1158. proc last*(n: PType): PType {.inline.} = n.sons[^1]
  1159. proc elementType*(n: PType): PType {.inline.} = n.sons[^1]
  1160. proc skipModifier*(n: PType): PType {.inline.} = n.sons[^1]
  1161. proc indexType*(n: PType): PType {.inline.} = n.sons[0]
  1162. proc baseClass*(n: PType): PType {.inline.} = n.sons[0]
  1163. proc base*(t: PType): PType {.inline.} =
  1164. result = t.sons[0]
  1165. proc returnType*(n: PType): PType {.inline.} = n.sons[0]
  1166. proc setReturnType*(n, r: PType) {.inline.} = n.sons[0] = r
  1167. proc setIndexType*(n, idx: PType) {.inline.} = n.sons[0] = idx
  1168. proc firstParamType*(n: PType): PType {.inline.} = n.sons[1]
  1169. proc firstGenericParam*(n: PType): PType {.inline.} = n.sons[1]
  1170. proc typeBodyImpl*(n: PType): PType {.inline.} = n.sons[^1]
  1171. proc genericHead*(n: PType): PType {.inline.} = n.sons[0]
  1172. proc skipTypes*(t: PType, kinds: TTypeKinds): PType =
  1173. ## Used throughout the compiler code to test whether a type tree contains or
  1174. ## doesn't contain a specific type/types - it is often the case that only the
  1175. ## last child nodes of a type tree need to be searched. This is a really hot
  1176. ## path within the compiler!
  1177. result = t
  1178. while result.kind in kinds: result = last(result)
  1179. proc newIntTypeNode*(intVal: BiggestInt, typ: PType): PNode =
  1180. let kind = skipTypes(typ, abstractVarRange).kind
  1181. case kind
  1182. of tyInt: result = newNode(nkIntLit)
  1183. of tyInt8: result = newNode(nkInt8Lit)
  1184. of tyInt16: result = newNode(nkInt16Lit)
  1185. of tyInt32: result = newNode(nkInt32Lit)
  1186. of tyInt64: result = newNode(nkInt64Lit)
  1187. of tyChar: result = newNode(nkCharLit)
  1188. of tyUInt: result = newNode(nkUIntLit)
  1189. of tyUInt8: result = newNode(nkUInt8Lit)
  1190. of tyUInt16: result = newNode(nkUInt16Lit)
  1191. of tyUInt32: result = newNode(nkUInt32Lit)
  1192. of tyUInt64: result = newNode(nkUInt64Lit)
  1193. of tyBool, tyEnum:
  1194. # XXX: does this really need to be the kind nkIntLit?
  1195. result = newNode(nkIntLit)
  1196. of tyStatic: # that's a pre-existing bug, will fix in another PR
  1197. result = newNode(nkIntLit)
  1198. else: raiseAssert $kind
  1199. result.intVal = intVal
  1200. result.typ() = typ
  1201. proc newIntTypeNode*(intVal: Int128, typ: PType): PNode =
  1202. # XXX: introduce range check
  1203. newIntTypeNode(castToInt64(intVal), typ)
  1204. proc newFloatNode*(kind: TNodeKind, floatVal: BiggestFloat): PNode =
  1205. result = newNode(kind)
  1206. result.floatVal = floatVal
  1207. proc newStrNode*(kind: TNodeKind, strVal: string): PNode =
  1208. result = newNode(kind)
  1209. result.strVal = strVal
  1210. proc newStrNode*(strVal: string; info: TLineInfo): PNode =
  1211. result = newNodeI(nkStrLit, info)
  1212. result.strVal = strVal
  1213. proc newProcNode*(kind: TNodeKind, info: TLineInfo, body: PNode,
  1214. params,
  1215. name, pattern, genericParams,
  1216. pragmas, exceptions: PNode): PNode =
  1217. result = newNodeI(kind, info)
  1218. result.sons = @[name, pattern, genericParams, params,
  1219. pragmas, exceptions, body]
  1220. const
  1221. AttachedOpToStr*: array[TTypeAttachedOp, string] = [
  1222. "=wasMoved", "=destroy", "=copy", "=dup", "=sink", "=trace", "=deepcopy"]
  1223. proc `$`*(s: PSym): string =
  1224. if s != nil:
  1225. result = s.name.s & "@" & $s.id
  1226. else:
  1227. result = "<nil>"
  1228. when false:
  1229. iterator items*(t: PType): PType =
  1230. for i in 0..<t.sons.len: yield t.sons[i]
  1231. iterator pairs*(n: PType): tuple[i: int, n: PType] =
  1232. for i in 0..<n.sons.len: yield (i, n.sons[i])
  1233. when true:
  1234. proc len*(n: PType): int {.inline.} =
  1235. result = n.sons.len
  1236. proc sameTupleLengths*(a, b: PType): bool {.inline.} =
  1237. result = a.sons.len == b.sons.len
  1238. iterator tupleTypePairs*(a, b: PType): (int, PType, PType) =
  1239. for i in 0 ..< a.sons.len:
  1240. yield (i, a.sons[i], b.sons[i])
  1241. iterator underspecifiedPairs*(a, b: PType; start = 0; without = 0): (PType, PType) =
  1242. # XXX Figure out with what typekinds this is called.
  1243. for i in start ..< min(a.sons.len, b.sons.len) + without:
  1244. yield (a.sons[i], b.sons[i])
  1245. proc signatureLen*(t: PType): int {.inline.} =
  1246. result = t.sons.len
  1247. proc paramsLen*(t: PType): int {.inline.} =
  1248. result = t.sons.len - 1
  1249. proc genericParamsLen*(t: PType): int {.inline.} =
  1250. assert t.kind == tyGenericInst
  1251. result = t.sons.len - 2 # without 'head' and 'body'
  1252. proc genericInvocationParamsLen*(t: PType): int {.inline.} =
  1253. assert t.kind == tyGenericInvocation
  1254. result = t.sons.len - 1 # without 'head'
  1255. proc kidsLen*(t: PType): int {.inline.} =
  1256. result = t.sons.len
  1257. proc genericParamHasConstraints*(t: PType): bool {.inline.} = t.sons.len > 0
  1258. proc hasElementType*(t: PType): bool {.inline.} = t.sons.len > 0
  1259. proc isEmptyTupleType*(t: PType): bool {.inline.} = t.sons.len == 0
  1260. proc isSingletonTupleType*(t: PType): bool {.inline.} = t.sons.len == 1
  1261. proc genericConstraint*(t: PType): PType {.inline.} = t.sons[0]
  1262. iterator genericInstParams*(t: PType): (bool, PType) =
  1263. for i in 1..<t.sons.len-1:
  1264. yield (i!=1, t.sons[i])
  1265. iterator genericInstParamPairs*(a, b: PType): (int, PType, PType) =
  1266. for i in 1..<min(a.sons.len, b.sons.len)-1:
  1267. yield (i-1, a.sons[i], b.sons[i])
  1268. iterator genericInvocationParams*(t: PType): (bool, PType) =
  1269. for i in 1..<t.sons.len:
  1270. yield (i!=1, t.sons[i])
  1271. iterator genericInvocationAndBodyElements*(a, b: PType): (PType, PType) =
  1272. for i in 1..<a.sons.len:
  1273. yield (a.sons[i], b.sons[i-1])
  1274. iterator genericInvocationParamPairs*(a, b: PType): (bool, PType, PType) =
  1275. for i in 1..<a.sons.len:
  1276. if i >= b.sons.len:
  1277. yield (false, nil, nil)
  1278. else:
  1279. yield (true, a.sons[i], b.sons[i])
  1280. iterator genericBodyParams*(t: PType): (int, PType) =
  1281. for i in 0..<t.sons.len-1:
  1282. yield (i, t.sons[i])
  1283. iterator userTypeClassInstParams*(t: PType): (bool, PType) =
  1284. for i in 1..<t.sons.len-1:
  1285. yield (i!=1, t.sons[i])
  1286. iterator ikids*(t: PType): (int, PType) =
  1287. for i in 0..<t.sons.len: yield (i, t.sons[i])
  1288. const
  1289. FirstParamAt* = 1
  1290. FirstGenericParamAt* = 1
  1291. iterator paramTypes*(t: PType): (int, PType) =
  1292. for i in FirstParamAt..<t.sons.len: yield (i, t.sons[i])
  1293. iterator paramTypePairs*(a, b: PType): (PType, PType) =
  1294. for i in FirstParamAt..<a.sons.len: yield (a.sons[i], b.sons[i])
  1295. template paramTypeToNodeIndex*(x: int): int = x
  1296. iterator kids*(t: PType): PType =
  1297. for i in 0..<t.sons.len: yield t.sons[i]
  1298. iterator signature*(t: PType): PType =
  1299. # yields return type + parameter types
  1300. for i in 0..<t.sons.len: yield t.sons[i]
  1301. proc newType*(kind: TTypeKind; idgen: IdGenerator; owner: PSym; son: sink PType = nil): PType =
  1302. let id = nextTypeId idgen
  1303. result = PType(kind: kind, ownerField: owner, size: defaultSize,
  1304. align: defaultAlignment, itemId: id,
  1305. uniqueId: id, sons: @[])
  1306. if son != nil: result.sons.add son
  1307. when false:
  1308. if result.itemId.module == 55 and result.itemId.item == 2:
  1309. echo "KNID ", kind
  1310. writeStackTrace()
  1311. proc setSons*(dest: PType; sons: sink seq[PType]) {.inline.} = dest.sons = sons
  1312. proc setSon*(dest: PType; son: sink PType) {.inline.} = dest.sons = @[son]
  1313. proc setSonsLen*(dest: PType; len: int) {.inline.} = setLen(dest.sons, len)
  1314. proc mergeLoc(a: var TLoc, b: TLoc) =
  1315. if a.k == low(typeof(a.k)): a.k = b.k
  1316. if a.storage == low(typeof(a.storage)): a.storage = b.storage
  1317. a.flags.incl b.flags
  1318. if a.lode == nil: a.lode = b.lode
  1319. if a.snippet == "": a.snippet = b.snippet
  1320. proc newSons*(father: PNode, length: int) =
  1321. setLen(father.sons, length)
  1322. proc newSons*(father: PType, length: int) =
  1323. setLen(father.sons, length)
  1324. proc truncateInferredTypeCandidates*(t: PType) {.inline.} =
  1325. assert t.kind == tyInferred
  1326. if t.sons.len > 1:
  1327. setLen(t.sons, 1)
  1328. proc assignType*(dest, src: PType) =
  1329. dest.kind = src.kind
  1330. dest.flags = src.flags
  1331. dest.callConv = src.callConv
  1332. dest.n = src.n
  1333. dest.size = src.size
  1334. dest.align = src.align
  1335. # this fixes 'type TLock = TSysLock':
  1336. if src.sym != nil:
  1337. if dest.sym != nil:
  1338. dest.sym.flags.incl src.sym.flags-{sfUsed, sfExported}
  1339. if dest.sym.annex == nil: dest.sym.annex = src.sym.annex
  1340. mergeLoc(dest.sym.loc, src.sym.loc)
  1341. else:
  1342. dest.sym = src.sym
  1343. newSons(dest, src.sons.len)
  1344. for i in 0..<src.sons.len: dest[i] = src[i]
  1345. proc copyType*(t: PType, idgen: IdGenerator, owner: PSym): PType =
  1346. result = newType(t.kind, idgen, owner)
  1347. assignType(result, t)
  1348. result.sym = t.sym # backend-info should not be copied
  1349. proc exactReplica*(t: PType): PType =
  1350. result = PType(kind: t.kind, ownerField: t.owner, size: defaultSize,
  1351. align: defaultAlignment, itemId: t.itemId,
  1352. uniqueId: t.uniqueId)
  1353. assignType(result, t)
  1354. result.sym = t.sym # backend-info should not be copied
  1355. proc copySym*(s: PSym; idgen: IdGenerator): PSym =
  1356. result = newSym(s.kind, s.name, idgen, s.owner, s.info, s.options)
  1357. #result.ast = nil # BUGFIX; was: s.ast which made problems
  1358. result.typ = s.typ
  1359. result.flags = s.flags
  1360. result.magic = s.magic
  1361. result.options = s.options
  1362. result.position = s.position
  1363. result.loc = s.loc
  1364. result.annex = s.annex # BUGFIX
  1365. result.constraint = s.constraint
  1366. if result.kind in {skVar, skLet, skField}:
  1367. result.guard = s.guard
  1368. result.bitsize = s.bitsize
  1369. result.alignment = s.alignment
  1370. proc createModuleAlias*(s: PSym, idgen: IdGenerator, newIdent: PIdent, info: TLineInfo;
  1371. options: TOptions): PSym =
  1372. result = newSym(s.kind, newIdent, idgen, s.owner, info, options)
  1373. # keep ID!
  1374. result.ast = s.ast
  1375. #result.id = s.id # XXX figure out what to do with the ID.
  1376. result.flags = s.flags
  1377. result.options = s.options
  1378. result.position = s.position
  1379. result.loc = s.loc
  1380. result.annex = s.annex
  1381. proc initStrTable*(): TStrTable =
  1382. result = TStrTable(counter: 0)
  1383. newSeq(result.data, StartSize)
  1384. proc initObjectSet*(): TObjectSet =
  1385. result = TObjectSet(counter: 0)
  1386. newSeq(result.data, StartSize)
  1387. proc initNodeTable*(): TNodeTable =
  1388. result = TNodeTable(counter: 0)
  1389. newSeq(result.data, StartSize)
  1390. proc skipTypes*(t: PType, kinds: TTypeKinds; maxIters: int): PType =
  1391. result = t
  1392. var i = maxIters
  1393. while result.kind in kinds:
  1394. result = last(result)
  1395. dec i
  1396. if i == 0: return nil
  1397. proc skipTypesOrNil*(t: PType, kinds: TTypeKinds): PType =
  1398. ## same as skipTypes but handles 'nil'
  1399. result = t
  1400. while result != nil and result.kind in kinds:
  1401. if result.sons.len == 0: return nil
  1402. result = last(result)
  1403. proc isGCedMem*(t: PType): bool {.inline.} =
  1404. result = t.kind in {tyString, tyRef, tySequence} or
  1405. t.kind == tyProc and t.callConv == ccClosure
  1406. proc propagateToOwner*(owner, elem: PType; propagateHasAsgn = true) =
  1407. owner.flags.incl elem.flags * {tfHasMeta, tfTriggersCompileTime}
  1408. if tfNotNil in elem.flags:
  1409. if owner.kind in {tyGenericInst, tyGenericBody, tyGenericInvocation}:
  1410. owner.flags.incl tfNotNil
  1411. if elem.isMetaType:
  1412. owner.flags.incl tfHasMeta
  1413. let mask = elem.flags * {tfHasAsgn, tfHasOwned}
  1414. if mask != {} and propagateHasAsgn:
  1415. let o2 = owner.skipTypes({tyGenericInst, tyAlias, tySink})
  1416. if o2.kind in {tyTuple, tyObject, tyArray,
  1417. tySequence, tyString, tySet, tyDistinct}:
  1418. o2.flags.incl mask
  1419. owner.flags.incl mask
  1420. if owner.kind notin {tyProc, tyGenericInst, tyGenericBody,
  1421. tyGenericInvocation, tyPtr}:
  1422. let elemB = elem.skipTypes({tyGenericInst, tyAlias, tySink})
  1423. if elemB.isGCedMem or tfHasGCedMem in elemB.flags:
  1424. # for simplicity, we propagate this flag even to generics. We then
  1425. # ensure this doesn't bite us in sempass2.
  1426. owner.flags.incl tfHasGCedMem
  1427. proc rawAddSon*(father, son: PType; propagateHasAsgn = true) =
  1428. father.sons.add(son)
  1429. if not son.isNil: propagateToOwner(father, son, propagateHasAsgn)
  1430. proc addSonNilAllowed*(father, son: PNode) =
  1431. father.sons.add(son)
  1432. proc delSon*(father: PNode, idx: int) =
  1433. if father.len == 0: return
  1434. for i in idx..<father.len - 1: father[i] = father[i + 1]
  1435. father.sons.setLen(father.len - 1)
  1436. proc copyNode*(src: PNode): PNode =
  1437. # does not copy its sons!
  1438. if src == nil:
  1439. return nil
  1440. result = newNode(src.kind)
  1441. result.info = src.info
  1442. result.typ() = src.typ
  1443. result.flags = src.flags * PersistentNodeFlags
  1444. result.comment = src.comment
  1445. when defined(useNodeIds):
  1446. if result.id == nodeIdToDebug:
  1447. echo "COMES FROM ", src.id
  1448. case src.kind
  1449. of nkCharLit..nkUInt64Lit: result.intVal = src.intVal
  1450. of nkFloatLiterals: result.floatVal = src.floatVal
  1451. of nkSym: result.sym = src.sym
  1452. of nkIdent: result.ident = src.ident
  1453. of nkStrLit..nkTripleStrLit: result.strVal = src.strVal
  1454. else: discard
  1455. when defined(nimsuggest):
  1456. result.endInfo = src.endInfo
  1457. template transitionNodeKindCommon(k: TNodeKind) =
  1458. let obj {.inject.} = n[]
  1459. n[] = TNode(kind: k, typField: n.typ, info: obj.info, flags: obj.flags)
  1460. # n.comment = obj.comment # shouldn't be needed, the address doesnt' change
  1461. when defined(useNodeIds):
  1462. n.id = obj.id
  1463. proc transitionSonsKind*(n: PNode, kind: range[nkComesFrom..nkTupleConstr]) =
  1464. transitionNodeKindCommon(kind)
  1465. n.sons = obj.sons
  1466. proc transitionIntKind*(n: PNode, kind: range[nkCharLit..nkUInt64Lit]) =
  1467. transitionNodeKindCommon(kind)
  1468. n.intVal = obj.intVal
  1469. proc transitionIntToFloatKind*(n: PNode, kind: range[nkFloatLit..nkFloat128Lit]) =
  1470. transitionNodeKindCommon(kind)
  1471. n.floatVal = BiggestFloat(obj.intVal)
  1472. proc transitionNoneToSym*(n: PNode) =
  1473. transitionNodeKindCommon(nkSym)
  1474. template transitionSymKindCommon*(k: TSymKind) =
  1475. let obj {.inject.} = s[]
  1476. s[] = TSym(kind: k, itemId: obj.itemId, magic: obj.magic, typ: obj.typ, name: obj.name,
  1477. info: obj.info, ownerField: obj.ownerField, flags: obj.flags, ast: obj.ast,
  1478. options: obj.options, position: obj.position, offset: obj.offset,
  1479. loc: obj.loc, annex: obj.annex, constraint: obj.constraint)
  1480. when hasFFI:
  1481. s.cname = obj.cname
  1482. when defined(nimsuggest):
  1483. s.allUsages = obj.allUsages
  1484. proc transitionGenericParamToType*(s: PSym) =
  1485. transitionSymKindCommon(skType)
  1486. proc transitionRoutineSymKind*(s: PSym, kind: range[skProc..skTemplate]) =
  1487. transitionSymKindCommon(kind)
  1488. s.gcUnsafetyReason = obj.gcUnsafetyReason
  1489. s.transformedBody = obj.transformedBody
  1490. proc transitionToLet*(s: PSym) =
  1491. transitionSymKindCommon(skLet)
  1492. s.guard = obj.guard
  1493. s.bitsize = obj.bitsize
  1494. s.alignment = obj.alignment
  1495. template copyNodeImpl(dst, src, processSonsStmt) =
  1496. if src == nil: return
  1497. dst = newNode(src.kind)
  1498. dst.info = src.info
  1499. when defined(nimsuggest):
  1500. result.endInfo = src.endInfo
  1501. dst.typ() = src.typ
  1502. dst.flags = src.flags * PersistentNodeFlags
  1503. dst.comment = src.comment
  1504. when defined(useNodeIds):
  1505. if dst.id == nodeIdToDebug:
  1506. echo "COMES FROM ", src.id
  1507. case src.kind
  1508. of nkCharLit..nkUInt64Lit: dst.intVal = src.intVal
  1509. of nkFloatLiterals: dst.floatVal = src.floatVal
  1510. of nkSym: dst.sym = src.sym
  1511. of nkIdent: dst.ident = src.ident
  1512. of nkStrLit..nkTripleStrLit: dst.strVal = src.strVal
  1513. else: processSonsStmt
  1514. proc shallowCopy*(src: PNode): PNode =
  1515. # does not copy its sons, but provides space for them:
  1516. copyNodeImpl(result, src):
  1517. newSeq(result.sons, src.len)
  1518. proc copyTree*(src: PNode): PNode =
  1519. # copy a whole syntax tree; performs deep copying
  1520. copyNodeImpl(result, src):
  1521. newSeq(result.sons, src.len)
  1522. for i in 0..<src.len:
  1523. result[i] = copyTree(src[i])
  1524. proc copyTreeWithoutNode*(src, skippedNode: PNode): PNode =
  1525. copyNodeImpl(result, src):
  1526. result.sons = newSeqOfCap[PNode](src.len)
  1527. for n in src.sons:
  1528. if n != skippedNode:
  1529. result.sons.add copyTreeWithoutNode(n, skippedNode)
  1530. proc hasSonWith*(n: PNode, kind: TNodeKind): bool =
  1531. for i in 0..<n.len:
  1532. if n[i].kind == kind:
  1533. return true
  1534. result = false
  1535. proc hasNilSon*(n: PNode): bool =
  1536. for i in 0..<n.safeLen:
  1537. if n[i] == nil:
  1538. return true
  1539. elif hasNilSon(n[i]):
  1540. return true
  1541. result = false
  1542. proc containsNode*(n: PNode, kinds: TNodeKinds): bool =
  1543. result = false
  1544. if n == nil: return
  1545. case n.kind
  1546. of nkEmpty..nkNilLit: result = n.kind in kinds
  1547. else:
  1548. for i in 0..<n.len:
  1549. if n.kind in kinds or containsNode(n[i], kinds): return true
  1550. proc hasSubnodeWith*(n: PNode, kind: TNodeKind): bool =
  1551. case n.kind
  1552. of nkEmpty..nkNilLit, nkFormalParams: result = n.kind == kind
  1553. else:
  1554. for i in 0..<n.len:
  1555. if (n[i].kind == kind) or hasSubnodeWith(n[i], kind):
  1556. return true
  1557. result = false
  1558. proc getInt*(a: PNode): Int128 =
  1559. case a.kind
  1560. of nkCharLit, nkUIntLit..nkUInt64Lit:
  1561. result = toInt128(cast[uint64](a.intVal))
  1562. of nkInt8Lit..nkInt64Lit:
  1563. result = toInt128(a.intVal)
  1564. of nkIntLit:
  1565. # XXX: enable this assert
  1566. # assert a.typ.kind notin {tyChar, tyUint..tyUInt64}
  1567. result = toInt128(a.intVal)
  1568. else:
  1569. raiseRecoverableError("cannot extract number from invalid AST node")
  1570. proc getInt64*(a: PNode): int64 {.deprecated: "use getInt".} =
  1571. case a.kind
  1572. of nkCharLit, nkUIntLit..nkUInt64Lit, nkIntLit..nkInt64Lit:
  1573. result = a.intVal
  1574. else:
  1575. raiseRecoverableError("cannot extract number from invalid AST node")
  1576. proc getFloat*(a: PNode): BiggestFloat =
  1577. case a.kind
  1578. of nkFloatLiterals: result = a.floatVal
  1579. of nkCharLit, nkUIntLit..nkUInt64Lit, nkIntLit..nkInt64Lit:
  1580. result = BiggestFloat a.intVal
  1581. else:
  1582. raiseRecoverableError("cannot extract number from invalid AST node")
  1583. #doAssert false, "getFloat"
  1584. #internalError(a.info, "getFloat")
  1585. #result = 0.0
  1586. proc getStr*(a: PNode): string =
  1587. case a.kind
  1588. of nkStrLit..nkTripleStrLit: result = a.strVal
  1589. of nkNilLit:
  1590. # let's hope this fixes more problems than it creates:
  1591. result = ""
  1592. else:
  1593. raiseRecoverableError("cannot extract string from invalid AST node")
  1594. #doAssert false, "getStr"
  1595. #internalError(a.info, "getStr")
  1596. #result = ""
  1597. proc getStrOrChar*(a: PNode): string =
  1598. case a.kind
  1599. of nkStrLit..nkTripleStrLit: result = a.strVal
  1600. of nkCharLit..nkUInt64Lit: result = $chr(int(a.intVal))
  1601. else:
  1602. raiseRecoverableError("cannot extract string from invalid AST node")
  1603. #doAssert false, "getStrOrChar"
  1604. #internalError(a.info, "getStrOrChar")
  1605. #result = ""
  1606. proc isGenericParams*(n: PNode): bool {.inline.} =
  1607. ## used to judge whether a node is generic params.
  1608. n != nil and n.kind == nkGenericParams
  1609. proc isGenericRoutine*(n: PNode): bool {.inline.} =
  1610. n != nil and n.kind in callableDefs and n[genericParamsPos].isGenericParams
  1611. proc isGenericRoutineStrict*(s: PSym): bool {.inline.} =
  1612. ## determines if this symbol represents a generic routine
  1613. ## the unusual name is so it doesn't collide and eventually replaces
  1614. ## `isGenericRoutine`
  1615. s.kind in skProcKinds and s.ast.isGenericRoutine
  1616. proc isGenericRoutine*(s: PSym): bool {.inline.} =
  1617. ## determines if this symbol represents a generic routine or an instance of
  1618. ## one. This should be renamed accordingly and `isGenericRoutineStrict`
  1619. ## should take this name instead.
  1620. ##
  1621. ## Warning/XXX: Unfortunately, it considers a proc kind symbol flagged with
  1622. ## sfFromGeneric as a generic routine. Instead this should likely not be the
  1623. ## case and the concepts should be teased apart:
  1624. ## - generic definition
  1625. ## - generic instance
  1626. ## - either generic definition or instance
  1627. s.kind in skProcKinds and (sfFromGeneric in s.flags or
  1628. s.ast.isGenericRoutine)
  1629. proc skipGenericOwner*(s: PSym): PSym =
  1630. ## Generic instantiations are owned by their originating generic
  1631. ## symbol. This proc skips such owners and goes straight to the owner
  1632. ## of the generic itself (the module or the enclosing proc).
  1633. result = if s.kind == skModule:
  1634. s
  1635. elif s.kind in skProcKinds and sfFromGeneric in s.flags and s.owner.kind != skModule:
  1636. s.owner.owner
  1637. else:
  1638. s.owner
  1639. proc originatingModule*(s: PSym): PSym =
  1640. result = s
  1641. while result.kind != skModule: result = result.owner
  1642. proc isRoutine*(s: PSym): bool {.inline.} =
  1643. result = s.kind in skProcKinds
  1644. proc isCompileTimeProc*(s: PSym): bool {.inline.} =
  1645. result = s.kind == skMacro or
  1646. s.kind in {skProc, skFunc} and sfCompileTime in s.flags
  1647. proc hasPattern*(s: PSym): bool {.inline.} =
  1648. result = isRoutine(s) and s.ast[patternPos].kind != nkEmpty
  1649. iterator items*(n: PNode): PNode =
  1650. for i in 0..<n.safeLen: yield n[i]
  1651. iterator pairs*(n: PNode): tuple[i: int, n: PNode] =
  1652. for i in 0..<n.safeLen: yield (i, n[i])
  1653. proc isAtom*(n: PNode): bool {.inline.} =
  1654. result = n.kind >= nkNone and n.kind <= nkNilLit
  1655. proc isEmptyType*(t: PType): bool {.inline.} =
  1656. ## 'void' and 'typed' types are often equivalent to 'nil' these days:
  1657. result = t == nil or t.kind in {tyVoid, tyTyped}
  1658. proc makeStmtList*(n: PNode): PNode =
  1659. if n.kind == nkStmtList:
  1660. result = n
  1661. else:
  1662. result = newNodeI(nkStmtList, n.info)
  1663. result.add n
  1664. proc skipStmtList*(n: PNode): PNode =
  1665. if n.kind in {nkStmtList, nkStmtListExpr}:
  1666. for i in 0..<n.len-1:
  1667. if n[i].kind notin {nkEmpty, nkCommentStmt}: return n
  1668. result = n.lastSon
  1669. else:
  1670. result = n
  1671. proc toVar*(typ: PType; kind: TTypeKind; idgen: IdGenerator): PType =
  1672. ## If ``typ`` is not a tyVar then it is converted into a `var <typ>` and
  1673. ## returned. Otherwise ``typ`` is simply returned as-is.
  1674. result = typ
  1675. if typ.kind != kind:
  1676. result = newType(kind, idgen, typ.owner, typ)
  1677. proc toRef*(typ: PType; idgen: IdGenerator): PType =
  1678. ## If ``typ`` is a tyObject then it is converted into a `ref <typ>` and
  1679. ## returned. Otherwise ``typ`` is simply returned as-is.
  1680. result = typ
  1681. if typ.skipTypes({tyAlias, tyGenericInst}).kind == tyObject:
  1682. result = newType(tyRef, idgen, typ.owner, typ)
  1683. proc toObject*(typ: PType): PType =
  1684. ## If ``typ`` is a tyRef then its immediate son is returned (which in many
  1685. ## cases should be a ``tyObject``).
  1686. ## Otherwise ``typ`` is simply returned as-is.
  1687. let t = typ.skipTypes({tyAlias, tyGenericInst})
  1688. if t.kind == tyRef: t.elementType
  1689. else: typ
  1690. proc toObjectFromRefPtrGeneric*(typ: PType): PType =
  1691. #[
  1692. See also `toObject`.
  1693. Finds the underlying `object`, even in cases like these:
  1694. type
  1695. B[T] = object f0: int
  1696. A1[T] = ref B[T]
  1697. A2[T] = ref object f1: int
  1698. A3 = ref object f2: int
  1699. A4 = object f3: int
  1700. ]#
  1701. result = typ
  1702. while true:
  1703. case result.kind
  1704. of tyGenericBody: result = result.last
  1705. of tyRef, tyPtr, tyGenericInst, tyGenericInvocation, tyAlias: result = result[0]
  1706. # automatic dereferencing is deep, refs #18298.
  1707. else: break
  1708. # result does not have to be object type
  1709. proc isImportedException*(t: PType; conf: ConfigRef): bool =
  1710. assert t != nil
  1711. if conf.exc != excCpp:
  1712. return false
  1713. let base = t.skipTypes({tyAlias, tyPtr, tyDistinct, tyGenericInst})
  1714. result = base.sym != nil and {sfCompileToCpp, sfImportc} * base.sym.flags != {}
  1715. proc isInfixAs*(n: PNode): bool =
  1716. return n.kind == nkInfix and n[0].kind == nkIdent and n[0].ident.id == ord(wAs)
  1717. proc skipColon*(n: PNode): PNode =
  1718. result = n
  1719. if n.kind == nkExprColonExpr:
  1720. result = n[1]
  1721. proc findUnresolvedStatic*(n: PNode): PNode =
  1722. if n.kind == nkSym and n.typ != nil and n.typ.kind == tyStatic and n.typ.n == nil:
  1723. return n
  1724. if n.typ != nil and n.typ.kind == tyTypeDesc:
  1725. let t = skipTypes(n.typ, {tyTypeDesc})
  1726. if t.kind == tyGenericParam and not t.genericParamHasConstraints:
  1727. return n
  1728. for son in n:
  1729. let n = son.findUnresolvedStatic
  1730. if n != nil: return n
  1731. return nil
  1732. when false:
  1733. proc containsNil*(n: PNode): bool =
  1734. # only for debugging
  1735. if n.isNil: return true
  1736. for i in 0..<n.safeLen:
  1737. if n[i].containsNil: return true
  1738. template hasDestructor*(t: PType): bool = {tfHasAsgn, tfHasOwned} * t.flags != {}
  1739. template incompleteType*(t: PType): bool =
  1740. t.sym != nil and {sfForward, sfNoForward} * t.sym.flags == {sfForward}
  1741. template typeCompleted*(s: PSym) =
  1742. incl s.flags, sfNoForward
  1743. template detailedInfo*(sym: PSym): string =
  1744. sym.name.s
  1745. proc isInlineIterator*(typ: PType): bool {.inline.} =
  1746. typ.kind == tyProc and tfIterator in typ.flags and typ.callConv != ccClosure
  1747. proc isIterator*(typ: PType): bool {.inline.} =
  1748. typ.kind == tyProc and tfIterator in typ.flags
  1749. proc isClosureIterator*(typ: PType): bool {.inline.} =
  1750. typ.kind == tyProc and tfIterator in typ.flags and typ.callConv == ccClosure
  1751. proc isClosure*(typ: PType): bool {.inline.} =
  1752. typ.kind == tyProc and typ.callConv == ccClosure
  1753. proc isNimcall*(s: PSym): bool {.inline.} =
  1754. s.typ.callConv == ccNimCall
  1755. proc isExplicitCallConv*(s: PSym): bool {.inline.} =
  1756. tfExplicitCallConv in s.typ.flags
  1757. proc isSinkParam*(s: PSym): bool {.inline.} =
  1758. s.kind == skParam and (s.typ.kind == tySink or tfHasOwned in s.typ.flags)
  1759. proc isSinkType*(t: PType): bool {.inline.} =
  1760. t.kind == tySink or tfHasOwned in t.flags
  1761. proc newProcType*(info: TLineInfo; idgen: IdGenerator; owner: PSym): PType =
  1762. result = newType(tyProc, idgen, owner)
  1763. result.n = newNodeI(nkFormalParams, info)
  1764. rawAddSon(result, nil) # return type
  1765. # result.n[0] used to be `nkType`, but now it's `nkEffectList` because
  1766. # the effects are now stored in there too ... this is a bit hacky, but as
  1767. # usual we desperately try to save memory:
  1768. result.n.add newNodeI(nkEffectList, info)
  1769. proc addParam*(procType: PType; param: PSym) =
  1770. param.position = procType.sons.len-1
  1771. procType.n.add newSymNode(param)
  1772. rawAddSon(procType, param.typ)
  1773. const magicsThatCanRaise = {
  1774. mNone, mSlurp, mStaticExec, mParseExprToAst, mParseStmtToAst, mEcho}
  1775. proc canRaiseConservative*(fn: PNode): bool =
  1776. if fn.kind == nkSym and fn.sym.magic notin magicsThatCanRaise:
  1777. result = false
  1778. else:
  1779. result = true
  1780. proc canRaise*(fn: PNode): bool =
  1781. if fn.kind == nkSym and (fn.sym.magic notin magicsThatCanRaise or
  1782. {sfImportc, sfInfixCall} * fn.sym.flags == {sfImportc} or
  1783. sfGeneratedOp in fn.sym.flags):
  1784. result = false
  1785. elif fn.kind == nkSym and fn.sym.magic == mEcho:
  1786. result = true
  1787. else:
  1788. # TODO check for n having sons? or just return false for now if not
  1789. if fn.typ != nil and fn.typ.n != nil and fn.typ.n[0].kind == nkSym:
  1790. result = false
  1791. else:
  1792. result = fn.typ != nil and fn.typ.n != nil and ((fn.typ.n[0].len < effectListLen) or
  1793. (fn.typ.n[0][exceptionEffects] != nil and
  1794. fn.typ.n[0][exceptionEffects].safeLen > 0))
  1795. proc toHumanStrImpl[T](kind: T, num: static int): string =
  1796. result = $kind
  1797. result = result[num..^1]
  1798. result[0] = result[0].toLowerAscii
  1799. proc toHumanStr*(kind: TSymKind): string =
  1800. ## strips leading `sk`
  1801. result = toHumanStrImpl(kind, 2)
  1802. proc toHumanStr*(kind: TTypeKind): string =
  1803. ## strips leading `tk`
  1804. result = toHumanStrImpl(kind, 2)
  1805. proc skipHiddenAddr*(n: PNode): PNode {.inline.} =
  1806. (if n.kind == nkHiddenAddr: n[0] else: n)
  1807. proc isNewStyleConcept*(n: PNode): bool {.inline.} =
  1808. assert n.kind == nkTypeClassTy
  1809. result = n[0].kind == nkEmpty
  1810. proc isOutParam*(t: PType): bool {.inline.} = tfIsOutParam in t.flags
  1811. const
  1812. nodesToIgnoreSet* = {nkNone..pred(nkSym), succ(nkSym)..nkNilLit,
  1813. nkTypeSection, nkProcDef, nkConverterDef,
  1814. nkMethodDef, nkIteratorDef, nkMacroDef, nkTemplateDef, nkLambda, nkDo,
  1815. nkFuncDef, nkConstSection, nkConstDef, nkIncludeStmt, nkImportStmt,
  1816. nkExportStmt, nkPragma, nkCommentStmt, nkBreakState,
  1817. nkTypeOfExpr, nkMixinStmt, nkBindStmt}
  1818. proc isTrue*(n: PNode): bool =
  1819. n.kind == nkSym and n.sym.kind == skEnumField and n.sym.position != 0 or
  1820. n.kind == nkIntLit and n.intVal != 0
  1821. type
  1822. TypeMapping* = Table[ItemId, PType]
  1823. SymMapping* = Table[ItemId, PSym]
  1824. template idTableGet*(tab: typed; key: PSym | PType): untyped = tab.getOrDefault(key.itemId)
  1825. template idTablePut*(tab: typed; key, val: PSym | PType) = tab[key.itemId] = val
  1826. template initSymMapping*(): Table[ItemId, PSym] = initTable[ItemId, PSym]()
  1827. template initTypeMapping*(): Table[ItemId, PType] = initTable[ItemId, PType]()
  1828. template resetIdTable*(tab: Table[ItemId, PSym]) = tab.clear()
  1829. template resetIdTable*(tab: Table[ItemId, PType]) = tab.clear()