ast.nim 66 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779
  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. nkReturnToken, # 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 33 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. sfGenSym # symbol is 'gensym'ed; do not add to symbol table
  258. TSymFlags* = set[TSymFlag]
  259. const
  260. sfNoInit* = sfMainModule # don't generate code to init the variable
  261. sfImmediate* = sfDispatcher
  262. # macro or template is immediately expanded
  263. # without considering any possible overloads
  264. sfAllUntyped* = sfVolatile # macro or template is immediately expanded \
  265. # in a generic context
  266. sfDirty* = sfPure
  267. # template is not hygienic (old styled template)
  268. # module, compiled from a dirty-buffer
  269. sfAnon* = sfDiscardable
  270. # symbol name that was generated by the compiler
  271. # the compiler will avoid printing such names
  272. # in user messages.
  273. sfHoisted* = sfForward
  274. # an expression was hoised to an anonymous variable.
  275. # the flag is applied to the var/let symbol
  276. sfNoForward* = sfRegister
  277. # forward declarations are not required (per module)
  278. sfReorder* = sfForward
  279. # reordering pass is enabled
  280. sfCompileToCpp* = sfInfixCall # compile the module as C++ code
  281. sfCompileToObjc* = sfNamedParamCall # compile the module as Objective-C code
  282. sfExperimental* = sfOverriden # module uses the .experimental switch
  283. sfGoto* = sfOverriden # var is used for 'goto' code generation
  284. sfWrittenTo* = sfBorrow # param is assigned to
  285. sfEscapes* = sfProcvar # param escapes
  286. sfBase* = sfDiscriminant
  287. sfIsSelf* = sfOverriden # param is 'self'
  288. sfCustomPragma* = sfRegister # symbol is custom pragma template
  289. const
  290. # getting ready for the future expr/stmt merge
  291. nkWhen* = nkWhenStmt
  292. nkWhenExpr* = nkWhenStmt
  293. nkEffectList* = nkArgList
  294. # hacks ahead: an nkEffectList is a node with 4 children:
  295. exceptionEffects* = 0 # exceptions at position 0
  296. usesEffects* = 1 # read effects at position 1
  297. writeEffects* = 2 # write effects at position 2
  298. tagEffects* = 3 # user defined tag ('gc', 'time' etc.)
  299. pragmasEffects* = 4 # not an effect, but a slot for pragmas in proc type
  300. effectListLen* = 5 # list of effects list
  301. type
  302. TTypeKind* = enum # order is important!
  303. # Don't forget to change hti.nim if you make a change here
  304. # XXX put this into an include file to avoid this issue!
  305. # several types are no longer used (guess which), but a
  306. # spot in the sequence is kept for backwards compatibility
  307. # (apparently something with bootstrapping)
  308. # if you need to add a type, they can apparently be reused
  309. tyNone, tyBool, tyChar,
  310. tyEmpty, tyAlias, tyNil, tyExpr, tyStmt, tyTypeDesc,
  311. tyGenericInvocation, # ``T[a, b]`` for types to invoke
  312. tyGenericBody, # ``T[a, b, body]`` last parameter is the body
  313. tyGenericInst, # ``T[a, b, realInstance]`` instantiated generic type
  314. # realInstance will be a concrete type like tyObject
  315. # unless this is an instance of a generic alias type.
  316. # then realInstance will be the tyGenericInst of the
  317. # completely (recursively) resolved alias.
  318. tyGenericParam, # ``a`` in the above patterns
  319. tyDistinct,
  320. tyEnum,
  321. tyOrdinal, # integer types (including enums and boolean)
  322. tyArray,
  323. tyObject,
  324. tyTuple,
  325. tySet,
  326. tyRange,
  327. tyPtr, tyRef,
  328. tyVar,
  329. tySequence,
  330. tyProc,
  331. tyPointer, tyOpenArray,
  332. tyString, tyCString, tyForward,
  333. tyInt, tyInt8, tyInt16, tyInt32, tyInt64, # signed integers
  334. tyFloat, tyFloat32, tyFloat64, tyFloat128,
  335. tyUInt, tyUInt8, tyUInt16, tyUInt32, tyUInt64,
  336. tyOptAsRef, tySink, tyLent,
  337. tyVarargs,
  338. tyUnused,
  339. tyProxy # used as errornous type (for idetools)
  340. tyBuiltInTypeClass
  341. # Type such as the catch-all object, tuple, seq, etc
  342. tyUserTypeClass
  343. # the body of a user-defined type class
  344. tyUserTypeClassInst
  345. # Instance of a parametric user-defined type class.
  346. # Structured similarly to tyGenericInst.
  347. # tyGenericInst represents concrete types, while
  348. # this is still a "generic param" that will bind types
  349. # and resolves them during sigmatch and instantiation.
  350. tyCompositeTypeClass
  351. # Type such as seq[Number]
  352. # The notes for tyUserTypeClassInst apply here as well
  353. # sons[0]: the original expression used by the user.
  354. # sons[1]: fully expanded and instantiated meta type
  355. # (potentially following aliases)
  356. tyInferred
  357. # In the initial state `base` stores a type class constraining
  358. # the types that can be inferred. After a candidate type is
  359. # selected, it's stored in `lastSon`. Between `base` and `lastSon`
  360. # there may be 0, 2 or more types that were also considered as
  361. # possible candidates in the inference process (i.e. lastSon will
  362. # be updated to store a type best conforming to all candidates)
  363. tyAnd, tyOr, tyNot
  364. # boolean type classes such as `string|int`,`not seq`,
  365. # `Sortable and Enumable`, etc
  366. tyAnything
  367. # a type class matching any type
  368. tyStatic
  369. # a value known at compile type (the underlying type is .base)
  370. tyFromExpr
  371. # This is a type representing an expression that depends
  372. # on generic parameters (the expression is stored in t.n)
  373. # It will be converted to a real type only during generic
  374. # instantiation and prior to this it has the potential to
  375. # be any type.
  376. tyOpt
  377. # Builtin optional type
  378. tyVoid
  379. # now different from tyEmpty, hurray!
  380. static:
  381. # remind us when TTypeKind stops to fit in a single 64-bit word
  382. assert TTypeKind.high.ord <= 63
  383. const
  384. tyPureObject* = tyTuple
  385. GcTypeKinds* = {tyRef, tySequence, tyString}
  386. tyError* = tyProxy # as an errornous node should match everything
  387. tyUnknown* = tyFromExpr
  388. tyUnknownTypes* = {tyError, tyFromExpr}
  389. tyTypeClasses* = {tyBuiltInTypeClass, tyCompositeTypeClass,
  390. tyUserTypeClass, tyUserTypeClassInst,
  391. tyAnd, tyOr, tyNot, tyAnything}
  392. tyMetaTypes* = {tyGenericParam, tyTypeDesc, tyExpr} + tyTypeClasses
  393. tyUserTypeClasses* = {tyUserTypeClass, tyUserTypeClassInst}
  394. type
  395. TTypeKinds* = set[TTypeKind]
  396. TNodeFlag* = enum
  397. nfNone,
  398. nfBase2, # nfBase10 is default, so not needed
  399. nfBase8,
  400. nfBase16,
  401. nfAllConst, # used to mark complex expressions constant; easy to get rid of
  402. # but unfortunately it has measurable impact for compilation
  403. # efficiency
  404. nfTransf, # node has been transformed
  405. nfNoRewrite # node should not be transformed anymore
  406. nfSem # node has been checked for semantics
  407. nfLL # node has gone through lambda lifting
  408. nfDotField # the call can use a dot operator
  409. nfDotSetter # the call can use a setter dot operarator
  410. nfExplicitCall # x.y() was used instead of x.y
  411. nfExprCall # this is an attempt to call a regular expression
  412. nfIsRef # this node is a 'ref' node; used for the VM
  413. nfPreventCg # this node should be ignored by the codegen
  414. nfBlockArg # this a stmtlist appearing in a call (e.g. a do block)
  415. nfFromTemplate # a top-level node returned from a template
  416. nfDefaultParam # an automatically inserter default parameter
  417. nfDefaultRefsParam # a default param value references another parameter
  418. # the flag is applied to proc default values and to calls
  419. TNodeFlags* = set[TNodeFlag]
  420. TTypeFlag* = enum # keep below 32 for efficiency reasons (now: beyond that)
  421. tfVarargs, # procedure has C styled varargs
  422. # tyArray type represeting a varargs list
  423. tfNoSideEffect, # procedure type does not allow side effects
  424. tfFinal, # is the object final?
  425. tfInheritable, # is the object inheritable?
  426. tfAcyclic, # type is acyclic (for GC optimization)
  427. tfEnumHasHoles, # enum cannot be mapped into a range
  428. tfShallow, # type can be shallow copied on assignment
  429. tfThread, # proc type is marked as ``thread``; alias for ``gcsafe``
  430. tfFromGeneric, # type is an instantiation of a generic; this is needed
  431. # because for instantiations of objects, structural
  432. # type equality has to be used
  433. tfUnresolved, # marks unresolved typedesc/static params: e.g.
  434. # proc foo(T: typedesc, list: seq[T]): var T
  435. # proc foo(L: static[int]): array[L, int]
  436. # can be attached to ranges to indicate that the range
  437. # can be attached to generic procs with free standing
  438. # type parameters: e.g. proc foo[T]()
  439. # depends on unresolved static params.
  440. tfResolved # marks a user type class, after it has been bound to a
  441. # concrete type (lastSon becomes the concrete type)
  442. tfRetType, # marks return types in proc (used to detect type classes
  443. # used as return types for return type inference)
  444. tfCapturesEnv, # whether proc really captures some environment
  445. tfByCopy, # pass object/tuple by copy (C backend)
  446. tfByRef, # pass object/tuple by reference (C backend)
  447. tfIterator, # type is really an iterator, not a tyProc
  448. tfPartial, # type is declared as 'partial'
  449. tfNotNil, # type cannot be 'nil'
  450. tfNeedsInit, # type constains a "not nil" constraint somewhere or some
  451. # other type so that it requires initialization
  452. tfVarIsPtr, # 'var' type is translated like 'ptr' even in C++ mode
  453. tfHasMeta, # type contains "wildcard" sub-types such as generic params
  454. # or other type classes
  455. tfHasGCedMem, # type contains GC'ed memory
  456. tfPacked
  457. tfHasStatic
  458. tfGenericTypeParam
  459. tfImplicitTypeParam
  460. tfInferrableStatic
  461. tfConceptMatchedTypeSym
  462. tfExplicit # for typedescs, marks types explicitly prefixed with the
  463. # `type` operator (e.g. type int)
  464. tfWildcard # consider a proc like foo[T, I](x: Type[T, I])
  465. # T and I here can bind to both typedesc and static types
  466. # before this is determined, we'll consider them to be a
  467. # wildcard type.
  468. tfHasAsgn # type has overloaded assignment operator
  469. tfBorrowDot # distinct type borrows '.'
  470. tfTriggersCompileTime # uses the NimNode type which make the proc
  471. # implicitly '.compiletime'
  472. tfRefsAnonObj # used for 'ref object' and 'ptr object'
  473. tfCovariant # covariant generic param mimicing a ptr type
  474. tfWeakCovariant # covariant generic param mimicing a seq/array type
  475. tfContravariant # contravariant generic param
  476. TTypeFlags* = set[TTypeFlag]
  477. TSymKind* = enum # the different symbols (start with the prefix sk);
  478. # order is important for the documentation generator!
  479. skUnknown, # unknown symbol: used for parsing assembler blocks
  480. # and first phase symbol lookup in generics
  481. skConditional, # symbol for the preprocessor (may become obsolete)
  482. skDynLib, # symbol represents a dynamic library; this is used
  483. # internally; it does not exist in Nim code
  484. skParam, # a parameter
  485. skGenericParam, # a generic parameter; eq in ``proc x[eq=`==`]()``
  486. skTemp, # a temporary variable (introduced by compiler)
  487. skModule, # module identifier
  488. skType, # a type
  489. skVar, # a variable
  490. skLet, # a 'let' symbol
  491. skConst, # a constant
  492. skResult, # special 'result' variable
  493. skProc, # a proc
  494. skFunc, # a func
  495. skMethod, # a method
  496. skIterator, # an iterator
  497. skConverter, # a type converter
  498. skMacro, # a macro
  499. skTemplate, # a template; currently also misused for user-defined
  500. # pragmas
  501. skField, # a field in a record or object
  502. skEnumField, # an identifier in an enum
  503. skForVar, # a for loop variable
  504. skLabel, # a label (for block statement)
  505. skStub, # symbol is a stub and not yet loaded from the ROD
  506. # file (it is loaded on demand, which may
  507. # mean: never)
  508. skPackage, # symbol is a package (used for canonicalization)
  509. skAlias # an alias (needs to be resolved immediately)
  510. TSymKinds* = set[TSymKind]
  511. const
  512. routineKinds* = {skProc, skFunc, skMethod, skIterator,
  513. skConverter, skMacro, skTemplate}
  514. tfIncompleteStruct* = tfVarargs
  515. tfUncheckedArray* = tfVarargs
  516. tfUnion* = tfNoSideEffect
  517. tfGcSafe* = tfThread
  518. tfObjHasKids* = tfEnumHasHoles
  519. tfOldSchoolExprStmt* = tfVarargs # for now used to distinguish \
  520. # 'varargs[expr]' from 'varargs[untyped]'. Eventually 'expr' will be
  521. # deprecated and this mess can be cleaned up.
  522. tfReturnsNew* = tfInheritable
  523. skError* = skUnknown
  524. # type flags that are essential for type equality:
  525. eqTypeFlags* = {tfIterator, tfNotNil, tfVarIsPtr}
  526. type
  527. TMagic* = enum # symbols that require compiler magic:
  528. mNone,
  529. mDefined, mDefinedInScope, mCompiles, mArrGet, mArrPut, mAsgn,
  530. mLow, mHigh, mSizeOf, mTypeTrait, mIs, mOf, mAddr, mType, mTypeOf,
  531. mRoof, mPlugin, mEcho, mShallowCopy, mSlurp, mStaticExec, mStatic,
  532. mParseExprToAst, mParseStmtToAst, mExpandToAst, mQuoteAst,
  533. mUnaryLt, mInc, mDec, mOrd,
  534. mNew, mNewFinalize, mNewSeq, mNewSeqOfCap,
  535. mLengthOpenArray, mLengthStr, mLengthArray, mLengthSeq,
  536. mXLenStr, mXLenSeq,
  537. mIncl, mExcl, mCard, mChr,
  538. mGCref, mGCunref,
  539. mAddI, mSubI, mMulI, mDivI, mModI,
  540. mSucc, mPred,
  541. mAddF64, mSubF64, mMulF64, mDivF64,
  542. mShrI, mShlI, mAshrI, mBitandI, mBitorI, mBitxorI,
  543. mMinI, mMaxI,
  544. mMinF64, mMaxF64,
  545. mAddU, mSubU, mMulU, mDivU, mModU,
  546. mEqI, mLeI, mLtI,
  547. mEqF64, mLeF64, mLtF64,
  548. mLeU, mLtU,
  549. mLeU64, mLtU64,
  550. mEqEnum, mLeEnum, mLtEnum,
  551. mEqCh, mLeCh, mLtCh,
  552. mEqB, mLeB, mLtB,
  553. mEqRef, mEqUntracedRef, mLePtr, mLtPtr,
  554. mXor, mEqCString, mEqProc,
  555. mUnaryMinusI, mUnaryMinusI64, mAbsI, mNot,
  556. mUnaryPlusI, mBitnotI,
  557. mUnaryPlusF64, mUnaryMinusF64, mAbsF64,
  558. mZe8ToI, mZe8ToI64,
  559. mZe16ToI, mZe16ToI64,
  560. mZe32ToI64, mZeIToI64,
  561. mToU8, mToU16, mToU32,
  562. mToFloat, mToBiggestFloat,
  563. mToInt, mToBiggestInt,
  564. mCharToStr, mBoolToStr, mIntToStr, mInt64ToStr, mFloatToStr, mCStrToStr,
  565. mStrToStr, mEnumToStr,
  566. mAnd, mOr,
  567. mEqStr, mLeStr, mLtStr,
  568. mEqSet, mLeSet, mLtSet, mMulSet, mPlusSet, mMinusSet, mSymDiffSet,
  569. mConStrStr, mSlice,
  570. mDotDot, # this one is only necessary to give nice compile time warnings
  571. mFields, mFieldPairs, mOmpParFor,
  572. mAppendStrCh, mAppendStrStr, mAppendSeqElem,
  573. mInRange, mInSet, mRepr, mExit,
  574. mSetLengthStr, mSetLengthSeq,
  575. mIsPartOf, mAstToStr, mParallel,
  576. mSwap, mIsNil, mArrToSeq, mCopyStr, mCopyStrLast,
  577. mNewString, mNewStringOfCap, mParseBiggestFloat,
  578. mMove, mWasMoved,
  579. mReset,
  580. mArray, mOpenArray, mRange, mSet, mSeq, mOpt, mVarargs,
  581. mRef, mPtr, mVar, mDistinct, mVoid, mTuple,
  582. mOrdinal,
  583. mInt, mInt8, mInt16, mInt32, mInt64,
  584. mUInt, mUInt8, mUInt16, mUInt32, mUInt64,
  585. mFloat, mFloat32, mFloat64, mFloat128,
  586. mBool, mChar, mString, mCstring,
  587. mPointer, mEmptySet, mIntSetBaseType, mNil, mExpr, mStmt, mTypeDesc,
  588. mVoidType, mPNimrodNode, mShared, mGuarded, mLock, mSpawn, mDeepCopy,
  589. mIsMainModule, mCompileDate, mCompileTime, mProcCall,
  590. mCpuEndian, mHostOS, mHostCPU, mBuildOS, mBuildCPU, mAppType,
  591. mNaN, mInf, mNegInf,
  592. mCompileOption, mCompileOptionArg,
  593. mNLen, mNChild, mNSetChild, mNAdd, mNAddMultiple, mNDel,
  594. mNKind, mNSymKind,
  595. mNccValue, mNccInc, mNcsAdd, mNcsIncl, mNcsLen, mNcsAt,
  596. mNctPut, mNctLen, mNctGet, mNctHasNext, mNctNext,
  597. mNIntVal, mNFloatVal, mNSymbol, mNIdent, mNGetType, mNStrVal, mNSetIntVal,
  598. mNSetFloatVal, mNSetSymbol, mNSetIdent, mNSetType, mNSetStrVal, mNLineInfo,
  599. mNNewNimNode, mNCopyNimNode, mNCopyNimTree, mStrToIdent,
  600. mNBindSym, mLocals, mNCallSite,
  601. mEqIdent, mEqNimrodNode, mSameNodeType, mGetImpl, mNGenSym,
  602. mNHint, mNWarning, mNError,
  603. mInstantiationInfo, mGetTypeInfo,
  604. mNimvm, mIntDefine, mStrDefine, mRunnableExamples,
  605. mException, mBuiltinType, mSymOwner
  606. # things that we can evaluate safely at compile time, even if not asked for it:
  607. const
  608. ctfeWhitelist* = {mNone, mUnaryLt, mSucc,
  609. mPred, mInc, mDec, mOrd, mLengthOpenArray,
  610. mLengthStr, mLengthArray, mLengthSeq, mXLenStr, mXLenSeq,
  611. mArrGet, mArrPut, mAsgn,
  612. mIncl, mExcl, mCard, mChr,
  613. mAddI, mSubI, mMulI, mDivI, mModI,
  614. mAddF64, mSubF64, mMulF64, mDivF64,
  615. mShrI, mShlI, mBitandI, mBitorI, mBitxorI,
  616. mMinI, mMaxI,
  617. mMinF64, mMaxF64,
  618. mAddU, mSubU, mMulU, mDivU, mModU,
  619. mEqI, mLeI, mLtI,
  620. mEqF64, mLeF64, mLtF64,
  621. mLeU, mLtU,
  622. mLeU64, mLtU64,
  623. mEqEnum, mLeEnum, mLtEnum,
  624. mEqCh, mLeCh, mLtCh,
  625. mEqB, mLeB, mLtB,
  626. mEqRef, mEqProc, mEqUntracedRef, mLePtr, mLtPtr, mEqCString, mXor,
  627. mUnaryMinusI, mUnaryMinusI64, mAbsI, mNot, mUnaryPlusI, mBitnotI,
  628. mUnaryPlusF64, mUnaryMinusF64, mAbsF64,
  629. mZe8ToI, mZe8ToI64,
  630. mZe16ToI, mZe16ToI64,
  631. mZe32ToI64, mZeIToI64,
  632. mToU8, mToU16, mToU32,
  633. mToFloat, mToBiggestFloat,
  634. mToInt, mToBiggestInt,
  635. mCharToStr, mBoolToStr, mIntToStr, mInt64ToStr, mFloatToStr, mCStrToStr,
  636. mStrToStr, mEnumToStr,
  637. mAnd, mOr,
  638. mEqStr, mLeStr, mLtStr,
  639. mEqSet, mLeSet, mLtSet, mMulSet, mPlusSet, mMinusSet, mSymDiffSet,
  640. mConStrStr, mAppendStrCh, mAppendStrStr, mAppendSeqElem,
  641. mInRange, mInSet, mRepr,
  642. mCopyStr, mCopyStrLast}
  643. # magics that require special semantic checking and
  644. # thus cannot be overloaded (also documented in the spec!):
  645. SpecialSemMagics* = {
  646. mDefined, mDefinedInScope, mCompiles, mLow, mHigh, mSizeOf, mIs, mOf,
  647. mShallowCopy, mExpandToAst, mParallel, mSpawn, mAstToStr}
  648. type
  649. PNode* = ref TNode
  650. TNodeSeq* = seq[PNode]
  651. PType* = ref TType
  652. PSym* = ref TSym
  653. TNode*{.final, acyclic.} = object # on a 32bit machine, this takes 32 bytes
  654. when defined(useNodeIds):
  655. id*: int
  656. typ*: PType
  657. info*: TLineInfo
  658. flags*: TNodeFlags
  659. case kind*: TNodeKind
  660. of nkCharLit..nkUInt64Lit:
  661. intVal*: BiggestInt
  662. of nkFloatLit..nkFloat128Lit:
  663. floatVal*: BiggestFloat
  664. of nkStrLit..nkTripleStrLit:
  665. strVal*: string
  666. of nkSym:
  667. sym*: PSym
  668. of nkIdent:
  669. ident*: PIdent
  670. else:
  671. sons*: TNodeSeq
  672. comment*: string
  673. TSymSeq* = seq[PSym]
  674. TStrTable* = object # a table[PIdent] of PSym
  675. counter*: int
  676. data*: TSymSeq
  677. # -------------- backend information -------------------------------
  678. TLocKind* = enum
  679. locNone, # no location
  680. locTemp, # temporary location
  681. locLocalVar, # location is a local variable
  682. locGlobalVar, # location is a global variable
  683. locParam, # location is a parameter
  684. locField, # location is a record field
  685. locExpr, # "location" is really an expression
  686. locProc, # location is a proc (an address of a procedure)
  687. locData, # location is a constant
  688. locCall, # location is a call expression
  689. locOther # location is something other
  690. TLocFlag* = enum
  691. lfIndirect, # backend introduced a pointer
  692. lfFullExternalName, # only used when 'conf.cmd == cmdPretty': Indicates
  693. # that the symbol has been imported via 'importc: "fullname"' and
  694. # no format string.
  695. lfNoDeepCopy, # no need for a deep copy
  696. lfNoDecl, # do not declare it in C
  697. lfDynamicLib, # link symbol to dynamic library
  698. lfExportLib, # export symbol for dynamic library generation
  699. lfHeader, # include header file for symbol
  700. lfImportCompilerProc, # ``importc`` of a compilerproc
  701. lfSingleUse # no location yet and will only be used once
  702. TStorageLoc* = enum
  703. OnUnknown, # location is unknown (stack, heap or static)
  704. OnStatic, # in a static section
  705. OnStack, # location is on hardware stack
  706. OnStackShadowDup, # location is on the stack but also replicated
  707. # on the shadow stack
  708. OnHeap # location is on heap or global
  709. # (reference counting needed)
  710. TLocFlags* = set[TLocFlag]
  711. TLoc* = object
  712. k*: TLocKind # kind of location
  713. storage*: TStorageLoc
  714. flags*: TLocFlags # location's flags
  715. lode*: PNode # Node where the location came from; can be faked
  716. r*: Rope # rope value of location (code generators)
  717. dup*: Rope # duplicated location for precise stack scans
  718. # ---------------- end of backend information ------------------------------
  719. TLibKind* = enum
  720. libHeader, libDynamic
  721. TLib* = object # also misused for headers!
  722. kind*: TLibKind
  723. generated*: bool # needed for the backends:
  724. isOverriden*: bool
  725. name*: Rope
  726. path*: PNode # can be a string literal!
  727. CompilesId* = int ## id that is used for the caching logic within
  728. ## ``system.compiles``. See the seminst module.
  729. TInstantiation* = object
  730. sym*: PSym
  731. concreteTypes*: seq[PType]
  732. compilesId*: CompilesId
  733. PInstantiation* = ref TInstantiation
  734. TScope* = object
  735. depthLevel*: int
  736. symbols*: TStrTable
  737. parent*: PScope
  738. PScope* = ref TScope
  739. PLib* = ref TLib
  740. TSym* {.acyclic.} = object of TIdObj
  741. # proc and type instantiations are cached in the generic symbol
  742. case kind*: TSymKind
  743. of skType, skGenericParam:
  744. typeInstCache*: seq[PType]
  745. of routineKinds:
  746. procInstCache*: seq[PInstantiation]
  747. gcUnsafetyReason*: PSym # for better error messages wrt gcsafe
  748. #scope*: PScope # the scope where the proc was defined
  749. of skModule, skPackage:
  750. # modules keep track of the generic symbols they use from other modules.
  751. # this is because in incremental compilation, when a module is about to
  752. # be replaced with a newer version, we must decrement the usage count
  753. # of all previously used generics.
  754. # For 'import as' we copy the module symbol but shallowCopy the 'tab'
  755. # and set the 'usedGenerics' to ... XXX gah! Better set module.name
  756. # instead? But this doesn't work either. --> We need an skModuleAlias?
  757. # No need, just leave it as skModule but set the owner accordingly and
  758. # check for the owner when touching 'usedGenerics'.
  759. usedGenerics*: seq[PInstantiation]
  760. tab*: TStrTable # interface table for modules
  761. of skLet, skVar, skField, skForVar:
  762. guard*: PSym
  763. bitsize*: int
  764. else: nil
  765. magic*: TMagic
  766. typ*: PType
  767. name*: PIdent
  768. info*: TLineInfo
  769. owner*: PSym
  770. flags*: TSymFlags
  771. ast*: PNode # syntax tree of proc, iterator, etc.:
  772. # the whole proc including header; this is used
  773. # for easy generation of proper error messages
  774. # for variant record fields the discriminant
  775. # expression
  776. # for modules, it's a placeholder for compiler
  777. # generated code that will be appended to the
  778. # module after the sem pass (see appendToModule)
  779. options*: TOptions
  780. position*: int # used for many different things:
  781. # for enum fields its position;
  782. # for fields its offset
  783. # for parameters its position
  784. # for a conditional:
  785. # 1 iff the symbol is defined, else 0
  786. # (or not in symbol table)
  787. # for modules, an unique index corresponding
  788. # to the module's fileIdx
  789. # for variables a slot index for the evaluator
  790. # for routines a superop-ID
  791. offset*: int # offset of record field
  792. loc*: TLoc
  793. annex*: PLib # additional fields (seldom used, so we use a
  794. # reference to another object to safe space)
  795. constraint*: PNode # additional constraints like 'lit|result'; also
  796. # misused for the codegenDecl pragma in the hope
  797. # it won't cause problems
  798. # for skModule the string literal to output for
  799. # deprecated modules.
  800. when defined(nimsuggest):
  801. allUsages*: seq[TLineInfo]
  802. TTypeSeq* = seq[PType]
  803. TLockLevel* = distinct int16
  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. destructor*: PSym # destructor. warning: nil here may not necessary
  825. # mean that there is no destructor.
  826. # see instantiateDestructor in semdestruct.nim
  827. deepCopy*: PSym # overriden 'deepCopy' operation
  828. assignment*: PSym # overriden '=' operation
  829. sink*: PSym # overriden '=sink' operation
  830. methods*: seq[(int,PSym)] # attached methods
  831. size*: BiggestInt # the size of the type in bytes
  832. # -1 means that the size is unkwown
  833. align*: int16 # the type's alignment requirements
  834. lockLevel*: TLockLevel # lock level as required for deadlock checking
  835. loc*: TLoc
  836. typeInst*: PType # for generic instantiations the tyGenericInst that led to this
  837. # type.
  838. TPair* = object
  839. key*, val*: RootRef
  840. TPairSeq* = seq[TPair]
  841. TIdPair* = object
  842. key*: PIdObj
  843. val*: RootRef
  844. TIdPairSeq* = seq[TIdPair]
  845. TIdTable* = object # the same as table[PIdent] of PObject
  846. counter*: int
  847. data*: TIdPairSeq
  848. TIdNodePair* = object
  849. key*: PIdObj
  850. val*: PNode
  851. TIdNodePairSeq* = seq[TIdNodePair]
  852. TIdNodeTable* = object # the same as table[PIdObj] of PNode
  853. counter*: int
  854. data*: TIdNodePairSeq
  855. TNodePair* = object
  856. h*: Hash # because it is expensive to compute!
  857. key*: PNode
  858. val*: int
  859. TNodePairSeq* = seq[TNodePair]
  860. TNodeTable* = object # the same as table[PNode] of int;
  861. # nodes are compared by structure!
  862. counter*: int
  863. data*: TNodePairSeq
  864. TObjectSeq* = seq[RootRef]
  865. TObjectSet* = object
  866. counter*: int
  867. data*: TObjectSeq
  868. TImplication* = enum
  869. impUnknown, impNo, impYes
  870. # BUGFIX: a module is overloadable so that a proc can have the
  871. # same name as an imported module. This is necessary because of
  872. # the poor naming choices in the standard library.
  873. const
  874. OverloadableSyms* = {skProc, skFunc, skMethod, skIterator,
  875. skConverter, skModule, skTemplate, skMacro}
  876. GenericTypes*: TTypeKinds = {tyGenericInvocation, tyGenericBody,
  877. tyGenericParam}
  878. StructuralEquivTypes*: TTypeKinds = {tyNil, tyTuple, tyArray,
  879. tySet, tyRange, tyPtr, tyRef, tyVar, tyLent, tySequence, tyProc, tyOpenArray,
  880. tyVarargs}
  881. ConcreteTypes*: TTypeKinds = { # types of the expr that may occur in::
  882. # var x = expr
  883. tyBool, tyChar, tyEnum, tyArray, tyObject,
  884. tySet, tyTuple, tyRange, tyPtr, tyRef, tyVar, tyLent, tySequence, tyProc,
  885. tyPointer,
  886. tyOpenArray, tyString, tyCString, tyInt..tyInt64, tyFloat..tyFloat128,
  887. tyUInt..tyUInt64}
  888. IntegralTypes* = {tyBool, tyChar, tyEnum, tyInt..tyInt64,
  889. tyFloat..tyFloat128, tyUInt..tyUInt64}
  890. ConstantDataTypes*: TTypeKinds = {tyArray, tySet,
  891. tyTuple, tySequence}
  892. NilableTypes*: TTypeKinds = {tyPointer, tyCString, tyRef, tyPtr,
  893. tyProc, tyError}
  894. ExportableSymKinds* = {skVar, skConst, skProc, skFunc, skMethod, skType,
  895. skIterator,
  896. skMacro, skTemplate, skConverter, skEnumField, skLet, skStub, skAlias}
  897. PersistentNodeFlags*: TNodeFlags = {nfBase2, nfBase8, nfBase16,
  898. nfDotSetter, nfDotField,
  899. nfIsRef, nfPreventCg, nfLL,
  900. nfFromTemplate, nfDefaultRefsParam}
  901. namePos* = 0
  902. patternPos* = 1 # empty except for term rewriting macros
  903. genericParamsPos* = 2
  904. paramsPos* = 3
  905. pragmasPos* = 4
  906. miscPos* = 5 # used for undocumented and hacky stuff
  907. bodyPos* = 6 # position of body; use rodread.getBody() instead!
  908. resultPos* = 7
  909. dispatcherPos* = 8 # caution: if method has no 'result' it can be position 7!
  910. nkCallKinds* = {nkCall, nkInfix, nkPrefix, nkPostfix,
  911. nkCommand, nkCallStrLit, nkHiddenCallConv}
  912. nkIdentKinds* = {nkIdent, nkSym, nkAccQuoted, nkOpenSymChoice,
  913. nkClosedSymChoice}
  914. nkPragmaCallKinds* = {nkExprColonExpr, nkCall, nkCallStrLit}
  915. nkLiterals* = {nkCharLit..nkTripleStrLit}
  916. nkFloatLiterals* = {nkFloatLit..nkFloat128Lit}
  917. nkLambdaKinds* = {nkLambda, nkDo}
  918. declarativeDefs* = {nkProcDef, nkFuncDef, nkMethodDef, nkIteratorDef, nkConverterDef}
  919. procDefs* = nkLambdaKinds + declarativeDefs
  920. nkSymChoices* = {nkClosedSymChoice, nkOpenSymChoice}
  921. nkStrKinds* = {nkStrLit..nkTripleStrLit}
  922. skLocalVars* = {skVar, skLet, skForVar, skParam, skResult}
  923. skProcKinds* = {skProc, skFunc, skTemplate, skMacro, skIterator,
  924. skMethod, skConverter}
  925. var ggDebug* {.deprecated.}: bool ## convenience switch for trying out things
  926. #var
  927. # gMainPackageId*: int
  928. proc isCallExpr*(n: PNode): bool =
  929. result = n.kind in nkCallKinds
  930. proc discardSons*(father: PNode)
  931. proc len*(n: PNode): int {.inline.} =
  932. when defined(nimNoNilSeqs):
  933. result = len(n.sons)
  934. else:
  935. if isNil(n.sons): result = 0
  936. else: result = len(n.sons)
  937. proc safeLen*(n: PNode): int {.inline.} =
  938. ## works even for leaves.
  939. if n.kind in {nkNone..nkNilLit}: result = 0
  940. else: result = len(n)
  941. proc safeArrLen*(n: PNode): int {.inline.} =
  942. ## works for array-like objects (strings passed as openArray in VM).
  943. if n.kind in {nkStrLit..nkTripleStrLit}:result = len(n.strVal)
  944. elif n.kind in {nkNone..nkFloat128Lit}: result = 0
  945. else: result = len(n)
  946. proc add*(father, son: PNode) =
  947. assert son != nil
  948. when not defined(nimNoNilSeqs):
  949. if isNil(father.sons): father.sons = @[]
  950. add(father.sons, son)
  951. type Indexable = PNode | PType
  952. template `[]`*(n: Indexable, i: int): Indexable = n.sons[i]
  953. template `[]=`*(n: Indexable, i: int; x: Indexable) = n.sons[i] = x
  954. template `[]`*(n: Indexable, i: BackwardsIndex): Indexable = n[n.len - i.int]
  955. template `[]=`*(n: Indexable, i: BackwardsIndex; x: Indexable) = n[n.len - i.int] = x
  956. when defined(useNodeIds):
  957. const nodeIdToDebug* = -1 # 299750 # 300761 #300863 # 300879
  958. var gNodeId: int
  959. proc newNode*(kind: TNodeKind): PNode =
  960. new(result)
  961. result.kind = kind
  962. #result.info = UnknownLineInfo() inlined:
  963. result.info.fileIndex = InvalidFileIdx
  964. result.info.col = int16(-1)
  965. result.info.line = uint16(0)
  966. when defined(useNodeIds):
  967. result.id = gNodeId
  968. if result.id == nodeIdToDebug:
  969. echo "KIND ", result.kind
  970. writeStackTrace()
  971. inc gNodeId
  972. proc newTree*(kind: TNodeKind; children: varargs[PNode]): PNode =
  973. result = newNode(kind)
  974. if children.len > 0:
  975. result.info = children[0].info
  976. result.sons = @children
  977. template previouslyInferred*(t: PType): PType =
  978. if t.sons.len > 1: t.lastSon else: nil
  979. proc newSym*(symKind: TSymKind, name: PIdent, owner: PSym,
  980. info: TLineInfo; options: TOptions = {}): PSym =
  981. # generates a symbol and initializes the hash field too
  982. new(result)
  983. result.name = name
  984. result.kind = symKind
  985. result.flags = {}
  986. result.info = info
  987. result.options = options
  988. result.owner = owner
  989. result.offset = -1
  990. result.id = getID()
  991. when debugIds:
  992. registerId(result)
  993. #if result.id == 77131:
  994. # writeStacktrace()
  995. # echo name.s
  996. proc isMetaType*(t: PType): bool =
  997. return t.kind in tyMetaTypes or
  998. (t.kind == tyStatic and t.n == nil) or
  999. tfHasMeta in t.flags
  1000. proc isUnresolvedStatic*(t: PType): bool =
  1001. return t.kind == tyStatic and t.n == nil
  1002. proc linkTo*(t: PType, s: PSym): PType {.discardable.} =
  1003. t.sym = s
  1004. s.typ = t
  1005. result = t
  1006. proc linkTo*(s: PSym, t: PType): PSym {.discardable.} =
  1007. t.sym = s
  1008. s.typ = t
  1009. result = s
  1010. template fileIdx*(c: PSym): FileIndex =
  1011. # XXX: this should be used only on module symbols
  1012. c.position.FileIndex
  1013. template filename*(c: PSym): string =
  1014. # XXX: this should be used only on module symbols
  1015. c.position.FileIndex.toFilename
  1016. proc appendToModule*(m: PSym, n: PNode) =
  1017. ## The compiler will use this internally to add nodes that will be
  1018. ## appended to the module after the sem pass
  1019. if m.ast == nil:
  1020. m.ast = newNode(nkStmtList)
  1021. m.ast.sons = @[n]
  1022. else:
  1023. assert m.ast.kind == nkStmtList
  1024. m.ast.sons.add(n)
  1025. const # for all kind of hash tables:
  1026. GrowthFactor* = 2 # must be power of 2, > 0
  1027. StartSize* = 8 # must be power of 2, > 0
  1028. proc copyStrTable*(dest: var TStrTable, src: TStrTable) =
  1029. dest.counter = src.counter
  1030. setLen(dest.data, len(src.data))
  1031. for i in countup(0, high(src.data)): dest.data[i] = src.data[i]
  1032. proc copyIdTable*(dest: var TIdTable, src: TIdTable) =
  1033. dest.counter = src.counter
  1034. newSeq(dest.data, len(src.data))
  1035. for i in countup(0, high(src.data)): dest.data[i] = src.data[i]
  1036. proc copyObjectSet*(dest: var TObjectSet, src: TObjectSet) =
  1037. dest.counter = src.counter
  1038. setLen(dest.data, len(src.data))
  1039. for i in countup(0, high(src.data)): dest.data[i] = src.data[i]
  1040. proc discardSons*(father: PNode) =
  1041. when defined(nimNoNilSeqs):
  1042. father.sons = @[]
  1043. else:
  1044. father.sons = nil
  1045. proc withInfo*(n: PNode, info: TLineInfo): PNode =
  1046. n.info = info
  1047. return n
  1048. proc newIdentNode*(ident: PIdent, info: TLineInfo): PNode =
  1049. result = newNode(nkIdent)
  1050. result.ident = ident
  1051. result.info = info
  1052. proc newSymNode*(sym: PSym): PNode =
  1053. result = newNode(nkSym)
  1054. result.sym = sym
  1055. result.typ = sym.typ
  1056. result.info = sym.info
  1057. proc newSymNode*(sym: PSym, info: TLineInfo): PNode =
  1058. result = newNode(nkSym)
  1059. result.sym = sym
  1060. result.typ = sym.typ
  1061. result.info = info
  1062. proc newNodeI*(kind: TNodeKind, info: TLineInfo): PNode =
  1063. new(result)
  1064. result.kind = kind
  1065. result.info = info
  1066. when defined(useNodeIds):
  1067. result.id = gNodeId
  1068. if result.id == nodeIdToDebug:
  1069. echo "KIND ", result.kind
  1070. writeStackTrace()
  1071. inc gNodeId
  1072. proc newNodeI*(kind: TNodeKind, info: TLineInfo, children: int): PNode =
  1073. new(result)
  1074. result.kind = kind
  1075. result.info = info
  1076. if children > 0:
  1077. newSeq(result.sons, children)
  1078. when defined(useNodeIds):
  1079. result.id = gNodeId
  1080. if result.id == nodeIdToDebug:
  1081. echo "KIND ", result.kind
  1082. writeStackTrace()
  1083. inc gNodeId
  1084. proc newNode*(kind: TNodeKind, info: TLineInfo, sons: TNodeSeq = @[],
  1085. typ: PType = nil): PNode =
  1086. new(result)
  1087. result.kind = kind
  1088. result.info = info
  1089. result.typ = typ
  1090. # XXX use shallowCopy here for ownership transfer:
  1091. result.sons = sons
  1092. when defined(useNodeIds):
  1093. result.id = gNodeId
  1094. if result.id == nodeIdToDebug:
  1095. echo "KIND ", result.kind
  1096. writeStackTrace()
  1097. inc gNodeId
  1098. proc newNodeIT*(kind: TNodeKind, info: TLineInfo, typ: PType): PNode =
  1099. result = newNode(kind)
  1100. result.info = info
  1101. result.typ = typ
  1102. proc newIntNode*(kind: TNodeKind, intVal: BiggestInt): PNode =
  1103. result = newNode(kind)
  1104. result.intVal = intVal
  1105. proc newIntTypeNode*(kind: TNodeKind, intVal: BiggestInt, typ: PType): PNode =
  1106. result = newIntNode(kind, intVal)
  1107. result.typ = typ
  1108. proc newFloatNode*(kind: TNodeKind, floatVal: BiggestFloat): PNode =
  1109. result = newNode(kind)
  1110. result.floatVal = floatVal
  1111. proc newStrNode*(kind: TNodeKind, strVal: string): PNode =
  1112. result = newNode(kind)
  1113. result.strVal = strVal
  1114. proc newStrNode*(strVal: string; info: TLineInfo): PNode =
  1115. result = newNodeI(nkStrLit, info)
  1116. result.strVal = strVal
  1117. proc addSon*(father, son: PNode) =
  1118. assert son != nil
  1119. when not defined(nimNoNilSeqs):
  1120. if isNil(father.sons): father.sons = @[]
  1121. add(father.sons, son)
  1122. proc newProcNode*(kind: TNodeKind, info: TLineInfo, body: PNode,
  1123. params,
  1124. name, pattern, genericParams,
  1125. pragmas, exceptions: PNode): PNode =
  1126. result = newNodeI(kind, info)
  1127. result.sons = @[name, pattern, genericParams, params,
  1128. pragmas, exceptions, body]
  1129. const
  1130. UnspecifiedLockLevel* = TLockLevel(-1'i16)
  1131. MaxLockLevel* = 1000'i16
  1132. UnknownLockLevel* = TLockLevel(1001'i16)
  1133. proc `$`*(x: TLockLevel): string =
  1134. if x.ord == UnspecifiedLockLevel.ord: result = "<unspecified>"
  1135. elif x.ord == UnknownLockLevel.ord: result = "<unknown>"
  1136. else: result = $int16(x)
  1137. proc newType*(kind: TTypeKind, owner: PSym): PType =
  1138. new(result)
  1139. result.kind = kind
  1140. result.owner = owner
  1141. result.size = -1
  1142. result.align = 2 # default alignment
  1143. result.id = getID()
  1144. result.lockLevel = UnspecifiedLockLevel
  1145. when debugIds:
  1146. registerId(result)
  1147. when false:
  1148. if result.id == 76426:
  1149. echo "KNID ", kind
  1150. writeStackTrace()
  1151. proc mergeLoc(a: var TLoc, b: TLoc) =
  1152. if a.k == low(a.k): a.k = b.k
  1153. if a.storage == low(a.storage): a.storage = b.storage
  1154. a.flags = a.flags + b.flags
  1155. if a.lode == nil: a.lode = b.lode
  1156. if a.r == nil: a.r = b.r
  1157. proc newSons*(father: PNode, length: int) =
  1158. when defined(nimNoNilSeqs):
  1159. setLen(father.sons, length)
  1160. else:
  1161. if isNil(father.sons):
  1162. newSeq(father.sons, length)
  1163. else:
  1164. setLen(father.sons, length)
  1165. proc newSons*(father: PType, 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 sonsLen*(n: PType): int = n.sons.len
  1174. proc len*(n: PType): int = n.sons.len
  1175. proc sonsLen*(n: PNode): int = n.sons.len
  1176. proc lastSon*(n: PNode): PNode = n.sons[^1]
  1177. proc lastSon*(n: PType): PType = n.sons[^1]
  1178. proc assignType*(dest, src: PType) =
  1179. dest.kind = src.kind
  1180. dest.flags = src.flags
  1181. dest.callConv = src.callConv
  1182. dest.n = src.n
  1183. dest.size = src.size
  1184. dest.align = src.align
  1185. dest.destructor = src.destructor
  1186. dest.deepCopy = src.deepCopy
  1187. dest.sink = src.sink
  1188. dest.assignment = src.assignment
  1189. dest.lockLevel = src.lockLevel
  1190. # this fixes 'type TLock = TSysLock':
  1191. if src.sym != nil:
  1192. if dest.sym != nil:
  1193. dest.sym.flags = dest.sym.flags + (src.sym.flags-{sfExported})
  1194. if dest.sym.annex == nil: dest.sym.annex = src.sym.annex
  1195. mergeLoc(dest.sym.loc, src.sym.loc)
  1196. else:
  1197. dest.sym = src.sym
  1198. newSons(dest, sonsLen(src))
  1199. for i in countup(0, sonsLen(src) - 1): dest.sons[i] = src.sons[i]
  1200. proc copyType*(t: PType, owner: PSym, keepId: bool): PType =
  1201. result = newType(t.kind, owner)
  1202. assignType(result, t)
  1203. if keepId:
  1204. result.id = t.id
  1205. else:
  1206. when debugIds: registerId(result)
  1207. result.sym = t.sym # backend-info should not be copied
  1208. proc exactReplica*(t: PType): PType = copyType(t, t.owner, true)
  1209. proc copySym*(s: PSym, keepId: bool = false): PSym =
  1210. result = newSym(s.kind, s.name, s.owner, s.info, s.options)
  1211. #result.ast = nil # BUGFIX; was: s.ast which made problems
  1212. result.typ = s.typ
  1213. if keepId:
  1214. result.id = s.id
  1215. else:
  1216. result.id = getID()
  1217. when debugIds: registerId(result)
  1218. result.flags = s.flags
  1219. result.magic = s.magic
  1220. if s.kind == skModule:
  1221. copyStrTable(result.tab, s.tab)
  1222. result.options = s.options
  1223. result.position = s.position
  1224. result.loc = s.loc
  1225. result.annex = s.annex # BUGFIX
  1226. if result.kind in {skVar, skLet, skField}:
  1227. result.guard = s.guard
  1228. proc createModuleAlias*(s: PSym, newIdent: PIdent, info: TLineInfo;
  1229. options: TOptions): PSym =
  1230. result = newSym(s.kind, newIdent, s.owner, info, options)
  1231. # keep ID!
  1232. result.ast = s.ast
  1233. result.id = s.id
  1234. result.flags = s.flags
  1235. system.shallowCopy(result.tab, s.tab)
  1236. result.options = s.options
  1237. result.position = s.position
  1238. result.loc = s.loc
  1239. result.annex = s.annex
  1240. # XXX once usedGenerics is used, ensure module aliases keep working!
  1241. assert s.usedGenerics.len == 0
  1242. proc initStrTable*(x: var TStrTable) =
  1243. x.counter = 0
  1244. newSeq(x.data, StartSize)
  1245. proc newStrTable*: TStrTable =
  1246. initStrTable(result)
  1247. proc initIdTable*(x: var TIdTable) =
  1248. x.counter = 0
  1249. newSeq(x.data, StartSize)
  1250. proc newIdTable*: TIdTable =
  1251. initIdTable(result)
  1252. proc resetIdTable*(x: var TIdTable) =
  1253. x.counter = 0
  1254. # clear and set to old initial size:
  1255. setLen(x.data, 0)
  1256. setLen(x.data, StartSize)
  1257. proc initObjectSet*(x: var TObjectSet) =
  1258. x.counter = 0
  1259. newSeq(x.data, StartSize)
  1260. proc initIdNodeTable*(x: var TIdNodeTable) =
  1261. x.counter = 0
  1262. newSeq(x.data, StartSize)
  1263. proc initNodeTable*(x: var TNodeTable) =
  1264. x.counter = 0
  1265. newSeq(x.data, StartSize)
  1266. proc skipTypes*(t: PType, kinds: TTypeKinds): PType =
  1267. ## Used throughout the compiler code to test whether a type tree contains or
  1268. ## doesn't contain a specific type/types - it is often the case that only the
  1269. ## last child nodes of a type tree need to be searched. This is a really hot
  1270. ## path within the compiler!
  1271. result = t
  1272. while result.kind in kinds: result = lastSon(result)
  1273. proc skipTypes*(t: PType, kinds: TTypeKinds; maxIters: int): PType =
  1274. result = t
  1275. var i = maxIters
  1276. while result.kind in kinds:
  1277. result = lastSon(result)
  1278. dec i
  1279. if i == 0: return nil
  1280. proc skipTypesOrNil*(t: PType, kinds: TTypeKinds): PType =
  1281. ## same as skipTypes but handles 'nil'
  1282. result = t
  1283. while result != nil and result.kind in kinds:
  1284. if result.len == 0: return nil
  1285. result = lastSon(result)
  1286. proc isGCedMem*(t: PType): bool {.inline.} =
  1287. result = t.kind in {tyString, tyRef, tySequence} or
  1288. t.kind == tyProc and t.callConv == ccClosure
  1289. proc propagateToOwner*(owner, elem: PType) =
  1290. const HaveTheirOwnEmpty = {tySequence, tyOpt, tySet, tyPtr, tyRef, tyProc}
  1291. owner.flags = owner.flags + (elem.flags * {tfHasMeta, tfTriggersCompileTime})
  1292. if tfNotNil in elem.flags:
  1293. if owner.kind in {tyGenericInst, tyGenericBody, tyGenericInvocation}:
  1294. owner.flags.incl tfNotNil
  1295. elif owner.kind notin HaveTheirOwnEmpty:
  1296. owner.flags.incl tfNeedsInit
  1297. if tfNeedsInit in elem.flags:
  1298. if owner.kind in HaveTheirOwnEmpty: discard
  1299. else: owner.flags.incl tfNeedsInit
  1300. if elem.isMetaType:
  1301. owner.flags.incl tfHasMeta
  1302. if tfHasAsgn in elem.flags:
  1303. let o2 = owner.skipTypes({tyGenericInst, tyAlias, tySink})
  1304. if o2.kind in {tyTuple, tyObject, tyArray,
  1305. tySequence, tyOpt, tySet, tyDistinct}:
  1306. o2.flags.incl tfHasAsgn
  1307. owner.flags.incl tfHasAsgn
  1308. if owner.kind notin {tyProc, tyGenericInst, tyGenericBody,
  1309. tyGenericInvocation, tyPtr}:
  1310. let elemB = elem.skipTypes({tyGenericInst, tyAlias, tySink})
  1311. if elemB.isGCedMem or tfHasGCedMem in elemB.flags:
  1312. # for simplicity, we propagate this flag even to generics. We then
  1313. # ensure this doesn't bite us in sempass2.
  1314. owner.flags.incl tfHasGCedMem
  1315. proc rawAddSon*(father, son: PType) =
  1316. when not defined(nimNoNilSeqs):
  1317. if isNil(father.sons): father.sons = @[]
  1318. add(father.sons, son)
  1319. if not son.isNil: propagateToOwner(father, son)
  1320. proc rawAddSonNoPropagationOfTypeFlags*(father, son: PType) =
  1321. when not defined(nimNoNilSeqs):
  1322. if isNil(father.sons): father.sons = @[]
  1323. add(father.sons, son)
  1324. proc addSonNilAllowed*(father, son: PNode) =
  1325. when not defined(nimNoNilSeqs):
  1326. if isNil(father.sons): father.sons = @[]
  1327. add(father.sons, son)
  1328. proc delSon*(father: PNode, idx: int) =
  1329. when defined(nimNoNilSeqs):
  1330. if father.len == 0: return
  1331. else:
  1332. if isNil(father.sons): return
  1333. var length = sonsLen(father)
  1334. for i in countup(idx, length - 2): father.sons[i] = father.sons[i + 1]
  1335. setLen(father.sons, length - 1)
  1336. proc copyNode*(src: PNode): PNode =
  1337. # does not copy its sons!
  1338. if src == nil:
  1339. return nil
  1340. result = newNode(src.kind)
  1341. result.info = src.info
  1342. result.typ = src.typ
  1343. result.flags = src.flags * PersistentNodeFlags
  1344. result.comment = src.comment
  1345. when defined(useNodeIds):
  1346. if result.id == nodeIdToDebug:
  1347. echo "COMES FROM ", src.id
  1348. case src.kind
  1349. of nkCharLit..nkUInt64Lit: result.intVal = src.intVal
  1350. of nkFloatLiterals: result.floatVal = src.floatVal
  1351. of nkSym: result.sym = src.sym
  1352. of nkIdent: result.ident = src.ident
  1353. of nkStrLit..nkTripleStrLit: result.strVal = src.strVal
  1354. else: discard
  1355. proc shallowCopy*(src: PNode): PNode =
  1356. # does not copy its sons, but provides space for them:
  1357. if src == nil: return nil
  1358. result = newNode(src.kind)
  1359. result.info = src.info
  1360. result.typ = src.typ
  1361. result.flags = src.flags * PersistentNodeFlags
  1362. result.comment = src.comment
  1363. when defined(useNodeIds):
  1364. if result.id == nodeIdToDebug:
  1365. echo "COMES FROM ", src.id
  1366. case src.kind
  1367. of nkCharLit..nkUInt64Lit: result.intVal = src.intVal
  1368. of nkFloatLiterals: result.floatVal = src.floatVal
  1369. of nkSym: result.sym = src.sym
  1370. of nkIdent: result.ident = src.ident
  1371. of nkStrLit..nkTripleStrLit: result.strVal = src.strVal
  1372. else: newSeq(result.sons, sonsLen(src))
  1373. proc copyTree*(src: PNode): PNode =
  1374. # copy a whole syntax tree; performs deep copying
  1375. if src == nil:
  1376. return nil
  1377. result = newNode(src.kind)
  1378. result.info = src.info
  1379. result.typ = src.typ
  1380. result.flags = src.flags * PersistentNodeFlags
  1381. result.comment = src.comment
  1382. when defined(useNodeIds):
  1383. if result.id == nodeIdToDebug:
  1384. echo "COMES FROM ", src.id
  1385. case src.kind
  1386. of nkCharLit..nkUInt64Lit: result.intVal = src.intVal
  1387. of nkFloatLiterals: result.floatVal = src.floatVal
  1388. of nkSym: result.sym = src.sym
  1389. of nkIdent: result.ident = src.ident
  1390. of nkStrLit..nkTripleStrLit: result.strVal = src.strVal
  1391. else:
  1392. newSeq(result.sons, sonsLen(src))
  1393. for i in countup(0, sonsLen(src) - 1):
  1394. result.sons[i] = copyTree(src.sons[i])
  1395. proc hasSonWith*(n: PNode, kind: TNodeKind): bool =
  1396. for i in countup(0, sonsLen(n) - 1):
  1397. if n.sons[i].kind == kind:
  1398. return true
  1399. result = false
  1400. proc hasNilSon*(n: PNode): bool =
  1401. for i in countup(0, safeLen(n) - 1):
  1402. if n.sons[i] == nil:
  1403. return true
  1404. elif hasNilSon(n.sons[i]):
  1405. return true
  1406. result = false
  1407. proc containsNode*(n: PNode, kinds: TNodeKinds): bool =
  1408. if n == nil: return
  1409. case n.kind
  1410. of nkEmpty..nkNilLit: result = n.kind in kinds
  1411. else:
  1412. for i in countup(0, sonsLen(n) - 1):
  1413. if n.kind in kinds or containsNode(n.sons[i], kinds): return true
  1414. proc hasSubnodeWith*(n: PNode, kind: TNodeKind): bool =
  1415. case n.kind
  1416. of nkEmpty..nkNilLit: result = n.kind == kind
  1417. else:
  1418. for i in countup(0, sonsLen(n) - 1):
  1419. if (n.sons[i].kind == kind) or hasSubnodeWith(n.sons[i], kind):
  1420. return true
  1421. result = false
  1422. proc getInt*(a: PNode): BiggestInt =
  1423. case a.kind
  1424. of nkCharLit..nkUInt64Lit: result = a.intVal
  1425. else:
  1426. raiseRecoverableError("cannot extract number from invalid AST node")
  1427. #internalError(a.info, "getInt")
  1428. #doAssert false, "getInt"
  1429. #result = 0
  1430. proc getFloat*(a: PNode): BiggestFloat =
  1431. case a.kind
  1432. of nkFloatLiterals: result = a.floatVal
  1433. else:
  1434. raiseRecoverableError("cannot extract number from invalid AST node")
  1435. #doAssert false, "getFloat"
  1436. #internalError(a.info, "getFloat")
  1437. #result = 0.0
  1438. proc getStr*(a: PNode): string =
  1439. case a.kind
  1440. of nkStrLit..nkTripleStrLit: result = a.strVal
  1441. of nkNilLit:
  1442. # let's hope this fixes more problems than it creates:
  1443. when defined(nimNoNilSeqs):
  1444. result = ""
  1445. else:
  1446. result = nil
  1447. else:
  1448. raiseRecoverableError("cannot extract string from invalid AST node")
  1449. #doAssert false, "getStr"
  1450. #internalError(a.info, "getStr")
  1451. #result = ""
  1452. proc getStrOrChar*(a: PNode): string =
  1453. case a.kind
  1454. of nkStrLit..nkTripleStrLit: result = a.strVal
  1455. of nkCharLit..nkUInt64Lit: result = $chr(int(a.intVal))
  1456. else:
  1457. raiseRecoverableError("cannot extract string from invalid AST node")
  1458. #doAssert false, "getStrOrChar"
  1459. #internalError(a.info, "getStrOrChar")
  1460. #result = ""
  1461. proc isGenericRoutine*(s: PSym): bool =
  1462. case s.kind
  1463. of skProcKinds:
  1464. result = sfFromGeneric in s.flags or
  1465. (s.ast != nil and s.ast[genericParamsPos].kind != nkEmpty)
  1466. else: discard
  1467. proc skipGenericOwner*(s: PSym): PSym =
  1468. ## Generic instantiations are owned by their originating generic
  1469. ## symbol. This proc skips such owners and goes straight to the owner
  1470. ## of the generic itself (the module or the enclosing proc).
  1471. result = if s.kind in skProcKinds and sfFromGeneric in s.flags:
  1472. s.owner.owner
  1473. else:
  1474. s.owner
  1475. proc originatingModule*(s: PSym): PSym =
  1476. result = s.owner
  1477. while result.kind != skModule: result = result.owner
  1478. proc isRoutine*(s: PSym): bool {.inline.} =
  1479. result = s.kind in skProcKinds
  1480. proc isCompileTimeProc*(s: PSym): bool {.inline.} =
  1481. result = s.kind == skMacro or
  1482. s.kind == skProc and sfCompileTime in s.flags
  1483. proc requiredParams*(s: PSym): int =
  1484. # Returns the number of required params (without default values)
  1485. # XXX: Perhaps we can store this in the `offset` field of the
  1486. # symbol instead?
  1487. for i in 1 ..< s.typ.len:
  1488. if s.typ.n[i].sym.ast != nil:
  1489. return i - 1
  1490. return s.typ.len - 1
  1491. proc hasPattern*(s: PSym): bool {.inline.} =
  1492. result = isRoutine(s) and s.ast.sons[patternPos].kind != nkEmpty
  1493. iterator items*(n: PNode): PNode =
  1494. for i in 0..<n.safeLen: yield n.sons[i]
  1495. iterator pairs*(n: PNode): tuple[i: int, n: PNode] =
  1496. for i in 0..<n.safeLen: yield (i, n.sons[i])
  1497. proc isAtom*(n: PNode): bool {.inline.} =
  1498. result = n.kind >= nkNone and n.kind <= nkNilLit
  1499. proc isEmptyType*(t: PType): bool {.inline.} =
  1500. ## 'void' and 'stmt' types are often equivalent to 'nil' these days:
  1501. result = t == nil or t.kind in {tyVoid, tyStmt}
  1502. proc makeStmtList*(n: PNode): PNode =
  1503. if n.kind == nkStmtList:
  1504. result = n
  1505. else:
  1506. result = newNodeI(nkStmtList, n.info)
  1507. result.add n
  1508. proc skipStmtList*(n: PNode): PNode =
  1509. if n.kind in {nkStmtList, nkStmtListExpr}:
  1510. for i in 0 .. n.len-2:
  1511. if n[i].kind notin {nkEmpty, nkCommentStmt}: return n
  1512. result = n.lastSon
  1513. else:
  1514. result = n
  1515. proc toVar*(typ: PType): PType =
  1516. ## If ``typ`` is not a tyVar then it is converted into a `var <typ>` and
  1517. ## returned. Otherwise ``typ`` is simply returned as-is.
  1518. result = typ
  1519. if typ.kind != tyVar:
  1520. result = newType(tyVar, typ.owner)
  1521. rawAddSon(result, typ)
  1522. proc toRef*(typ: PType): PType =
  1523. ## If ``typ`` is a tyObject then it is converted into a `ref <typ>` and
  1524. ## returned. Otherwise ``typ`` is simply returned as-is.
  1525. result = typ
  1526. if typ.kind == tyObject:
  1527. result = newType(tyRef, typ.owner)
  1528. rawAddSon(result, typ)
  1529. proc toObject*(typ: PType): PType =
  1530. ## If ``typ`` is a tyRef then its immediate son is returned (which in many
  1531. ## cases should be a ``tyObject``).
  1532. ## Otherwise ``typ`` is simply returned as-is.
  1533. result = typ
  1534. if result.kind == tyRef:
  1535. result = result.lastSon
  1536. proc isException*(t: PType): bool =
  1537. # check if `y` is object type and it inherits from Exception
  1538. assert(t != nil)
  1539. if t.kind != tyObject:
  1540. return false
  1541. var base = t
  1542. while base != nil:
  1543. if base.sym != nil and base.sym.magic == mException:
  1544. return true
  1545. base = base.lastSon
  1546. return false
  1547. proc isImportedException*(t: PType; conf: ConfigRef): bool =
  1548. assert(t != nil)
  1549. if optNoCppExceptions in conf.globalOptions:
  1550. return false
  1551. let base = t.skipTypes({tyAlias, tyPtr, tyDistinct, tyGenericInst})
  1552. if base.sym != nil and sfCompileToCpp in base.sym.flags:
  1553. result = true
  1554. proc isInfixAs*(n: PNode): bool =
  1555. return n.kind == nkInfix and n[0].kind == nkIdent and n[0].ident.s == "as"
  1556. proc findUnresolvedStatic*(n: PNode): PNode =
  1557. if n.kind == nkSym and n.typ.kind == tyStatic and n.typ.n == nil:
  1558. return n
  1559. for son in n:
  1560. let n = son.findUnresolvedStatic
  1561. if n != nil: return n
  1562. return nil
  1563. when false:
  1564. proc containsNil*(n: PNode): bool =
  1565. # only for debugging
  1566. if n.isNil: return true
  1567. for i in 0 ..< n.safeLen:
  1568. if n[i].containsNil: return true
  1569. template hasDestructor*(t: PType): bool = tfHasAsgn in t.flags
  1570. template incompleteType*(t: PType): bool =
  1571. t.sym != nil and {sfForward, sfNoForward} * t.sym.flags == {sfForward}
  1572. template typeCompleted*(s: PSym) =
  1573. incl s.flags, sfNoForward
  1574. template getBody*(s: PSym): PNode = s.ast[bodyPos]