ast.nim 78 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863186418651866186718681869187018711872187318741875187618771878187918801881188218831884188518861887188818891890189118921893189418951896189718981899190019011902190319041905190619071908190919101911191219131914191519161917191819191920192119221923192419251926192719281929193019311932193319341935193619371938193919401941194219431944194519461947194819491950195119521953195419551956195719581959196019611962196319641965196619671968196919701971197219731974197519761977197819791980198119821983198419851986198719881989199019911992199319941995199619971998199920002001200220032004200520062007200820092010201120122013201420152016201720182019202020212022202320242025202620272028202920302031203220332034203520362037203820392040204120422043204420452046204720482049205020512052205320542055205620572058205920602061206220632064206520662067206820692070207120722073207420752076207720782079208020812082208320842085208620872088208920902091209220932094209520962097209820992100210121022103210421052106210721082109211021112112211321142115211621172118211921202121212221232124212521262127212821292130213121322133
  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 # 53 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. sfNosinks, # symbol has a `nosinks` pragma
  46. sfImportc, # symbol is external; imported
  47. sfExportc, # symbol is exported (under a specified name)
  48. sfMangleCpp, # mangle as cpp (combines with `sfExportc`)
  49. sfVolatile, # variable is volatile
  50. sfRegister, # variable should be placed in a register
  51. sfPure, # object is "pure" that means it has no type-information
  52. # enum is "pure", its values need qualified access
  53. # variable is "pure"; it's an explicit "global"
  54. sfNoSideEffect, # proc has no side effects
  55. sfSideEffect, # proc may have side effects; cannot prove it has none
  56. sfMainModule, # module is the main module
  57. sfSystemModule, # module is the system module
  58. sfNoReturn, # proc never returns (an exit proc)
  59. sfAddrTaken, # the variable's address is taken (ex- or implicitly);
  60. # *OR*: a proc is indirectly called (used as first class)
  61. sfCompilerProc, # proc is a compiler proc, that is a C proc that is
  62. # needed for the code generator
  63. sfEscapes # param escapes
  64. # currently unimplemented
  65. sfDiscriminant, # field is a discriminant in a record/object
  66. sfRequiresInit, # field must be initialized during construction
  67. sfDeprecated, # symbol is deprecated
  68. sfExplain, # provide more diagnostics when this symbol is used
  69. sfError, # usage of symbol should trigger a compile-time error
  70. sfShadowed, # a symbol that was shadowed in some inner scope
  71. sfThread, # proc will run as a thread
  72. # variable is a thread variable
  73. sfCppNonPod, # tells compiler to treat such types as non-pod's, so that
  74. # `thread_local` is used instead of `__thread` for
  75. # {.threadvar.} + `--threads`. Only makes sense for importcpp types.
  76. # This has a performance impact so isn't set by default.
  77. sfCompileTime, # proc can be evaluated at compile time
  78. sfConstructor, # proc is a C++ constructor
  79. sfDispatcher, # copied method symbol is the dispatcher
  80. # deprecated and unused, except for the con
  81. sfBorrow, # proc is borrowed
  82. sfInfixCall, # symbol needs infix call syntax in target language;
  83. # for interfacing with C++, JS
  84. sfNamedParamCall, # symbol needs named parameter call syntax in target
  85. # language; for interfacing with Objective C
  86. sfDiscardable, # returned value may be discarded implicitly
  87. sfOverridden, # proc is overridden
  88. sfCallsite # A flag for template symbols to tell the
  89. # compiler it should use line information from
  90. # the calling side of the macro, not from the
  91. # implementation.
  92. sfGenSym # symbol is 'gensym'ed; do not add to symbol table
  93. sfNonReloadable # symbol will be left as-is when hot code reloading is on -
  94. # meaning that it won't be renamed and/or changed in any way
  95. sfGeneratedOp # proc is a generated '='; do not inject destructors in it
  96. # variable is generated closure environment; requires early
  97. # destruction for --newruntime.
  98. sfTemplateParam # symbol is a template parameter
  99. sfCursor # variable/field is a cursor, see RFC 177 for details
  100. sfInjectDestructors # whether the proc needs the 'injectdestructors' transformation
  101. sfNeverRaises # proc can never raise an exception, not even OverflowDefect
  102. # or out-of-memory
  103. sfSystemRaisesDefect # proc in the system can raise defects
  104. sfUsedInFinallyOrExcept # symbol is used inside an 'except' or 'finally'
  105. sfSingleUsedTemp # For temporaries that we know will only be used once
  106. sfNoalias # 'noalias' annotation, means C's 'restrict'
  107. # for templates and macros, means cannot be called
  108. # as a lone symbol (cannot use alias syntax)
  109. sfEffectsDelayed # an 'effectsDelayed' parameter
  110. sfGeneratedType # A anonymous generic type that is generated by the compiler for
  111. # objects that do not have generic parameters in case one of the
  112. # object fields has one.
  113. #
  114. # This is disallowed but can cause the typechecking to go into
  115. # an infinite loop, this flag is used as a sentinel to stop it.
  116. sfVirtual # proc is a C++ virtual function
  117. sfByCopy # param is marked as pass bycopy
  118. sfMember # proc is a C++ member of a type
  119. sfCodegenDecl # type, proc, global or proc param is marked as codegenDecl
  120. sfWasGenSym # symbol was 'gensym'ed
  121. sfForceLift # variable has to be lifted into closure environment
  122. TSymFlags* = set[TSymFlag]
  123. const
  124. sfNoInit* = sfMainModule # don't generate code to init the variable
  125. sfAllUntyped* = sfVolatile # macro or template is immediately expanded \
  126. # in a generic context
  127. sfDirty* = sfPure
  128. # template is not hygienic (old styled template)
  129. # module, compiled from a dirty-buffer
  130. sfAnon* = sfDiscardable
  131. # symbol name that was generated by the compiler
  132. # the compiler will avoid printing such names
  133. # in user messages.
  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. sfGoto* = sfOverridden # var is used for 'goto' code generation
  142. sfWrittenTo* = sfBorrow # param is assigned to
  143. # currently unimplemented
  144. sfBase* = sfDiscriminant
  145. sfCustomPragma* = sfRegister # symbol is custom pragma template
  146. sfTemplateRedefinition* = sfExportc # symbol is a redefinition of an earlier template
  147. sfCppMember* = { sfVirtual, sfMember, sfConstructor } # proc is a C++ member, meaning it will be attached to the type definition
  148. const
  149. # getting ready for the future expr/stmt merge
  150. nkWhen* = nkWhenStmt
  151. nkWhenExpr* = nkWhenStmt
  152. nkEffectList* = nkArgList
  153. # hacks ahead: an nkEffectList is a node with 4 children:
  154. exceptionEffects* = 0 # exceptions at position 0
  155. requiresEffects* = 1 # 'requires' annotation
  156. ensuresEffects* = 2 # 'ensures' annotation
  157. tagEffects* = 3 # user defined tag ('gc', 'time' etc.)
  158. pragmasEffects* = 4 # not an effect, but a slot for pragmas in proc type
  159. forbiddenEffects* = 5 # list of illegal effects
  160. effectListLen* = 6 # list of effects list
  161. nkLastBlockStmts* = {nkRaiseStmt, nkReturnStmt, nkBreakStmt, nkContinueStmt}
  162. # these must be last statements in a block
  163. type
  164. TTypeKind* = enum # order is important!
  165. # Don't forget to change hti.nim if you make a change here
  166. # XXX put this into an include file to avoid this issue!
  167. # several types are no longer used (guess which), but a
  168. # spot in the sequence is kept for backwards compatibility
  169. # (apparently something with bootstrapping)
  170. # if you need to add a type, they can apparently be reused
  171. tyNone, tyBool, tyChar,
  172. tyEmpty, tyAlias, tyNil, tyUntyped, tyTyped, tyTypeDesc,
  173. tyGenericInvocation, # ``T[a, b]`` for types to invoke
  174. tyGenericBody, # ``T[a, b, body]`` last parameter is the body
  175. tyGenericInst, # ``T[a, b, realInstance]`` instantiated generic type
  176. # realInstance will be a concrete type like tyObject
  177. # unless this is an instance of a generic alias type.
  178. # then realInstance will be the tyGenericInst of the
  179. # completely (recursively) resolved alias.
  180. tyGenericParam, # ``a`` in the above patterns
  181. tyDistinct,
  182. tyEnum,
  183. tyOrdinal, # integer types (including enums and boolean)
  184. tyArray,
  185. tyObject,
  186. tyTuple,
  187. tySet,
  188. tyRange,
  189. tyPtr, tyRef,
  190. tyVar,
  191. tySequence,
  192. tyProc,
  193. tyPointer, tyOpenArray,
  194. tyString, tyCstring, tyForward,
  195. tyInt, tyInt8, tyInt16, tyInt32, tyInt64, # signed integers
  196. tyFloat, tyFloat32, tyFloat64, tyFloat128,
  197. tyUInt, tyUInt8, tyUInt16, tyUInt32, tyUInt64,
  198. tyOwned, tySink, tyLent,
  199. tyVarargs,
  200. tyUncheckedArray
  201. # An array with boundaries [0,+∞]
  202. tyProxy # used as errornous type (for idetools)
  203. tyBuiltInTypeClass
  204. # Type such as the catch-all object, tuple, seq, etc
  205. tyUserTypeClass
  206. # the body of a user-defined type class
  207. tyUserTypeClassInst
  208. # Instance of a parametric user-defined type class.
  209. # Structured similarly to tyGenericInst.
  210. # tyGenericInst represents concrete types, while
  211. # this is still a "generic param" that will bind types
  212. # and resolves them during sigmatch and instantiation.
  213. tyCompositeTypeClass
  214. # Type such as seq[Number]
  215. # The notes for tyUserTypeClassInst apply here as well
  216. # sons[0]: the original expression used by the user.
  217. # sons[1]: fully expanded and instantiated meta type
  218. # (potentially following aliases)
  219. tyInferred
  220. # In the initial state `base` stores a type class constraining
  221. # the types that can be inferred. After a candidate type is
  222. # selected, it's stored in `last`. Between `base` and `last`
  223. # there may be 0, 2 or more types that were also considered as
  224. # possible candidates in the inference process (i.e. last will
  225. # be updated to store a type best conforming to all candidates)
  226. tyAnd, tyOr, tyNot
  227. # boolean type classes such as `string|int`,`not seq`,
  228. # `Sortable and Enumable`, etc
  229. tyAnything
  230. # a type class matching any type
  231. tyStatic
  232. # a value known at compile type (the underlying type is .base)
  233. tyFromExpr
  234. # This is a type representing an expression that depends
  235. # on generic parameters (the expression is stored in t.n)
  236. # It will be converted to a real type only during generic
  237. # instantiation and prior to this it has the potential to
  238. # be any type.
  239. tyConcept
  240. # new style concept.
  241. tyVoid
  242. # now different from tyEmpty, hurray!
  243. tyIterable
  244. static:
  245. # remind us when TTypeKind stops to fit in a single 64-bit word
  246. # assert TTypeKind.high.ord <= 63
  247. discard
  248. const
  249. tyPureObject* = tyTuple
  250. GcTypeKinds* = {tyRef, tySequence, tyString}
  251. tyError* = tyProxy # as an errornous node should match everything
  252. tyUnknown* = tyFromExpr
  253. tyUnknownTypes* = {tyError, tyFromExpr}
  254. tyTypeClasses* = {tyBuiltInTypeClass, tyCompositeTypeClass,
  255. tyUserTypeClass, tyUserTypeClassInst,
  256. tyAnd, tyOr, tyNot, tyAnything}
  257. tyMetaTypes* = {tyGenericParam, tyTypeDesc, tyUntyped} + tyTypeClasses
  258. tyUserTypeClasses* = {tyUserTypeClass, tyUserTypeClassInst}
  259. # consider renaming as `tyAbstractVarRange`
  260. abstractVarRange* = {tyGenericInst, tyRange, tyVar, tyDistinct, tyOrdinal,
  261. tyTypeDesc, tyAlias, tyInferred, tySink, tyOwned}
  262. abstractInst* = {tyGenericInst, tyDistinct, tyOrdinal, tyTypeDesc, tyAlias,
  263. tyInferred, tySink, tyOwned} # xxx what about tyStatic?
  264. type
  265. TTypeKinds* = set[TTypeKind]
  266. TNodeFlag* = enum
  267. nfNone,
  268. nfBase2, # nfBase10 is default, so not needed
  269. nfBase8,
  270. nfBase16,
  271. nfAllConst, # used to mark complex expressions constant; easy to get rid of
  272. # but unfortunately it has measurable impact for compilation
  273. # efficiency
  274. nfTransf, # node has been transformed
  275. nfNoRewrite # node should not be transformed anymore
  276. nfSem # node has been checked for semantics
  277. nfLL # node has gone through lambda lifting
  278. nfDotField # the call can use a dot operator
  279. nfDotSetter # the call can use a setter dot operarator
  280. nfExplicitCall # x.y() was used instead of x.y
  281. nfExprCall # this is an attempt to call a regular expression
  282. nfIsRef # this node is a 'ref' node; used for the VM
  283. nfIsPtr # this node is a 'ptr' node; used for the VM
  284. nfPreventCg # this node should be ignored by the codegen
  285. nfBlockArg # this a stmtlist appearing in a call (e.g. a do block)
  286. nfFromTemplate # a top-level node returned from a template
  287. nfDefaultParam # an automatically inserter default parameter
  288. nfDefaultRefsParam # a default param value references another parameter
  289. # the flag is applied to proc default values and to calls
  290. nfExecuteOnReload # A top-level statement that will be executed during reloads
  291. nfLastRead # this node is a last read
  292. nfFirstWrite # this node is a first write
  293. nfHasComment # node has a comment
  294. nfSkipFieldChecking # node skips field visable checking
  295. nfOpenSym # node is a captured sym but can be overriden by local symbols
  296. TNodeFlags* = set[TNodeFlag]
  297. TTypeFlag* = enum # keep below 32 for efficiency reasons (now: 47)
  298. tfVarargs, # procedure has C styled varargs
  299. # tyArray type represeting a varargs list
  300. tfNoSideEffect, # procedure type does not allow side effects
  301. tfFinal, # is the object final?
  302. tfInheritable, # is the object inheritable?
  303. tfHasOwned, # type contains an 'owned' type and must be moved
  304. tfEnumHasHoles, # enum cannot be mapped into a range
  305. tfShallow, # type can be shallow copied on assignment
  306. tfThread, # proc type is marked as ``thread``; alias for ``gcsafe``
  307. tfFromGeneric, # type is an instantiation of a generic; this is needed
  308. # because for instantiations of objects, structural
  309. # type equality has to be used
  310. tfUnresolved, # marks unresolved typedesc/static params: e.g.
  311. # proc foo(T: typedesc, list: seq[T]): var T
  312. # proc foo(L: static[int]): array[L, int]
  313. # can be attached to ranges to indicate that the range
  314. # can be attached to generic procs with free standing
  315. # type parameters: e.g. proc foo[T]()
  316. # depends on unresolved static params.
  317. tfResolved # marks a user type class, after it has been bound to a
  318. # concrete type (lastSon becomes the concrete type)
  319. tfRetType, # marks return types in proc (used to detect type classes
  320. # used as return types for return type inference)
  321. tfCapturesEnv, # whether proc really captures some environment
  322. tfByCopy, # pass object/tuple by copy (C backend)
  323. tfByRef, # pass object/tuple by reference (C backend)
  324. tfIterator, # type is really an iterator, not a tyProc
  325. tfPartial, # type is declared as 'partial'
  326. tfNotNil, # type cannot be 'nil'
  327. tfRequiresInit, # type contains a "not nil" constraint somewhere or
  328. # a `requiresInit` field, so the default zero init
  329. # is not appropriate
  330. tfNeedsFullInit, # object type marked with {.requiresInit.}
  331. # all fields must be initialized
  332. tfVarIsPtr, # 'var' type is translated like 'ptr' even in C++ mode
  333. tfHasMeta, # type contains "wildcard" sub-types such as generic params
  334. # or other type classes
  335. tfHasGCedMem, # type contains GC'ed memory
  336. tfPacked
  337. tfHasStatic
  338. tfGenericTypeParam
  339. tfImplicitTypeParam
  340. tfInferrableStatic
  341. tfConceptMatchedTypeSym
  342. tfExplicit # for typedescs, marks types explicitly prefixed with the
  343. # `type` operator (e.g. type int)
  344. tfWildcard # consider a proc like foo[T, I](x: Type[T, I])
  345. # T and I here can bind to both typedesc and static types
  346. # before this is determined, we'll consider them to be a
  347. # wildcard type.
  348. tfHasAsgn # type has overloaded assignment operator
  349. tfBorrowDot # distinct type borrows '.'
  350. tfTriggersCompileTime # uses the NimNode type which make the proc
  351. # implicitly '.compiletime'
  352. tfRefsAnonObj # used for 'ref object' and 'ptr object'
  353. tfCovariant # covariant generic param mimicking a ptr type
  354. tfWeakCovariant # covariant generic param mimicking a seq/array type
  355. tfContravariant # contravariant generic param
  356. tfCheckedForDestructor # type was checked for having a destructor.
  357. # If it has one, t.destructor is not nil.
  358. tfAcyclic # object type was annotated as .acyclic
  359. tfIncompleteStruct # treat this type as if it had sizeof(pointer)
  360. tfCompleteStruct
  361. # (for importc types); type is fully specified, allowing to compute
  362. # sizeof, alignof, offsetof at CT
  363. tfExplicitCallConv
  364. tfIsConstructor
  365. tfEffectSystemWorkaround
  366. tfIsOutParam
  367. tfSendable
  368. tfImplicitStatic
  369. TTypeFlags* = set[TTypeFlag]
  370. TSymKind* = enum # the different symbols (start with the prefix sk);
  371. # order is important for the documentation generator!
  372. skUnknown, # unknown symbol: used for parsing assembler blocks
  373. # and first phase symbol lookup in generics
  374. skConditional, # symbol for the preprocessor (may become obsolete)
  375. skDynLib, # symbol represents a dynamic library; this is used
  376. # internally; it does not exist in Nim code
  377. skParam, # a parameter
  378. skGenericParam, # a generic parameter; eq in ``proc x[eq=`==`]()``
  379. skTemp, # a temporary variable (introduced by compiler)
  380. skModule, # module identifier
  381. skType, # a type
  382. skVar, # a variable
  383. skLet, # a 'let' symbol
  384. skConst, # a constant
  385. skResult, # special 'result' variable
  386. skProc, # a proc
  387. skFunc, # a func
  388. skMethod, # a method
  389. skIterator, # an iterator
  390. skConverter, # a type converter
  391. skMacro, # a macro
  392. skTemplate, # a template; currently also misused for user-defined
  393. # pragmas
  394. skField, # a field in a record or object
  395. skEnumField, # an identifier in an enum
  396. skForVar, # a for loop variable
  397. skLabel, # a label (for block statement)
  398. skStub, # symbol is a stub and not yet loaded from the ROD
  399. # file (it is loaded on demand, which may
  400. # mean: never)
  401. skPackage, # symbol is a package (used for canonicalization)
  402. TSymKinds* = set[TSymKind]
  403. const
  404. routineKinds* = {skProc, skFunc, skMethod, skIterator,
  405. skConverter, skMacro, skTemplate}
  406. ExportableSymKinds* = {skVar, skLet, skConst, skType, skEnumField, skStub} + routineKinds
  407. tfUnion* = tfNoSideEffect
  408. tfGcSafe* = tfThread
  409. tfObjHasKids* = tfEnumHasHoles
  410. tfReturnsNew* = tfInheritable
  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,
  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,
  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. typ*: 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. r*: Rope # rope value 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. owner*: 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. owner*: 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. type Gconfig = object
  744. # we put comments in a side channel to avoid increasing `sizeof(TNode)`, which
  745. # reduces memory usage given that `PNode` is the most allocated type by far.
  746. comments: Table[int, string] # nodeId => comment
  747. useIc*: bool
  748. var gconfig {.threadvar.}: Gconfig
  749. proc setUseIc*(useIc: bool) = gconfig.useIc = useIc
  750. proc comment*(n: PNode): string =
  751. if nfHasComment in n.flags and not gconfig.useIc:
  752. # IC doesn't track comments, see `packed_ast`, so this could fail
  753. result = gconfig.comments[n.nodeId]
  754. else:
  755. result = ""
  756. proc `comment=`*(n: PNode, a: string) =
  757. let id = n.nodeId
  758. if a.len > 0:
  759. # if needed, we could periodically cleanup gconfig.comments when its size increases,
  760. # to ensure only live nodes (and with nfHasComment) have an entry in gconfig.comments;
  761. # for compiling compiler, the waste is very small:
  762. # num calls to newNodeImpl: 14984160 (num of PNode allocations)
  763. # size of gconfig.comments: 33585
  764. # num of nodes with comments that were deleted and hence wasted: 3081
  765. n.flags.incl nfHasComment
  766. gconfig.comments[id] = a
  767. elif nfHasComment in n.flags:
  768. n.flags.excl nfHasComment
  769. gconfig.comments.del(id)
  770. # BUGFIX: a module is overloadable so that a proc can have the
  771. # same name as an imported module. This is necessary because of
  772. # the poor naming choices in the standard library.
  773. const
  774. OverloadableSyms* = {skProc, skFunc, skMethod, skIterator,
  775. skConverter, skModule, skTemplate, skMacro, skEnumField}
  776. GenericTypes*: TTypeKinds = {tyGenericInvocation, tyGenericBody,
  777. tyGenericParam}
  778. StructuralEquivTypes*: TTypeKinds = {tyNil, tyTuple, tyArray,
  779. tySet, tyRange, tyPtr, tyRef, tyVar, tyLent, tySequence, tyProc, tyOpenArray,
  780. tyVarargs}
  781. ConcreteTypes*: TTypeKinds = { # types of the expr that may occur in::
  782. # var x = expr
  783. tyBool, tyChar, tyEnum, tyArray, tyObject,
  784. tySet, tyTuple, tyRange, tyPtr, tyRef, tyVar, tyLent, tySequence, tyProc,
  785. tyPointer,
  786. tyOpenArray, tyString, tyCstring, tyInt..tyInt64, tyFloat..tyFloat128,
  787. tyUInt..tyUInt64}
  788. IntegralTypes* = {tyBool, tyChar, tyEnum, tyInt..tyInt64,
  789. tyFloat..tyFloat128, tyUInt..tyUInt64} # weird name because it contains tyFloat
  790. ConstantDataTypes*: TTypeKinds = {tyArray, tySet,
  791. tyTuple, tySequence}
  792. NilableTypes*: TTypeKinds = {tyPointer, tyCstring, tyRef, tyPtr,
  793. tyProc, tyError} # TODO
  794. PtrLikeKinds*: TTypeKinds = {tyPointer, tyPtr} # for VM
  795. PersistentNodeFlags*: TNodeFlags = {nfBase2, nfBase8, nfBase16,
  796. nfDotSetter, nfDotField,
  797. nfIsRef, nfIsPtr, nfPreventCg, nfLL,
  798. nfFromTemplate, nfDefaultRefsParam,
  799. nfExecuteOnReload, nfLastRead,
  800. nfFirstWrite, nfSkipFieldChecking,
  801. nfOpenSym}
  802. namePos* = 0
  803. patternPos* = 1 # empty except for term rewriting macros
  804. genericParamsPos* = 2
  805. paramsPos* = 3
  806. pragmasPos* = 4
  807. miscPos* = 5 # used for undocumented and hacky stuff
  808. bodyPos* = 6 # position of body; use rodread.getBody() instead!
  809. resultPos* = 7
  810. dispatcherPos* = 8
  811. nfAllFieldsSet* = nfBase2
  812. nkIdentKinds* = {nkIdent, nkSym, nkAccQuoted, nkOpenSymChoice,
  813. nkClosedSymChoice}
  814. nkPragmaCallKinds* = {nkExprColonExpr, nkCall, nkCallStrLit}
  815. nkLiterals* = {nkCharLit..nkTripleStrLit}
  816. nkFloatLiterals* = {nkFloatLit..nkFloat128Lit}
  817. nkLambdaKinds* = {nkLambda, nkDo}
  818. declarativeDefs* = {nkProcDef, nkFuncDef, nkMethodDef, nkIteratorDef, nkConverterDef}
  819. routineDefs* = declarativeDefs + {nkMacroDef, nkTemplateDef}
  820. procDefs* = nkLambdaKinds + declarativeDefs
  821. callableDefs* = nkLambdaKinds + routineDefs
  822. nkSymChoices* = {nkClosedSymChoice, nkOpenSymChoice}
  823. nkStrKinds* = {nkStrLit..nkTripleStrLit}
  824. skLocalVars* = {skVar, skLet, skForVar, skParam, skResult}
  825. skProcKinds* = {skProc, skFunc, skTemplate, skMacro, skIterator,
  826. skMethod, skConverter}
  827. defaultSize = -1
  828. defaultAlignment = -1
  829. defaultOffset* = -1
  830. proc getPIdent*(a: PNode): PIdent {.inline.} =
  831. ## Returns underlying `PIdent` for `{nkSym, nkIdent}`, or `nil`.
  832. case a.kind
  833. of nkSym: a.sym.name
  834. of nkIdent: a.ident
  835. of nkOpenSymChoice, nkClosedSymChoice: a.sons[0].sym.name
  836. else: nil
  837. const
  838. moduleShift = when defined(cpu32): 20 else: 24
  839. template id*(a: PType | PSym): int =
  840. let x = a
  841. (x.itemId.module.int shl moduleShift) + x.itemId.item.int
  842. type
  843. IdGenerator* = ref object # unfortunately, we really need the 'shared mutable' aspect here.
  844. module*: int32
  845. symId*: int32
  846. typeId*: int32
  847. sealed*: bool
  848. disambTable*: CountTable[PIdent]
  849. const
  850. PackageModuleId* = -3'i32
  851. proc idGeneratorFromModule*(m: PSym): IdGenerator =
  852. assert m.kind == skModule
  853. result = IdGenerator(module: m.itemId.module, symId: m.itemId.item, typeId: 0, disambTable: initCountTable[PIdent]())
  854. proc idGeneratorForPackage*(nextIdWillBe: int32): IdGenerator =
  855. result = IdGenerator(module: PackageModuleId, symId: nextIdWillBe - 1'i32, typeId: 0, disambTable: initCountTable[PIdent]())
  856. proc nextSymId(x: IdGenerator): ItemId {.inline.} =
  857. assert(not x.sealed)
  858. inc x.symId
  859. result = ItemId(module: x.module, item: x.symId)
  860. proc nextTypeId*(x: IdGenerator): ItemId {.inline.} =
  861. assert(not x.sealed)
  862. inc x.typeId
  863. result = ItemId(module: x.module, item: x.typeId)
  864. when false:
  865. proc nextId*(x: IdGenerator): ItemId {.inline.} =
  866. inc x.item
  867. result = x[]
  868. when false:
  869. proc storeBack*(dest: var IdGenerator; src: IdGenerator) {.inline.} =
  870. assert dest.ItemId.module == src.ItemId.module
  871. if dest.ItemId.item > src.ItemId.item:
  872. echo dest.ItemId.item, " ", src.ItemId.item, " ", src.ItemId.module
  873. assert dest.ItemId.item <= src.ItemId.item
  874. dest = src
  875. var ggDebug* {.deprecated.}: bool ## convenience switch for trying out things
  876. proc isCallExpr*(n: PNode): bool =
  877. result = n.kind in nkCallKinds
  878. proc discardSons*(father: PNode)
  879. proc len*(n: PNode): int {.inline.} =
  880. result = n.sons.len
  881. proc safeLen*(n: PNode): int {.inline.} =
  882. ## works even for leaves.
  883. if n.kind in {nkNone..nkNilLit}: result = 0
  884. else: result = n.len
  885. proc safeArrLen*(n: PNode): int {.inline.} =
  886. ## works for array-like objects (strings passed as openArray in VM).
  887. if n.kind in {nkStrLit..nkTripleStrLit}: result = n.strVal.len
  888. elif n.kind in {nkNone..nkFloat128Lit}: result = 0
  889. else: result = n.len
  890. proc add*(father, son: PNode) =
  891. assert son != nil
  892. father.sons.add(son)
  893. proc addAllowNil*(father, son: PNode) {.inline.} =
  894. father.sons.add(son)
  895. template `[]`*(n: PNode, i: int): PNode = n.sons[i]
  896. template `[]=`*(n: PNode, i: int; x: PNode) = n.sons[i] = x
  897. template `[]`*(n: PNode, i: BackwardsIndex): PNode = n[n.len - i.int]
  898. template `[]=`*(n: PNode, i: BackwardsIndex; x: PNode) = n[n.len - i.int] = x
  899. proc add*(father, son: PType) =
  900. assert son != nil
  901. father.sons.add(son)
  902. proc addAllowNil*(father, son: PType) {.inline.} =
  903. father.sons.add(son)
  904. template `[]`*(n: PType, i: int): PType = n.sons[i]
  905. template `[]=`*(n: PType, i: int; x: PType) = n.sons[i] = x
  906. template `[]`*(n: PType, i: BackwardsIndex): PType = n[n.len - i.int]
  907. template `[]=`*(n: PType, i: BackwardsIndex; x: PType) = n[n.len - i.int] = x
  908. proc getDeclPragma*(n: PNode): PNode =
  909. ## return the `nkPragma` node for declaration `n`, or `nil` if no pragma was found.
  910. ## Currently only supports routineDefs + {nkTypeDef}.
  911. case n.kind
  912. of routineDefs:
  913. if n[pragmasPos].kind != nkEmpty: result = n[pragmasPos]
  914. else: result = nil
  915. of nkTypeDef:
  916. #[
  917. type F3*{.deprecated: "x3".} = int
  918. TypeSection
  919. TypeDef
  920. PragmaExpr
  921. Postfix
  922. Ident "*"
  923. Ident "F3"
  924. Pragma
  925. ExprColonExpr
  926. Ident "deprecated"
  927. StrLit "x3"
  928. Empty
  929. Ident "int"
  930. ]#
  931. if n[0].kind == nkPragmaExpr:
  932. result = n[0][1]
  933. else:
  934. result = nil
  935. else:
  936. # support as needed for `nkIdentDefs` etc.
  937. result = nil
  938. if result != nil:
  939. assert result.kind == nkPragma, $(result.kind, n.kind)
  940. proc extractPragma*(s: PSym): PNode =
  941. ## gets the pragma node of routine/type/var/let/const symbol `s`
  942. if s.kind in routineKinds:
  943. result = s.ast[pragmasPos]
  944. elif s.kind in {skType, skVar, skLet, skConst}:
  945. if s.ast != nil and s.ast.len > 0:
  946. if s.ast[0].kind == nkPragmaExpr and s.ast[0].len > 1:
  947. # s.ast = nkTypedef / nkPragmaExpr / [nkSym, nkPragma]
  948. result = s.ast[0][1]
  949. else:
  950. result = nil
  951. else:
  952. result = nil
  953. else:
  954. result = nil
  955. assert result == nil or result.kind == nkPragma
  956. proc skipPragmaExpr*(n: PNode): PNode =
  957. ## if pragma expr, give the node the pragmas are applied to,
  958. ## otherwise give node itself
  959. if n.kind == nkPragmaExpr:
  960. result = n[0]
  961. else:
  962. result = n
  963. proc setInfoRecursive*(n: PNode, info: TLineInfo) =
  964. ## set line info recursively
  965. if n != nil:
  966. for i in 0..<n.safeLen: setInfoRecursive(n[i], info)
  967. n.info = info
  968. when defined(useNodeIds):
  969. const nodeIdToDebug* = -1 # 2322968
  970. var gNodeId: int
  971. template newNodeImpl(info2) =
  972. result = PNode(kind: kind, info: info2)
  973. when false:
  974. # this would add overhead, so we skip it; it results in a small amount of leaked entries
  975. # for old PNode that gets re-allocated at the same address as a PNode that
  976. # has `nfHasComment` set (and an entry in that table). Only `nfHasComment`
  977. # should be used to test whether a PNode has a comment; gconfig.comments
  978. # can contain extra entries for deleted PNode's with comments.
  979. gconfig.comments.del(cast[int](result))
  980. template setIdMaybe() =
  981. when defined(useNodeIds):
  982. result.id = gNodeId
  983. if result.id == nodeIdToDebug:
  984. echo "KIND ", result.kind
  985. writeStackTrace()
  986. inc gNodeId
  987. proc newNode*(kind: TNodeKind): PNode =
  988. ## new node with unknown line info, no type, and no children
  989. newNodeImpl(unknownLineInfo)
  990. setIdMaybe()
  991. proc newNodeI*(kind: TNodeKind, info: TLineInfo): PNode =
  992. ## new node with line info, no type, and no children
  993. newNodeImpl(info)
  994. setIdMaybe()
  995. proc newNodeI*(kind: TNodeKind, info: TLineInfo, children: int): PNode =
  996. ## new node with line info, type, and children
  997. newNodeImpl(info)
  998. if children > 0:
  999. newSeq(result.sons, children)
  1000. setIdMaybe()
  1001. proc newNodeIT*(kind: TNodeKind, info: TLineInfo, typ: PType): PNode =
  1002. ## new node with line info, type, and no children
  1003. result = newNode(kind)
  1004. result.info = info
  1005. result.typ = typ
  1006. proc newNode*(kind: TNodeKind, info: TLineInfo): PNode =
  1007. ## new node with line info, no type, and no children
  1008. newNodeImpl(info)
  1009. setIdMaybe()
  1010. proc newAtom*(ident: PIdent, info: TLineInfo): PNode =
  1011. result = newNode(nkIdent, info)
  1012. result.ident = ident
  1013. proc newAtom*(kind: TNodeKind, intVal: BiggestInt, info: TLineInfo): PNode =
  1014. result = newNode(kind, info)
  1015. result.intVal = intVal
  1016. proc newAtom*(kind: TNodeKind, floatVal: BiggestFloat, info: TLineInfo): PNode =
  1017. result = newNode(kind, info)
  1018. result.floatVal = floatVal
  1019. proc newAtom*(kind: TNodeKind; strVal: sink string; info: TLineInfo): PNode =
  1020. result = newNode(kind, info)
  1021. result.strVal = strVal
  1022. proc newTree*(kind: TNodeKind; info: TLineInfo; children: varargs[PNode]): PNode =
  1023. result = newNodeI(kind, info)
  1024. if children.len > 0:
  1025. result.info = children[0].info
  1026. result.sons = @children
  1027. proc newTree*(kind: TNodeKind; children: varargs[PNode]): PNode =
  1028. result = newNode(kind)
  1029. if children.len > 0:
  1030. result.info = children[0].info
  1031. result.sons = @children
  1032. proc newTreeI*(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 newTreeIT*(kind: TNodeKind; info: TLineInfo; typ: PType; children: varargs[PNode]): PNode =
  1038. result = newNodeIT(kind, info, typ)
  1039. if children.len > 0:
  1040. result.info = children[0].info
  1041. result.sons = @children
  1042. template previouslyInferred*(t: PType): PType =
  1043. if t.sons.len > 1: t.last else: nil
  1044. when false:
  1045. import tables, strutils
  1046. var x: CountTable[string]
  1047. addQuitProc proc () {.noconv.} =
  1048. for k, v in pairs(x):
  1049. echo k
  1050. echo v
  1051. proc newSym*(symKind: TSymKind, name: PIdent, idgen: IdGenerator; owner: PSym,
  1052. info: TLineInfo; options: TOptions = {}): PSym =
  1053. # generates a symbol and initializes the hash field too
  1054. assert not name.isNil
  1055. let id = nextSymId idgen
  1056. result = PSym(name: name, kind: symKind, flags: {}, info: info, itemId: id,
  1057. options: options, owner: owner, offset: defaultOffset,
  1058. disamb: getOrDefault(idgen.disambTable, name).int32)
  1059. idgen.disambTable.inc name
  1060. when false:
  1061. if id.module == 48 and id.item == 39:
  1062. writeStackTrace()
  1063. echo "kind ", symKind, " ", name.s
  1064. if owner != nil: echo owner.name.s
  1065. proc astdef*(s: PSym): PNode =
  1066. # get only the definition (initializer) portion of the ast
  1067. if s.ast != nil and s.ast.kind in {nkIdentDefs, nkConstDef}:
  1068. s.ast[2]
  1069. else:
  1070. s.ast
  1071. proc isMetaType*(t: PType): bool =
  1072. return t.kind in tyMetaTypes or
  1073. (t.kind == tyStatic and t.n == nil) or
  1074. tfHasMeta in t.flags
  1075. proc isUnresolvedStatic*(t: PType): bool =
  1076. return t.kind == tyStatic and t.n == nil
  1077. proc linkTo*(t: PType, s: PSym): PType {.discardable.} =
  1078. t.sym = s
  1079. s.typ = t
  1080. result = t
  1081. proc linkTo*(s: PSym, t: PType): PSym {.discardable.} =
  1082. t.sym = s
  1083. s.typ = t
  1084. result = s
  1085. template fileIdx*(c: PSym): FileIndex =
  1086. # XXX: this should be used only on module symbols
  1087. c.position.FileIndex
  1088. template filename*(c: PSym): string =
  1089. # XXX: this should be used only on module symbols
  1090. c.position.FileIndex.toFilename
  1091. proc appendToModule*(m: PSym, n: PNode) =
  1092. ## The compiler will use this internally to add nodes that will be
  1093. ## appended to the module after the sem pass
  1094. if m.ast == nil:
  1095. m.ast = newNode(nkStmtList)
  1096. m.ast.sons = @[n]
  1097. else:
  1098. assert m.ast.kind == nkStmtList
  1099. m.ast.sons.add(n)
  1100. const # for all kind of hash tables:
  1101. GrowthFactor* = 2 # must be power of 2, > 0
  1102. StartSize* = 8 # must be power of 2, > 0
  1103. proc copyStrTable*(dest: var TStrTable, src: TStrTable) =
  1104. dest.counter = src.counter
  1105. setLen(dest.data, src.data.len)
  1106. for i in 0..high(src.data): dest.data[i] = src.data[i]
  1107. proc copyObjectSet*(dest: var TObjectSet, src: TObjectSet) =
  1108. dest.counter = src.counter
  1109. setLen(dest.data, src.data.len)
  1110. for i in 0..high(src.data): dest.data[i] = src.data[i]
  1111. proc discardSons*(father: PNode) =
  1112. father.sons = @[]
  1113. proc withInfo*(n: PNode, info: TLineInfo): PNode =
  1114. n.info = info
  1115. return n
  1116. proc newIdentNode*(ident: PIdent, info: TLineInfo): PNode =
  1117. result = newNode(nkIdent)
  1118. result.ident = ident
  1119. result.info = info
  1120. proc newSymNode*(sym: PSym): PNode =
  1121. result = newNode(nkSym)
  1122. result.sym = sym
  1123. result.typ = sym.typ
  1124. result.info = sym.info
  1125. proc newSymNode*(sym: PSym, info: TLineInfo): PNode =
  1126. result = newNode(nkSym)
  1127. result.sym = sym
  1128. result.typ = sym.typ
  1129. result.info = info
  1130. proc newIntNode*(kind: TNodeKind, intVal: BiggestInt): PNode =
  1131. result = newNode(kind)
  1132. result.intVal = intVal
  1133. proc newIntNode*(kind: TNodeKind, intVal: Int128): PNode =
  1134. result = newNode(kind)
  1135. result.intVal = castToInt64(intVal)
  1136. proc lastSon*(n: PNode): PNode {.inline.} = n.sons[^1]
  1137. template setLastSon*(n: PNode, s: PNode) = n.sons[^1] = s
  1138. template firstSon*(n: PNode): PNode = n.sons[0]
  1139. template secondSon*(n: PNode): PNode = n.sons[1]
  1140. template hasSon*(n: PNode): bool = n.len > 0
  1141. template has2Sons*(n: PNode): bool = n.len > 1
  1142. proc replaceFirstSon*(n, newson: PNode) {.inline.} =
  1143. n.sons[0] = newson
  1144. proc replaceSon*(n: PNode; i: int; newson: PNode) {.inline.} =
  1145. n.sons[i] = newson
  1146. proc last*(n: PType): PType {.inline.} = n.sons[^1]
  1147. proc elementType*(n: PType): PType {.inline.} = n.sons[^1]
  1148. proc skipModifier*(n: PType): PType {.inline.} = n.sons[^1]
  1149. proc indexType*(n: PType): PType {.inline.} = n.sons[0]
  1150. proc baseClass*(n: PType): PType {.inline.} = n.sons[0]
  1151. proc base*(t: PType): PType {.inline.} =
  1152. result = t.sons[0]
  1153. proc returnType*(n: PType): PType {.inline.} = n.sons[0]
  1154. proc setReturnType*(n, r: PType) {.inline.} = n.sons[0] = r
  1155. proc setIndexType*(n, idx: PType) {.inline.} = n.sons[0] = idx
  1156. proc firstParamType*(n: PType): PType {.inline.} = n.sons[1]
  1157. proc firstGenericParam*(n: PType): PType {.inline.} = n.sons[1]
  1158. proc typeBodyImpl*(n: PType): PType {.inline.} = n.sons[^1]
  1159. proc genericHead*(n: PType): PType {.inline.} = n.sons[0]
  1160. proc skipTypes*(t: PType, kinds: TTypeKinds): PType =
  1161. ## Used throughout the compiler code to test whether a type tree contains or
  1162. ## doesn't contain a specific type/types - it is often the case that only the
  1163. ## last child nodes of a type tree need to be searched. This is a really hot
  1164. ## path within the compiler!
  1165. result = t
  1166. while result.kind in kinds: result = last(result)
  1167. proc newIntTypeNode*(intVal: BiggestInt, typ: PType): PNode =
  1168. let kind = skipTypes(typ, abstractVarRange).kind
  1169. case kind
  1170. of tyInt: result = newNode(nkIntLit)
  1171. of tyInt8: result = newNode(nkInt8Lit)
  1172. of tyInt16: result = newNode(nkInt16Lit)
  1173. of tyInt32: result = newNode(nkInt32Lit)
  1174. of tyInt64: result = newNode(nkInt64Lit)
  1175. of tyChar: result = newNode(nkCharLit)
  1176. of tyUInt: result = newNode(nkUIntLit)
  1177. of tyUInt8: result = newNode(nkUInt8Lit)
  1178. of tyUInt16: result = newNode(nkUInt16Lit)
  1179. of tyUInt32: result = newNode(nkUInt32Lit)
  1180. of tyUInt64: result = newNode(nkUInt64Lit)
  1181. of tyBool, tyEnum:
  1182. # XXX: does this really need to be the kind nkIntLit?
  1183. result = newNode(nkIntLit)
  1184. of tyStatic: # that's a pre-existing bug, will fix in another PR
  1185. result = newNode(nkIntLit)
  1186. else: raiseAssert $kind
  1187. result.intVal = intVal
  1188. result.typ = typ
  1189. proc newIntTypeNode*(intVal: Int128, typ: PType): PNode =
  1190. # XXX: introduce range check
  1191. newIntTypeNode(castToInt64(intVal), typ)
  1192. proc newFloatNode*(kind: TNodeKind, floatVal: BiggestFloat): PNode =
  1193. result = newNode(kind)
  1194. result.floatVal = floatVal
  1195. proc newStrNode*(kind: TNodeKind, strVal: string): PNode =
  1196. result = newNode(kind)
  1197. result.strVal = strVal
  1198. proc newStrNode*(strVal: string; info: TLineInfo): PNode =
  1199. result = newNodeI(nkStrLit, info)
  1200. result.strVal = strVal
  1201. proc newProcNode*(kind: TNodeKind, info: TLineInfo, body: PNode,
  1202. params,
  1203. name, pattern, genericParams,
  1204. pragmas, exceptions: PNode): PNode =
  1205. result = newNodeI(kind, info)
  1206. result.sons = @[name, pattern, genericParams, params,
  1207. pragmas, exceptions, body]
  1208. const
  1209. AttachedOpToStr*: array[TTypeAttachedOp, string] = [
  1210. "=wasMoved", "=destroy", "=copy", "=dup", "=sink", "=trace", "=deepcopy"]
  1211. proc `$`*(s: PSym): string =
  1212. if s != nil:
  1213. result = s.name.s & "@" & $s.id
  1214. else:
  1215. result = "<nil>"
  1216. when false:
  1217. iterator items*(t: PType): PType =
  1218. for i in 0..<t.sons.len: yield t.sons[i]
  1219. iterator pairs*(n: PType): tuple[i: int, n: PType] =
  1220. for i in 0..<n.sons.len: yield (i, n.sons[i])
  1221. when true:
  1222. proc len*(n: PType): int {.inline.} =
  1223. result = n.sons.len
  1224. proc sameTupleLengths*(a, b: PType): bool {.inline.} =
  1225. result = a.sons.len == b.sons.len
  1226. iterator tupleTypePairs*(a, b: PType): (int, PType, PType) =
  1227. for i in 0 ..< a.sons.len:
  1228. yield (i, a.sons[i], b.sons[i])
  1229. iterator underspecifiedPairs*(a, b: PType; start = 0; without = 0): (PType, PType) =
  1230. # XXX Figure out with what typekinds this is called.
  1231. for i in start ..< min(a.sons.len, b.sons.len) + without:
  1232. yield (a.sons[i], b.sons[i])
  1233. proc signatureLen*(t: PType): int {.inline.} =
  1234. result = t.sons.len
  1235. proc paramsLen*(t: PType): int {.inline.} =
  1236. result = t.sons.len - 1
  1237. proc genericParamsLen*(t: PType): int {.inline.} =
  1238. assert t.kind == tyGenericInst
  1239. result = t.sons.len - 2 # without 'head' and 'body'
  1240. proc genericInvocationParamsLen*(t: PType): int {.inline.} =
  1241. assert t.kind == tyGenericInvocation
  1242. result = t.sons.len - 1 # without 'head'
  1243. proc kidsLen*(t: PType): int {.inline.} =
  1244. result = t.sons.len
  1245. proc genericParamHasConstraints*(t: PType): bool {.inline.} = t.sons.len > 0
  1246. proc hasElementType*(t: PType): bool {.inline.} = t.sons.len > 0
  1247. proc isEmptyTupleType*(t: PType): bool {.inline.} = t.sons.len == 0
  1248. proc isSingletonTupleType*(t: PType): bool {.inline.} = t.sons.len == 1
  1249. proc genericConstraint*(t: PType): PType {.inline.} = t.sons[0]
  1250. iterator genericInstParams*(t: PType): (bool, PType) =
  1251. for i in 1..<t.sons.len-1:
  1252. yield (i!=1, t.sons[i])
  1253. iterator genericInstParamPairs*(a, b: PType): (int, PType, PType) =
  1254. for i in 1..<min(a.sons.len, b.sons.len)-1:
  1255. yield (i-1, a.sons[i], b.sons[i])
  1256. iterator genericInvocationParams*(t: PType): (bool, PType) =
  1257. for i in 1..<t.sons.len:
  1258. yield (i!=1, t.sons[i])
  1259. iterator genericInvocationAndBodyElements*(a, b: PType): (PType, PType) =
  1260. for i in 1..<a.sons.len:
  1261. yield (a.sons[i], b.sons[i-1])
  1262. iterator genericInvocationParamPairs*(a, b: PType): (bool, PType, PType) =
  1263. for i in 1..<a.sons.len:
  1264. if i >= b.sons.len:
  1265. yield (false, nil, nil)
  1266. else:
  1267. yield (true, a.sons[i], b.sons[i])
  1268. iterator genericBodyParams*(t: PType): (int, PType) =
  1269. for i in 0..<t.sons.len-1:
  1270. yield (i, t.sons[i])
  1271. iterator userTypeClassInstParams*(t: PType): (bool, PType) =
  1272. for i in 1..<t.sons.len-1:
  1273. yield (i!=1, t.sons[i])
  1274. iterator ikids*(t: PType): (int, PType) =
  1275. for i in 0..<t.sons.len: yield (i, t.sons[i])
  1276. const
  1277. FirstParamAt* = 1
  1278. FirstGenericParamAt* = 1
  1279. iterator paramTypes*(t: PType): (int, PType) =
  1280. for i in FirstParamAt..<t.sons.len: yield (i, t.sons[i])
  1281. iterator paramTypePairs*(a, b: PType): (PType, PType) =
  1282. for i in FirstParamAt..<a.sons.len: yield (a.sons[i], b.sons[i])
  1283. template paramTypeToNodeIndex*(x: int): int = x
  1284. iterator kids*(t: PType): PType =
  1285. for i in 0..<t.sons.len: yield t.sons[i]
  1286. iterator signature*(t: PType): PType =
  1287. # yields return type + parameter types
  1288. for i in 0..<t.sons.len: yield t.sons[i]
  1289. proc newType*(kind: TTypeKind; idgen: IdGenerator; owner: PSym; son: sink PType = nil): PType =
  1290. let id = nextTypeId idgen
  1291. result = PType(kind: kind, owner: owner, size: defaultSize,
  1292. align: defaultAlignment, itemId: id,
  1293. uniqueId: id, sons: @[])
  1294. if son != nil: result.sons.add son
  1295. when false:
  1296. if result.itemId.module == 55 and result.itemId.item == 2:
  1297. echo "KNID ", kind
  1298. writeStackTrace()
  1299. proc setSons*(dest: PType; sons: sink seq[PType]) {.inline.} = dest.sons = sons
  1300. proc setSon*(dest: PType; son: sink PType) {.inline.} = dest.sons = @[son]
  1301. proc mergeLoc(a: var TLoc, b: TLoc) =
  1302. if a.k == low(typeof(a.k)): a.k = b.k
  1303. if a.storage == low(typeof(a.storage)): a.storage = b.storage
  1304. a.flags.incl b.flags
  1305. if a.lode == nil: a.lode = b.lode
  1306. if a.r == "": a.r = b.r
  1307. proc newSons*(father: PNode, length: int) =
  1308. setLen(father.sons, length)
  1309. proc newSons*(father: PType, length: int) =
  1310. setLen(father.sons, length)
  1311. proc truncateInferredTypeCandidates*(t: PType) {.inline.} =
  1312. assert t.kind == tyInferred
  1313. if t.sons.len > 1:
  1314. setLen(t.sons, 1)
  1315. proc assignType*(dest, src: PType) =
  1316. dest.kind = src.kind
  1317. dest.flags = src.flags
  1318. dest.callConv = src.callConv
  1319. dest.n = src.n
  1320. dest.size = src.size
  1321. dest.align = src.align
  1322. # this fixes 'type TLock = TSysLock':
  1323. if src.sym != nil:
  1324. if dest.sym != nil:
  1325. dest.sym.flags.incl src.sym.flags-{sfUsed, sfExported}
  1326. if dest.sym.annex == nil: dest.sym.annex = src.sym.annex
  1327. mergeLoc(dest.sym.loc, src.sym.loc)
  1328. else:
  1329. dest.sym = src.sym
  1330. newSons(dest, src.sons.len)
  1331. for i in 0..<src.sons.len: dest[i] = src[i]
  1332. proc copyType*(t: PType, idgen: IdGenerator, owner: PSym): PType =
  1333. result = newType(t.kind, idgen, owner)
  1334. assignType(result, t)
  1335. result.sym = t.sym # backend-info should not be copied
  1336. proc exactReplica*(t: PType): PType =
  1337. result = PType(kind: t.kind, owner: t.owner, size: defaultSize,
  1338. align: defaultAlignment, itemId: t.itemId,
  1339. uniqueId: t.uniqueId)
  1340. assignType(result, t)
  1341. result.sym = t.sym # backend-info should not be copied
  1342. proc copySym*(s: PSym; idgen: IdGenerator): PSym =
  1343. result = newSym(s.kind, s.name, idgen, s.owner, s.info, s.options)
  1344. #result.ast = nil # BUGFIX; was: s.ast which made problems
  1345. result.typ = s.typ
  1346. result.flags = s.flags
  1347. result.magic = s.magic
  1348. result.options = s.options
  1349. result.position = s.position
  1350. result.loc = s.loc
  1351. result.annex = s.annex # BUGFIX
  1352. result.constraint = s.constraint
  1353. if result.kind in {skVar, skLet, skField}:
  1354. result.guard = s.guard
  1355. result.bitsize = s.bitsize
  1356. result.alignment = s.alignment
  1357. proc createModuleAlias*(s: PSym, idgen: IdGenerator, newIdent: PIdent, info: TLineInfo;
  1358. options: TOptions): PSym =
  1359. result = newSym(s.kind, newIdent, idgen, s.owner, info, options)
  1360. # keep ID!
  1361. result.ast = s.ast
  1362. #result.id = s.id # XXX figure out what to do with the ID.
  1363. result.flags = s.flags
  1364. result.options = s.options
  1365. result.position = s.position
  1366. result.loc = s.loc
  1367. result.annex = s.annex
  1368. proc initStrTable*(): TStrTable =
  1369. result = TStrTable(counter: 0)
  1370. newSeq(result.data, StartSize)
  1371. proc initObjectSet*(): TObjectSet =
  1372. result = TObjectSet(counter: 0)
  1373. newSeq(result.data, StartSize)
  1374. proc initNodeTable*(): TNodeTable =
  1375. result = TNodeTable(counter: 0)
  1376. newSeq(result.data, StartSize)
  1377. proc skipTypes*(t: PType, kinds: TTypeKinds; maxIters: int): PType =
  1378. result = t
  1379. var i = maxIters
  1380. while result.kind in kinds:
  1381. result = last(result)
  1382. dec i
  1383. if i == 0: return nil
  1384. proc skipTypesOrNil*(t: PType, kinds: TTypeKinds): PType =
  1385. ## same as skipTypes but handles 'nil'
  1386. result = t
  1387. while result != nil and result.kind in kinds:
  1388. if result.sons.len == 0: return nil
  1389. result = last(result)
  1390. proc isGCedMem*(t: PType): bool {.inline.} =
  1391. result = t.kind in {tyString, tyRef, tySequence} or
  1392. t.kind == tyProc and t.callConv == ccClosure
  1393. proc propagateToOwner*(owner, elem: PType; propagateHasAsgn = true) =
  1394. owner.flags.incl elem.flags * {tfHasMeta, tfTriggersCompileTime}
  1395. if tfNotNil in elem.flags:
  1396. if owner.kind in {tyGenericInst, tyGenericBody, tyGenericInvocation}:
  1397. owner.flags.incl tfNotNil
  1398. if elem.isMetaType:
  1399. owner.flags.incl tfHasMeta
  1400. let mask = elem.flags * {tfHasAsgn, tfHasOwned}
  1401. if mask != {} and propagateHasAsgn:
  1402. let o2 = owner.skipTypes({tyGenericInst, tyAlias, tySink})
  1403. if o2.kind in {tyTuple, tyObject, tyArray,
  1404. tySequence, tySet, tyDistinct}:
  1405. o2.flags.incl mask
  1406. owner.flags.incl mask
  1407. if owner.kind notin {tyProc, tyGenericInst, tyGenericBody,
  1408. tyGenericInvocation, tyPtr}:
  1409. let elemB = elem.skipTypes({tyGenericInst, tyAlias, tySink})
  1410. if elemB.isGCedMem or tfHasGCedMem in elemB.flags:
  1411. # for simplicity, we propagate this flag even to generics. We then
  1412. # ensure this doesn't bite us in sempass2.
  1413. owner.flags.incl tfHasGCedMem
  1414. proc rawAddSon*(father, son: PType; propagateHasAsgn = true) =
  1415. father.sons.add(son)
  1416. if not son.isNil: propagateToOwner(father, son, propagateHasAsgn)
  1417. proc addSonNilAllowed*(father, son: PNode) =
  1418. father.sons.add(son)
  1419. proc delSon*(father: PNode, idx: int) =
  1420. if father.len == 0: return
  1421. for i in idx..<father.len - 1: father[i] = father[i + 1]
  1422. father.sons.setLen(father.len - 1)
  1423. proc copyNode*(src: PNode): PNode =
  1424. # does not copy its sons!
  1425. if src == nil:
  1426. return nil
  1427. result = newNode(src.kind)
  1428. result.info = src.info
  1429. result.typ = src.typ
  1430. result.flags = src.flags * PersistentNodeFlags
  1431. result.comment = src.comment
  1432. when defined(useNodeIds):
  1433. if result.id == nodeIdToDebug:
  1434. echo "COMES FROM ", src.id
  1435. case src.kind
  1436. of nkCharLit..nkUInt64Lit: result.intVal = src.intVal
  1437. of nkFloatLiterals: result.floatVal = src.floatVal
  1438. of nkSym: result.sym = src.sym
  1439. of nkIdent: result.ident = src.ident
  1440. of nkStrLit..nkTripleStrLit: result.strVal = src.strVal
  1441. else: discard
  1442. when defined(nimsuggest):
  1443. result.endInfo = src.endInfo
  1444. template transitionNodeKindCommon(k: TNodeKind) =
  1445. let obj {.inject.} = n[]
  1446. n[] = TNode(kind: k, typ: obj.typ, info: obj.info, flags: obj.flags)
  1447. # n.comment = obj.comment # shouldn't be needed, the address doesnt' change
  1448. when defined(useNodeIds):
  1449. n.id = obj.id
  1450. proc transitionSonsKind*(n: PNode, kind: range[nkComesFrom..nkTupleConstr]) =
  1451. transitionNodeKindCommon(kind)
  1452. n.sons = obj.sons
  1453. proc transitionIntKind*(n: PNode, kind: range[nkCharLit..nkUInt64Lit]) =
  1454. transitionNodeKindCommon(kind)
  1455. n.intVal = obj.intVal
  1456. proc transitionIntToFloatKind*(n: PNode, kind: range[nkFloatLit..nkFloat128Lit]) =
  1457. transitionNodeKindCommon(kind)
  1458. n.floatVal = BiggestFloat(obj.intVal)
  1459. proc transitionNoneToSym*(n: PNode) =
  1460. transitionNodeKindCommon(nkSym)
  1461. template transitionSymKindCommon*(k: TSymKind) =
  1462. let obj {.inject.} = s[]
  1463. s[] = TSym(kind: k, itemId: obj.itemId, magic: obj.magic, typ: obj.typ, name: obj.name,
  1464. info: obj.info, owner: obj.owner, flags: obj.flags, ast: obj.ast,
  1465. options: obj.options, position: obj.position, offset: obj.offset,
  1466. loc: obj.loc, annex: obj.annex, constraint: obj.constraint)
  1467. when hasFFI:
  1468. s.cname = obj.cname
  1469. when defined(nimsuggest):
  1470. s.allUsages = obj.allUsages
  1471. proc transitionGenericParamToType*(s: PSym) =
  1472. transitionSymKindCommon(skType)
  1473. proc transitionRoutineSymKind*(s: PSym, kind: range[skProc..skTemplate]) =
  1474. transitionSymKindCommon(kind)
  1475. s.gcUnsafetyReason = obj.gcUnsafetyReason
  1476. s.transformedBody = obj.transformedBody
  1477. proc transitionToLet*(s: PSym) =
  1478. transitionSymKindCommon(skLet)
  1479. s.guard = obj.guard
  1480. s.bitsize = obj.bitsize
  1481. s.alignment = obj.alignment
  1482. template copyNodeImpl(dst, src, processSonsStmt) =
  1483. if src == nil: return
  1484. dst = newNode(src.kind)
  1485. dst.info = src.info
  1486. when defined(nimsuggest):
  1487. result.endInfo = src.endInfo
  1488. dst.typ = src.typ
  1489. dst.flags = src.flags * PersistentNodeFlags
  1490. dst.comment = src.comment
  1491. when defined(useNodeIds):
  1492. if dst.id == nodeIdToDebug:
  1493. echo "COMES FROM ", src.id
  1494. case src.kind
  1495. of nkCharLit..nkUInt64Lit: dst.intVal = src.intVal
  1496. of nkFloatLiterals: dst.floatVal = src.floatVal
  1497. of nkSym: dst.sym = src.sym
  1498. of nkIdent: dst.ident = src.ident
  1499. of nkStrLit..nkTripleStrLit: dst.strVal = src.strVal
  1500. else: processSonsStmt
  1501. proc shallowCopy*(src: PNode): PNode =
  1502. # does not copy its sons, but provides space for them:
  1503. copyNodeImpl(result, src):
  1504. newSeq(result.sons, src.len)
  1505. proc copyTree*(src: PNode): PNode =
  1506. # copy a whole syntax tree; performs deep copying
  1507. copyNodeImpl(result, src):
  1508. newSeq(result.sons, src.len)
  1509. for i in 0..<src.len:
  1510. result[i] = copyTree(src[i])
  1511. proc copyTreeWithoutNode*(src, skippedNode: PNode): PNode =
  1512. copyNodeImpl(result, src):
  1513. result.sons = newSeqOfCap[PNode](src.len)
  1514. for n in src.sons:
  1515. if n != skippedNode:
  1516. result.sons.add copyTreeWithoutNode(n, skippedNode)
  1517. proc hasSonWith*(n: PNode, kind: TNodeKind): bool =
  1518. for i in 0..<n.len:
  1519. if n[i].kind == kind:
  1520. return true
  1521. result = false
  1522. proc hasNilSon*(n: PNode): bool =
  1523. for i in 0..<n.safeLen:
  1524. if n[i] == nil:
  1525. return true
  1526. elif hasNilSon(n[i]):
  1527. return true
  1528. result = false
  1529. proc containsNode*(n: PNode, kinds: TNodeKinds): bool =
  1530. result = false
  1531. if n == nil: return
  1532. case n.kind
  1533. of nkEmpty..nkNilLit: result = n.kind in kinds
  1534. else:
  1535. for i in 0..<n.len:
  1536. if n.kind in kinds or containsNode(n[i], kinds): return true
  1537. proc hasSubnodeWith*(n: PNode, kind: TNodeKind): bool =
  1538. case n.kind
  1539. of nkEmpty..nkNilLit, nkFormalParams: result = n.kind == kind
  1540. else:
  1541. for i in 0..<n.len:
  1542. if (n[i].kind == kind) or hasSubnodeWith(n[i], kind):
  1543. return true
  1544. result = false
  1545. proc getInt*(a: PNode): Int128 =
  1546. case a.kind
  1547. of nkCharLit, nkUIntLit..nkUInt64Lit:
  1548. result = toInt128(cast[uint64](a.intVal))
  1549. of nkInt8Lit..nkInt64Lit:
  1550. result = toInt128(a.intVal)
  1551. of nkIntLit:
  1552. # XXX: enable this assert
  1553. # assert a.typ.kind notin {tyChar, tyUint..tyUInt64}
  1554. result = toInt128(a.intVal)
  1555. else:
  1556. raiseRecoverableError("cannot extract number from invalid AST node")
  1557. proc getInt64*(a: PNode): int64 {.deprecated: "use getInt".} =
  1558. case a.kind
  1559. of nkCharLit, nkUIntLit..nkUInt64Lit, nkIntLit..nkInt64Lit:
  1560. result = a.intVal
  1561. else:
  1562. raiseRecoverableError("cannot extract number from invalid AST node")
  1563. proc getFloat*(a: PNode): BiggestFloat =
  1564. case a.kind
  1565. of nkFloatLiterals: result = a.floatVal
  1566. of nkCharLit, nkUIntLit..nkUInt64Lit, nkIntLit..nkInt64Lit:
  1567. result = BiggestFloat a.intVal
  1568. else:
  1569. raiseRecoverableError("cannot extract number from invalid AST node")
  1570. #doAssert false, "getFloat"
  1571. #internalError(a.info, "getFloat")
  1572. #result = 0.0
  1573. proc getStr*(a: PNode): string =
  1574. case a.kind
  1575. of nkStrLit..nkTripleStrLit: result = a.strVal
  1576. of nkNilLit:
  1577. # let's hope this fixes more problems than it creates:
  1578. result = ""
  1579. else:
  1580. raiseRecoverableError("cannot extract string from invalid AST node")
  1581. #doAssert false, "getStr"
  1582. #internalError(a.info, "getStr")
  1583. #result = ""
  1584. proc getStrOrChar*(a: PNode): string =
  1585. case a.kind
  1586. of nkStrLit..nkTripleStrLit: result = a.strVal
  1587. of nkCharLit..nkUInt64Lit: result = $chr(int(a.intVal))
  1588. else:
  1589. raiseRecoverableError("cannot extract string from invalid AST node")
  1590. #doAssert false, "getStrOrChar"
  1591. #internalError(a.info, "getStrOrChar")
  1592. #result = ""
  1593. proc isGenericParams*(n: PNode): bool {.inline.} =
  1594. ## used to judge whether a node is generic params.
  1595. n != nil and n.kind == nkGenericParams
  1596. proc isGenericRoutine*(n: PNode): bool {.inline.} =
  1597. n != nil and n.kind in callableDefs and n[genericParamsPos].isGenericParams
  1598. proc isGenericRoutineStrict*(s: PSym): bool {.inline.} =
  1599. ## determines if this symbol represents a generic routine
  1600. ## the unusual name is so it doesn't collide and eventually replaces
  1601. ## `isGenericRoutine`
  1602. s.kind in skProcKinds and s.ast.isGenericRoutine
  1603. proc isGenericRoutine*(s: PSym): bool {.inline.} =
  1604. ## determines if this symbol represents a generic routine or an instance of
  1605. ## one. This should be renamed accordingly and `isGenericRoutineStrict`
  1606. ## should take this name instead.
  1607. ##
  1608. ## Warning/XXX: Unfortunately, it considers a proc kind symbol flagged with
  1609. ## sfFromGeneric as a generic routine. Instead this should likely not be the
  1610. ## case and the concepts should be teased apart:
  1611. ## - generic definition
  1612. ## - generic instance
  1613. ## - either generic definition or instance
  1614. s.kind in skProcKinds and (sfFromGeneric in s.flags or
  1615. s.ast.isGenericRoutine)
  1616. proc skipGenericOwner*(s: PSym): PSym =
  1617. ## Generic instantiations are owned by their originating generic
  1618. ## symbol. This proc skips such owners and goes straight to the owner
  1619. ## of the generic itself (the module or the enclosing proc).
  1620. result = if s.kind == skModule:
  1621. s
  1622. elif s.kind in skProcKinds and sfFromGeneric in s.flags and s.owner.kind != skModule:
  1623. s.owner.owner
  1624. else:
  1625. s.owner
  1626. proc originatingModule*(s: PSym): PSym =
  1627. result = s
  1628. while result.kind != skModule: result = result.owner
  1629. proc isRoutine*(s: PSym): bool {.inline.} =
  1630. result = s.kind in skProcKinds
  1631. proc isCompileTimeProc*(s: PSym): bool {.inline.} =
  1632. result = s.kind == skMacro or
  1633. s.kind in {skProc, skFunc} and sfCompileTime in s.flags
  1634. proc hasPattern*(s: PSym): bool {.inline.} =
  1635. result = isRoutine(s) and s.ast[patternPos].kind != nkEmpty
  1636. iterator items*(n: PNode): PNode =
  1637. for i in 0..<n.safeLen: yield n[i]
  1638. iterator pairs*(n: PNode): tuple[i: int, n: PNode] =
  1639. for i in 0..<n.safeLen: yield (i, n[i])
  1640. proc isAtom*(n: PNode): bool {.inline.} =
  1641. result = n.kind >= nkNone and n.kind <= nkNilLit
  1642. proc isEmptyType*(t: PType): bool {.inline.} =
  1643. ## 'void' and 'typed' types are often equivalent to 'nil' these days:
  1644. result = t == nil or t.kind in {tyVoid, tyTyped}
  1645. proc makeStmtList*(n: PNode): PNode =
  1646. if n.kind == nkStmtList:
  1647. result = n
  1648. else:
  1649. result = newNodeI(nkStmtList, n.info)
  1650. result.add n
  1651. proc skipStmtList*(n: PNode): PNode =
  1652. if n.kind in {nkStmtList, nkStmtListExpr}:
  1653. for i in 0..<n.len-1:
  1654. if n[i].kind notin {nkEmpty, nkCommentStmt}: return n
  1655. result = n.lastSon
  1656. else:
  1657. result = n
  1658. proc toVar*(typ: PType; kind: TTypeKind; idgen: IdGenerator): PType =
  1659. ## If ``typ`` is not a tyVar then it is converted into a `var <typ>` and
  1660. ## returned. Otherwise ``typ`` is simply returned as-is.
  1661. result = typ
  1662. if typ.kind != kind:
  1663. result = newType(kind, idgen, typ.owner, typ)
  1664. proc toRef*(typ: PType; idgen: IdGenerator): PType =
  1665. ## If ``typ`` is a tyObject then it is converted into a `ref <typ>` and
  1666. ## returned. Otherwise ``typ`` is simply returned as-is.
  1667. result = typ
  1668. if typ.skipTypes({tyAlias, tyGenericInst}).kind == tyObject:
  1669. result = newType(tyRef, idgen, typ.owner, typ)
  1670. proc toObject*(typ: PType): PType =
  1671. ## If ``typ`` is a tyRef then its immediate son is returned (which in many
  1672. ## cases should be a ``tyObject``).
  1673. ## Otherwise ``typ`` is simply returned as-is.
  1674. let t = typ.skipTypes({tyAlias, tyGenericInst})
  1675. if t.kind == tyRef: t.elementType
  1676. else: typ
  1677. proc toObjectFromRefPtrGeneric*(typ: PType): PType =
  1678. #[
  1679. See also `toObject`.
  1680. Finds the underlying `object`, even in cases like these:
  1681. type
  1682. B[T] = object f0: int
  1683. A1[T] = ref B[T]
  1684. A2[T] = ref object f1: int
  1685. A3 = ref object f2: int
  1686. A4 = object f3: int
  1687. ]#
  1688. result = typ
  1689. while true:
  1690. case result.kind
  1691. of tyGenericBody: result = result.last
  1692. of tyRef, tyPtr, tyGenericInst, tyGenericInvocation, tyAlias: result = result[0]
  1693. # automatic dereferencing is deep, refs #18298.
  1694. else: break
  1695. # result does not have to be object type
  1696. proc isImportedException*(t: PType; conf: ConfigRef): bool =
  1697. assert t != nil
  1698. if conf.exc != excCpp:
  1699. return false
  1700. let base = t.skipTypes({tyAlias, tyPtr, tyDistinct, tyGenericInst})
  1701. result = base.sym != nil and {sfCompileToCpp, sfImportc} * base.sym.flags != {}
  1702. proc isInfixAs*(n: PNode): bool =
  1703. return n.kind == nkInfix and n[0].kind == nkIdent and n[0].ident.id == ord(wAs)
  1704. proc skipColon*(n: PNode): PNode =
  1705. result = n
  1706. if n.kind == nkExprColonExpr:
  1707. result = n[1]
  1708. proc findUnresolvedStatic*(n: PNode): PNode =
  1709. if n.kind == nkSym and n.typ != nil and n.typ.kind == tyStatic and n.typ.n == nil:
  1710. return n
  1711. if n.typ != nil and n.typ.kind == tyTypeDesc:
  1712. let t = skipTypes(n.typ, {tyTypeDesc})
  1713. if t.kind == tyGenericParam and not t.genericParamHasConstraints:
  1714. return n
  1715. for son in n:
  1716. let n = son.findUnresolvedStatic
  1717. if n != nil: return n
  1718. return nil
  1719. when false:
  1720. proc containsNil*(n: PNode): bool =
  1721. # only for debugging
  1722. if n.isNil: return true
  1723. for i in 0..<n.safeLen:
  1724. if n[i].containsNil: return true
  1725. template hasDestructor*(t: PType): bool = {tfHasAsgn, tfHasOwned} * t.flags != {}
  1726. template incompleteType*(t: PType): bool =
  1727. t.sym != nil and {sfForward, sfNoForward} * t.sym.flags == {sfForward}
  1728. template typeCompleted*(s: PSym) =
  1729. incl s.flags, sfNoForward
  1730. template detailedInfo*(sym: PSym): string =
  1731. sym.name.s
  1732. proc isInlineIterator*(typ: PType): bool {.inline.} =
  1733. typ.kind == tyProc and tfIterator in typ.flags and typ.callConv != ccClosure
  1734. proc isIterator*(typ: PType): bool {.inline.} =
  1735. typ.kind == tyProc and tfIterator in typ.flags
  1736. proc isClosureIterator*(typ: PType): bool {.inline.} =
  1737. typ.kind == tyProc and tfIterator in typ.flags and typ.callConv == ccClosure
  1738. proc isClosure*(typ: PType): bool {.inline.} =
  1739. typ.kind == tyProc and typ.callConv == ccClosure
  1740. proc isNimcall*(s: PSym): bool {.inline.} =
  1741. s.typ.callConv == ccNimCall
  1742. proc isExplicitCallConv*(s: PSym): bool {.inline.} =
  1743. tfExplicitCallConv in s.typ.flags
  1744. proc isSinkParam*(s: PSym): bool {.inline.} =
  1745. s.kind == skParam and (s.typ.kind == tySink or tfHasOwned in s.typ.flags)
  1746. proc isSinkType*(t: PType): bool {.inline.} =
  1747. t.kind == tySink or tfHasOwned in t.flags
  1748. proc newProcType*(info: TLineInfo; idgen: IdGenerator; owner: PSym): PType =
  1749. result = newType(tyProc, idgen, owner)
  1750. result.n = newNodeI(nkFormalParams, info)
  1751. rawAddSon(result, nil) # return type
  1752. # result.n[0] used to be `nkType`, but now it's `nkEffectList` because
  1753. # the effects are now stored in there too ... this is a bit hacky, but as
  1754. # usual we desperately try to save memory:
  1755. result.n.add newNodeI(nkEffectList, info)
  1756. proc addParam*(procType: PType; param: PSym) =
  1757. param.position = procType.sons.len-1
  1758. procType.n.add newSymNode(param)
  1759. rawAddSon(procType, param.typ)
  1760. const magicsThatCanRaise = {
  1761. mNone, mSlurp, mStaticExec, mParseExprToAst, mParseStmtToAst, mEcho}
  1762. proc canRaiseConservative*(fn: PNode): bool =
  1763. if fn.kind == nkSym and fn.sym.magic notin magicsThatCanRaise:
  1764. result = false
  1765. else:
  1766. result = true
  1767. proc canRaise*(fn: PNode): bool =
  1768. if fn.kind == nkSym and (fn.sym.magic notin magicsThatCanRaise or
  1769. {sfImportc, sfInfixCall} * fn.sym.flags == {sfImportc} or
  1770. sfGeneratedOp in fn.sym.flags):
  1771. result = false
  1772. elif fn.kind == nkSym and fn.sym.magic == mEcho:
  1773. result = true
  1774. else:
  1775. # TODO check for n having sons? or just return false for now if not
  1776. if fn.typ != nil and fn.typ.n != nil and fn.typ.n[0].kind == nkSym:
  1777. result = false
  1778. else:
  1779. result = fn.typ != nil and fn.typ.n != nil and ((fn.typ.n[0].len < effectListLen) or
  1780. (fn.typ.n[0][exceptionEffects] != nil and
  1781. fn.typ.n[0][exceptionEffects].safeLen > 0))
  1782. proc toHumanStrImpl[T](kind: T, num: static int): string =
  1783. result = $kind
  1784. result = result[num..^1]
  1785. result[0] = result[0].toLowerAscii
  1786. proc toHumanStr*(kind: TSymKind): string =
  1787. ## strips leading `sk`
  1788. result = toHumanStrImpl(kind, 2)
  1789. proc toHumanStr*(kind: TTypeKind): string =
  1790. ## strips leading `tk`
  1791. result = toHumanStrImpl(kind, 2)
  1792. proc skipHiddenAddr*(n: PNode): PNode {.inline.} =
  1793. (if n.kind == nkHiddenAddr: n[0] else: n)
  1794. proc isNewStyleConcept*(n: PNode): bool {.inline.} =
  1795. assert n.kind == nkTypeClassTy
  1796. result = n[0].kind == nkEmpty
  1797. proc isOutParam*(t: PType): bool {.inline.} = tfIsOutParam in t.flags
  1798. const
  1799. nodesToIgnoreSet* = {nkNone..pred(nkSym), succ(nkSym)..nkNilLit,
  1800. nkTypeSection, nkProcDef, nkConverterDef,
  1801. nkMethodDef, nkIteratorDef, nkMacroDef, nkTemplateDef, nkLambda, nkDo,
  1802. nkFuncDef, nkConstSection, nkConstDef, nkIncludeStmt, nkImportStmt,
  1803. nkExportStmt, nkPragma, nkCommentStmt, nkBreakState,
  1804. nkTypeOfExpr, nkMixinStmt, nkBindStmt}
  1805. proc isTrue*(n: PNode): bool =
  1806. n.kind == nkSym and n.sym.kind == skEnumField and n.sym.position != 0 or
  1807. n.kind == nkIntLit and n.intVal != 0
  1808. type
  1809. TypeMapping* = Table[ItemId, PType]
  1810. SymMapping* = Table[ItemId, PSym]
  1811. template idTableGet*(tab: typed; key: PSym | PType): untyped = tab.getOrDefault(key.itemId)
  1812. template idTablePut*(tab: typed; key, val: PSym | PType) = tab[key.itemId] = val
  1813. template initSymMapping*(): Table[ItemId, PSym] = initTable[ItemId, PSym]()
  1814. template initTypeMapping*(): Table[ItemId, PType] = initTable[ItemId, PType]()
  1815. template resetIdTable*(tab: Table[ItemId, PSym]) = tab.clear()
  1816. template resetIdTable*(tab: Table[ItemId, PType]) = tab.clear()