ast.nim 66 KB

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