diff options
Diffstat (limited to 'compiler/ast.nim')
-rw-r--r-- | compiler/ast.nim | 1889 |
1 files changed, 1144 insertions, 745 deletions
diff --git a/compiler/ast.nim b/compiler/ast.nim index 40c1b064d..a342e1ea7 100644 --- a/compiler/ast.nim +++ b/compiler/ast.nim @@ -10,224 +10,38 @@ # abstract syntax tree + symbol table import - lineinfos, hashes, nversion, options, strutils, std / sha1, ropes, idents, - intsets, idgen + lineinfos, options, ropes, idents, int128, wordrecg -type - TCallingConvention* = enum - ccDefault, # proc has no explicit calling convention - ccStdCall, # procedure is stdcall - ccCDecl, # cdecl - ccSafeCall, # safecall - ccSysCall, # system call - ccInline, # proc should be inlined - ccNoInline, # proc should not be inlined - ccFastCall, # fastcall (pass parameters in registers) - ccClosure, # proc has a closure - ccNoConvention # needed for generating proper C procs sometimes +import std/[tables, hashes] +from std/strutils import toLowerAscii -const - CallingConvToStr*: array[TCallingConvention, string] = ["", "stdcall", - "cdecl", "safecall", "syscall", "inline", "noinline", "fastcall", - "closure", "noconv"] +when defined(nimPreviewSlimSystem): + import std/assertions + +export int128 + +import nodekinds +export nodekinds type - TNodeKind* = enum # order is extremely important, because ranges are used - # to check whether a node belongs to a certain class - nkNone, # unknown node kind: indicates an error - # Expressions: - # Atoms: - nkEmpty, # the node is empty - nkIdent, # node is an identifier - nkSym, # node is a symbol - nkType, # node is used for its typ field - - nkCharLit, # a character literal '' - nkIntLit, # an integer literal - nkInt8Lit, - nkInt16Lit, - nkInt32Lit, - nkInt64Lit, - nkUIntLit, # an unsigned integer literal - nkUInt8Lit, - nkUInt16Lit, - nkUInt32Lit, - nkUInt64Lit, - nkFloatLit, # a floating point literal - nkFloat32Lit, - nkFloat64Lit, - nkFloat128Lit, - nkStrLit, # a string literal "" - nkRStrLit, # a raw string literal r"" - nkTripleStrLit, # a triple string literal """ - nkNilLit, # the nil literal - # end of atoms - nkComesFrom, # "comes from" template/macro information for - # better stack trace generation - nkDotCall, # used to temporarily flag a nkCall node; - # this is used - # for transforming ``s.len`` to ``len(s)`` - - nkCommand, # a call like ``p 2, 4`` without parenthesis - nkCall, # a call like p(x, y) or an operation like +(a, b) - nkCallStrLit, # a call with a string literal - # x"abc" has two sons: nkIdent, nkRStrLit - # x"""abc""" has two sons: nkIdent, nkTripleStrLit - nkInfix, # a call like (a + b) - nkPrefix, # a call like !a - nkPostfix, # something like a! (also used for visibility) - nkHiddenCallConv, # an implicit type conversion via a type converter - - nkExprEqExpr, # a named parameter with equals: ''expr = expr'' - nkExprColonExpr, # a named parameter with colon: ''expr: expr'' - nkIdentDefs, # a definition like `a, b: typeDesc = expr` - # either typeDesc or expr may be nil; used in - # formal parameters, var statements, etc. - nkVarTuple, # a ``var (a, b) = expr`` construct - nkPar, # syntactic (); may be a tuple constructor - nkObjConstr, # object constructor: T(a: 1, b: 2) - nkCurly, # syntactic {} - nkCurlyExpr, # an expression like a{i} - nkBracket, # syntactic [] - nkBracketExpr, # an expression like a[i..j, k] - nkPragmaExpr, # an expression like a{.pragmas.} - nkRange, # an expression like i..j - nkDotExpr, # a.b - nkCheckedFieldExpr, # a.b, but b is a field that needs to be checked - nkDerefExpr, # a^ - nkIfExpr, # if as an expression - nkElifExpr, - nkElseExpr, - nkLambda, # lambda expression - nkDo, # lambda block appering as trailing proc param - nkAccQuoted, # `a` as a node - - nkTableConstr, # a table constructor {expr: expr} - nkBind, # ``bind expr`` node - nkClosedSymChoice, # symbol choice node; a list of nkSyms (closed) - nkOpenSymChoice, # symbol choice node; a list of nkSyms (open) - nkHiddenStdConv, # an implicit standard type conversion - nkHiddenSubConv, # an implicit type conversion from a subtype - # to a supertype - nkConv, # a type conversion - nkCast, # a type cast - nkStaticExpr, # a static expr - nkAddr, # a addr expression - nkHiddenAddr, # implicit address operator - nkHiddenDeref, # implicit ^ operator - nkObjDownConv, # down conversion between object types - nkObjUpConv, # up conversion between object types - nkChckRangeF, # range check for floats - nkChckRange64, # range check for 64 bit ints - nkChckRange, # range check for ints - nkStringToCString, # string to cstring - nkCStringToString, # cstring to string - # end of expressions - - nkAsgn, # a = b - nkFastAsgn, # internal node for a fast ``a = b`` - # (no string copy) - nkGenericParams, # generic parameters - nkFormalParams, # formal parameters - nkOfInherit, # inherited from symbol - - nkImportAs, # a 'as' b in an import statement - nkProcDef, # a proc - nkMethodDef, # a method - nkConverterDef, # a converter - nkMacroDef, # a macro - nkTemplateDef, # a template - nkIteratorDef, # an iterator - - nkOfBranch, # used inside case statements - # for (cond, action)-pairs - nkElifBranch, # used in if statements - nkExceptBranch, # an except section - nkElse, # an else part - nkAsmStmt, # an assembler block - nkPragma, # a pragma statement - nkPragmaBlock, # a pragma with a block - nkIfStmt, # an if statement - nkWhenStmt, # a when expression or statement - nkForStmt, # a for statement - nkParForStmt, # a parallel for statement - nkWhileStmt, # a while statement - nkCaseStmt, # a case statement - nkTypeSection, # a type section (consists of type definitions) - nkVarSection, # a var section - nkLetSection, # a let section - nkConstSection, # a const section - nkConstDef, # a const definition - nkTypeDef, # a type definition - nkYieldStmt, # the yield statement as a tree - nkDefer, # the 'defer' statement - nkTryStmt, # a try statement - nkFinally, # a finally section - nkRaiseStmt, # a raise statement - nkReturnStmt, # a return statement - nkBreakStmt, # a break statement - nkContinueStmt, # a continue statement - nkBlockStmt, # a block statement - nkStaticStmt, # a static statement - nkDiscardStmt, # a discard statement - nkStmtList, # a list of statements - nkImportStmt, # an import statement - nkImportExceptStmt, # an import x except a statement - nkExportStmt, # an export statement - nkExportExceptStmt, # an 'export except' statement - nkFromStmt, # a from * import statement - nkIncludeStmt, # an include statement - nkBindStmt, # a bind statement - nkMixinStmt, # a mixin statement - nkUsingStmt, # an using statement - nkCommentStmt, # a comment statement - nkStmtListExpr, # a statement list followed by an expr; this is used - # to allow powerful multi-line templates - nkBlockExpr, # a statement block ending in an expr; this is used - # to allowe powerful multi-line templates that open a - # temporary scope - nkStmtListType, # a statement list ending in a type; for macros - nkBlockType, # a statement block ending in a type; for macros - # types as syntactic trees: - - nkWith, # distinct with `foo` - nkWithout, # distinct without `foo` - - nkTypeOfExpr, # type(1+2) - nkObjectTy, # object body - nkTupleTy, # tuple body - nkTupleClassTy, # tuple type class - nkTypeClassTy, # user-defined type class - nkStaticTy, # ``static[T]`` - nkRecList, # list of object parts - nkRecCase, # case section of object - nkRecWhen, # when section of object - nkRefTy, # ``ref T`` - nkPtrTy, # ``ptr T`` - nkVarTy, # ``var T`` - nkConstTy, # ``const T`` - nkMutableTy, # ``mutable T`` - nkDistinctTy, # distinct type - nkProcTy, # proc type - nkIteratorTy, # iterator type - nkSharedTy, # 'shared T' - # we use 'nkPostFix' for the 'not nil' addition - nkEnumTy, # enum body - nkEnumFieldDef, # `ident = expr` in an enumeration - nkArgList, # argument list - nkPattern, # a special pattern; used for matching - nkReturnToken, # token used for interpretation - nkClosure, # (prc, env)-pair (internally used for code gen) - nkGotoState, # used for the state machine (for iterators) - nkState, # give a label to a code section (for iterators) - nkBreakState, # special break statement for easier code generation - nkFuncDef, # a func - nkTupleConstr # a tuple constructor + TCallingConvention* = enum + ccNimCall = "nimcall" # nimcall, also the default + ccStdCall = "stdcall" # procedure is stdcall + ccCDecl = "cdecl" # cdecl + ccSafeCall = "safecall" # safecall + ccSysCall = "syscall" # system call + ccInline = "inline" # proc should be inlined + ccNoInline = "noinline" # proc should not be inlined + ccFastCall = "fastcall" # fastcall (pass parameters in registers) + ccThisCall = "thiscall" # thiscall (parameters are pushed right-to-left) + ccClosure = "closure" # proc has a closure + ccNoConvention = "noconv" # needed for generating proper C procs sometimes + ccMember = "member" # proc is a (cpp) member TNodeKinds* = set[TNodeKind] type - TSymFlag* = enum # already 33 flags! + TSymFlag* = enum # 63 flags! sfUsed, # read access of sym (for warnings) or simply used sfExported, # symbol is exported from module sfFromGeneric, # symbol is instantiation of a generic; this is needed @@ -236,8 +50,11 @@ type sfGlobal, # symbol is at global scope sfForward, # symbol is forward declared + sfWasForwarded, # symbol had a forward declaration + # (implies it's too dangerous to patch its type signature) sfImportc, # symbol is external; imported sfExportc, # symbol is exported (under a specified name) + sfMangleCpp, # mangle as cpp (combines with `sfExportc`) sfVolatile, # variable is volatile sfRegister, # variable should be placed in a register sfPure, # object is "pure" that means it has no type-information @@ -252,14 +69,20 @@ type # *OR*: a proc is indirectly called (used as first class) sfCompilerProc, # proc is a compiler proc, that is a C proc that is # needed for the code generator - sfProcvar, # proc can be passed to a proc var + sfEscapes # param escapes + # currently unimplemented sfDiscriminant, # field is a discriminant in a record/object + sfRequiresInit, # field must be initialized during construction sfDeprecated, # symbol is deprecated sfExplain, # provide more diagnostics when this symbol is used sfError, # usage of symbol should trigger a compile-time error sfShadowed, # a symbol that was shadowed in some inner scope sfThread, # proc will run as a thread # variable is a thread variable + sfCppNonPod, # tells compiler to treat such types as non-pod's, so that + # `thread_local` is used instead of `__thread` for + # {.threadvar.} + `--threads`. Only makes sense for importcpp types. + # This has a performance impact so isn't set by default. sfCompileTime, # proc can be evaluated at compile time sfConstructor, # proc is a C++ constructor sfDispatcher, # copied method symbol is the dispatcher @@ -270,29 +93,58 @@ type sfNamedParamCall, # symbol needs named parameter call syntax in target # language; for interfacing with Objective C sfDiscardable, # returned value may be discarded implicitly - sfOverriden, # proc is overriden + sfOverridden, # proc is overridden + sfCallsite # A flag for template symbols to tell the + # compiler it should use line information from + # the calling side of the macro, not from the + # implementation. sfGenSym # symbol is 'gensym'ed; do not add to symbol table + sfNonReloadable # symbol will be left as-is when hot code reloading is on - + # meaning that it won't be renamed and/or changed in any way + sfGeneratedOp # proc is a generated '='; do not inject destructors in it + # variable is generated closure environment; requires early + # destruction for --newruntime. + sfTemplateParam # symbol is a template parameter + sfCursor # variable/field is a cursor, see RFC 177 for details + sfInjectDestructors # whether the proc needs the 'injectdestructors' transformation + sfNeverRaises # proc can never raise an exception, not even OverflowDefect + # or out-of-memory + sfSystemRaisesDefect # proc in the system can raise defects + sfUsedInFinallyOrExcept # symbol is used inside an 'except' or 'finally' + sfSingleUsedTemp # For temporaries that we know will only be used once + sfNoalias # 'noalias' annotation, means C's 'restrict' + # for templates and macros, means cannot be called + # as a lone symbol (cannot use alias syntax) + sfEffectsDelayed # an 'effectsDelayed' parameter + sfGeneratedType # A anonymous generic type that is generated by the compiler for + # objects that do not have generic parameters in case one of the + # object fields has one. + # + # This is disallowed but can cause the typechecking to go into + # an infinite loop, this flag is used as a sentinel to stop it. + sfVirtual # proc is a C++ virtual function + sfByCopy # param is marked as pass bycopy + sfMember # proc is a C++ member of a type + sfCodegenDecl # type, proc, global or proc param is marked as codegenDecl + sfWasGenSym # symbol was 'gensym'ed + sfForceLift # variable has to be lifted into closure environment + + sfDirty # template is not hygienic (old styled template) module, + # compiled from a dirty-buffer + sfCustomPragma # symbol is custom pragma template + sfBase, # a base method + sfGoto # var is used for 'goto' code generation + sfAnon, # symbol name that was generated by the compiler + # the compiler will avoid printing such names + # in user messages. + sfAllUntyped # macro or template is immediately expanded in a generic context + sfTemplateRedefinition # symbol is a redefinition of an earlier template TSymFlags* = set[TSymFlag] const sfNoInit* = sfMainModule # don't generate code to init the variable - sfImmediate* = sfDispatcher - # macro or template is immediately expanded - # without considering any possible overloads - sfAllUntyped* = sfVolatile # macro or template is immediately expanded \ - # in a generic context - - sfDirty* = sfPure - # template is not hygienic (old styled template) - # module, compiled from a dirty-buffer - - sfAnon* = sfDiscardable - # symbol name that was generated by the compiler - # the compiler will avoid printing such names - # in user messages. - sfNoForward* = sfRegister # forward declarations are not required (per module) sfReorder* = sfForward @@ -300,13 +152,10 @@ const sfCompileToCpp* = sfInfixCall # compile the module as C++ code sfCompileToObjc* = sfNamedParamCall # compile the module as Objective-C code - sfExperimental* = sfOverriden # module uses the .experimental switch - sfGoto* = sfOverriden # var is used for 'goto' code generation + sfExperimental* = sfOverridden # module uses the .experimental switch sfWrittenTo* = sfBorrow # param is assigned to - sfEscapes* = sfProcvar # param escapes - sfBase* = sfDiscriminant - sfIsSelf* = sfOverriden # param is 'self' - sfCustomPragma* = sfRegister # symbol is custom pragma template + # currently unimplemented + sfCppMember* = { sfVirtual, sfMember, sfConstructor } # proc is a C++ member, meaning it will be attached to the type definition const # getting ready for the future expr/stmt merge @@ -315,10 +164,14 @@ const nkEffectList* = nkArgList # hacks ahead: an nkEffectList is a node with 4 children: exceptionEffects* = 0 # exceptions at position 0 - usesEffects* = 1 # read effects at position 1 - writeEffects* = 2 # write effects at position 2 + requiresEffects* = 1 # 'requires' annotation + ensuresEffects* = 2 # 'ensures' annotation tagEffects* = 3 # user defined tag ('gc', 'time' etc.) - effectListLen* = 4 # list of effects list + pragmasEffects* = 4 # not an effect, but a slot for pragmas in proc type + forbiddenEffects* = 5 # list of illegal effects + effectListLen* = 6 # list of effects list + nkLastBlockStmts* = {nkRaiseStmt, nkReturnStmt, nkBreakStmt, nkContinueStmt} + # these must be last statements in a block type TTypeKind* = enum # order is important! @@ -329,7 +182,7 @@ type # (apparently something with bootstrapping) # if you need to add a type, they can apparently be reused tyNone, tyBool, tyChar, - tyEmpty, tyAlias, tyNil, tyExpr, tyStmt, tyTypeDesc, + tyEmpty, tyAlias, tyNil, tyUntyped, tyTyped, tyTypeDesc, tyGenericInvocation, # ``T[a, b]`` for types to invoke tyGenericBody, # ``T[a, b, body]`` last parameter is the body tyGenericInst, # ``T[a, b, realInstance]`` instantiated generic type @@ -352,14 +205,17 @@ type tySequence, tyProc, tyPointer, tyOpenArray, - tyString, tyCString, tyForward, + tyString, tyCstring, tyForward, tyInt, tyInt8, tyInt16, tyInt32, tyInt64, # signed integers tyFloat, tyFloat32, tyFloat64, tyFloat128, tyUInt, tyUInt8, tyUInt16, tyUInt32, tyUInt64, - tyOptAsRef, tySink, tyLent, + tyOwned, tySink, tyLent, tyVarargs, - tyUnused, - tyProxy # used as errornous type (for idetools) + tyUncheckedArray + # An array with boundaries [0,+∞] + + tyError # used as erroneous type (for idetools) + # as an erroneous node should match everything tyBuiltInTypeClass # Type such as the catch-all object, tuple, seq, etc @@ -384,9 +240,9 @@ type tyInferred # In the initial state `base` stores a type class constraining # the types that can be inferred. After a candidate type is - # selected, it's stored in `lastSon`. Between `base` and `lastSon` + # selected, it's stored in `last`. Between `base` and `last` # there may be 0, 2 or more types that were also considered as - # possible candidates in the inference process (i.e. lastSon will + # possible candidates in the inference process (i.e. last will # be updated to store a type best conforming to all candidates) tyAnd, tyOr, tyNot @@ -406,30 +262,33 @@ type # instantiation and prior to this it has the potential to # be any type. - tyOpt - # Builtin optional type + tyConcept + # new style concept. tyVoid # now different from tyEmpty, hurray! + tyIterable static: # remind us when TTypeKind stops to fit in a single 64-bit word - assert TTypeKind.high.ord <= 63 + # assert TTypeKind.high.ord <= 63 + discard const tyPureObject* = tyTuple GcTypeKinds* = {tyRef, tySequence, tyString} - tyError* = tyProxy # as an errornous node should match everything - tyUnknown* = tyFromExpr - - tyUnknownTypes* = {tyError, tyFromExpr} tyTypeClasses* = {tyBuiltInTypeClass, tyCompositeTypeClass, tyUserTypeClass, tyUserTypeClassInst, tyAnd, tyOr, tyNot, tyAnything} - tyMetaTypes* = {tyGenericParam, tyTypeDesc, tyExpr} + tyTypeClasses + tyMetaTypes* = {tyGenericParam, tyTypeDesc, tyUntyped} + tyTypeClasses tyUserTypeClasses* = {tyUserTypeClass, tyUserTypeClassInst} + # consider renaming as `tyAbstractVarRange` + abstractVarRange* = {tyGenericInst, tyRange, tyVar, tyDistinct, tyOrdinal, + tyTypeDesc, tyAlias, tyInferred, tySink, tyOwned} + abstractInst* = {tyGenericInst, tyDistinct, tyOrdinal, tyTypeDesc, tyAlias, + tyInferred, tySink, tyOwned} # xxx what about tyStatic? type TTypeKinds* = set[TTypeKind] @@ -451,18 +310,30 @@ type nfExplicitCall # x.y() was used instead of x.y nfExprCall # this is an attempt to call a regular expression nfIsRef # this node is a 'ref' node; used for the VM + nfIsPtr # this node is a 'ptr' node; used for the VM nfPreventCg # this node should be ignored by the codegen nfBlockArg # this a stmtlist appearing in a call (e.g. a do block) nfFromTemplate # a top-level node returned from a template + nfDefaultParam # an automatically inserter default parameter + nfDefaultRefsParam # a default param value references another parameter + # the flag is applied to proc default values and to calls + nfExecuteOnReload # A top-level statement that will be executed during reloads + nfLastRead # this node is a last read + nfFirstWrite # this node is a first write + nfHasComment # node has a comment + nfSkipFieldChecking # node skips field visable checking + nfDisabledOpenSym # temporary: node should be nkOpenSym but cannot + # because openSym experimental switch is disabled + # gives warning instead TNodeFlags* = set[TNodeFlag] - TTypeFlag* = enum # keep below 32 for efficiency reasons (now: beyond that) + TTypeFlag* = enum # keep below 32 for efficiency reasons (now: 47) tfVarargs, # procedure has C styled varargs # tyArray type represeting a varargs list tfNoSideEffect, # procedure type does not allow side effects tfFinal, # is the object final? tfInheritable, # is the object inheritable? - tfAcyclic, # type is acyclic (for GC optimization) + tfHasOwned, # type contains an 'owned' type and must be moved tfEnumHasHoles, # enum cannot be mapped into a range tfShallow, # type can be shallow copied on assignment tfThread, # proc type is marked as ``thread``; alias for ``gcsafe`` @@ -486,9 +357,11 @@ type tfIterator, # type is really an iterator, not a tyProc tfPartial, # type is declared as 'partial' tfNotNil, # type cannot be 'nil' - - tfNeedsInit, # type constains a "not nil" constraint somewhere or some - # other type so that it requires initialization + tfRequiresInit, # type contains a "not nil" constraint somewhere or + # a `requiresInit` field, so the default zero init + # is not appropriate + tfNeedsFullInit, # object type marked with {.requiresInit.} + # all fields must be initialized tfVarIsPtr, # 'var' type is translated like 'ptr' even in C++ mode tfHasMeta, # type contains "wildcard" sub-types such as generic params # or other type classes @@ -498,6 +371,7 @@ type tfGenericTypeParam tfImplicitTypeParam tfInferrableStatic + tfConceptMatchedTypeSym tfExplicit # for typedescs, marks types explicitly prefixed with the # `type` operator (e.g. type int) tfWildcard # consider a proc like foo[T, I](x: Type[T, I]) @@ -509,9 +383,22 @@ type tfTriggersCompileTime # uses the NimNode type which make the proc # implicitly '.compiletime' tfRefsAnonObj # used for 'ref object' and 'ptr object' - tfCovariant # covariant generic param mimicing a ptr type - tfWeakCovariant # covariant generic param mimicing a seq/array type + tfCovariant # covariant generic param mimicking a ptr type + tfWeakCovariant # covariant generic param mimicking a seq/array type tfContravariant # contravariant generic param + tfCheckedForDestructor # type was checked for having a destructor. + # If it has one, t.destructor is not nil. + tfAcyclic # object type was annotated as .acyclic + tfIncompleteStruct # treat this type as if it had sizeof(pointer) + tfCompleteStruct + # (for importc types); type is fully specified, allowing to compute + # sizeof, alignof, offsetof at CT + tfExplicitCallConv + tfIsConstructor + tfEffectSystemWorkaround + tfIsOutParam + tfSendable + tfImplicitStatic TTypeFlags* = set[TTypeFlag] @@ -547,91 +434,86 @@ type # file (it is loaded on demand, which may # mean: never) skPackage, # symbol is a package (used for canonicalization) - skAlias # an alias (needs to be resolved immediately) TSymKinds* = set[TSymKind] const routineKinds* = {skProc, skFunc, skMethod, skIterator, skConverter, skMacro, skTemplate} - tfIncompleteStruct* = tfVarargs - tfUncheckedArray* = tfVarargs + ExportableSymKinds* = {skVar, skLet, skConst, skType, skEnumField, skStub} + routineKinds + tfUnion* = tfNoSideEffect tfGcSafe* = tfThread tfObjHasKids* = tfEnumHasHoles - tfOldSchoolExprStmt* = tfVarargs # for now used to distinguish \ - # 'varargs[expr]' from 'varargs[untyped]'. Eventually 'expr' will be - # deprecated and this mess can be cleaned up. tfReturnsNew* = tfInheritable + tfNonConstExpr* = tfExplicitCallConv + ## tyFromExpr where the expression shouldn't be evaluated as a static value skError* = skUnknown - # type flags that are essential for type equality: - eqTypeFlags* = {tfIterator, tfNotNil, tfVarIsPtr} +var + eqTypeFlags* = {tfIterator, tfNotNil, tfVarIsPtr, tfGcSafe, tfNoSideEffect, tfIsOutParam} + ## type flags that are essential for type equality. + ## This is now a variable because for emulation of version:1.0 we + ## might exclude {tfGcSafe, tfNoSideEffect}. type TMagic* = enum # symbols that require compiler magic: mNone, - mDefined, mDefinedInScope, mCompiles, mArrGet, mArrPut, mAsgn, - mLow, mHigh, mSizeOf, mTypeTrait, mIs, mOf, mAddr, mTypeOf, mRoof, mPlugin, - mEcho, mShallowCopy, mSlurp, mStaticExec, + mDefined, mDeclared, mDeclaredInScope, mCompiles, mArrGet, mArrPut, mAsgn, + mLow, mHigh, mSizeOf, mAlignOf, mOffsetOf, mTypeTrait, + mIs, mOf, mAddr, mType, mTypeOf, + mPlugin, mEcho, mShallowCopy, mSlurp, mStaticExec, mStatic, mParseExprToAst, mParseStmtToAst, mExpandToAst, mQuoteAst, - mUnaryLt, mInc, mDec, mOrd, + mInc, mDec, mOrd, mNew, mNewFinalize, mNewSeq, mNewSeqOfCap, mLengthOpenArray, mLengthStr, mLengthArray, mLengthSeq, - mXLenStr, mXLenSeq, mIncl, mExcl, mCard, mChr, mGCref, mGCunref, mAddI, mSubI, mMulI, mDivI, mModI, mSucc, mPred, mAddF64, mSubF64, mMulF64, mDivF64, - mShrI, mShlI, mBitandI, mBitorI, mBitxorI, + mShrI, mShlI, mAshrI, mBitandI, mBitorI, mBitxorI, mMinI, mMaxI, - mMinF64, mMaxF64, mAddU, mSubU, mMulU, mDivU, mModU, mEqI, mLeI, mLtI, mEqF64, mLeF64, mLtF64, mLeU, mLtU, - mLeU64, mLtU64, mEqEnum, mLeEnum, mLtEnum, mEqCh, mLeCh, mLtCh, mEqB, mLeB, mLtB, - mEqRef, mEqUntracedRef, mLePtr, mLtPtr, + mEqRef, mLePtr, mLtPtr, mXor, mEqCString, mEqProc, mUnaryMinusI, mUnaryMinusI64, mAbsI, mNot, mUnaryPlusI, mBitnotI, - mUnaryPlusF64, mUnaryMinusF64, mAbsF64, - mZe8ToI, mZe8ToI64, - mZe16ToI, mZe16ToI64, - mZe32ToI64, mZeIToI64, - mToU8, mToU16, mToU32, - mToFloat, mToBiggestFloat, - mToInt, mToBiggestInt, - mCharToStr, mBoolToStr, mIntToStr, mInt64ToStr, mFloatToStr, mCStrToStr, + mUnaryPlusF64, mUnaryMinusF64, + mCharToStr, mBoolToStr, + mCStrToStr, mStrToStr, mEnumToStr, mAnd, mOr, + mImplies, mIff, mExists, mForall, mOld, mEqStr, mLeStr, mLtStr, - mEqSet, mLeSet, mLtSet, mMulSet, mPlusSet, mMinusSet, mSymDiffSet, + mEqSet, mLeSet, mLtSet, mMulSet, mPlusSet, mMinusSet, mConStrStr, mSlice, mDotDot, # this one is only necessary to give nice compile time warnings mFields, mFieldPairs, mOmpParFor, mAppendStrCh, mAppendStrStr, mAppendSeqElem, - mInRange, mInSet, mRepr, mExit, + mInSet, mRepr, mExit, mSetLengthStr, mSetLengthSeq, mIsPartOf, mAstToStr, mParallel, - mSwap, mIsNil, mArrToSeq, mCopyStr, mCopyStrLast, + mSwap, mIsNil, mArrToSeq, mOpenArrayToSeq, mNewString, mNewStringOfCap, mParseBiggestFloat, - mReset, - mArray, mOpenArray, mRange, mSet, mSeq, mOpt, mVarargs, + mMove, mEnsureMove, mWasMoved, mDup, mDestroy, mTrace, + mDefault, mUnown, mFinished, mIsolate, mAccessEnv, mAccessTypeField, + mArray, mOpenArray, mRange, mSet, mSeq, mVarargs, mRef, mPtr, mVar, mDistinct, mVoid, mTuple, - mOrdinal, + mOrdinal, mIterableType, mInt, mInt8, mInt16, mInt32, mInt64, mUInt, mUInt8, mUInt16, mUInt32, mUInt64, mFloat, mFloat32, mFloat64, mFloat128, mBool, mChar, mString, mCstring, - mPointer, mEmptySet, mIntSetBaseType, mNil, mExpr, mStmt, mTypeDesc, - mVoidType, mPNimrodNode, mShared, mGuarded, mLock, mSpawn, mDeepCopy, + mPointer, mNil, mExpr, mStmt, mTypeDesc, + mVoidType, mPNimrodNode, mSpawn, mDeepCopy, mIsMainModule, mCompileDate, mCompileTime, mProcCall, mCpuEndian, mHostOS, mHostCPU, mBuildOS, mBuildCPU, mAppType, - mNaN, mInf, mNegInf, mCompileOption, mCompileOptionArg, mNLen, mNChild, mNSetChild, mNAdd, mNAddMultiple, mNDel, mNKind, mNSymKind, @@ -640,57 +522,66 @@ type mNctPut, mNctLen, mNctGet, mNctHasNext, mNctNext, mNIntVal, mNFloatVal, mNSymbol, mNIdent, mNGetType, mNStrVal, mNSetIntVal, - mNSetFloatVal, mNSetSymbol, mNSetIdent, mNSetType, mNSetStrVal, mNLineInfo, - mNNewNimNode, mNCopyNimNode, mNCopyNimTree, mStrToIdent, - mNBindSym, mLocals, mNCallSite, + mNSetFloatVal, mNSetSymbol, mNSetIdent, mNSetStrVal, mNLineInfo, + mNNewNimNode, mNCopyNimNode, mNCopyNimTree, mStrToIdent, mNSigHash, mNSizeOf, + mNBindSym, mNCallSite, mEqIdent, mEqNimrodNode, mSameNodeType, mGetImpl, mNGenSym, mNHint, mNWarning, mNError, - mInstantiationInfo, mGetTypeInfo, - mNimvm, mIntDefine, mStrDefine, mRunnableExamples, - mException, mBuiltinType + mInstantiationInfo, mGetTypeInfo, mGetTypeInfoV2, + mNimvm, mIntDefine, mStrDefine, mBoolDefine, mGenericDefine, mRunnableExamples, + mException, mBuiltinType, mSymOwner, mUncheckedArray, mGetImplTransf, + mSymIsInstantiationOf, mNodeId, mPrivateAccess, mZeroDefault + -# things that we can evaluate safely at compile time, even if not asked for it: const - ctfeWhitelist* = {mNone, mUnaryLt, mSucc, + # things that we can evaluate safely at compile time, even if not asked for it: + ctfeWhitelist* = {mNone, mSucc, mPred, mInc, mDec, mOrd, mLengthOpenArray, - mLengthStr, mLengthArray, mLengthSeq, mXLenStr, mXLenSeq, - mArrGet, mArrPut, mAsgn, + mLengthStr, mLengthArray, mLengthSeq, + mArrGet, mArrPut, mAsgn, mDestroy, mIncl, mExcl, mCard, mChr, mAddI, mSubI, mMulI, mDivI, mModI, mAddF64, mSubF64, mMulF64, mDivF64, mShrI, mShlI, mBitandI, mBitorI, mBitxorI, mMinI, mMaxI, - mMinF64, mMaxF64, mAddU, mSubU, mMulU, mDivU, mModU, mEqI, mLeI, mLtI, mEqF64, mLeF64, mLtF64, mLeU, mLtU, - mLeU64, mLtU64, mEqEnum, mLeEnum, mLtEnum, mEqCh, mLeCh, mLtCh, mEqB, mLeB, mLtB, - mEqRef, mEqProc, mEqUntracedRef, mLePtr, mLtPtr, mEqCString, mXor, + mEqRef, mEqProc, mLePtr, mLtPtr, mEqCString, mXor, mUnaryMinusI, mUnaryMinusI64, mAbsI, mNot, mUnaryPlusI, mBitnotI, - mUnaryPlusF64, mUnaryMinusF64, mAbsF64, - mZe8ToI, mZe8ToI64, - mZe16ToI, mZe16ToI64, - mZe32ToI64, mZeIToI64, - mToU8, mToU16, mToU32, - mToFloat, mToBiggestFloat, - mToInt, mToBiggestInt, - mCharToStr, mBoolToStr, mIntToStr, mInt64ToStr, mFloatToStr, mCStrToStr, + mUnaryPlusF64, mUnaryMinusF64, + mCharToStr, mBoolToStr, + mCStrToStr, mStrToStr, mEnumToStr, mAnd, mOr, mEqStr, mLeStr, mLtStr, - mEqSet, mLeSet, mLtSet, mMulSet, mPlusSet, mMinusSet, mSymDiffSet, + mEqSet, mLeSet, mLtSet, mMulSet, mPlusSet, mMinusSet, mConStrStr, mAppendStrCh, mAppendStrStr, mAppendSeqElem, - mInRange, mInSet, mRepr, - mCopyStr, mCopyStrLast} - # magics that require special semantic checking and - # thus cannot be overloaded (also documented in the spec!): - SpecialSemMagics* = { - mDefined, mDefinedInScope, mCompiles, mLow, mHigh, mSizeOf, mIs, mOf, - mShallowCopy, mExpandToAst, mParallel, mSpawn, mAstToStr} + mInSet, mRepr, mOpenArrayToSeq} + + generatedMagics* = {mNone, mIsolate, mFinished, mOpenArrayToSeq} + ## magics that are generated as normal procs in the backend + +type + ItemId* = object + module*: int32 + item*: int32 + +proc `$`*(x: ItemId): string = + "(module: " & $x.module & ", item: " & $x.item & ")" + +proc `==`*(a, b: ItemId): bool {.inline.} = + a.item == b.item and a.module == b.module + +proc hash*(x: ItemId): Hash = + var h: Hash = hash(x.module) + h = h !& hash(x.item) + result = !$h + type PNode* = ref TNode @@ -716,12 +607,12 @@ type ident*: PIdent else: sons*: TNodeSeq - comment*: string + when defined(nimsuggest): + endInfo*: TLineInfo - TSymSeq* = seq[PSym] TStrTable* = object # a table[PIdent] of PSym counter*: int - data*: TSymSeq + data*: seq[PSym] # -------------- backend information ------------------------------- TLocKind* = enum @@ -738,9 +629,6 @@ type locOther # location is something other TLocFlag* = enum lfIndirect, # backend introduced a pointer - lfFullExternalName, # only used when 'conf.cmd == cmdPretty': Indicates - # that the symbol has been imported via 'importc: "fullname"' and - # no format string. lfNoDeepCopy, # no need for a deep copy lfNoDecl, # do not declare it in C lfDynamicLib, # link symbol to dynamic library @@ -748,12 +636,14 @@ type lfHeader, # include header file for symbol lfImportCompilerProc, # ``importc`` of a compilerproc lfSingleUse # no location yet and will only be used once + lfEnforceDeref # a copyMem is required to dereference if this a + # ptr array due to C array limitations. + # See #1181, #6422, #11171 + lfPrepareForMutation # string location is about to be mutated (V2) TStorageLoc* = enum OnUnknown, # location is unknown (stack, heap or static) OnStatic, # in a static section OnStack, # location is on hardware stack - OnStackShadowDup, # location is on the stack but also replicated - # on the shadow stack OnHeap # location is on heap or global # (reference counting needed) TLocFlags* = set[TLocFlag] @@ -762,8 +652,7 @@ type storage*: TStorageLoc flags*: TLocFlags # location's flags lode*: PNode # Node where the location came from; can be faked - r*: Rope # rope value of location (code generators) - dup*: Rope # duplicated location for precise stack scans + snippet*: Rope # C code snippet of location (code generators) # ---------------- end of backend information ------------------------------ @@ -771,9 +660,10 @@ type libHeader, libDynamic TLib* = object # also misused for headers! + # keep in sync with PackedLib kind*: TLibKind generated*: bool # needed for the backends: - isOverriden*: bool + isOverridden*: bool name*: Rope path*: PNode # can be a string literal! @@ -787,43 +677,35 @@ type PInstantiation* = ref TInstantiation - TScope* = object + TScope* {.acyclic.} = object depthLevel*: int symbols*: TStrTable parent*: PScope + allowPrivateAccess*: seq[PSym] # # enable access to private fields PScope* = ref TScope PLib* = ref TLib - TSym* {.acyclic.} = object of TIdObj + TSym* {.acyclic.} = object # Keep in sync with PackedSym + itemId*: ItemId # proc and type instantiations are cached in the generic symbol case kind*: TSymKind - of skType, skGenericParam: - typeInstCache*: seq[PType] of routineKinds: - procInstCache*: seq[PInstantiation] - gcUnsafetyReason*: PSym # for better error messages wrt gcsafe - #scope*: PScope # the scope where the proc was defined - of skModule, skPackage: - # modules keep track of the generic symbols they use from other modules. - # this is because in incremental compilation, when a module is about to - # be replaced with a newer version, we must decrement the usage count - # of all previously used generics. - # For 'import as' we copy the module symbol but shallowCopy the 'tab' - # and set the 'usedGenerics' to ... XXX gah! Better set module.name - # instead? But this doesn't work either. --> We need an skModuleAlias? - # No need, just leave it as skModule but set the owner accordingly and - # check for the owner when touching 'usedGenerics'. - usedGenerics*: seq[PInstantiation] - tab*: TStrTable # interface table for modules + #procInstCache*: seq[PInstantiation] + gcUnsafetyReason*: PSym # for better error messages regarding gcsafe + transformedBody*: PNode # cached body after transf pass of skLet, skVar, skField, skForVar: guard*: PSym bitsize*: int + alignment*: int # for alignment else: nil magic*: TMagic typ*: PType name*: PIdent info*: TLineInfo + when defined(nimsuggest): + endInfo*: TLineInfo + hasUserSpecifiedType*: bool # used for determining whether to display inlay type hints owner*: PSym flags*: TSymFlags ast*: PNode # syntax tree of proc, iterator, etc.: @@ -838,41 +720,57 @@ type position*: int # used for many different things: # for enum fields its position; # for fields its offset - # for parameters its position + # for parameters its position (starting with 0) # for a conditional: # 1 iff the symbol is defined, else 0 # (or not in symbol table) # for modules, an unique index corresponding # to the module's fileIdx # for variables a slot index for the evaluator - # for routines a superop-ID - offset*: int # offset of record field + offset*: int32 # offset of record field + disamb*: int32 # disambiguation number; the basic idea is that + # `<procname>__<module>_<disamb>` is unique loc*: TLoc annex*: PLib # additional fields (seldom used, so we use a - # reference to another object to safe space) + # reference to another object to save space) + when hasFFI: + cname*: string # resolved C declaration name in importc decl, e.g.: + # proc fun() {.importc: "$1aux".} => cname = funaux constraint*: PNode # additional constraints like 'lit|result'; also - # misused for the codegenDecl pragma in the hope + # misused for the codegenDecl and virtual pragmas in the hope # it won't cause problems # for skModule the string literal to output for # deprecated modules. + instantiatedFrom*: PSym # for instances, the generic symbol where it came from. when defined(nimsuggest): allUsages*: seq[TLineInfo] TTypeSeq* = seq[PType] - TLockLevel* = distinct int16 - TType* {.acyclic.} = object of TIdObj # \ + + TTypeAttachedOp* = enum ## as usual, order is important here + attachedWasMoved, + attachedDestructor, + attachedAsgn, + attachedDup, + attachedSink, + attachedTrace, + attachedDeepCopy + + TType* {.acyclic.} = object # \ # types are identical iff they have the # same id; there may be multiple copies of a type # in memory! + # Keep in sync with PackedType + itemId*: ItemId kind*: TTypeKind # kind of type callConv*: TCallingConvention # for procs flags*: TTypeFlags # flags of the type - sons*: TTypeSeq # base types, etc. + sons: TTypeSeq # base types, etc. n*: PNode # node for types: # for range types a nkRange node # for record types a nkRecord node # for enum types a list of symbols - # for tyInt it can be the int literal + # if kind == tyInt: it is an 'int literal(x)' type # for procs and tyGenericBody, it's the # formal param list # for concepts, the concept body @@ -880,44 +778,21 @@ type owner*: PSym # the 'owner' of the type sym*: PSym # types have the sym associated with them # it is used for converting types to strings - destructor*: PSym # destructor. warning: nil here may not necessary - # mean that there is no destructor. - # see instantiateDestructor in semdestruct.nim - deepCopy*: PSym # overriden 'deepCopy' operation - assignment*: PSym # overriden '=' operation - sink*: PSym # overriden '=sink' operation - methods*: seq[(int,PSym)] # attached methods size*: BiggestInt # the size of the type in bytes # -1 means that the size is unkwown align*: int16 # the type's alignment requirements - lockLevel*: TLockLevel # lock level as required for deadlock checking + paddingAtEnd*: int16 # loc*: TLoc typeInst*: PType # for generic instantiations the tyGenericInst that led to this # type. + uniqueId*: ItemId # due to a design mistake, we need to keep the real ID here as it + # is required by the --incremental:on mode. TPair* = object key*, val*: RootRef TPairSeq* = seq[TPair] - TIdPair* = object - key*: PIdObj - val*: RootRef - - TIdPairSeq* = seq[TIdPair] - TIdTable* = object # the same as table[PIdent] of PObject - counter*: int - data*: TIdPairSeq - - TIdNodePair* = object - key*: PIdObj - val*: PNode - - TIdNodePairSeq* = seq[TIdNodePair] - TIdNodeTable* = object # the same as table[PIdObj] of PNode - counter*: int - data*: TIdNodePairSeq - TNodePair* = object h*: Hash # because it is expensive to compute! key*: PNode @@ -937,13 +812,47 @@ type TImplication* = enum impUnknown, impNo, impYes +template nodeId(n: PNode): int = cast[int](n) + +type Gconfig = object + # we put comments in a side channel to avoid increasing `sizeof(TNode)`, which + # reduces memory usage given that `PNode` is the most allocated type by far. + comments: Table[int, string] # nodeId => comment + useIc*: bool + +var gconfig {.threadvar.}: Gconfig + +proc setUseIc*(useIc: bool) = gconfig.useIc = useIc + +proc comment*(n: PNode): string = + if nfHasComment in n.flags and not gconfig.useIc: + # IC doesn't track comments, see `packed_ast`, so this could fail + result = gconfig.comments[n.nodeId] + else: + result = "" + +proc `comment=`*(n: PNode, a: string) = + let id = n.nodeId + if a.len > 0: + # if needed, we could periodically cleanup gconfig.comments when its size increases, + # to ensure only live nodes (and with nfHasComment) have an entry in gconfig.comments; + # for compiling compiler, the waste is very small: + # num calls to newNodeImpl: 14984160 (num of PNode allocations) + # size of gconfig.comments: 33585 + # num of nodes with comments that were deleted and hence wasted: 3081 + n.flags.incl nfHasComment + gconfig.comments[id] = a + elif nfHasComment in n.flags: + n.flags.excl nfHasComment + gconfig.comments.del(id) + # BUGFIX: a module is overloadable so that a proc can have the # same name as an imported module. This is necessary because of # the poor naming choices in the standard library. const OverloadableSyms* = {skProc, skFunc, skMethod, skIterator, - skConverter, skModule, skTemplate, skMacro} + skConverter, skModule, skTemplate, skMacro, skEnumField} GenericTypes*: TTypeKinds = {tyGenericInvocation, tyGenericBody, tyGenericParam} @@ -957,21 +866,22 @@ const tyBool, tyChar, tyEnum, tyArray, tyObject, tySet, tyTuple, tyRange, tyPtr, tyRef, tyVar, tyLent, tySequence, tyProc, tyPointer, - tyOpenArray, tyString, tyCString, tyInt..tyInt64, tyFloat..tyFloat128, + tyOpenArray, tyString, tyCstring, tyInt..tyInt64, tyFloat..tyFloat128, tyUInt..tyUInt64} IntegralTypes* = {tyBool, tyChar, tyEnum, tyInt..tyInt64, - tyFloat..tyFloat128, tyUInt..tyUInt64} + tyFloat..tyFloat128, tyUInt..tyUInt64} # weird name because it contains tyFloat ConstantDataTypes*: TTypeKinds = {tyArray, tySet, tyTuple, tySequence} - NilableTypes*: TTypeKinds = {tyPointer, tyCString, tyRef, tyPtr, tySequence, - tyProc, tyString, tyError} - ExportableSymKinds* = {skVar, skConst, skProc, skFunc, skMethod, skType, - skIterator, - skMacro, skTemplate, skConverter, skEnumField, skLet, skStub, skAlias} + NilableTypes*: TTypeKinds = {tyPointer, tyCstring, tyRef, tyPtr, + tyProc, tyError} # TODO + PtrLikeKinds*: TTypeKinds = {tyPointer, tyPtr} # for VM PersistentNodeFlags*: TNodeFlags = {nfBase2, nfBase8, nfBase16, nfDotSetter, nfDotField, - nfIsRef, nfPreventCg, nfLL, - nfFromTemplate} + nfIsRef, nfIsPtr, nfPreventCg, nfLL, + nfFromTemplate, nfDefaultRefsParam, + nfExecuteOnReload, nfLastRead, + nfFirstWrite, nfSkipFieldChecking, + nfDisabledOpenSym} namePos* = 0 patternPos* = 1 # empty except for term rewriting macros genericParamsPos* = 2 @@ -980,19 +890,21 @@ const miscPos* = 5 # used for undocumented and hacky stuff bodyPos* = 6 # position of body; use rodread.getBody() instead! resultPos* = 7 - dispatcherPos* = 8 # caution: if method has no 'result' it can be position 7! + dispatcherPos* = 8 + + nfAllFieldsSet* = nfBase2 - nkCallKinds* = {nkCall, nkInfix, nkPrefix, nkPostfix, - nkCommand, nkCallStrLit, nkHiddenCallConv} nkIdentKinds* = {nkIdent, nkSym, nkAccQuoted, nkOpenSymChoice, - nkClosedSymChoice} + nkClosedSymChoice, nkOpenSym} nkPragmaCallKinds* = {nkExprColonExpr, nkCall, nkCallStrLit} nkLiterals* = {nkCharLit..nkTripleStrLit} nkFloatLiterals* = {nkFloatLit..nkFloat128Lit} nkLambdaKinds* = {nkLambda, nkDo} declarativeDefs* = {nkProcDef, nkFuncDef, nkMethodDef, nkIteratorDef, nkConverterDef} + routineDefs* = declarativeDefs + {nkMacroDef, nkTemplateDef} procDefs* = nkLambdaKinds + declarativeDefs + callableDefs* = nkLambdaKinds + routineDefs nkSymChoices* = {nkClosedSymChoice, nkOpenSymChoice} nkStrKinds* = {nkStrLit..nkTripleStrLit} @@ -1001,9 +913,68 @@ const skProcKinds* = {skProc, skFunc, skTemplate, skMacro, skIterator, skMethod, skConverter} + defaultSize = -1 + defaultAlignment = -1 + defaultOffset* = -1 + +proc getPIdent*(a: PNode): PIdent {.inline.} = + ## Returns underlying `PIdent` for `{nkSym, nkIdent}`, or `nil`. + case a.kind + of nkSym: a.sym.name + of nkIdent: a.ident + of nkOpenSymChoice, nkClosedSymChoice: a.sons[0].sym.name + of nkOpenSym: getPIdent(a.sons[0]) + else: nil + +const + moduleShift = when defined(cpu32): 20 else: 24 + +template id*(a: PType | PSym): int = + let x = a + (x.itemId.module.int shl moduleShift) + x.itemId.item.int + +type + IdGenerator* = ref object # unfortunately, we really need the 'shared mutable' aspect here. + module*: int32 + symId*: int32 + typeId*: int32 + sealed*: bool + disambTable*: CountTable[PIdent] + +const + PackageModuleId* = -3'i32 + +proc idGeneratorFromModule*(m: PSym): IdGenerator = + assert m.kind == skModule + result = IdGenerator(module: m.itemId.module, symId: m.itemId.item, typeId: 0, disambTable: initCountTable[PIdent]()) + +proc idGeneratorForPackage*(nextIdWillBe: int32): IdGenerator = + result = IdGenerator(module: PackageModuleId, symId: nextIdWillBe - 1'i32, typeId: 0, disambTable: initCountTable[PIdent]()) + +proc nextSymId(x: IdGenerator): ItemId {.inline.} = + assert(not x.sealed) + inc x.symId + result = ItemId(module: x.module, item: x.symId) + +proc nextTypeId*(x: IdGenerator): ItemId {.inline.} = + assert(not x.sealed) + inc x.typeId + result = ItemId(module: x.module, item: x.typeId) + +when false: + proc nextId*(x: IdGenerator): ItemId {.inline.} = + inc x.item + result = x[] + +when false: + proc storeBack*(dest: var IdGenerator; src: IdGenerator) {.inline.} = + assert dest.ItemId.module == src.ItemId.module + if dest.ItemId.item > src.ItemId.item: + echo dest.ItemId.item, " ", src.ItemId.item, " ", src.ItemId.module + assert dest.ItemId.item <= src.ItemId.item + dest = src + var ggDebug* {.deprecated.}: bool ## convenience switch for trying out things -#var -# gMainPackageId*: int proc isCallExpr*(n: PNode): bool = result = n.kind in nkCallKinds @@ -1011,44 +982,128 @@ proc isCallExpr*(n: PNode): bool = proc discardSons*(father: PNode) proc len*(n: PNode): int {.inline.} = - if isNil(n.sons): result = 0 - else: result = len(n.sons) + result = n.sons.len proc safeLen*(n: PNode): int {.inline.} = ## works even for leaves. - if n.kind in {nkNone..nkNilLit} or isNil(n.sons): result = 0 - else: result = len(n.sons) + if n.kind in {nkNone..nkNilLit}: result = 0 + else: result = n.len proc safeArrLen*(n: PNode): int {.inline.} = ## works for array-like objects (strings passed as openArray in VM). - if n.kind in {nkStrLit..nkTripleStrLit}:result = len(n.strVal) + if n.kind in {nkStrLit..nkTripleStrLit}: result = n.strVal.len elif n.kind in {nkNone..nkFloat128Lit}: result = 0 - else: result = len(n) + else: result = n.len proc add*(father, son: PNode) = assert son != nil - if isNil(father.sons): father.sons = @[] - add(father.sons, son) + father.sons.add(son) + +proc addAllowNil*(father, son: PNode) {.inline.} = + father.sons.add(son) + +template `[]`*(n: PNode, i: int): PNode = n.sons[i] +template `[]=`*(n: PNode, i: int; x: PNode) = n.sons[i] = x + +template `[]`*(n: PNode, i: BackwardsIndex): PNode = n[n.len - i.int] +template `[]=`*(n: PNode, i: BackwardsIndex; x: PNode) = n[n.len - i.int] = x + +proc add*(father, son: PType) = + assert son != nil + father.sons.add(son) -type Indexable = PNode | PType +proc addAllowNil*(father, son: PType) {.inline.} = + father.sons.add(son) -template `[]`*(n: Indexable, i: int): Indexable = n.sons[i] -template `[]=`*(n: Indexable, i: int; x: Indexable) = n.sons[i] = x +template `[]`*(n: PType, i: int): PType = n.sons[i] +template `[]=`*(n: PType, i: int; x: PType) = n.sons[i] = x -template `[]`*(n: Indexable, i: BackwardsIndex): Indexable = n[n.len - i.int] -template `[]=`*(n: Indexable, i: BackwardsIndex; x: Indexable) = n[n.len - i.int] = x +template `[]`*(n: PType, i: BackwardsIndex): PType = n[n.len - i.int] +template `[]=`*(n: PType, i: BackwardsIndex; x: PType) = n[n.len - i.int] = x + +proc getDeclPragma*(n: PNode): PNode = + ## return the `nkPragma` node for declaration `n`, or `nil` if no pragma was found. + ## Currently only supports routineDefs + {nkTypeDef}. + case n.kind + of routineDefs: + if n[pragmasPos].kind != nkEmpty: result = n[pragmasPos] + else: result = nil + of nkTypeDef: + #[ + type F3*{.deprecated: "x3".} = int + + TypeSection + TypeDef + PragmaExpr + Postfix + Ident "*" + Ident "F3" + Pragma + ExprColonExpr + Ident "deprecated" + StrLit "x3" + Empty + Ident "int" + ]# + if n[0].kind == nkPragmaExpr: + result = n[0][1] + else: + result = nil + else: + # support as needed for `nkIdentDefs` etc. + result = nil + if result != nil: + assert result.kind == nkPragma, $(result.kind, n.kind) + +proc extractPragma*(s: PSym): PNode = + ## gets the pragma node of routine/type/var/let/const symbol `s` + if s.kind in routineKinds: # bug #24167 + if s.ast[pragmasPos] != nil and s.ast[pragmasPos].kind != nkEmpty: + result = s.ast[pragmasPos] + else: + result = nil + elif s.kind in {skType, skVar, skLet, skConst}: + if s.ast != nil and s.ast.len > 0: + if s.ast[0].kind == nkPragmaExpr and s.ast[0].len > 1: + # s.ast = nkTypedef / nkPragmaExpr / [nkSym, nkPragma] + result = s.ast[0][1] + else: + result = nil + else: + result = nil + else: + result = nil + assert result == nil or result.kind == nkPragma + +proc skipPragmaExpr*(n: PNode): PNode = + ## if pragma expr, give the node the pragmas are applied to, + ## otherwise give node itself + if n.kind == nkPragmaExpr: + result = n[0] + else: + result = n + +proc setInfoRecursive*(n: PNode, info: TLineInfo) = + ## set line info recursively + if n != nil: + for i in 0..<n.safeLen: setInfoRecursive(n[i], info) + n.info = info when defined(useNodeIds): - const nodeIdToDebug* = -1 # 299750 # 300761 #300863 # 300879 + const nodeIdToDebug* = -1 # 2322968 var gNodeId: int -proc newNode*(kind: TNodeKind): PNode = - new(result) - result.kind = kind - #result.info = UnknownLineInfo() inlined: - result.info.fileIndex = InvalidFileIdx - result.info.col = int16(-1) - result.info.line = uint16(0) +template newNodeImpl(info2) = + result = PNode(kind: kind, info: info2) + when false: + # this would add overhead, so we skip it; it results in a small amount of leaked entries + # for old PNode that gets re-allocated at the same address as a PNode that + # has `nfHasComment` set (and an entry in that table). Only `nfHasComment` + # should be used to test whether a PNode has a comment; gconfig.comments + # can contain extra entries for deleted PNode's with comments. + gconfig.comments.del(cast[int](result)) + +template setIdMaybe() = when defined(useNodeIds): result.id = gNodeId if result.id == nodeIdToDebug: @@ -1056,32 +1111,107 @@ proc newNode*(kind: TNodeKind): PNode = writeStackTrace() inc gNodeId +proc newNode*(kind: TNodeKind): PNode = + ## new node with unknown line info, no type, and no children + newNodeImpl(unknownLineInfo) + setIdMaybe() + +proc newNodeI*(kind: TNodeKind, info: TLineInfo): PNode = + ## new node with line info, no type, and no children + newNodeImpl(info) + setIdMaybe() + +proc newNodeI*(kind: TNodeKind, info: TLineInfo, children: int): PNode = + ## new node with line info, type, and children + newNodeImpl(info) + if children > 0: + newSeq(result.sons, children) + setIdMaybe() + +proc newNodeIT*(kind: TNodeKind, info: TLineInfo, typ: PType): PNode = + ## new node with line info, type, and no children + result = newNode(kind) + result.info = info + result.typ = typ + +proc newNode*(kind: TNodeKind, info: TLineInfo): PNode = + ## new node with line info, no type, and no children + newNodeImpl(info) + setIdMaybe() + +proc newAtom*(ident: PIdent, info: TLineInfo): PNode = + result = newNode(nkIdent, info) + result.ident = ident + +proc newAtom*(kind: TNodeKind, intVal: BiggestInt, info: TLineInfo): PNode = + result = newNode(kind, info) + result.intVal = intVal + +proc newAtom*(kind: TNodeKind, floatVal: BiggestFloat, info: TLineInfo): PNode = + result = newNode(kind, info) + result.floatVal = floatVal + +proc newAtom*(kind: TNodeKind; strVal: sink string; info: TLineInfo): PNode = + result = newNode(kind, info) + result.strVal = strVal + +proc newTree*(kind: TNodeKind; info: TLineInfo; children: varargs[PNode]): PNode = + result = newNodeI(kind, info) + if children.len > 0: + result.info = children[0].info + result.sons = @children + proc newTree*(kind: TNodeKind; children: varargs[PNode]): PNode = result = newNode(kind) if children.len > 0: result.info = children[0].info result.sons = @children +proc newTreeI*(kind: TNodeKind; info: TLineInfo; children: varargs[PNode]): PNode = + result = newNodeI(kind, info) + if children.len > 0: + result.info = children[0].info + result.sons = @children + +proc newTreeIT*(kind: TNodeKind; info: TLineInfo; typ: PType; children: varargs[PNode]): PNode = + result = newNodeIT(kind, info, typ) + if children.len > 0: + result.info = children[0].info + result.sons = @children + template previouslyInferred*(t: PType): PType = - if t.sons.len > 1: t.lastSon else: nil + if t.sons.len > 1: t.last else: nil -proc newSym*(symKind: TSymKind, name: PIdent, owner: PSym, +when false: + import tables, strutils + var x: CountTable[string] + + addQuitProc proc () {.noconv.} = + for k, v in pairs(x): + echo k + echo v + +proc newSym*(symKind: TSymKind, name: PIdent, idgen: IdGenerator; owner: PSym, info: TLineInfo; options: TOptions = {}): PSym = # generates a symbol and initializes the hash field too - new(result) - result.name = name - result.kind = symKind - result.flags = {} - result.info = info - result.options = options - result.owner = owner - result.offset = -1 - result.id = getID() - when debugIds: - registerId(result) - #if result.id == 93289: - # writeStacktrace() - # MessageOut(name.s & " has id: " & toString(result.id)) + assert not name.isNil + let id = nextSymId idgen + result = PSym(name: name, kind: symKind, flags: {}, info: info, itemId: id, + options: options, owner: owner, offset: defaultOffset, + disamb: getOrDefault(idgen.disambTable, name).int32) + idgen.disambTable.inc name + when false: + if id.module == 48 and id.item == 39: + writeStackTrace() + echo "kind ", symKind, " ", name.s + if owner != nil: echo owner.name.s + +proc astdef*(s: PSym): PNode = + # get only the definition (initializer) portion of the ast + if s.ast != nil and s.ast.kind in {nkIdentDefs, nkConstDef}: + s.ast[2] + else: + s.ast proc isMetaType*(t: PType): bool = return t.kind in tyMetaTypes or @@ -1125,24 +1255,16 @@ const # for all kind of hash tables: proc copyStrTable*(dest: var TStrTable, src: TStrTable) = dest.counter = src.counter - if isNil(src.data): return - setLen(dest.data, len(src.data)) - for i in countup(0, high(src.data)): dest.data[i] = src.data[i] - -proc copyIdTable*(dest: var TIdTable, src: TIdTable) = - dest.counter = src.counter - if isNil(src.data): return - newSeq(dest.data, len(src.data)) - for i in countup(0, high(src.data)): dest.data[i] = src.data[i] + setLen(dest.data, src.data.len) + for i in 0..high(src.data): dest.data[i] = src.data[i] proc copyObjectSet*(dest: var TObjectSet, src: TObjectSet) = dest.counter = src.counter - if isNil(src.data): return - setLen(dest.data, len(src.data)) - for i in countup(0, high(src.data)): dest.data[i] = src.data[i] + setLen(dest.data, src.data.len) + for i in 0..high(src.data): dest.data[i] = src.data[i] proc discardSons*(father: PNode) = - father.sons = nil + father.sons = @[] proc withInfo*(n: PNode, info: TLineInfo): PNode = n.info = info @@ -1165,58 +1287,89 @@ proc newSymNode*(sym: PSym, info: TLineInfo): PNode = result.typ = sym.typ result.info = info -proc newNodeI*(kind: TNodeKind, info: TLineInfo): PNode = - new(result) - result.kind = kind - result.info = info - when defined(useNodeIds): - result.id = gNodeId - if result.id == nodeIdToDebug: - echo "KIND ", result.kind - writeStackTrace() - inc gNodeId - -proc newNodeI*(kind: TNodeKind, info: TLineInfo, children: int): PNode = - new(result) - result.kind = kind - result.info = info - if children > 0: - newSeq(result.sons, children) - when defined(useNodeIds): - result.id = gNodeId - if result.id == nodeIdToDebug: - echo "KIND ", result.kind - writeStackTrace() - inc gNodeId - -proc newNode*(kind: TNodeKind, info: TLineInfo, sons: TNodeSeq = @[], - typ: PType = nil): PNode = - new(result) - result.kind = kind - result.info = info - result.typ = typ - # XXX use shallowCopy here for ownership transfer: - result.sons = sons - when defined(useNodeIds): - result.id = gNodeId - if result.id == nodeIdToDebug: - echo "KIND ", result.kind - writeStackTrace() - inc gNodeId - -proc newNodeIT*(kind: TNodeKind, info: TLineInfo, typ: PType): PNode = - result = newNode(kind) - result.info = info - result.typ = typ +proc newOpenSym*(n: PNode): PNode {.inline.} = + result = newTreeI(nkOpenSym, n.info, n) proc newIntNode*(kind: TNodeKind, intVal: BiggestInt): PNode = result = newNode(kind) result.intVal = intVal -proc newIntTypeNode*(kind: TNodeKind, intVal: BiggestInt, typ: PType): PNode = - result = newIntNode(kind, intVal) +proc newIntNode*(kind: TNodeKind, intVal: Int128): PNode = + result = newNode(kind) + result.intVal = castToInt64(intVal) + +proc lastSon*(n: PNode): PNode {.inline.} = n.sons[^1] +template setLastSon*(n: PNode, s: PNode) = n.sons[^1] = s + +template firstSon*(n: PNode): PNode = n.sons[0] +template secondSon*(n: PNode): PNode = n.sons[1] + +template hasSon*(n: PNode): bool = n.len > 0 +template has2Sons*(n: PNode): bool = n.len > 1 + +proc replaceFirstSon*(n, newson: PNode) {.inline.} = + n.sons[0] = newson + +proc replaceSon*(n: PNode; i: int; newson: PNode) {.inline.} = + n.sons[i] = newson + +proc last*(n: PType): PType {.inline.} = n.sons[^1] + +proc elementType*(n: PType): PType {.inline.} = n.sons[^1] +proc skipModifier*(n: PType): PType {.inline.} = n.sons[^1] + +proc indexType*(n: PType): PType {.inline.} = n.sons[0] +proc baseClass*(n: PType): PType {.inline.} = n.sons[0] + +proc base*(t: PType): PType {.inline.} = + result = t.sons[0] + +proc returnType*(n: PType): PType {.inline.} = n.sons[0] +proc setReturnType*(n, r: PType) {.inline.} = n.sons[0] = r +proc setIndexType*(n, idx: PType) {.inline.} = n.sons[0] = idx + +proc firstParamType*(n: PType): PType {.inline.} = n.sons[1] +proc firstGenericParam*(n: PType): PType {.inline.} = n.sons[1] + +proc typeBodyImpl*(n: PType): PType {.inline.} = n.sons[^1] + +proc genericHead*(n: PType): PType {.inline.} = n.sons[0] + +proc skipTypes*(t: PType, kinds: TTypeKinds): PType = + ## Used throughout the compiler code to test whether a type tree contains or + ## doesn't contain a specific type/types - it is often the case that only the + ## last child nodes of a type tree need to be searched. This is a really hot + ## path within the compiler! + result = t + while result.kind in kinds: result = last(result) + +proc newIntTypeNode*(intVal: BiggestInt, typ: PType): PNode = + let kind = skipTypes(typ, abstractVarRange).kind + case kind + of tyInt: result = newNode(nkIntLit) + of tyInt8: result = newNode(nkInt8Lit) + of tyInt16: result = newNode(nkInt16Lit) + of tyInt32: result = newNode(nkInt32Lit) + of tyInt64: result = newNode(nkInt64Lit) + of tyChar: result = newNode(nkCharLit) + of tyUInt: result = newNode(nkUIntLit) + of tyUInt8: result = newNode(nkUInt8Lit) + of tyUInt16: result = newNode(nkUInt16Lit) + of tyUInt32: result = newNode(nkUInt32Lit) + of tyUInt64: result = newNode(nkUInt64Lit) + of tyBool, tyEnum: + # XXX: does this really need to be the kind nkIntLit? + result = newNode(nkIntLit) + of tyStatic: # that's a pre-existing bug, will fix in another PR + result = newNode(nkIntLit) + else: raiseAssert $kind + result.intVal = intVal result.typ = typ +proc newIntTypeNode*(intVal: Int128, typ: PType): PNode = + # XXX: introduce range check + newIntTypeNode(castToInt64(intVal), typ) + proc newFloatNode*(kind: TNodeKind, floatVal: BiggestFloat): PNode = result = newNode(kind) result.floatVal = floatVal @@ -1229,11 +1382,6 @@ proc newStrNode*(strVal: string; info: TLineInfo): PNode = result = newNodeI(nkStrLit, info) result.strVal = strVal -proc addSon*(father, son: PNode) = - assert son != nil - if isNil(father.sons): father.sons = @[] - add(father.sons, son) - proc newProcNode*(kind: TNodeKind, info: TLineInfo, body: PNode, params, name, pattern, genericParams, @@ -1243,54 +1391,148 @@ proc newProcNode*(kind: TNodeKind, info: TLineInfo, body: PNode, pragmas, exceptions, body] const - UnspecifiedLockLevel* = TLockLevel(-1'i16) - MaxLockLevel* = 1000'i16 - UnknownLockLevel* = TLockLevel(1001'i16) - -proc `$`*(x: TLockLevel): string = - if x.ord == UnspecifiedLockLevel.ord: result = "<unspecified>" - elif x.ord == UnknownLockLevel.ord: result = "<unknown>" - else: result = $int16(x) - -proc newType*(kind: TTypeKind, owner: PSym): PType = - new(result) - result.kind = kind - result.owner = owner - result.size = - 1 - result.align = 2 # default alignment - result.id = getID() - result.lockLevel = UnspecifiedLockLevel - when debugIds: - registerId(result) + AttachedOpToStr*: array[TTypeAttachedOp, string] = [ + "=wasMoved", "=destroy", "=copy", "=dup", "=sink", "=trace", "=deepcopy"] + +proc `$`*(s: PSym): string = + if s != nil: + result = s.name.s & "@" & $s.id + else: + result = "<nil>" + +when false: + iterator items*(t: PType): PType = + for i in 0..<t.sons.len: yield t.sons[i] + + iterator pairs*(n: PType): tuple[i: int, n: PType] = + for i in 0..<n.sons.len: yield (i, n.sons[i]) + +when true: + proc len*(n: PType): int {.inline.} = + result = n.sons.len + +proc sameTupleLengths*(a, b: PType): bool {.inline.} = + result = a.sons.len == b.sons.len + +iterator tupleTypePairs*(a, b: PType): (int, PType, PType) = + for i in 0 ..< a.sons.len: + yield (i, a.sons[i], b.sons[i]) + +iterator underspecifiedPairs*(a, b: PType; start = 0; without = 0): (PType, PType) = + # XXX Figure out with what typekinds this is called. + for i in start ..< min(a.sons.len, b.sons.len) + without: + yield (a.sons[i], b.sons[i]) + +proc signatureLen*(t: PType): int {.inline.} = + result = t.sons.len + +proc paramsLen*(t: PType): int {.inline.} = + result = t.sons.len - 1 + +proc genericParamsLen*(t: PType): int {.inline.} = + assert t.kind == tyGenericInst + result = t.sons.len - 2 # without 'head' and 'body' + +proc genericInvocationParamsLen*(t: PType): int {.inline.} = + assert t.kind == tyGenericInvocation + result = t.sons.len - 1 # without 'head' + +proc kidsLen*(t: PType): int {.inline.} = + result = t.sons.len + +proc genericParamHasConstraints*(t: PType): bool {.inline.} = t.sons.len > 0 + +proc hasElementType*(t: PType): bool {.inline.} = t.sons.len > 0 +proc isEmptyTupleType*(t: PType): bool {.inline.} = t.sons.len == 0 +proc isSingletonTupleType*(t: PType): bool {.inline.} = t.sons.len == 1 + +proc genericConstraint*(t: PType): PType {.inline.} = t.sons[0] + +iterator genericInstParams*(t: PType): (bool, PType) = + for i in 1..<t.sons.len-1: + yield (i!=1, t.sons[i]) + +iterator genericInstParamPairs*(a, b: PType): (int, PType, PType) = + for i in 1..<min(a.sons.len, b.sons.len)-1: + yield (i-1, a.sons[i], b.sons[i]) + +iterator genericInvocationParams*(t: PType): (bool, PType) = + for i in 1..<t.sons.len: + yield (i!=1, t.sons[i]) + +iterator genericInvocationAndBodyElements*(a, b: PType): (PType, PType) = + for i in 1..<a.sons.len: + yield (a.sons[i], b.sons[i-1]) + +iterator genericInvocationParamPairs*(a, b: PType): (bool, PType, PType) = + for i in 1..<a.sons.len: + if i >= b.sons.len: + yield (false, nil, nil) + else: + yield (true, a.sons[i], b.sons[i]) + +iterator genericBodyParams*(t: PType): (int, PType) = + for i in 0..<t.sons.len-1: + yield (i, t.sons[i]) + +iterator userTypeClassInstParams*(t: PType): (bool, PType) = + for i in 1..<t.sons.len-1: + yield (i!=1, t.sons[i]) + +iterator ikids*(t: PType): (int, PType) = + for i in 0..<t.sons.len: yield (i, t.sons[i]) + +const + FirstParamAt* = 1 + FirstGenericParamAt* = 1 + +iterator paramTypes*(t: PType): (int, PType) = + for i in FirstParamAt..<t.sons.len: yield (i, t.sons[i]) + +iterator paramTypePairs*(a, b: PType): (PType, PType) = + for i in FirstParamAt..<a.sons.len: yield (a.sons[i], b.sons[i]) + +template paramTypeToNodeIndex*(x: int): int = x + +iterator kids*(t: PType): PType = + for i in 0..<t.sons.len: yield t.sons[i] + +iterator signature*(t: PType): PType = + # yields return type + parameter types + for i in 0..<t.sons.len: yield t.sons[i] + +proc newType*(kind: TTypeKind; idgen: IdGenerator; owner: PSym; son: sink PType = nil): PType = + let id = nextTypeId idgen + result = PType(kind: kind, owner: owner, size: defaultSize, + align: defaultAlignment, itemId: id, + uniqueId: id, sons: @[]) + if son != nil: result.sons.add son when false: - if result.id == 205734: + if result.itemId.module == 55 and result.itemId.item == 2: echo "KNID ", kind writeStackTrace() +proc setSons*(dest: PType; sons: sink seq[PType]) {.inline.} = dest.sons = sons +proc setSon*(dest: PType; son: sink PType) {.inline.} = dest.sons = @[son] +proc setSonsLen*(dest: PType; len: int) {.inline.} = setLen(dest.sons, len) + proc mergeLoc(a: var TLoc, b: TLoc) = - if a.k == low(a.k): a.k = b.k - if a.storage == low(a.storage): a.storage = b.storage - a.flags = a.flags + b.flags + if a.k == low(typeof(a.k)): a.k = b.k + if a.storage == low(typeof(a.storage)): a.storage = b.storage + a.flags.incl b.flags if a.lode == nil: a.lode = b.lode - if a.r == nil: a.r = b.r + if a.snippet == "": a.snippet = b.snippet proc newSons*(father: PNode, length: int) = - if isNil(father.sons): - newSeq(father.sons, length) - else: - setLen(father.sons, length) + setLen(father.sons, length) proc newSons*(father: PType, length: int) = - if isNil(father.sons): - newSeq(father.sons, length) - else: - setLen(father.sons, length) + setLen(father.sons, length) -proc sonsLen*(n: PType): int = n.sons.len -proc len*(n: PType): int = n.sons.len -proc sonsLen*(n: PNode): int = n.sons.len -proc lastSon*(n: PNode): PNode = n.sons[^1] -proc lastSon*(n: PType): PType = n.sons[^1] +proc truncateInferredTypeCandidates*(t: PType) {.inline.} = + assert t.kind == tyInferred + if t.sons.len > 1: + setLen(t.sons, 1) proc assignType*(dest, src: PType) = dest.kind = src.kind @@ -1299,113 +1541,74 @@ proc assignType*(dest, src: PType) = dest.n = src.n dest.size = src.size dest.align = src.align - dest.destructor = src.destructor - dest.deepCopy = src.deepCopy - dest.sink = src.sink - dest.assignment = src.assignment - dest.lockLevel = src.lockLevel # this fixes 'type TLock = TSysLock': if src.sym != nil: if dest.sym != nil: - dest.sym.flags = dest.sym.flags + (src.sym.flags-{sfExported}) + dest.sym.flags.incl src.sym.flags-{sfUsed, sfExported} if dest.sym.annex == nil: dest.sym.annex = src.sym.annex mergeLoc(dest.sym.loc, src.sym.loc) else: dest.sym = src.sym - newSons(dest, sonsLen(src)) - for i in countup(0, sonsLen(src) - 1): dest.sons[i] = src.sons[i] + newSons(dest, src.sons.len) + for i in 0..<src.sons.len: dest[i] = src[i] -proc copyType*(t: PType, owner: PSym, keepId: bool): PType = - result = newType(t.kind, owner) +proc copyType*(t: PType, idgen: IdGenerator, owner: PSym): PType = + result = newType(t.kind, idgen, owner) assignType(result, t) - if keepId: - result.id = t.id - else: - when debugIds: registerId(result) result.sym = t.sym # backend-info should not be copied -proc exactReplica*(t: PType): PType = copyType(t, t.owner, true) +proc exactReplica*(t: PType): PType = + result = PType(kind: t.kind, owner: t.owner, size: defaultSize, + align: defaultAlignment, itemId: t.itemId, + uniqueId: t.uniqueId) + assignType(result, t) + result.sym = t.sym # backend-info should not be copied -proc copySym*(s: PSym, keepId: bool = false): PSym = - result = newSym(s.kind, s.name, s.owner, s.info, s.options) +proc copySym*(s: PSym; idgen: IdGenerator): PSym = + result = newSym(s.kind, s.name, idgen, s.owner, s.info, s.options) #result.ast = nil # BUGFIX; was: s.ast which made problems result.typ = s.typ - if keepId: - result.id = s.id - else: - result.id = getID() - when debugIds: registerId(result) result.flags = s.flags result.magic = s.magic - if s.kind == skModule: - copyStrTable(result.tab, s.tab) result.options = s.options result.position = s.position result.loc = s.loc result.annex = s.annex # BUGFIX + result.constraint = s.constraint if result.kind in {skVar, skLet, skField}: result.guard = s.guard + result.bitsize = s.bitsize + result.alignment = s.alignment -proc createModuleAlias*(s: PSym, newIdent: PIdent, info: TLineInfo; +proc createModuleAlias*(s: PSym, idgen: IdGenerator, newIdent: PIdent, info: TLineInfo; options: TOptions): PSym = - result = newSym(s.kind, newIdent, s.owner, info, options) + result = newSym(s.kind, newIdent, idgen, s.owner, info, options) # keep ID! result.ast = s.ast - result.id = s.id + #result.id = s.id # XXX figure out what to do with the ID. result.flags = s.flags - system.shallowCopy(result.tab, s.tab) result.options = s.options result.position = s.position result.loc = s.loc result.annex = s.annex - # XXX once usedGenerics is used, ensure module aliases keep working! - assert s.usedGenerics == nil - -proc initStrTable*(x: var TStrTable) = - x.counter = 0 - newSeq(x.data, StartSize) - -proc newStrTable*: TStrTable = - initStrTable(result) - -proc initIdTable*(x: var TIdTable) = - x.counter = 0 - newSeq(x.data, StartSize) - -proc newIdTable*: TIdTable = - initIdTable(result) -proc resetIdTable*(x: var TIdTable) = - x.counter = 0 - # clear and set to old initial size: - setLen(x.data, 0) - setLen(x.data, StartSize) +proc initStrTable*(): TStrTable = + result = TStrTable(counter: 0) + newSeq(result.data, StartSize) -proc initObjectSet*(x: var TObjectSet) = - x.counter = 0 - newSeq(x.data, StartSize) +proc initObjectSet*(): TObjectSet = + result = TObjectSet(counter: 0) + newSeq(result.data, StartSize) -proc initIdNodeTable*(x: var TIdNodeTable) = - x.counter = 0 - newSeq(x.data, StartSize) - -proc initNodeTable*(x: var TNodeTable) = - x.counter = 0 - newSeq(x.data, StartSize) - -proc skipTypes*(t: PType, kinds: TTypeKinds): PType = - ## Used throughout the compiler code to test whether a type tree contains or - ## doesn't contain a specific type/types - it is often the case that only the - ## last child nodes of a type tree need to be searched. This is a really hot - ## path within the compiler! - result = t - while result.kind in kinds: result = lastSon(result) +proc initNodeTable*(): TNodeTable = + result = TNodeTable(counter: 0) + newSeq(result.data, StartSize) proc skipTypes*(t: PType, kinds: TTypeKinds; maxIters: int): PType = result = t var i = maxIters while result.kind in kinds: - result = lastSon(result) + result = last(result) dec i if i == 0: return nil @@ -1413,35 +1616,29 @@ proc skipTypesOrNil*(t: PType, kinds: TTypeKinds): PType = ## same as skipTypes but handles 'nil' result = t while result != nil and result.kind in kinds: - if result.len == 0: return nil - result = lastSon(result) + if result.sons.len == 0: return nil + result = last(result) proc isGCedMem*(t: PType): bool {.inline.} = result = t.kind in {tyString, tyRef, tySequence} or t.kind == tyProc and t.callConv == ccClosure -proc propagateToOwner*(owner, elem: PType) = - const HaveTheirOwnEmpty = {tySequence, tyOpt, tySet, tyPtr, tyRef, tyProc} - owner.flags = owner.flags + (elem.flags * {tfHasMeta, tfTriggersCompileTime}) +proc propagateToOwner*(owner, elem: PType; propagateHasAsgn = true) = + owner.flags.incl elem.flags * {tfHasMeta, tfTriggersCompileTime} if tfNotNil in elem.flags: if owner.kind in {tyGenericInst, tyGenericBody, tyGenericInvocation}: owner.flags.incl tfNotNil - elif owner.kind notin HaveTheirOwnEmpty: - owner.flags.incl tfNeedsInit - - if tfNeedsInit in elem.flags: - if owner.kind in HaveTheirOwnEmpty: discard - else: owner.flags.incl tfNeedsInit if elem.isMetaType: owner.flags.incl tfHasMeta - if tfHasAsgn in elem.flags: + let mask = elem.flags * {tfHasAsgn, tfHasOwned} + if mask != {} and propagateHasAsgn: let o2 = owner.skipTypes({tyGenericInst, tyAlias, tySink}) if o2.kind in {tyTuple, tyObject, tyArray, - tySequence, tyOpt, tySet, tyDistinct}: - o2.flags.incl tfHasAsgn - owner.flags.incl tfHasAsgn + tySequence, tySet, tyDistinct}: + o2.flags.incl mask + owner.flags.incl mask if owner.kind notin {tyProc, tyGenericInst, tyGenericBody, tyGenericInvocation, tyPtr}: @@ -1451,24 +1648,17 @@ proc propagateToOwner*(owner, elem: PType) = # ensure this doesn't bite us in sempass2. owner.flags.incl tfHasGCedMem -proc rawAddSon*(father, son: PType) = - if isNil(father.sons): father.sons = @[] - add(father.sons, son) - if not son.isNil: propagateToOwner(father, son) - -proc rawAddSonNoPropagationOfTypeFlags*(father, son: PType) = - if isNil(father.sons): father.sons = @[] - add(father.sons, son) +proc rawAddSon*(father, son: PType; propagateHasAsgn = true) = + father.sons.add(son) + if not son.isNil: propagateToOwner(father, son, propagateHasAsgn) proc addSonNilAllowed*(father, son: PNode) = - if isNil(father.sons): father.sons = @[] - add(father.sons, son) + father.sons.add(son) proc delSon*(father: PNode, idx: int) = - if isNil(father.sons): return - var length = sonsLen(father) - for i in countup(idx, length - 2): father.sons[i] = father.sons[i + 1] - setLen(father.sons, length - 1) + if father.len == 0: return + for i in idx..<father.len - 1: father[i] = father[i + 1] + father.sons.setLen(father.len - 1) proc copyNode*(src: PNode): PNode = # does not copy its sons! @@ -1489,93 +1679,155 @@ proc copyNode*(src: PNode): PNode = of nkIdent: result.ident = src.ident of nkStrLit..nkTripleStrLit: result.strVal = src.strVal else: discard + when defined(nimsuggest): + result.endInfo = src.endInfo -proc shallowCopy*(src: PNode): PNode = - # does not copy its sons, but provides space for them: - if src == nil: return nil - result = newNode(src.kind) - result.info = src.info - result.typ = src.typ - result.flags = src.flags * PersistentNodeFlags - result.comment = src.comment +template transitionNodeKindCommon(k: TNodeKind) = + let obj {.inject.} = n[] + n[] = TNode(kind: k, typ: obj.typ, info: obj.info, flags: obj.flags) + # n.comment = obj.comment # shouldn't be needed, the address doesnt' change when defined(useNodeIds): - if result.id == nodeIdToDebug: + n.id = obj.id + +proc transitionSonsKind*(n: PNode, kind: range[nkComesFrom..nkTupleConstr]) = + transitionNodeKindCommon(kind) + n.sons = obj.sons + +proc transitionIntKind*(n: PNode, kind: range[nkCharLit..nkUInt64Lit]) = + transitionNodeKindCommon(kind) + n.intVal = obj.intVal + +proc transitionIntToFloatKind*(n: PNode, kind: range[nkFloatLit..nkFloat128Lit]) = + transitionNodeKindCommon(kind) + n.floatVal = BiggestFloat(obj.intVal) + +proc transitionNoneToSym*(n: PNode) = + transitionNodeKindCommon(nkSym) + +template transitionSymKindCommon*(k: TSymKind) = + let obj {.inject.} = s[] + s[] = TSym(kind: k, itemId: obj.itemId, magic: obj.magic, typ: obj.typ, name: obj.name, + info: obj.info, owner: obj.owner, flags: obj.flags, ast: obj.ast, + options: obj.options, position: obj.position, offset: obj.offset, + loc: obj.loc, annex: obj.annex, constraint: obj.constraint) + when hasFFI: + s.cname = obj.cname + when defined(nimsuggest): + s.allUsages = obj.allUsages + +proc transitionGenericParamToType*(s: PSym) = + transitionSymKindCommon(skType) + +proc transitionRoutineSymKind*(s: PSym, kind: range[skProc..skTemplate]) = + transitionSymKindCommon(kind) + s.gcUnsafetyReason = obj.gcUnsafetyReason + s.transformedBody = obj.transformedBody + +proc transitionToLet*(s: PSym) = + transitionSymKindCommon(skLet) + s.guard = obj.guard + s.bitsize = obj.bitsize + s.alignment = obj.alignment + +template copyNodeImpl(dst, src, processSonsStmt) = + if src == nil: return + dst = newNode(src.kind) + dst.info = src.info + when defined(nimsuggest): + result.endInfo = src.endInfo + dst.typ = src.typ + dst.flags = src.flags * PersistentNodeFlags + dst.comment = src.comment + when defined(useNodeIds): + if dst.id == nodeIdToDebug: echo "COMES FROM ", src.id case src.kind - of nkCharLit..nkUInt64Lit: result.intVal = src.intVal - of nkFloatLiterals: result.floatVal = src.floatVal - of nkSym: result.sym = src.sym - of nkIdent: result.ident = src.ident - of nkStrLit..nkTripleStrLit: result.strVal = src.strVal - else: newSeq(result.sons, sonsLen(src)) + of nkCharLit..nkUInt64Lit: dst.intVal = src.intVal + of nkFloatLiterals: dst.floatVal = src.floatVal + of nkSym: dst.sym = src.sym + of nkIdent: dst.ident = src.ident + of nkStrLit..nkTripleStrLit: dst.strVal = src.strVal + else: processSonsStmt + +proc shallowCopy*(src: PNode): PNode = + # does not copy its sons, but provides space for them: + copyNodeImpl(result, src): + newSeq(result.sons, src.len) proc copyTree*(src: PNode): PNode = # copy a whole syntax tree; performs deep copying - if src == nil: - return nil - result = newNode(src.kind) - result.info = src.info - result.typ = src.typ - result.flags = src.flags * PersistentNodeFlags - result.comment = src.comment - when defined(useNodeIds): - if result.id == nodeIdToDebug: - echo "COMES FROM ", src.id - case src.kind - of nkCharLit..nkUInt64Lit: result.intVal = src.intVal - of nkFloatLiterals: result.floatVal = src.floatVal - of nkSym: result.sym = src.sym - of nkIdent: result.ident = src.ident - of nkStrLit..nkTripleStrLit: result.strVal = src.strVal - else: - newSeq(result.sons, sonsLen(src)) - for i in countup(0, sonsLen(src) - 1): - result.sons[i] = copyTree(src.sons[i]) + copyNodeImpl(result, src): + newSeq(result.sons, src.len) + for i in 0..<src.len: + result[i] = copyTree(src[i]) + +proc copyTreeWithoutNode*(src, skippedNode: PNode): PNode = + copyNodeImpl(result, src): + result.sons = newSeqOfCap[PNode](src.len) + for n in src.sons: + if n != skippedNode: + result.sons.add copyTreeWithoutNode(n, skippedNode) proc hasSonWith*(n: PNode, kind: TNodeKind): bool = - for i in countup(0, sonsLen(n) - 1): - if n.sons[i].kind == kind: + for i in 0..<n.len: + if n[i].kind == kind: return true result = false proc hasNilSon*(n: PNode): bool = - for i in countup(0, safeLen(n) - 1): - if n.sons[i] == nil: + for i in 0..<n.safeLen: + if n[i] == nil: return true - elif hasNilSon(n.sons[i]): + elif hasNilSon(n[i]): return true result = false proc containsNode*(n: PNode, kinds: TNodeKinds): bool = + result = false if n == nil: return case n.kind of nkEmpty..nkNilLit: result = n.kind in kinds else: - for i in countup(0, sonsLen(n) - 1): - if n.kind in kinds or containsNode(n.sons[i], kinds): return true + for i in 0..<n.len: + if n.kind in kinds or containsNode(n[i], kinds): return true proc hasSubnodeWith*(n: PNode, kind: TNodeKind): bool = case n.kind - of nkEmpty..nkNilLit: result = n.kind == kind + of nkEmpty..nkNilLit, nkFormalParams: result = n.kind == kind else: - for i in countup(0, sonsLen(n) - 1): - if (n.sons[i].kind == kind) or hasSubnodeWith(n.sons[i], kind): + for i in 0..<n.len: + if (n[i].kind == kind) or hasSubnodeWith(n[i], kind): return true result = false -proc getInt*(a: PNode): BiggestInt = +proc getInt*(a: PNode): Int128 = + case a.kind + of nkCharLit, nkUIntLit..nkUInt64Lit: + result = toInt128(cast[uint64](a.intVal)) + of nkInt8Lit..nkInt64Lit: + result = toInt128(a.intVal) + of nkIntLit: + # XXX: enable this assert + # assert a.typ.kind notin {tyChar, tyUint..tyUInt64} + result = toInt128(a.intVal) + else: + raiseRecoverableError("cannot extract number from invalid AST node") + +proc getInt64*(a: PNode): int64 {.deprecated: "use getInt".} = case a.kind - of nkCharLit..nkUInt64Lit: result = a.intVal + of nkCharLit, nkUIntLit..nkUInt64Lit, nkIntLit..nkInt64Lit: + result = a.intVal else: - #internalError(a.info, "getInt") - doAssert false, "getInt" - #result = 0 + raiseRecoverableError("cannot extract number from invalid AST node") proc getFloat*(a: PNode): BiggestFloat = case a.kind of nkFloatLiterals: result = a.floatVal + of nkCharLit, nkUIntLit..nkUInt64Lit, nkIntLit..nkInt64Lit: + result = BiggestFloat a.intVal else: - doAssert false, "getFloat" + raiseRecoverableError("cannot extract number from invalid AST node") + #doAssert false, "getFloat" #internalError(a.info, "getFloat") #result = 0.0 @@ -1584,9 +1836,10 @@ proc getStr*(a: PNode): string = of nkStrLit..nkTripleStrLit: result = a.strVal of nkNilLit: # let's hope this fixes more problems than it creates: - result = nil + result = "" else: - doAssert false, "getStr" + raiseRecoverableError("cannot extract string from invalid AST node") + #doAssert false, "getStr" #internalError(a.info, "getStr") #result = "" @@ -1595,28 +1848,51 @@ proc getStrOrChar*(a: PNode): string = of nkStrLit..nkTripleStrLit: result = a.strVal of nkCharLit..nkUInt64Lit: result = $chr(int(a.intVal)) else: - doAssert false, "getStrOrChar" + raiseRecoverableError("cannot extract string from invalid AST node") + #doAssert false, "getStrOrChar" #internalError(a.info, "getStrOrChar") #result = "" -proc isGenericRoutine*(s: PSym): bool = - case s.kind - of skProcKinds: - result = sfFromGeneric in s.flags or - (s.ast != nil and s.ast[genericParamsPos].kind != nkEmpty) - else: discard +proc isGenericParams*(n: PNode): bool {.inline.} = + ## used to judge whether a node is generic params. + n != nil and n.kind == nkGenericParams + +proc isGenericRoutine*(n: PNode): bool {.inline.} = + n != nil and n.kind in callableDefs and n[genericParamsPos].isGenericParams + +proc isGenericRoutineStrict*(s: PSym): bool {.inline.} = + ## determines if this symbol represents a generic routine + ## the unusual name is so it doesn't collide and eventually replaces + ## `isGenericRoutine` + s.kind in skProcKinds and s.ast.isGenericRoutine + +proc isGenericRoutine*(s: PSym): bool {.inline.} = + ## determines if this symbol represents a generic routine or an instance of + ## one. This should be renamed accordingly and `isGenericRoutineStrict` + ## should take this name instead. + ## + ## Warning/XXX: Unfortunately, it considers a proc kind symbol flagged with + ## sfFromGeneric as a generic routine. Instead this should likely not be the + ## case and the concepts should be teased apart: + ## - generic definition + ## - generic instance + ## - either generic definition or instance + s.kind in skProcKinds and (sfFromGeneric in s.flags or + s.ast.isGenericRoutine) proc skipGenericOwner*(s: PSym): PSym = ## Generic instantiations are owned by their originating generic ## symbol. This proc skips such owners and goes straight to the owner ## of the generic itself (the module or the enclosing proc). - result = if s.kind in skProcKinds and sfFromGeneric in s.flags: + result = if s.kind == skModule: + s + elif s.kind in skProcKinds and sfFromGeneric in s.flags and s.owner.kind != skModule: s.owner.owner else: s.owner proc originatingModule*(s: PSym): PSym = - result = s.owner + result = s while result.kind != skModule: result = result.owner proc isRoutine*(s: PSym): bool {.inline.} = @@ -1624,32 +1900,23 @@ proc isRoutine*(s: PSym): bool {.inline.} = proc isCompileTimeProc*(s: PSym): bool {.inline.} = result = s.kind == skMacro or - s.kind == skProc and sfCompileTime in s.flags - -proc requiredParams*(s: PSym): int = - # Returns the number of required params (without default values) - # XXX: Perhaps we can store this in the `offset` field of the - # symbol instead? - for i in 1 ..< s.typ.len: - if s.typ.n[i].sym.ast != nil: - return i - 1 - return s.typ.len - 1 + s.kind in {skProc, skFunc} and sfCompileTime in s.flags proc hasPattern*(s: PSym): bool {.inline.} = - result = isRoutine(s) and s.ast.sons[patternPos].kind != nkEmpty + result = isRoutine(s) and s.ast[patternPos].kind != nkEmpty iterator items*(n: PNode): PNode = - for i in 0..<n.safeLen: yield n.sons[i] + for i in 0..<n.safeLen: yield n[i] iterator pairs*(n: PNode): tuple[i: int, n: PNode] = - for i in 0..<n.safeLen: yield (i, n.sons[i]) + for i in 0..<n.safeLen: yield (i, n[i]) proc isAtom*(n: PNode): bool {.inline.} = result = n.kind >= nkNone and n.kind <= nkNilLit proc isEmptyType*(t: PType): bool {.inline.} = - ## 'void' and 'stmt' types are often equivalent to 'nil' these days: - result = t == nil or t.kind in {tyVoid, tyStmt} + ## 'void' and 'typed' types are often equivalent to 'nil' these days: + result = t == nil or t.kind in {tyVoid, tyTyped} proc makeStmtList*(n: PNode): PNode = if n.kind == nkStmtList: @@ -1660,59 +1927,78 @@ proc makeStmtList*(n: PNode): PNode = proc skipStmtList*(n: PNode): PNode = if n.kind in {nkStmtList, nkStmtListExpr}: - for i in 0 .. n.len-2: + for i in 0..<n.len-1: if n[i].kind notin {nkEmpty, nkCommentStmt}: return n result = n.lastSon else: result = n -proc toRef*(typ: PType): PType = +proc toVar*(typ: PType; kind: TTypeKind; idgen: IdGenerator): PType = + ## If ``typ`` is not a tyVar then it is converted into a `var <typ>` and + ## returned. Otherwise ``typ`` is simply returned as-is. + result = typ + if typ.kind != kind: + result = newType(kind, idgen, typ.owner, typ) + +proc toRef*(typ: PType; idgen: IdGenerator): PType = ## If ``typ`` is a tyObject then it is converted into a `ref <typ>` and ## returned. Otherwise ``typ`` is simply returned as-is. result = typ - if typ.kind == tyObject: - result = newType(tyRef, typ.owner) - rawAddSon(result, typ) + if typ.skipTypes({tyAlias, tyGenericInst}).kind == tyObject: + result = newType(tyRef, idgen, typ.owner, typ) proc toObject*(typ: PType): PType = ## If ``typ`` is a tyRef then its immediate son is returned (which in many ## cases should be a ``tyObject``). ## Otherwise ``typ`` is simply returned as-is. + let t = typ.skipTypes({tyAlias, tyGenericInst}) + if t.kind == tyRef: t.elementType + else: typ + +proc toObjectFromRefPtrGeneric*(typ: PType): PType = + #[ + See also `toObject`. + Finds the underlying `object`, even in cases like these: + type + B[T] = object f0: int + A1[T] = ref B[T] + A2[T] = ref object f1: int + A3 = ref object f2: int + A4 = object f3: int + ]# result = typ - if result.kind == tyRef: - result = result.lastSon - -proc isException*(t: PType): bool = - # check if `y` is object type and it inherits from Exception - assert(t != nil) - - if t.kind != tyObject: - return false - - var base = t - while base != nil: - if base.sym != nil and base.sym.magic == mException: - return true - base = base.lastSon - return false + while true: + case result.kind + of tyGenericBody: result = result.last + of tyRef, tyPtr, tyGenericInst, tyGenericInvocation, tyAlias: result = result[0] + # automatic dereferencing is deep, refs #18298. + else: break + # result does not have to be object type proc isImportedException*(t: PType; conf: ConfigRef): bool = - assert(t != nil) - if optNoCppExceptions in conf.globalOptions: + assert t != nil + + if conf.exc != excCpp: return false let base = t.skipTypes({tyAlias, tyPtr, tyDistinct, tyGenericInst}) - - if base.sym != nil and sfCompileToCpp in base.sym.flags: - result = true + result = base.sym != nil and {sfCompileToCpp, sfImportc} * base.sym.flags != {} proc isInfixAs*(n: PNode): bool = - return n.kind == nkInfix and n[0].kind == nkIdent and n[0].ident.s == "as" + return n.kind == nkInfix and n[0].kind == nkIdent and n[0].ident.id == ord(wAs) + +proc skipColon*(n: PNode): PNode = + result = n + if n.kind == nkExprColonExpr: + result = n[1] proc findUnresolvedStatic*(n: PNode): PNode = - if n.kind == nkSym and n.typ.kind == tyStatic and n.typ.n == nil: + if n.kind == nkSym and n.typ != nil and n.typ.kind == tyStatic and n.typ.n == nil: return n - + if n.typ != nil and n.typ.kind == tyTypeDesc: + let t = skipTypes(n.typ, {tyTypeDesc}) + if t.kind == tyGenericParam and not t.genericParamHasConstraints: + return n for son in n: let n = son.findUnresolvedStatic if n != nil: return n @@ -1723,14 +2009,127 @@ when false: proc containsNil*(n: PNode): bool = # only for debugging if n.isNil: return true - for i in 0 ..< n.safeLen: + for i in 0..<n.safeLen: if n[i].containsNil: return true -template hasDestructor*(t: PType): bool = tfHasAsgn in t.flags + +template hasDestructor*(t: PType): bool = {tfHasAsgn, tfHasOwned} * t.flags != {} + template incompleteType*(t: PType): bool = t.sym != nil and {sfForward, sfNoForward} * t.sym.flags == {sfForward} template typeCompleted*(s: PSym) = incl s.flags, sfNoForward -template getBody*(s: PSym): PNode = s.ast[bodyPos] +template detailedInfo*(sym: PSym): string = + sym.name.s + +proc isInlineIterator*(typ: PType): bool {.inline.} = + typ.kind == tyProc and tfIterator in typ.flags and typ.callConv != ccClosure + +proc isIterator*(typ: PType): bool {.inline.} = + typ.kind == tyProc and tfIterator in typ.flags + +proc isClosureIterator*(typ: PType): bool {.inline.} = + typ.kind == tyProc and tfIterator in typ.flags and typ.callConv == ccClosure + +proc isClosure*(typ: PType): bool {.inline.} = + typ.kind == tyProc and typ.callConv == ccClosure + +proc isNimcall*(s: PSym): bool {.inline.} = + s.typ.callConv == ccNimCall + +proc isExplicitCallConv*(s: PSym): bool {.inline.} = + tfExplicitCallConv in s.typ.flags + +proc isSinkParam*(s: PSym): bool {.inline.} = + s.kind == skParam and (s.typ.kind == tySink or tfHasOwned in s.typ.flags) + +proc isSinkType*(t: PType): bool {.inline.} = + t.kind == tySink or tfHasOwned in t.flags + +proc newProcType*(info: TLineInfo; idgen: IdGenerator; owner: PSym): PType = + result = newType(tyProc, idgen, owner) + result.n = newNodeI(nkFormalParams, info) + rawAddSon(result, nil) # return type + # result.n[0] used to be `nkType`, but now it's `nkEffectList` because + # the effects are now stored in there too ... this is a bit hacky, but as + # usual we desperately try to save memory: + result.n.add newNodeI(nkEffectList, info) + +proc addParam*(procType: PType; param: PSym) = + param.position = procType.sons.len-1 + procType.n.add newSymNode(param) + rawAddSon(procType, param.typ) + +const magicsThatCanRaise = { + mNone, mSlurp, mStaticExec, mParseExprToAst, mParseStmtToAst, mEcho} + +proc canRaiseConservative*(fn: PNode): bool = + if fn.kind == nkSym and fn.sym.magic notin magicsThatCanRaise: + result = false + else: + result = true + +proc canRaise*(fn: PNode): bool = + if fn.kind == nkSym and (fn.sym.magic notin magicsThatCanRaise or + {sfImportc, sfInfixCall} * fn.sym.flags == {sfImportc} or + sfGeneratedOp in fn.sym.flags): + result = false + elif fn.kind == nkSym and fn.sym.magic == mEcho: + result = true + else: + # TODO check for n having sons? or just return false for now if not + if fn.typ != nil and fn.typ.n != nil and fn.typ.n[0].kind == nkSym: + result = false + else: + result = fn.typ != nil and fn.typ.n != nil and ((fn.typ.n[0].len < effectListLen) or + (fn.typ.n[0][exceptionEffects] != nil and + fn.typ.n[0][exceptionEffects].safeLen > 0)) + +proc toHumanStrImpl[T](kind: T, num: static int): string = + result = $kind + result = result[num..^1] + result[0] = result[0].toLowerAscii + +proc toHumanStr*(kind: TSymKind): string = + ## strips leading `sk` + result = toHumanStrImpl(kind, 2) + +proc toHumanStr*(kind: TTypeKind): string = + ## strips leading `tk` + result = toHumanStrImpl(kind, 2) + +proc skipHiddenAddr*(n: PNode): PNode {.inline.} = + (if n.kind == nkHiddenAddr: n[0] else: n) + +proc isNewStyleConcept*(n: PNode): bool {.inline.} = + assert n.kind == nkTypeClassTy + result = n[0].kind == nkEmpty + +proc isOutParam*(t: PType): bool {.inline.} = tfIsOutParam in t.flags + +const + nodesToIgnoreSet* = {nkNone..pred(nkSym), succ(nkSym)..nkNilLit, + nkTypeSection, nkProcDef, nkConverterDef, + nkMethodDef, nkIteratorDef, nkMacroDef, nkTemplateDef, nkLambda, nkDo, + nkFuncDef, nkConstSection, nkConstDef, nkIncludeStmt, nkImportStmt, + nkExportStmt, nkPragma, nkCommentStmt, nkBreakState, + nkTypeOfExpr, nkMixinStmt, nkBindStmt} + +proc isTrue*(n: PNode): bool = + n.kind == nkSym and n.sym.kind == skEnumField and n.sym.position != 0 or + n.kind == nkIntLit and n.intVal != 0 + +type + TypeMapping* = Table[ItemId, PType] + SymMapping* = Table[ItemId, PSym] + +template idTableGet*(tab: typed; key: PSym | PType): untyped = tab.getOrDefault(key.itemId) +template idTablePut*(tab: typed; key, val: PSym | PType) = tab[key.itemId] = val + +template initSymMapping*(): Table[ItemId, PSym] = initTable[ItemId, PSym]() +template initTypeMapping*(): Table[ItemId, PType] = initTable[ItemId, PType]() + +template resetIdTable*(tab: Table[ItemId, PSym]) = tab.clear() +template resetIdTable*(tab: Table[ItemId, PType]) = tab.clear() |