ast.nim 68 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818
  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, hashes, nversion, options, strutils, std / sha1, ropes, idents,
  12. intsets, idgen
  13. type
  14. TCallingConvention* = enum
  15. ccDefault, # proc has no explicit calling convention
  16. ccStdCall, # procedure is stdcall
  17. ccCDecl, # cdecl
  18. ccSafeCall, # safecall
  19. ccSysCall, # system call
  20. ccInline, # proc should be inlined
  21. ccNoInline, # proc should not be inlined
  22. ccFastCall, # fastcall (pass parameters in registers)
  23. ccClosure, # proc has a closure
  24. ccNoConvention # needed for generating proper C procs sometimes
  25. const
  26. CallingConvToStr*: array[TCallingConvention, string] = ["", "stdcall",
  27. "cdecl", "safecall", "syscall", "inline", "noinline", "fastcall",
  28. "closure", "noconv"]
  29. type
  30. TNodeKind* = enum # order is extremely important, because ranges are used
  31. # to check whether a node belongs to a certain class
  32. nkNone, # unknown node kind: indicates an error
  33. # Expressions:
  34. # Atoms:
  35. nkEmpty, # the node is empty
  36. nkIdent, # node is an identifier
  37. nkSym, # node is a symbol
  38. nkType, # node is used for its typ field
  39. nkCharLit, # a character literal ''
  40. nkIntLit, # an integer literal
  41. nkInt8Lit,
  42. nkInt16Lit,
  43. nkInt32Lit,
  44. nkInt64Lit,
  45. nkUIntLit, # an unsigned integer literal
  46. nkUInt8Lit,
  47. nkUInt16Lit,
  48. nkUInt32Lit,
  49. nkUInt64Lit,
  50. nkFloatLit, # a floating point literal
  51. nkFloat32Lit,
  52. nkFloat64Lit,
  53. nkFloat128Lit,
  54. nkStrLit, # a string literal ""
  55. nkRStrLit, # a raw string literal r""
  56. nkTripleStrLit, # a triple string literal """
  57. nkNilLit, # the nil literal
  58. # end of atoms
  59. nkComesFrom, # "comes from" template/macro information for
  60. # better stack trace generation
  61. nkDotCall, # used to temporarily flag a nkCall node;
  62. # this is used
  63. # for transforming ``s.len`` to ``len(s)``
  64. nkCommand, # a call like ``p 2, 4`` without parenthesis
  65. nkCall, # a call like p(x, y) or an operation like +(a, b)
  66. nkCallStrLit, # a call with a string literal
  67. # x"abc" has two sons: nkIdent, nkRStrLit
  68. # x"""abc""" has two sons: nkIdent, nkTripleStrLit
  69. nkInfix, # a call like (a + b)
  70. nkPrefix, # a call like !a
  71. nkPostfix, # something like a! (also used for visibility)
  72. nkHiddenCallConv, # an implicit type conversion via a type converter
  73. nkExprEqExpr, # a named parameter with equals: ''expr = expr''
  74. nkExprColonExpr, # a named parameter with colon: ''expr: expr''
  75. nkIdentDefs, # a definition like `a, b: typeDesc = expr`
  76. # either typeDesc or expr may be nil; used in
  77. # formal parameters, var statements, etc.
  78. nkVarTuple, # a ``var (a, b) = expr`` construct
  79. nkPar, # syntactic (); may be a tuple constructor
  80. nkObjConstr, # object constructor: T(a: 1, b: 2)
  81. nkCurly, # syntactic {}
  82. nkCurlyExpr, # an expression like a{i}
  83. nkBracket, # syntactic []
  84. nkBracketExpr, # an expression like a[i..j, k]
  85. nkPragmaExpr, # an expression like a{.pragmas.}
  86. nkRange, # an expression like i..j
  87. nkDotExpr, # a.b
  88. nkCheckedFieldExpr, # a.b, but b is a field that needs to be checked
  89. nkDerefExpr, # a^
  90. nkIfExpr, # if as an expression
  91. nkElifExpr,
  92. nkElseExpr,
  93. nkLambda, # lambda expression
  94. nkDo, # lambda block appering as trailing proc param
  95. nkAccQuoted, # `a` as a node
  96. nkTableConstr, # a table constructor {expr: expr}
  97. nkBind, # ``bind expr`` node
  98. nkClosedSymChoice, # symbol choice node; a list of nkSyms (closed)
  99. nkOpenSymChoice, # symbol choice node; a list of nkSyms (open)
  100. nkHiddenStdConv, # an implicit standard type conversion
  101. nkHiddenSubConv, # an implicit type conversion from a subtype
  102. # to a supertype
  103. nkConv, # a type conversion
  104. nkCast, # a type cast
  105. nkStaticExpr, # a static expr
  106. nkAddr, # a addr expression
  107. nkHiddenAddr, # implicit address operator
  108. nkHiddenDeref, # implicit ^ operator
  109. nkObjDownConv, # down conversion between object types
  110. nkObjUpConv, # up conversion between object types
  111. nkChckRangeF, # range check for floats
  112. nkChckRange64, # range check for 64 bit ints
  113. nkChckRange, # range check for ints
  114. nkStringToCString, # string to cstring
  115. nkCStringToString, # cstring to string
  116. # end of expressions
  117. nkAsgn, # a = b
  118. nkFastAsgn, # internal node for a fast ``a = b``
  119. # (no string copy)
  120. nkGenericParams, # generic parameters
  121. nkFormalParams, # formal parameters
  122. nkOfInherit, # inherited from symbol
  123. nkImportAs, # a 'as' b in an import statement
  124. nkProcDef, # a proc
  125. nkMethodDef, # a method
  126. nkConverterDef, # a converter
  127. nkMacroDef, # a macro
  128. nkTemplateDef, # a template
  129. nkIteratorDef, # an iterator
  130. nkOfBranch, # used inside case statements
  131. # for (cond, action)-pairs
  132. nkElifBranch, # used in if statements
  133. nkExceptBranch, # an except section
  134. nkElse, # an else part
  135. nkAsmStmt, # an assembler block
  136. nkPragma, # a pragma statement
  137. nkPragmaBlock, # a pragma with a block
  138. nkIfStmt, # an if statement
  139. nkWhenStmt, # a when expression or statement
  140. nkForStmt, # a for statement
  141. nkParForStmt, # a parallel for statement
  142. nkWhileStmt, # a while statement
  143. nkCaseStmt, # a case statement
  144. nkTypeSection, # a type section (consists of type definitions)
  145. nkVarSection, # a var section
  146. nkLetSection, # a let section
  147. nkConstSection, # a const section
  148. nkConstDef, # a const definition
  149. nkTypeDef, # a type definition
  150. nkYieldStmt, # the yield statement as a tree
  151. nkDefer, # the 'defer' statement
  152. nkTryStmt, # a try statement
  153. nkFinally, # a finally section
  154. nkRaiseStmt, # a raise statement
  155. nkReturnStmt, # a return statement
  156. nkBreakStmt, # a break statement
  157. nkContinueStmt, # a continue statement
  158. nkBlockStmt, # a block statement
  159. nkStaticStmt, # a static statement
  160. nkDiscardStmt, # a discard statement
  161. nkStmtList, # a list of statements
  162. nkImportStmt, # an import statement
  163. nkImportExceptStmt, # an import x except a statement
  164. nkExportStmt, # an export statement
  165. nkExportExceptStmt, # an 'export except' statement
  166. nkFromStmt, # a from * import statement
  167. nkIncludeStmt, # an include statement
  168. nkBindStmt, # a bind statement
  169. nkMixinStmt, # a mixin statement
  170. nkUsingStmt, # an using statement
  171. nkCommentStmt, # a comment statement
  172. nkStmtListExpr, # a statement list followed by an expr; this is used
  173. # to allow powerful multi-line templates
  174. nkBlockExpr, # a statement block ending in an expr; this is used
  175. # to allowe powerful multi-line templates that open a
  176. # temporary scope
  177. nkStmtListType, # a statement list ending in a type; for macros
  178. nkBlockType, # a statement block ending in a type; for macros
  179. # types as syntactic trees:
  180. nkWith, # distinct with `foo`
  181. nkWithout, # distinct without `foo`
  182. nkTypeOfExpr, # type(1+2)
  183. nkObjectTy, # object body
  184. nkTupleTy, # tuple body
  185. nkTupleClassTy, # tuple type class
  186. nkTypeClassTy, # user-defined type class
  187. nkStaticTy, # ``static[T]``
  188. nkRecList, # list of object parts
  189. nkRecCase, # case section of object
  190. nkRecWhen, # when section of object
  191. nkRefTy, # ``ref T``
  192. nkPtrTy, # ``ptr T``
  193. nkVarTy, # ``var T``
  194. nkConstTy, # ``const T``
  195. nkMutableTy, # ``mutable T``
  196. nkDistinctTy, # distinct type
  197. nkProcTy, # proc type
  198. nkIteratorTy, # iterator type
  199. nkSharedTy, # 'shared T'
  200. # we use 'nkPostFix' for the 'not nil' addition
  201. nkEnumTy, # enum body
  202. nkEnumFieldDef, # `ident = expr` in an enumeration
  203. nkArgList, # argument list
  204. nkPattern, # a special pattern; used for matching
  205. nkHiddenTryStmt, # token used for interpretation
  206. nkClosure, # (prc, env)-pair (internally used for code gen)
  207. nkGotoState, # used for the state machine (for iterators)
  208. nkState, # give a label to a code section (for iterators)
  209. nkBreakState, # special break statement for easier code generation
  210. nkFuncDef, # a func
  211. nkTupleConstr # a tuple constructor
  212. TNodeKinds* = set[TNodeKind]
  213. type
  214. TSymFlag* = enum # already 36 flags!
  215. sfUsed, # read access of sym (for warnings) or simply used
  216. sfExported, # symbol is exported from module
  217. sfFromGeneric, # symbol is instantiation of a generic; this is needed
  218. # for symbol file generation; such symbols should always
  219. # be written into the ROD file
  220. sfGlobal, # symbol is at global scope
  221. sfForward, # symbol is forward declared
  222. sfImportc, # symbol is external; imported
  223. sfExportc, # symbol is exported (under a specified name)
  224. sfVolatile, # variable is volatile
  225. sfRegister, # variable should be placed in a register
  226. sfPure, # object is "pure" that means it has no type-information
  227. # enum is "pure", its values need qualified access
  228. # variable is "pure"; it's an explicit "global"
  229. sfNoSideEffect, # proc has no side effects
  230. sfSideEffect, # proc may have side effects; cannot prove it has none
  231. sfMainModule, # module is the main module
  232. sfSystemModule, # module is the system module
  233. sfNoReturn, # proc never returns (an exit proc)
  234. sfAddrTaken, # the variable's address is taken (ex- or implicitly);
  235. # *OR*: a proc is indirectly called (used as first class)
  236. sfCompilerProc, # proc is a compiler proc, that is a C proc that is
  237. # needed for the code generator
  238. sfProcvar, # proc can be passed to a proc var
  239. sfDiscriminant, # field is a discriminant in a record/object
  240. sfDeprecated, # symbol is deprecated
  241. sfExplain, # provide more diagnostics when this symbol is used
  242. sfError, # usage of symbol should trigger a compile-time error
  243. sfShadowed, # a symbol that was shadowed in some inner scope
  244. sfThread, # proc will run as a thread
  245. # variable is a thread variable
  246. sfCompileTime, # proc can be evaluated at compile time
  247. sfConstructor, # proc is a C++ constructor
  248. sfDispatcher, # copied method symbol is the dispatcher
  249. # deprecated and unused, except for the con
  250. sfBorrow, # proc is borrowed
  251. sfInfixCall, # symbol needs infix call syntax in target language;
  252. # for interfacing with C++, JS
  253. sfNamedParamCall, # symbol needs named parameter call syntax in target
  254. # language; for interfacing with Objective C
  255. sfDiscardable, # returned value may be discarded implicitly
  256. sfOverriden, # proc is overriden
  257. sfCallsite # A flag for template symbols to tell the
  258. # compiler it should use line information from
  259. # the calling side of the macro, not from the
  260. # implementation.
  261. sfGenSym # symbol is 'gensym'ed; do not add to symbol table
  262. sfNonReloadable # symbol will be left as-is when hot code reloading is on -
  263. # meaning that it won't be renamed and/or changed in any way
  264. sfGeneratedOp # proc is a generated '='; do not inject destructors in it
  265. # variable is generated closure environment; requires early
  266. # destruction for --newruntime.
  267. TSymFlags* = set[TSymFlag]
  268. const
  269. sfNoInit* = sfMainModule # don't generate code to init the variable
  270. sfCursor* = sfDispatcher
  271. # local variable has been computed to be a "cursor".
  272. # see cursors.nim for details about what that means.
  273. sfAllUntyped* = sfVolatile # macro or template is immediately expanded \
  274. # in a generic context
  275. sfDirty* = sfPure
  276. # template is not hygienic (old styled template)
  277. # module, compiled from a dirty-buffer
  278. sfAnon* = sfDiscardable
  279. # symbol name that was generated by the compiler
  280. # the compiler will avoid printing such names
  281. # in user messages.
  282. sfHoisted* = sfForward
  283. # an expression was hoised to an anonymous variable.
  284. # the flag is applied to the var/let symbol
  285. sfNoForward* = sfRegister
  286. # forward declarations are not required (per module)
  287. sfReorder* = sfForward
  288. # reordering pass is enabled
  289. sfCompileToCpp* = sfInfixCall # compile the module as C++ code
  290. sfCompileToObjc* = sfNamedParamCall # compile the module as Objective-C code
  291. sfExperimental* = sfOverriden # module uses the .experimental switch
  292. sfGoto* = sfOverriden # var is used for 'goto' code generation
  293. sfWrittenTo* = sfBorrow # param is assigned to
  294. sfEscapes* = sfProcvar # param escapes
  295. sfBase* = sfDiscriminant
  296. sfIsSelf* = sfOverriden # param is 'self'
  297. sfCustomPragma* = sfRegister # symbol is custom pragma template
  298. const
  299. # getting ready for the future expr/stmt merge
  300. nkWhen* = nkWhenStmt
  301. nkWhenExpr* = nkWhenStmt
  302. nkEffectList* = nkArgList
  303. # hacks ahead: an nkEffectList is a node with 4 children:
  304. exceptionEffects* = 0 # exceptions at position 0
  305. usesEffects* = 1 # read effects at position 1
  306. writeEffects* = 2 # write effects at position 2
  307. tagEffects* = 3 # user defined tag ('gc', 'time' etc.)
  308. pragmasEffects* = 4 # not an effect, but a slot for pragmas in proc type
  309. effectListLen* = 5 # list of effects list
  310. type
  311. TTypeKind* = enum # order is important!
  312. # Don't forget to change hti.nim if you make a change here
  313. # XXX put this into an include file to avoid this issue!
  314. # several types are no longer used (guess which), but a
  315. # spot in the sequence is kept for backwards compatibility
  316. # (apparently something with bootstrapping)
  317. # if you need to add a type, they can apparently be reused
  318. tyNone, tyBool, tyChar,
  319. tyEmpty, tyAlias, tyNil, tyUntyped, tyTyped, tyTypeDesc,
  320. tyGenericInvocation, # ``T[a, b]`` for types to invoke
  321. tyGenericBody, # ``T[a, b, body]`` last parameter is the body
  322. tyGenericInst, # ``T[a, b, realInstance]`` instantiated generic type
  323. # realInstance will be a concrete type like tyObject
  324. # unless this is an instance of a generic alias type.
  325. # then realInstance will be the tyGenericInst of the
  326. # completely (recursively) resolved alias.
  327. tyGenericParam, # ``a`` in the above patterns
  328. tyDistinct,
  329. tyEnum,
  330. tyOrdinal, # integer types (including enums and boolean)
  331. tyArray,
  332. tyObject,
  333. tyTuple,
  334. tySet,
  335. tyRange,
  336. tyPtr, tyRef,
  337. tyVar,
  338. tySequence,
  339. tyProc,
  340. tyPointer, tyOpenArray,
  341. tyString, tyCString, tyForward,
  342. tyInt, tyInt8, tyInt16, tyInt32, tyInt64, # signed integers
  343. tyFloat, tyFloat32, tyFloat64, tyFloat128,
  344. tyUInt, tyUInt8, tyUInt16, tyUInt32, tyUInt64,
  345. tyOwned, tySink, tyLent,
  346. tyVarargs,
  347. tyUncheckedArray
  348. # An array with boundaries [0,+∞]
  349. tyProxy # used as errornous type (for idetools)
  350. tyBuiltInTypeClass
  351. # Type such as the catch-all object, tuple, seq, etc
  352. tyUserTypeClass
  353. # the body of a user-defined type class
  354. tyUserTypeClassInst
  355. # Instance of a parametric user-defined type class.
  356. # Structured similarly to tyGenericInst.
  357. # tyGenericInst represents concrete types, while
  358. # this is still a "generic param" that will bind types
  359. # and resolves them during sigmatch and instantiation.
  360. tyCompositeTypeClass
  361. # Type such as seq[Number]
  362. # The notes for tyUserTypeClassInst apply here as well
  363. # sons[0]: the original expression used by the user.
  364. # sons[1]: fully expanded and instantiated meta type
  365. # (potentially following aliases)
  366. tyInferred
  367. # In the initial state `base` stores a type class constraining
  368. # the types that can be inferred. After a candidate type is
  369. # selected, it's stored in `lastSon`. Between `base` and `lastSon`
  370. # there may be 0, 2 or more types that were also considered as
  371. # possible candidates in the inference process (i.e. lastSon will
  372. # be updated to store a type best conforming to all candidates)
  373. tyAnd, tyOr, tyNot
  374. # boolean type classes such as `string|int`,`not seq`,
  375. # `Sortable and Enumable`, etc
  376. tyAnything
  377. # a type class matching any type
  378. tyStatic
  379. # a value known at compile type (the underlying type is .base)
  380. tyFromExpr
  381. # This is a type representing an expression that depends
  382. # on generic parameters (the expression is stored in t.n)
  383. # It will be converted to a real type only during generic
  384. # instantiation and prior to this it has the potential to
  385. # be any type.
  386. tyOpt
  387. # Builtin optional type
  388. tyVoid
  389. # now different from tyEmpty, hurray!
  390. static:
  391. # remind us when TTypeKind stops to fit in a single 64-bit word
  392. assert TTypeKind.high.ord <= 63
  393. const
  394. tyPureObject* = tyTuple
  395. GcTypeKinds* = {tyRef, tySequence, tyString}
  396. tyError* = tyProxy # as an errornous node should match everything
  397. tyUnknown* = tyFromExpr
  398. tyUnknownTypes* = {tyError, tyFromExpr}
  399. tyTypeClasses* = {tyBuiltInTypeClass, tyCompositeTypeClass,
  400. tyUserTypeClass, tyUserTypeClassInst,
  401. tyAnd, tyOr, tyNot, tyAnything}
  402. tyMetaTypes* = {tyGenericParam, tyTypeDesc, tyUntyped} + tyTypeClasses
  403. tyUserTypeClasses* = {tyUserTypeClass, tyUserTypeClassInst}
  404. type
  405. TTypeKinds* = set[TTypeKind]
  406. TNodeFlag* = enum
  407. nfNone,
  408. nfBase2, # nfBase10 is default, so not needed
  409. nfBase8,
  410. nfBase16,
  411. nfAllConst, # used to mark complex expressions constant; easy to get rid of
  412. # but unfortunately it has measurable impact for compilation
  413. # efficiency
  414. nfTransf, # node has been transformed
  415. nfNoRewrite # node should not be transformed anymore
  416. nfSem # node has been checked for semantics
  417. nfLL # node has gone through lambda lifting
  418. nfDotField # the call can use a dot operator
  419. nfDotSetter # the call can use a setter dot operarator
  420. nfExplicitCall # x.y() was used instead of x.y
  421. nfExprCall # this is an attempt to call a regular expression
  422. nfIsRef # this node is a 'ref' node; used for the VM
  423. nfPreventCg # this node should be ignored by the codegen
  424. nfBlockArg # this a stmtlist appearing in a call (e.g. a do block)
  425. nfFromTemplate # a top-level node returned from a template
  426. nfDefaultParam # an automatically inserter default parameter
  427. nfDefaultRefsParam # a default param value references another parameter
  428. # the flag is applied to proc default values and to calls
  429. nfExecuteOnReload # A top-level statement that will be executed during reloads
  430. TNodeFlags* = set[TNodeFlag]
  431. TTypeFlag* = enum # keep below 32 for efficiency reasons (now: ~38)
  432. tfVarargs, # procedure has C styled varargs
  433. # tyArray type represeting a varargs list
  434. tfNoSideEffect, # procedure type does not allow side effects
  435. tfFinal, # is the object final?
  436. tfInheritable, # is the object inheritable?
  437. tfHasOwned, # type contains an 'owned' type and must be moved
  438. tfEnumHasHoles, # enum cannot be mapped into a range
  439. tfShallow, # type can be shallow copied on assignment
  440. tfThread, # proc type is marked as ``thread``; alias for ``gcsafe``
  441. tfFromGeneric, # type is an instantiation of a generic; this is needed
  442. # because for instantiations of objects, structural
  443. # type equality has to be used
  444. tfUnresolved, # marks unresolved typedesc/static params: e.g.
  445. # proc foo(T: typedesc, list: seq[T]): var T
  446. # proc foo(L: static[int]): array[L, int]
  447. # can be attached to ranges to indicate that the range
  448. # can be attached to generic procs with free standing
  449. # type parameters: e.g. proc foo[T]()
  450. # depends on unresolved static params.
  451. tfResolved # marks a user type class, after it has been bound to a
  452. # concrete type (lastSon becomes the concrete type)
  453. tfRetType, # marks return types in proc (used to detect type classes
  454. # used as return types for return type inference)
  455. tfCapturesEnv, # whether proc really captures some environment
  456. tfByCopy, # pass object/tuple by copy (C backend)
  457. tfByRef, # pass object/tuple by reference (C backend)
  458. tfIterator, # type is really an iterator, not a tyProc
  459. tfPartial, # type is declared as 'partial'
  460. tfNotNil, # type cannot be 'nil'
  461. tfNeedsInit, # type constains a "not nil" constraint somewhere or some
  462. # other type so that it requires initialization
  463. tfVarIsPtr, # 'var' type is translated like 'ptr' even in C++ mode
  464. tfHasMeta, # type contains "wildcard" sub-types such as generic params
  465. # or other type classes
  466. tfHasGCedMem, # type contains GC'ed memory
  467. tfPacked
  468. tfHasStatic
  469. tfGenericTypeParam
  470. tfImplicitTypeParam
  471. tfInferrableStatic
  472. tfConceptMatchedTypeSym
  473. tfExplicit # for typedescs, marks types explicitly prefixed with the
  474. # `type` operator (e.g. type int)
  475. tfWildcard # consider a proc like foo[T, I](x: Type[T, I])
  476. # T and I here can bind to both typedesc and static types
  477. # before this is determined, we'll consider them to be a
  478. # wildcard type.
  479. tfHasAsgn # type has overloaded assignment operator
  480. tfBorrowDot # distinct type borrows '.'
  481. tfTriggersCompileTime # uses the NimNode type which make the proc
  482. # implicitly '.compiletime'
  483. tfRefsAnonObj # used for 'ref object' and 'ptr object'
  484. tfCovariant # covariant generic param mimicing a ptr type
  485. tfWeakCovariant # covariant generic param mimicing a seq/array type
  486. tfContravariant # contravariant generic param
  487. tfCheckedForDestructor # type was checked for having a destructor.
  488. # If it has one, t.destructor is not nil.
  489. TTypeFlags* = set[TTypeFlag]
  490. TSymKind* = enum # the different symbols (start with the prefix sk);
  491. # order is important for the documentation generator!
  492. skUnknown, # unknown symbol: used for parsing assembler blocks
  493. # and first phase symbol lookup in generics
  494. skConditional, # symbol for the preprocessor (may become obsolete)
  495. skDynLib, # symbol represents a dynamic library; this is used
  496. # internally; it does not exist in Nim code
  497. skParam, # a parameter
  498. skGenericParam, # a generic parameter; eq in ``proc x[eq=`==`]()``
  499. skTemp, # a temporary variable (introduced by compiler)
  500. skModule, # module identifier
  501. skType, # a type
  502. skVar, # a variable
  503. skLet, # a 'let' symbol
  504. skConst, # a constant
  505. skResult, # special 'result' variable
  506. skProc, # a proc
  507. skFunc, # a func
  508. skMethod, # a method
  509. skIterator, # an iterator
  510. skConverter, # a type converter
  511. skMacro, # a macro
  512. skTemplate, # a template; currently also misused for user-defined
  513. # pragmas
  514. skField, # a field in a record or object
  515. skEnumField, # an identifier in an enum
  516. skForVar, # a for loop variable
  517. skLabel, # a label (for block statement)
  518. skStub, # symbol is a stub and not yet loaded from the ROD
  519. # file (it is loaded on demand, which may
  520. # mean: never)
  521. skPackage, # symbol is a package (used for canonicalization)
  522. skAlias # an alias (needs to be resolved immediately)
  523. TSymKinds* = set[TSymKind]
  524. const
  525. routineKinds* = {skProc, skFunc, skMethod, skIterator,
  526. skConverter, skMacro, skTemplate}
  527. tfIncompleteStruct* = tfVarargs
  528. tfUnion* = tfNoSideEffect
  529. tfGcSafe* = tfThread
  530. tfObjHasKids* = tfEnumHasHoles
  531. tfReturnsNew* = tfInheritable
  532. skError* = skUnknown
  533. # type flags that are essential for type equality:
  534. eqTypeFlags* = {tfIterator, tfNotNil, tfVarIsPtr}
  535. type
  536. TMagic* = enum # symbols that require compiler magic:
  537. mNone,
  538. mDefined, mDefinedInScope, mCompiles, mArrGet, mArrPut, mAsgn,
  539. mLow, mHigh, mSizeOf, mAlignOf, mOffsetOf, mTypeTrait,
  540. mIs, mOf, mAddr, mType, mTypeOf,
  541. mRoof, mPlugin, mEcho, mShallowCopy, mSlurp, mStaticExec, mStatic,
  542. mParseExprToAst, mParseStmtToAst, mExpandToAst, mQuoteAst,
  543. mUnaryLt, mInc, mDec, mOrd,
  544. mNew, mNewFinalize, mNewSeq, mNewSeqOfCap,
  545. mLengthOpenArray, mLengthStr, mLengthArray, mLengthSeq,
  546. mXLenStr, mXLenSeq,
  547. mIncl, mExcl, mCard, mChr,
  548. mGCref, mGCunref,
  549. mAddI, mSubI, mMulI, mDivI, mModI,
  550. mSucc, mPred,
  551. mAddF64, mSubF64, mMulF64, mDivF64,
  552. mShrI, mShlI, mAshrI, mBitandI, mBitorI, mBitxorI,
  553. mMinI, mMaxI,
  554. mMinF64, mMaxF64,
  555. mAddU, mSubU, mMulU, mDivU, mModU,
  556. mEqI, mLeI, mLtI,
  557. mEqF64, mLeF64, mLtF64,
  558. mLeU, mLtU,
  559. mLeU64, mLtU64,
  560. mEqEnum, mLeEnum, mLtEnum,
  561. mEqCh, mLeCh, mLtCh,
  562. mEqB, mLeB, mLtB,
  563. mEqRef, mEqUntracedRef, mLePtr, mLtPtr,
  564. mXor, mEqCString, mEqProc,
  565. mUnaryMinusI, mUnaryMinusI64, mAbsI, mNot,
  566. mUnaryPlusI, mBitnotI,
  567. mUnaryPlusF64, mUnaryMinusF64, mAbsF64,
  568. mToFloat, mToBiggestFloat,
  569. mToInt, mToBiggestInt,
  570. mCharToStr, mBoolToStr, mIntToStr, mInt64ToStr, mFloatToStr, mCStrToStr,
  571. mStrToStr, mEnumToStr,
  572. mAnd, mOr,
  573. mEqStr, mLeStr, mLtStr,
  574. mEqSet, mLeSet, mLtSet, mMulSet, mPlusSet, mMinusSet, mSymDiffSet,
  575. mConStrStr, mSlice,
  576. mDotDot, # this one is only necessary to give nice compile time warnings
  577. mFields, mFieldPairs, mOmpParFor,
  578. mAppendStrCh, mAppendStrStr, mAppendSeqElem,
  579. mInRange, mInSet, mRepr, mExit,
  580. mSetLengthStr, mSetLengthSeq,
  581. mIsPartOf, mAstToStr, mParallel,
  582. mSwap, mIsNil, mArrToSeq, mCopyStr, mCopyStrLast,
  583. mNewString, mNewStringOfCap, mParseBiggestFloat,
  584. mMove, mWasMoved, mDestroy,
  585. mDefault, mUnown, mAccessEnv, mReset,
  586. mArray, mOpenArray, mRange, mSet, mSeq, mOpt, mVarargs,
  587. mRef, mPtr, mVar, mDistinct, mVoid, mTuple,
  588. mOrdinal,
  589. mInt, mInt8, mInt16, mInt32, mInt64,
  590. mUInt, mUInt8, mUInt16, mUInt32, mUInt64,
  591. mFloat, mFloat32, mFloat64, mFloat128,
  592. mBool, mChar, mString, mCstring,
  593. mPointer, mEmptySet, mIntSetBaseType, mNil, mExpr, mStmt, mTypeDesc,
  594. mVoidType, mPNimrodNode, mShared, mGuarded, mLock, mSpawn, mDeepCopy,
  595. mIsMainModule, mCompileDate, mCompileTime, mProcCall,
  596. mCpuEndian, mHostOS, mHostCPU, mBuildOS, mBuildCPU, mAppType,
  597. mCompileOption, mCompileOptionArg,
  598. mNLen, mNChild, mNSetChild, mNAdd, mNAddMultiple, mNDel,
  599. mNKind, mNSymKind,
  600. mNccValue, mNccInc, mNcsAdd, mNcsIncl, mNcsLen, mNcsAt,
  601. mNctPut, mNctLen, mNctGet, mNctHasNext, mNctNext,
  602. mNIntVal, mNFloatVal, mNSymbol, mNIdent, mNGetType, mNStrVal, mNSetIntVal,
  603. mNSetFloatVal, mNSetSymbol, mNSetIdent, mNSetType, mNSetStrVal, mNLineInfo,
  604. mNNewNimNode, mNCopyNimNode, mNCopyNimTree, mStrToIdent, mNSigHash, mNSizeOf,
  605. mNBindSym, mLocals, mNCallSite,
  606. mEqIdent, mEqNimrodNode, mSameNodeType, mGetImpl, mNGenSym,
  607. mNHint, mNWarning, mNError,
  608. mInstantiationInfo, mGetTypeInfo,
  609. mNimvm, mIntDefine, mStrDefine, mBoolDefine, mRunnableExamples,
  610. mException, mBuiltinType, mSymOwner, mUncheckedArray, mGetImplTransf,
  611. mSymIsInstantiationOf
  612. # things that we can evaluate safely at compile time, even if not asked for it:
  613. const
  614. ctfeWhitelist* = {mNone, mUnaryLt, mSucc,
  615. mPred, mInc, mDec, mOrd, mLengthOpenArray,
  616. mLengthStr, mLengthArray, mLengthSeq, mXLenStr, mXLenSeq,
  617. mArrGet, mArrPut, mAsgn, mDestroy,
  618. mIncl, mExcl, mCard, mChr,
  619. mAddI, mSubI, mMulI, mDivI, mModI,
  620. mAddF64, mSubF64, mMulF64, mDivF64,
  621. mShrI, mShlI, mBitandI, mBitorI, mBitxorI,
  622. mMinI, mMaxI,
  623. mMinF64, mMaxF64,
  624. mAddU, mSubU, mMulU, mDivU, mModU,
  625. mEqI, mLeI, mLtI,
  626. mEqF64, mLeF64, mLtF64,
  627. mLeU, mLtU,
  628. mLeU64, mLtU64,
  629. mEqEnum, mLeEnum, mLtEnum,
  630. mEqCh, mLeCh, mLtCh,
  631. mEqB, mLeB, mLtB,
  632. mEqRef, mEqProc, mEqUntracedRef, mLePtr, mLtPtr, mEqCString, mXor,
  633. mUnaryMinusI, mUnaryMinusI64, mAbsI, mNot, mUnaryPlusI, mBitnotI,
  634. mUnaryPlusF64, mUnaryMinusF64, mAbsF64,
  635. mToFloat, mToBiggestFloat,
  636. mToInt, mToBiggestInt,
  637. mCharToStr, mBoolToStr, mIntToStr, mInt64ToStr, mFloatToStr, mCStrToStr,
  638. mStrToStr, mEnumToStr,
  639. mAnd, mOr,
  640. mEqStr, mLeStr, mLtStr,
  641. mEqSet, mLeSet, mLtSet, mMulSet, mPlusSet, mMinusSet, mSymDiffSet,
  642. mConStrStr, mAppendStrCh, mAppendStrStr, mAppendSeqElem,
  643. mInRange, mInSet, mRepr,
  644. mCopyStr, mCopyStrLast}
  645. type
  646. PNode* = ref TNode
  647. TNodeSeq* = seq[PNode]
  648. PType* = ref TType
  649. PSym* = ref TSym
  650. TNode*{.final, acyclic.} = object # on a 32bit machine, this takes 32 bytes
  651. when defined(useNodeIds):
  652. id*: int
  653. typ*: PType
  654. info*: TLineInfo
  655. flags*: TNodeFlags
  656. case kind*: TNodeKind
  657. of nkCharLit..nkUInt64Lit:
  658. intVal*: BiggestInt
  659. of nkFloatLit..nkFloat128Lit:
  660. floatVal*: BiggestFloat
  661. of nkStrLit..nkTripleStrLit:
  662. strVal*: string
  663. of nkSym:
  664. sym*: PSym
  665. of nkIdent:
  666. ident*: PIdent
  667. else:
  668. sons*: TNodeSeq
  669. comment*: string
  670. TStrTable* = object # a table[PIdent] of PSym
  671. counter*: int
  672. data*: seq[PSym]
  673. # -------------- backend information -------------------------------
  674. TLocKind* = enum
  675. locNone, # no location
  676. locTemp, # temporary location
  677. locLocalVar, # location is a local variable
  678. locGlobalVar, # location is a global variable
  679. locParam, # location is a parameter
  680. locField, # location is a record field
  681. locExpr, # "location" is really an expression
  682. locProc, # location is a proc (an address of a procedure)
  683. locData, # location is a constant
  684. locCall, # location is a call expression
  685. locOther # location is something other
  686. TLocFlag* = enum
  687. lfIndirect, # backend introduced a pointer
  688. lfFullExternalName, # only used when 'conf.cmd == cmdPretty': Indicates
  689. # that the symbol has been imported via 'importc: "fullname"' and
  690. # no format string.
  691. lfNoDeepCopy, # no need for a deep copy
  692. lfNoDecl, # do not declare it in C
  693. lfDynamicLib, # link symbol to dynamic library
  694. lfExportLib, # export symbol for dynamic library generation
  695. lfHeader, # include header file for symbol
  696. lfImportCompilerProc, # ``importc`` of a compilerproc
  697. lfSingleUse # no location yet and will only be used once
  698. lfEnforceDeref # a copyMem is required to dereference if this a
  699. # ptr array due to C array limitations. See #1181, #6422, #11171
  700. TStorageLoc* = enum
  701. OnUnknown, # location is unknown (stack, heap or static)
  702. OnStatic, # in a static section
  703. OnStack, # location is on hardware stack
  704. OnHeap # location is on heap or global
  705. # (reference counting needed)
  706. TLocFlags* = set[TLocFlag]
  707. TLoc* = object
  708. k*: TLocKind # kind of location
  709. storage*: TStorageLoc
  710. flags*: TLocFlags # location's flags
  711. lode*: PNode # Node where the location came from; can be faked
  712. r*: Rope # rope value of location (code generators)
  713. # ---------------- end of backend information ------------------------------
  714. TLibKind* = enum
  715. libHeader, libDynamic
  716. TLib* = object # also misused for headers!
  717. kind*: TLibKind
  718. generated*: bool # needed for the backends:
  719. isOverriden*: bool
  720. name*: Rope
  721. path*: PNode # can be a string literal!
  722. CompilesId* = int ## id that is used for the caching logic within
  723. ## ``system.compiles``. See the seminst module.
  724. TInstantiation* = object
  725. sym*: PSym
  726. concreteTypes*: seq[PType]
  727. compilesId*: CompilesId
  728. PInstantiation* = ref TInstantiation
  729. TScope* = object
  730. depthLevel*: int
  731. symbols*: TStrTable
  732. parent*: PScope
  733. PScope* = ref TScope
  734. PLib* = ref TLib
  735. TSym* {.acyclic.} = object of TIdObj
  736. # proc and type instantiations are cached in the generic symbol
  737. case kind*: TSymKind
  738. of skType, skGenericParam:
  739. typeInstCache*: seq[PType]
  740. of routineKinds:
  741. procInstCache*: seq[PInstantiation]
  742. gcUnsafetyReason*: PSym # for better error messages wrt gcsafe
  743. transformedBody*: PNode # cached body after transf pass
  744. of skModule, skPackage:
  745. # modules keep track of the generic symbols they use from other modules.
  746. # this is because in incremental compilation, when a module is about to
  747. # be replaced with a newer version, we must decrement the usage count
  748. # of all previously used generics.
  749. # For 'import as' we copy the module symbol but shallowCopy the 'tab'
  750. # and set the 'usedGenerics' to ... XXX gah! Better set module.name
  751. # instead? But this doesn't work either. --> We need an skModuleAlias?
  752. # No need, just leave it as skModule but set the owner accordingly and
  753. # check for the owner when touching 'usedGenerics'.
  754. usedGenerics*: seq[PInstantiation]
  755. tab*: TStrTable # interface table for modules
  756. of skLet, skVar, skField, skForVar:
  757. guard*: PSym
  758. bitsize*: int
  759. else: nil
  760. magic*: TMagic
  761. typ*: PType
  762. name*: PIdent
  763. info*: TLineInfo
  764. owner*: PSym
  765. flags*: TSymFlags
  766. ast*: PNode # syntax tree of proc, iterator, etc.:
  767. # the whole proc including header; this is used
  768. # for easy generation of proper error messages
  769. # for variant record fields the discriminant
  770. # expression
  771. # for modules, it's a placeholder for compiler
  772. # generated code that will be appended to the
  773. # module after the sem pass (see appendToModule)
  774. options*: TOptions
  775. position*: int # used for many different things:
  776. # for enum fields its position;
  777. # for fields its offset
  778. # for parameters its position
  779. # for a conditional:
  780. # 1 iff the symbol is defined, else 0
  781. # (or not in symbol table)
  782. # for modules, an unique index corresponding
  783. # to the module's fileIdx
  784. # for variables a slot index for the evaluator
  785. # for routines a superop-ID
  786. offset*: int # offset of record field
  787. loc*: TLoc
  788. annex*: PLib # additional fields (seldom used, so we use a
  789. # reference to another object to save space)
  790. constraint*: PNode # additional constraints like 'lit|result'; also
  791. # misused for the codegenDecl pragma in the hope
  792. # it won't cause problems
  793. # for skModule the string literal to output for
  794. # deprecated modules.
  795. when defined(nimsuggest):
  796. allUsages*: seq[TLineInfo]
  797. TTypeSeq* = seq[PType]
  798. TLockLevel* = distinct int16
  799. TTypeAttachedOp* = enum ## as usual, order is important here
  800. attachedDestructor,
  801. attachedAsgn,
  802. attachedSink,
  803. attachedDeepCopy
  804. TType* {.acyclic.} = object of TIdObj # \
  805. # types are identical iff they have the
  806. # same id; there may be multiple copies of a type
  807. # in memory!
  808. kind*: TTypeKind # kind of type
  809. callConv*: TCallingConvention # for procs
  810. flags*: TTypeFlags # flags of the type
  811. sons*: TTypeSeq # base types, etc.
  812. n*: PNode # node for types:
  813. # for range types a nkRange node
  814. # for record types a nkRecord node
  815. # for enum types a list of symbols
  816. # for tyInt it can be the int literal
  817. # for procs and tyGenericBody, it's the
  818. # formal param list
  819. # for concepts, the concept body
  820. # else: unused
  821. owner*: PSym # the 'owner' of the type
  822. sym*: PSym # types have the sym associated with them
  823. # it is used for converting types to strings
  824. attachedOps*: array[TTypeAttachedOp, PSym] # destructors, etc.
  825. methods*: seq[(int,PSym)] # attached methods
  826. size*: BiggestInt # the size of the type in bytes
  827. # -1 means that the size is unkwown
  828. align*: int16 # the type's alignment requirements
  829. lockLevel*: TLockLevel # lock level as required for deadlock checking
  830. loc*: TLoc
  831. typeInst*: PType # for generic instantiations the tyGenericInst that led to this
  832. # type.
  833. uniqueId*: int # due to a design mistake, we need to keep the real ID here as it
  834. # required by the --incremental:on mode.
  835. TPair* = object
  836. key*, val*: RootRef
  837. TPairSeq* = seq[TPair]
  838. TIdPair* = object
  839. key*: PIdObj
  840. val*: RootRef
  841. TIdPairSeq* = seq[TIdPair]
  842. TIdTable* = object # the same as table[PIdent] of PObject
  843. counter*: int
  844. data*: TIdPairSeq
  845. TIdNodePair* = object
  846. key*: PIdObj
  847. val*: PNode
  848. TIdNodePairSeq* = seq[TIdNodePair]
  849. TIdNodeTable* = object # the same as table[PIdObj] of PNode
  850. counter*: int
  851. data*: TIdNodePairSeq
  852. TNodePair* = object
  853. h*: Hash # because it is expensive to compute!
  854. key*: PNode
  855. val*: int
  856. TNodePairSeq* = seq[TNodePair]
  857. TNodeTable* = object # the same as table[PNode] of int;
  858. # nodes are compared by structure!
  859. counter*: int
  860. data*: TNodePairSeq
  861. TObjectSeq* = seq[RootRef]
  862. TObjectSet* = object
  863. counter*: int
  864. data*: TObjectSeq
  865. TImplication* = enum
  866. impUnknown, impNo, impYes
  867. # BUGFIX: a module is overloadable so that a proc can have the
  868. # same name as an imported module. This is necessary because of
  869. # the poor naming choices in the standard library.
  870. const
  871. OverloadableSyms* = {skProc, skFunc, skMethod, skIterator,
  872. skConverter, skModule, skTemplate, skMacro}
  873. GenericTypes*: TTypeKinds = {tyGenericInvocation, tyGenericBody,
  874. tyGenericParam}
  875. StructuralEquivTypes*: TTypeKinds = {tyNil, tyTuple, tyArray,
  876. tySet, tyRange, tyPtr, tyRef, tyVar, tyLent, tySequence, tyProc, tyOpenArray,
  877. tyVarargs}
  878. ConcreteTypes*: TTypeKinds = { # types of the expr that may occur in::
  879. # var x = expr
  880. tyBool, tyChar, tyEnum, tyArray, tyObject,
  881. tySet, tyTuple, tyRange, tyPtr, tyRef, tyVar, tyLent, tySequence, tyProc,
  882. tyPointer,
  883. tyOpenArray, tyString, tyCString, tyInt..tyInt64, tyFloat..tyFloat128,
  884. tyUInt..tyUInt64}
  885. IntegralTypes* = {tyBool, tyChar, tyEnum, tyInt..tyInt64,
  886. tyFloat..tyFloat128, tyUInt..tyUInt64}
  887. ConstantDataTypes*: TTypeKinds = {tyArray, tySet,
  888. tyTuple, tySequence}
  889. NilableTypes*: TTypeKinds = {tyPointer, tyCString, tyRef, tyPtr,
  890. tyProc, tyError}
  891. ExportableSymKinds* = {skVar, skConst, skProc, skFunc, skMethod, skType,
  892. skIterator,
  893. skMacro, skTemplate, skConverter, skEnumField, skLet, skStub, skAlias}
  894. PersistentNodeFlags*: TNodeFlags = {nfBase2, nfBase8, nfBase16,
  895. nfDotSetter, nfDotField,
  896. nfIsRef, nfPreventCg, nfLL,
  897. nfFromTemplate, nfDefaultRefsParam,
  898. nfExecuteOnReload}
  899. namePos* = 0
  900. patternPos* = 1 # empty except for term rewriting macros
  901. genericParamsPos* = 2
  902. paramsPos* = 3
  903. pragmasPos* = 4
  904. miscPos* = 5 # used for undocumented and hacky stuff
  905. bodyPos* = 6 # position of body; use rodread.getBody() instead!
  906. resultPos* = 7
  907. dispatcherPos* = 8
  908. nkCallKinds* = {nkCall, nkInfix, nkPrefix, nkPostfix,
  909. nkCommand, nkCallStrLit, nkHiddenCallConv}
  910. nkIdentKinds* = {nkIdent, nkSym, nkAccQuoted, nkOpenSymChoice,
  911. nkClosedSymChoice}
  912. nkPragmaCallKinds* = {nkExprColonExpr, nkCall, nkCallStrLit}
  913. nkLiterals* = {nkCharLit..nkTripleStrLit}
  914. nkFloatLiterals* = {nkFloatLit..nkFloat128Lit}
  915. nkLambdaKinds* = {nkLambda, nkDo}
  916. declarativeDefs* = {nkProcDef, nkFuncDef, nkMethodDef, nkIteratorDef, nkConverterDef}
  917. procDefs* = nkLambdaKinds + declarativeDefs
  918. nkSymChoices* = {nkClosedSymChoice, nkOpenSymChoice}
  919. nkStrKinds* = {nkStrLit..nkTripleStrLit}
  920. skLocalVars* = {skVar, skLet, skForVar, skParam, skResult}
  921. skProcKinds* = {skProc, skFunc, skTemplate, skMacro, skIterator,
  922. skMethod, skConverter}
  923. var ggDebug* {.deprecated.}: bool ## convenience switch for trying out things
  924. #var
  925. # gMainPackageId*: int
  926. proc isCallExpr*(n: PNode): bool =
  927. result = n.kind in nkCallKinds
  928. proc discardSons*(father: PNode)
  929. proc len*(n: PNode): int {.inline.} =
  930. when defined(nimNoNilSeqs):
  931. result = len(n.sons)
  932. else:
  933. if isNil(n.sons): result = 0
  934. else: result = len(n.sons)
  935. proc safeLen*(n: PNode): int {.inline.} =
  936. ## works even for leaves.
  937. if n.kind in {nkNone..nkNilLit}: result = 0
  938. else: result = len(n)
  939. proc safeArrLen*(n: PNode): int {.inline.} =
  940. ## works for array-like objects (strings passed as openArray in VM).
  941. if n.kind in {nkStrLit..nkTripleStrLit}:result = len(n.strVal)
  942. elif n.kind in {nkNone..nkFloat128Lit}: result = 0
  943. else: result = len(n)
  944. proc add*(father, son: PNode) =
  945. assert son != nil
  946. when not defined(nimNoNilSeqs):
  947. if isNil(father.sons): father.sons = @[]
  948. add(father.sons, son)
  949. type Indexable = PNode | PType
  950. template `[]`*(n: Indexable, i: int): Indexable = n.sons[i]
  951. template `[]=`*(n: Indexable, i: int; x: Indexable) = n.sons[i] = x
  952. template `[]`*(n: Indexable, i: BackwardsIndex): Indexable = n[n.len - i.int]
  953. template `[]=`*(n: Indexable, i: BackwardsIndex; x: Indexable) = n[n.len - i.int] = x
  954. when defined(useNodeIds):
  955. const nodeIdToDebug* = -1 # 299750 # 300761 #300863 # 300879
  956. var gNodeId: int
  957. proc newNode*(kind: TNodeKind): PNode =
  958. new(result)
  959. result.kind = kind
  960. #result.info = UnknownLineInfo() inlined:
  961. result.info.fileIndex = InvalidFileIdx
  962. result.info.col = int16(-1)
  963. result.info.line = uint16(0)
  964. when defined(useNodeIds):
  965. result.id = gNodeId
  966. if result.id == nodeIdToDebug:
  967. echo "KIND ", result.kind
  968. writeStackTrace()
  969. inc gNodeId
  970. proc newTree*(kind: TNodeKind; children: varargs[PNode]): PNode =
  971. result = newNode(kind)
  972. if children.len > 0:
  973. result.info = children[0].info
  974. result.sons = @children
  975. template previouslyInferred*(t: PType): PType =
  976. if t.sons.len > 1: t.lastSon else: nil
  977. proc newSym*(symKind: TSymKind, name: PIdent, owner: PSym,
  978. info: TLineInfo; options: TOptions = {}): PSym =
  979. # generates a symbol and initializes the hash field too
  980. new(result)
  981. result.name = name
  982. result.kind = symKind
  983. result.flags = {}
  984. result.info = info
  985. result.options = options
  986. result.owner = owner
  987. result.offset = -1
  988. result.id = getID()
  989. when debugIds:
  990. registerId(result)
  991. proc astdef*(s: PSym): PNode =
  992. # get only the definition (initializer) portion of the ast
  993. if s.ast != nil and s.ast.kind == nkIdentDefs:
  994. s.ast[2]
  995. else:
  996. s.ast
  997. proc isMetaType*(t: PType): bool =
  998. return t.kind in tyMetaTypes or
  999. (t.kind == tyStatic and t.n == nil) or
  1000. tfHasMeta in t.flags
  1001. proc isUnresolvedStatic*(t: PType): bool =
  1002. return t.kind == tyStatic and t.n == nil
  1003. proc linkTo*(t: PType, s: PSym): PType {.discardable.} =
  1004. t.sym = s
  1005. s.typ = t
  1006. result = t
  1007. proc linkTo*(s: PSym, t: PType): PSym {.discardable.} =
  1008. t.sym = s
  1009. s.typ = t
  1010. result = s
  1011. template fileIdx*(c: PSym): FileIndex =
  1012. # XXX: this should be used only on module symbols
  1013. c.position.FileIndex
  1014. template filename*(c: PSym): string =
  1015. # XXX: this should be used only on module symbols
  1016. c.position.FileIndex.toFilename
  1017. proc appendToModule*(m: PSym, n: PNode) =
  1018. ## The compiler will use this internally to add nodes that will be
  1019. ## appended to the module after the sem pass
  1020. if m.ast == nil:
  1021. m.ast = newNode(nkStmtList)
  1022. m.ast.sons = @[n]
  1023. else:
  1024. assert m.ast.kind == nkStmtList
  1025. m.ast.sons.add(n)
  1026. const # for all kind of hash tables:
  1027. GrowthFactor* = 2 # must be power of 2, > 0
  1028. StartSize* = 8 # must be power of 2, > 0
  1029. proc copyStrTable*(dest: var TStrTable, src: TStrTable) =
  1030. dest.counter = src.counter
  1031. setLen(dest.data, len(src.data))
  1032. for i in 0 .. high(src.data): dest.data[i] = src.data[i]
  1033. proc copyIdTable*(dest: var TIdTable, src: TIdTable) =
  1034. dest.counter = src.counter
  1035. newSeq(dest.data, len(src.data))
  1036. for i in 0 .. high(src.data): dest.data[i] = src.data[i]
  1037. proc copyObjectSet*(dest: var TObjectSet, src: TObjectSet) =
  1038. dest.counter = src.counter
  1039. setLen(dest.data, len(src.data))
  1040. for i in 0 .. high(src.data): dest.data[i] = src.data[i]
  1041. proc discardSons*(father: PNode) =
  1042. when defined(nimNoNilSeqs):
  1043. father.sons = @[]
  1044. else:
  1045. father.sons = nil
  1046. proc withInfo*(n: PNode, info: TLineInfo): PNode =
  1047. n.info = info
  1048. return n
  1049. proc newIdentNode*(ident: PIdent, info: TLineInfo): PNode =
  1050. result = newNode(nkIdent)
  1051. result.ident = ident
  1052. result.info = info
  1053. proc newSymNode*(sym: PSym): PNode =
  1054. result = newNode(nkSym)
  1055. result.sym = sym
  1056. result.typ = sym.typ
  1057. result.info = sym.info
  1058. proc newSymNode*(sym: PSym, info: TLineInfo): PNode =
  1059. result = newNode(nkSym)
  1060. result.sym = sym
  1061. result.typ = sym.typ
  1062. result.info = info
  1063. proc newNodeI*(kind: TNodeKind, info: TLineInfo): PNode =
  1064. new(result)
  1065. result.kind = kind
  1066. result.info = info
  1067. when defined(useNodeIds):
  1068. result.id = gNodeId
  1069. if result.id == nodeIdToDebug:
  1070. echo "KIND ", result.kind
  1071. writeStackTrace()
  1072. inc gNodeId
  1073. proc newNodeI*(kind: TNodeKind, info: TLineInfo, children: int): PNode =
  1074. new(result)
  1075. result.kind = kind
  1076. result.info = info
  1077. if children > 0:
  1078. newSeq(result.sons, children)
  1079. when defined(useNodeIds):
  1080. result.id = gNodeId
  1081. if result.id == nodeIdToDebug:
  1082. echo "KIND ", result.kind
  1083. writeStackTrace()
  1084. inc gNodeId
  1085. proc newNode*(kind: TNodeKind, info: TLineInfo, sons: TNodeSeq = @[],
  1086. typ: PType = nil): PNode =
  1087. new(result)
  1088. result.kind = kind
  1089. result.info = info
  1090. result.typ = typ
  1091. # XXX use shallowCopy here for ownership transfer:
  1092. result.sons = sons
  1093. when defined(useNodeIds):
  1094. result.id = gNodeId
  1095. if result.id == nodeIdToDebug:
  1096. echo "KIND ", result.kind
  1097. writeStackTrace()
  1098. inc gNodeId
  1099. proc newNodeIT*(kind: TNodeKind, info: TLineInfo, typ: PType): PNode =
  1100. result = newNode(kind)
  1101. result.info = info
  1102. result.typ = typ
  1103. proc newIntNode*(kind: TNodeKind, intVal: BiggestInt): PNode =
  1104. result = newNode(kind)
  1105. result.intVal = intVal
  1106. proc newIntTypeNode*(kind: TNodeKind, intVal: BiggestInt, typ: PType): PNode =
  1107. result = newIntNode(kind, intVal)
  1108. result.typ = typ
  1109. proc newFloatNode*(kind: TNodeKind, floatVal: BiggestFloat): PNode =
  1110. result = newNode(kind)
  1111. result.floatVal = floatVal
  1112. proc newStrNode*(kind: TNodeKind, strVal: string): PNode =
  1113. result = newNode(kind)
  1114. result.strVal = strVal
  1115. proc newStrNode*(strVal: string; info: TLineInfo): PNode =
  1116. result = newNodeI(nkStrLit, info)
  1117. result.strVal = strVal
  1118. proc addSon*(father, son: PNode) =
  1119. assert son != nil
  1120. when not defined(nimNoNilSeqs):
  1121. if isNil(father.sons): father.sons = @[]
  1122. add(father.sons, son)
  1123. proc newProcNode*(kind: TNodeKind, info: TLineInfo, body: PNode,
  1124. params,
  1125. name, pattern, genericParams,
  1126. pragmas, exceptions: PNode): PNode =
  1127. result = newNodeI(kind, info)
  1128. result.sons = @[name, pattern, genericParams, params,
  1129. pragmas, exceptions, body]
  1130. const
  1131. UnspecifiedLockLevel* = TLockLevel(-1'i16)
  1132. MaxLockLevel* = 1000'i16
  1133. UnknownLockLevel* = TLockLevel(1001'i16)
  1134. AttachedOpToStr*: array[TTypeAttachedOp, string] = ["=destroy", "=", "=sink", "=deepcopy"]
  1135. proc `$`*(x: TLockLevel): string =
  1136. if x.ord == UnspecifiedLockLevel.ord: result = "<unspecified>"
  1137. elif x.ord == UnknownLockLevel.ord: result = "<unknown>"
  1138. else: result = $int16(x)
  1139. proc `$`*(s: PSym): string =
  1140. if s != nil:
  1141. result = s.name.s & "@" & $s.id
  1142. else:
  1143. result = "<nil>"
  1144. proc newType*(kind: TTypeKind, owner: PSym): PType =
  1145. new(result)
  1146. result.kind = kind
  1147. result.owner = owner
  1148. result.size = -1
  1149. result.align = -1 # default alignment
  1150. result.id = getID()
  1151. result.uniqueId = result.id
  1152. result.lockLevel = UnspecifiedLockLevel
  1153. when debugIds:
  1154. registerId(result)
  1155. when false:
  1156. if result.id == 76426:
  1157. echo "KNID ", kind
  1158. writeStackTrace()
  1159. proc mergeLoc(a: var TLoc, b: TLoc) =
  1160. if a.k == low(a.k): a.k = b.k
  1161. if a.storage == low(a.storage): a.storage = b.storage
  1162. a.flags = a.flags + b.flags
  1163. if a.lode == nil: a.lode = b.lode
  1164. if a.r == nil: a.r = b.r
  1165. proc newSons*(father: PNode, length: int) =
  1166. when defined(nimNoNilSeqs):
  1167. setLen(father.sons, length)
  1168. else:
  1169. if isNil(father.sons):
  1170. newSeq(father.sons, length)
  1171. else:
  1172. setLen(father.sons, length)
  1173. proc newSons*(father: PType, length: int) =
  1174. when defined(nimNoNilSeqs):
  1175. setLen(father.sons, length)
  1176. else:
  1177. if isNil(father.sons):
  1178. newSeq(father.sons, length)
  1179. else:
  1180. setLen(father.sons, length)
  1181. proc sonsLen*(n: PType): int = n.sons.len
  1182. proc len*(n: PType): int = n.sons.len
  1183. proc sonsLen*(n: PNode): int = n.sons.len
  1184. proc lastSon*(n: PNode): PNode = n.sons[^1]
  1185. proc lastSon*(n: PType): PType = n.sons[^1]
  1186. proc assignType*(dest, src: PType) =
  1187. dest.kind = src.kind
  1188. dest.flags = src.flags
  1189. dest.callConv = src.callConv
  1190. dest.n = src.n
  1191. dest.size = src.size
  1192. dest.align = src.align
  1193. dest.attachedOps = src.attachedOps
  1194. dest.lockLevel = src.lockLevel
  1195. # this fixes 'type TLock = TSysLock':
  1196. if src.sym != nil:
  1197. if dest.sym != nil:
  1198. dest.sym.flags = dest.sym.flags + (src.sym.flags-{sfExported})
  1199. if dest.sym.annex == nil: dest.sym.annex = src.sym.annex
  1200. mergeLoc(dest.sym.loc, src.sym.loc)
  1201. else:
  1202. dest.sym = src.sym
  1203. newSons(dest, sonsLen(src))
  1204. for i in 0 ..< sonsLen(src): dest.sons[i] = src.sons[i]
  1205. proc copyType*(t: PType, owner: PSym, keepId: bool): PType =
  1206. result = newType(t.kind, owner)
  1207. assignType(result, t)
  1208. if keepId:
  1209. result.id = t.id
  1210. else:
  1211. when debugIds: registerId(result)
  1212. result.sym = t.sym # backend-info should not be copied
  1213. proc exactReplica*(t: PType): PType = copyType(t, t.owner, true)
  1214. proc copySym*(s: PSym): PSym =
  1215. result = newSym(s.kind, s.name, s.owner, s.info, s.options)
  1216. #result.ast = nil # BUGFIX; was: s.ast which made problems
  1217. result.typ = s.typ
  1218. when debugIds: registerId(result)
  1219. result.flags = s.flags
  1220. result.magic = s.magic
  1221. if s.kind == skModule:
  1222. copyStrTable(result.tab, s.tab)
  1223. result.options = s.options
  1224. result.position = s.position
  1225. result.loc = s.loc
  1226. result.annex = s.annex # BUGFIX
  1227. if result.kind in {skVar, skLet, skField}:
  1228. result.guard = s.guard
  1229. proc createModuleAlias*(s: PSym, newIdent: PIdent, info: TLineInfo;
  1230. options: TOptions): PSym =
  1231. result = newSym(s.kind, newIdent, s.owner, info, options)
  1232. # keep ID!
  1233. result.ast = s.ast
  1234. result.id = s.id
  1235. result.flags = s.flags
  1236. system.shallowCopy(result.tab, s.tab)
  1237. result.options = s.options
  1238. result.position = s.position
  1239. result.loc = s.loc
  1240. result.annex = s.annex
  1241. # XXX once usedGenerics is used, ensure module aliases keep working!
  1242. assert s.usedGenerics.len == 0
  1243. proc initStrTable*(x: var TStrTable) =
  1244. x.counter = 0
  1245. newSeq(x.data, StartSize)
  1246. proc newStrTable*: TStrTable =
  1247. initStrTable(result)
  1248. proc initIdTable*(x: var TIdTable) =
  1249. x.counter = 0
  1250. newSeq(x.data, StartSize)
  1251. proc newIdTable*: TIdTable =
  1252. initIdTable(result)
  1253. proc resetIdTable*(x: var TIdTable) =
  1254. x.counter = 0
  1255. # clear and set to old initial size:
  1256. setLen(x.data, 0)
  1257. setLen(x.data, StartSize)
  1258. proc initObjectSet*(x: var TObjectSet) =
  1259. x.counter = 0
  1260. newSeq(x.data, StartSize)
  1261. proc initIdNodeTable*(x: var TIdNodeTable) =
  1262. x.counter = 0
  1263. newSeq(x.data, StartSize)
  1264. proc initNodeTable*(x: var TNodeTable) =
  1265. x.counter = 0
  1266. newSeq(x.data, StartSize)
  1267. proc skipTypes*(t: PType, kinds: TTypeKinds): PType =
  1268. ## Used throughout the compiler code to test whether a type tree contains or
  1269. ## doesn't contain a specific type/types - it is often the case that only the
  1270. ## last child nodes of a type tree need to be searched. This is a really hot
  1271. ## path within the compiler!
  1272. result = t
  1273. while result.kind in kinds: result = lastSon(result)
  1274. proc skipTypes*(t: PType, kinds: TTypeKinds; maxIters: int): PType =
  1275. result = t
  1276. var i = maxIters
  1277. while result.kind in kinds:
  1278. result = lastSon(result)
  1279. dec i
  1280. if i == 0: return nil
  1281. proc skipTypesOrNil*(t: PType, kinds: TTypeKinds): PType =
  1282. ## same as skipTypes but handles 'nil'
  1283. result = t
  1284. while result != nil and result.kind in kinds:
  1285. if result.len == 0: return nil
  1286. result = lastSon(result)
  1287. proc isGCedMem*(t: PType): bool {.inline.} =
  1288. result = t.kind in {tyString, tyRef, tySequence} or
  1289. t.kind == tyProc and t.callConv == ccClosure
  1290. proc propagateToOwner*(owner, elem: PType) =
  1291. const HaveTheirOwnEmpty = {tySequence, tyOpt, tySet, tyPtr, tyRef, tyProc}
  1292. owner.flags = owner.flags + (elem.flags * {tfHasMeta, tfTriggersCompileTime})
  1293. if tfNotNil in elem.flags:
  1294. if owner.kind in {tyGenericInst, tyGenericBody, tyGenericInvocation}:
  1295. owner.flags.incl tfNotNil
  1296. elif owner.kind notin HaveTheirOwnEmpty:
  1297. owner.flags.incl tfNeedsInit
  1298. if tfNeedsInit in elem.flags:
  1299. if owner.kind in HaveTheirOwnEmpty: discard
  1300. else: owner.flags.incl tfNeedsInit
  1301. if elem.isMetaType:
  1302. owner.flags.incl tfHasMeta
  1303. if tfHasAsgn in elem.flags:
  1304. let o2 = owner.skipTypes({tyGenericInst, tyAlias, tySink})
  1305. if o2.kind in {tyTuple, tyObject, tyArray,
  1306. tySequence, tyOpt, tySet, tyDistinct}:
  1307. o2.flags.incl tfHasAsgn
  1308. owner.flags.incl tfHasAsgn
  1309. if tfHasOwned in elem.flags:
  1310. let o2 = owner.skipTypes({tyGenericInst, tyAlias, tySink})
  1311. if o2.kind in {tyTuple, tyObject, tyArray,
  1312. tySequence, tyOpt, tySet, tyDistinct}:
  1313. o2.flags.incl tfHasOwned
  1314. owner.flags.incl tfHasOwned
  1315. if owner.kind notin {tyProc, tyGenericInst, tyGenericBody,
  1316. tyGenericInvocation, tyPtr}:
  1317. let elemB = elem.skipTypes({tyGenericInst, tyAlias, tySink})
  1318. if elemB.isGCedMem or tfHasGCedMem in elemB.flags:
  1319. # for simplicity, we propagate this flag even to generics. We then
  1320. # ensure this doesn't bite us in sempass2.
  1321. owner.flags.incl tfHasGCedMem
  1322. proc rawAddSon*(father, son: PType) =
  1323. when not defined(nimNoNilSeqs):
  1324. if isNil(father.sons): father.sons = @[]
  1325. add(father.sons, son)
  1326. if not son.isNil: propagateToOwner(father, son)
  1327. proc rawAddSonNoPropagationOfTypeFlags*(father, son: PType) =
  1328. when not defined(nimNoNilSeqs):
  1329. if isNil(father.sons): father.sons = @[]
  1330. add(father.sons, son)
  1331. proc addSonNilAllowed*(father, son: PNode) =
  1332. when not defined(nimNoNilSeqs):
  1333. if isNil(father.sons): father.sons = @[]
  1334. add(father.sons, son)
  1335. proc delSon*(father: PNode, idx: int) =
  1336. when defined(nimNoNilSeqs):
  1337. if father.len == 0: return
  1338. else:
  1339. if isNil(father.sons): return
  1340. var length = sonsLen(father)
  1341. for i in idx .. length - 2: father.sons[i] = father.sons[i + 1]
  1342. setLen(father.sons, length - 1)
  1343. proc copyNode*(src: PNode): PNode =
  1344. # does not copy its sons!
  1345. if src == nil:
  1346. return nil
  1347. result = newNode(src.kind)
  1348. result.info = src.info
  1349. result.typ = src.typ
  1350. result.flags = src.flags * PersistentNodeFlags
  1351. result.comment = src.comment
  1352. when defined(useNodeIds):
  1353. if result.id == nodeIdToDebug:
  1354. echo "COMES FROM ", src.id
  1355. case src.kind
  1356. of nkCharLit..nkUInt64Lit: result.intVal = src.intVal
  1357. of nkFloatLiterals: result.floatVal = src.floatVal
  1358. of nkSym: result.sym = src.sym
  1359. of nkIdent: result.ident = src.ident
  1360. of nkStrLit..nkTripleStrLit: result.strVal = src.strVal
  1361. else: discard
  1362. proc shallowCopy*(src: PNode): PNode =
  1363. # does not copy its sons, but provides space for them:
  1364. if src == nil: return nil
  1365. result = newNode(src.kind)
  1366. result.info = src.info
  1367. result.typ = src.typ
  1368. result.flags = src.flags * PersistentNodeFlags
  1369. result.comment = src.comment
  1370. when defined(useNodeIds):
  1371. if result.id == nodeIdToDebug:
  1372. echo "COMES FROM ", src.id
  1373. case src.kind
  1374. of nkCharLit..nkUInt64Lit: result.intVal = src.intVal
  1375. of nkFloatLiterals: result.floatVal = src.floatVal
  1376. of nkSym: result.sym = src.sym
  1377. of nkIdent: result.ident = src.ident
  1378. of nkStrLit..nkTripleStrLit: result.strVal = src.strVal
  1379. else: newSeq(result.sons, sonsLen(src))
  1380. proc copyTree*(src: PNode): PNode =
  1381. # copy a whole syntax tree; performs deep copying
  1382. if src == nil:
  1383. return nil
  1384. result = newNode(src.kind)
  1385. result.info = src.info
  1386. result.typ = src.typ
  1387. result.flags = src.flags * PersistentNodeFlags
  1388. result.comment = src.comment
  1389. when defined(useNodeIds):
  1390. if result.id == nodeIdToDebug:
  1391. echo "COMES FROM ", src.id
  1392. case src.kind
  1393. of nkCharLit..nkUInt64Lit: result.intVal = src.intVal
  1394. of nkFloatLiterals: result.floatVal = src.floatVal
  1395. of nkSym: result.sym = src.sym
  1396. of nkIdent: result.ident = src.ident
  1397. of nkStrLit..nkTripleStrLit: result.strVal = src.strVal
  1398. else:
  1399. newSeq(result.sons, sonsLen(src))
  1400. for i in 0 ..< sonsLen(src):
  1401. result.sons[i] = copyTree(src.sons[i])
  1402. proc hasSonWith*(n: PNode, kind: TNodeKind): bool =
  1403. for i in 0 ..< sonsLen(n):
  1404. if n.sons[i].kind == kind:
  1405. return true
  1406. result = false
  1407. proc hasNilSon*(n: PNode): bool =
  1408. for i in 0 ..< safeLen(n):
  1409. if n.sons[i] == nil:
  1410. return true
  1411. elif hasNilSon(n.sons[i]):
  1412. return true
  1413. result = false
  1414. proc containsNode*(n: PNode, kinds: TNodeKinds): bool =
  1415. if n == nil: return
  1416. case n.kind
  1417. of nkEmpty..nkNilLit: result = n.kind in kinds
  1418. else:
  1419. for i in 0 ..< sonsLen(n):
  1420. if n.kind in kinds or containsNode(n.sons[i], kinds): return true
  1421. proc hasSubnodeWith*(n: PNode, kind: TNodeKind): bool =
  1422. case n.kind
  1423. of nkEmpty..nkNilLit: result = n.kind == kind
  1424. else:
  1425. for i in 0 ..< sonsLen(n):
  1426. if (n.sons[i].kind == kind) or hasSubnodeWith(n.sons[i], kind):
  1427. return true
  1428. result = false
  1429. proc getInt*(a: PNode): BiggestInt =
  1430. case a.kind
  1431. of nkCharLit..nkUInt64Lit: result = a.intVal
  1432. else:
  1433. raiseRecoverableError("cannot extract number from invalid AST node")
  1434. #internalError(a.info, "getInt")
  1435. #doAssert false, "getInt"
  1436. #result = 0
  1437. proc getFloat*(a: PNode): BiggestFloat =
  1438. case a.kind
  1439. of nkFloatLiterals: result = a.floatVal
  1440. else:
  1441. raiseRecoverableError("cannot extract number from invalid AST node")
  1442. #doAssert false, "getFloat"
  1443. #internalError(a.info, "getFloat")
  1444. #result = 0.0
  1445. proc getStr*(a: PNode): string =
  1446. case a.kind
  1447. of nkStrLit..nkTripleStrLit: result = a.strVal
  1448. of nkNilLit:
  1449. # let's hope this fixes more problems than it creates:
  1450. when defined(nimNoNilSeqs):
  1451. result = ""
  1452. else:
  1453. result = nil
  1454. else:
  1455. raiseRecoverableError("cannot extract string from invalid AST node")
  1456. #doAssert false, "getStr"
  1457. #internalError(a.info, "getStr")
  1458. #result = ""
  1459. proc getStrOrChar*(a: PNode): string =
  1460. case a.kind
  1461. of nkStrLit..nkTripleStrLit: result = a.strVal
  1462. of nkCharLit..nkUInt64Lit: result = $chr(int(a.intVal))
  1463. else:
  1464. raiseRecoverableError("cannot extract string from invalid AST node")
  1465. #doAssert false, "getStrOrChar"
  1466. #internalError(a.info, "getStrOrChar")
  1467. #result = ""
  1468. proc isGenericRoutine*(s: PSym): bool =
  1469. case s.kind
  1470. of skProcKinds:
  1471. result = sfFromGeneric in s.flags or
  1472. (s.ast != nil and s.ast[genericParamsPos].kind != nkEmpty)
  1473. else: discard
  1474. proc skipGenericOwner*(s: PSym): PSym =
  1475. ## Generic instantiations are owned by their originating generic
  1476. ## symbol. This proc skips such owners and goes straight to the owner
  1477. ## of the generic itself (the module or the enclosing proc).
  1478. result = if s.kind in skProcKinds and sfFromGeneric in s.flags:
  1479. s.owner.owner
  1480. else:
  1481. s.owner
  1482. proc originatingModule*(s: PSym): PSym =
  1483. result = s.owner
  1484. while result.kind != skModule: result = result.owner
  1485. proc isRoutine*(s: PSym): bool {.inline.} =
  1486. result = s.kind in skProcKinds
  1487. proc isCompileTimeProc*(s: PSym): bool {.inline.} =
  1488. result = s.kind == skMacro or
  1489. s.kind == skProc and sfCompileTime in s.flags
  1490. proc isRunnableExamples*(n: PNode): bool =
  1491. # Templates and generics don't perform symbol lookups.
  1492. result = n.kind == nkSym and n.sym.magic == mRunnableExamples or
  1493. n.kind == nkIdent and n.ident.s == "runnableExamples"
  1494. proc requiredParams*(s: PSym): int =
  1495. # Returns the number of required params (without default values)
  1496. # XXX: Perhaps we can store this in the `offset` field of the
  1497. # symbol instead?
  1498. for i in 1 ..< s.typ.len:
  1499. if s.typ.n[i].sym.ast != nil:
  1500. return i - 1
  1501. return s.typ.len - 1
  1502. proc hasPattern*(s: PSym): bool {.inline.} =
  1503. result = isRoutine(s) and s.ast.sons[patternPos].kind != nkEmpty
  1504. iterator items*(n: PNode): PNode =
  1505. for i in 0..<n.safeLen: yield n.sons[i]
  1506. iterator pairs*(n: PNode): tuple[i: int, n: PNode] =
  1507. for i in 0..<n.safeLen: yield (i, n.sons[i])
  1508. proc isAtom*(n: PNode): bool {.inline.} =
  1509. result = n.kind >= nkNone and n.kind <= nkNilLit
  1510. proc isEmptyType*(t: PType): bool {.inline.} =
  1511. ## 'void' and 'stmt' types are often equivalent to 'nil' these days:
  1512. result = t == nil or t.kind in {tyVoid, tyTyped}
  1513. proc makeStmtList*(n: PNode): PNode =
  1514. if n.kind == nkStmtList:
  1515. result = n
  1516. else:
  1517. result = newNodeI(nkStmtList, n.info)
  1518. result.add n
  1519. proc skipStmtList*(n: PNode): PNode =
  1520. if n.kind in {nkStmtList, nkStmtListExpr}:
  1521. for i in 0 .. n.len-2:
  1522. if n[i].kind notin {nkEmpty, nkCommentStmt}: return n
  1523. result = n.lastSon
  1524. else:
  1525. result = n
  1526. proc toVar*(typ: PType): PType =
  1527. ## If ``typ`` is not a tyVar then it is converted into a `var <typ>` and
  1528. ## returned. Otherwise ``typ`` is simply returned as-is.
  1529. result = typ
  1530. if typ.kind != tyVar:
  1531. result = newType(tyVar, typ.owner)
  1532. rawAddSon(result, typ)
  1533. proc toRef*(typ: PType): PType =
  1534. ## If ``typ`` is a tyObject then it is converted into a `ref <typ>` and
  1535. ## returned. Otherwise ``typ`` is simply returned as-is.
  1536. if typ.skipTypes({tyAlias, tyGenericInst}).kind == tyObject:
  1537. result = newType(tyRef, typ.owner)
  1538. rawAddSon(result, typ)
  1539. proc toObject*(typ: PType): PType =
  1540. ## If ``typ`` is a tyRef then its immediate son is returned (which in many
  1541. ## cases should be a ``tyObject``).
  1542. ## Otherwise ``typ`` is simply returned as-is.
  1543. let t = typ.skipTypes({tyAlias, tyGenericInst})
  1544. if t.kind == tyRef: t.lastSon
  1545. else: typ
  1546. proc isImportedException*(t: PType; conf: ConfigRef): bool =
  1547. assert t != nil
  1548. if optNoCppExceptions in conf.globalOptions:
  1549. return false
  1550. let base = t.skipTypes({tyAlias, tyPtr, tyDistinct, tyGenericInst})
  1551. if base.sym != nil and {sfCompileToCpp, sfImportc} * base.sym.flags != {}:
  1552. result = true
  1553. proc isInfixAs*(n: PNode): bool =
  1554. return n.kind == nkInfix and n[0].kind == nkIdent and n[0].ident.s == "as"
  1555. proc findUnresolvedStatic*(n: PNode): PNode =
  1556. if n.kind == nkSym and n.typ.kind == tyStatic and n.typ.n == nil:
  1557. return n
  1558. for son in n:
  1559. let n = son.findUnresolvedStatic
  1560. if n != nil: return n
  1561. return nil
  1562. when false:
  1563. proc containsNil*(n: PNode): bool =
  1564. # only for debugging
  1565. if n.isNil: return true
  1566. for i in 0 ..< n.safeLen:
  1567. if n[i].containsNil: return true
  1568. template hasDestructor*(t: PType): bool = {tfHasAsgn, tfHasOwned} * t.flags != {}
  1569. template incompleteType*(t: PType): bool =
  1570. t.sym != nil and {sfForward, sfNoForward} * t.sym.flags == {sfForward}
  1571. template typeCompleted*(s: PSym) =
  1572. incl s.flags, sfNoForward
  1573. template getBody*(s: PSym): PNode = s.ast[bodyPos]
  1574. template detailedInfo*(sym: PSym): string =
  1575. sym.name.s
  1576. proc isInlineIterator*(s: PSym): bool {.inline.} =
  1577. s.kind == skIterator and s.typ.callConv != ccClosure
  1578. proc isClosureIterator*(s: PSym): bool {.inline.} =
  1579. s.kind == skIterator and s.typ.callConv == ccClosure
  1580. proc isSinkParam*(s: PSym): bool {.inline.} =
  1581. s.kind == skParam and (s.typ.kind == tySink or tfHasOwned in s.typ.flags)
  1582. proc isSinkType*(t: PType): bool {.inline.} =
  1583. t.kind == tySink or tfHasOwned in t.flags
  1584. proc newProcType*(info: TLineInfo; owner: PSym): PType =
  1585. result = newType(tyProc, owner)
  1586. result.n = newNodeI(nkFormalParams, info)
  1587. rawAddSon(result, nil) # return type
  1588. # result.n[0] used to be `nkType`, but now it's `nkEffectList` because
  1589. # the effects are now stored in there too ... this is a bit hacky, but as
  1590. # usual we desperately try to save memory:
  1591. addSon(result.n, newNodeI(nkEffectList, info))
  1592. proc addParam*(procType: PType; param: PSym) =
  1593. param.position = procType.len-1
  1594. addSon(procType.n, newSymNode(param))
  1595. rawAddSon(procType, param.typ)
  1596. template destructor*(t: PType): PSym = t.attachedOps[attachedDestructor]
  1597. template assignment*(t: PType): PSym = t.attachedOps[attachedAsgn]
  1598. template asink*(t: PType): PSym = t.attachedOps[attachedSink]