ast

    Dark Mode
Search:
Group by:

Types

TCallingConvention = enum
  ccNimCall, ccStdCall, ccCDecl, ccSafeCall, ccSysCall, ccInline, ccNoInline,
  ccFastCall, ccThisCall, ccClosure, ccNoConvention
  Source Edit
TNodeKind = enum
  nkNone, nkEmpty, nkIdent, nkSym, nkType, nkCharLit, nkIntLit, nkInt8Lit,
  nkInt16Lit, nkInt32Lit, nkInt64Lit, nkUIntLit, nkUInt8Lit, nkUInt16Lit,
  nkUInt32Lit, nkUInt64Lit, nkFloatLit, nkFloat32Lit, nkFloat64Lit,
  nkFloat128Lit, nkStrLit, nkRStrLit, nkTripleStrLit, nkNilLit, nkComesFrom,
  nkDotCall, nkCommand, nkCall, nkCallStrLit, nkInfix, nkPrefix, nkPostfix,
  nkHiddenCallConv, nkExprEqExpr, nkExprColonExpr, nkIdentDefs, nkVarTuple,
  nkPar, nkObjConstr, nkCurly, nkCurlyExpr, nkBracket, nkBracketExpr,
  nkPragmaExpr, nkRange, nkDotExpr, nkCheckedFieldExpr, nkDerefExpr, nkIfExpr,
  nkElifExpr, nkElseExpr, nkLambda, nkDo, nkAccQuoted, nkTableConstr, nkBind,
  nkClosedSymChoice, nkOpenSymChoice, nkHiddenStdConv, nkHiddenSubConv, nkConv,
  nkCast, nkStaticExpr, nkAddr, nkHiddenAddr, nkHiddenDeref, nkObjDownConv,
  nkObjUpConv, nkChckRangeF, nkChckRange64, nkChckRange, nkStringToCString,
  nkCStringToString, nkAsgn, nkFastAsgn, nkGenericParams, nkFormalParams,
  nkOfInherit, nkImportAs, nkProcDef, nkMethodDef, nkConverterDef, nkMacroDef,
  nkTemplateDef, nkIteratorDef, nkOfBranch, nkElifBranch, nkExceptBranch,
  nkElse, nkAsmStmt, nkPragma, nkPragmaBlock, nkIfStmt, nkWhenStmt, nkForStmt,
  nkParForStmt, nkWhileStmt, nkCaseStmt, nkTypeSection, nkVarSection,
  nkLetSection, nkConstSection, nkConstDef, nkTypeDef, nkYieldStmt, nkDefer,
  nkTryStmt, nkFinally, nkRaiseStmt, nkReturnStmt, nkBreakStmt, nkContinueStmt,
  nkBlockStmt, nkStaticStmt, nkDiscardStmt, nkStmtList, nkImportStmt,
  nkImportExceptStmt, nkExportStmt, nkExportExceptStmt, nkFromStmt,
  nkIncludeStmt, nkBindStmt, nkMixinStmt, nkUsingStmt, nkCommentStmt,
  nkStmtListExpr, nkBlockExpr, nkStmtListType, nkBlockType, nkWith, nkWithout,
  nkTypeOfExpr, nkObjectTy, nkTupleTy, nkTupleClassTy, nkTypeClassTy,
  nkStaticTy, nkRecList, nkRecCase, nkRecWhen, nkRefTy, nkPtrTy, nkVarTy,
  nkConstTy, nkMutableTy, nkDistinctTy, nkProcTy, nkIteratorTy, nkSharedTy,
  nkEnumTy, nkEnumFieldDef, nkArgList, nkPattern, nkHiddenTryStmt, nkClosure,
  nkGotoState, nkState, nkBreakState, nkFuncDef, nkTupleConstr
  Source Edit
TNodeKinds = set[TNodeKind]
  Source Edit
TSymFlag = enum
  sfUsed, sfExported, sfFromGeneric, sfGlobal, sfForward, sfWasForwarded,
  sfImportc, sfExportc, sfMangleCpp, sfVolatile, sfRegister, sfPure,
  sfNoSideEffect, sfSideEffect, sfMainModule, sfSystemModule, sfNoReturn,
  sfAddrTaken, sfCompilerProc, sfProcvar, sfDiscriminant, sfRequiresInit,
  sfDeprecated, sfExplain, sfError, sfShadowed, sfThread, sfCompileTime,
  sfConstructor, sfDispatcher, sfBorrow, sfInfixCall, sfNamedParamCall,
  sfDiscardable, sfOverriden, sfCallsite, sfGenSym, sfNonReloadable,
  sfGeneratedOp, sfTemplateParam, sfCursor, sfInjectDestructors, sfNeverRaises,
  sfUsedInFinallyOrExcept, sfSingleUsedTemp, sfNoalias
  Source Edit
TSymFlags = set[TSymFlag]
  Source Edit
TTypeKind = enum
  tyNone, tyBool, tyChar, tyEmpty, tyAlias, tyNil, tyUntyped, tyTyped,
  tyTypeDesc, tyGenericInvocation, tyGenericBody, tyGenericInst, tyGenericParam,
  tyDistinct, tyEnum, tyOrdinal, tyArray, tyObject, tyTuple, tySet, tyRange,
  tyPtr, tyRef, tyVar, tySequence, tyProc, tyPointer, tyOpenArray, tyString,
  tyCString, tyForward, tyInt, tyInt8, tyInt16, tyInt32, tyInt64, tyFloat,
  tyFloat32, tyFloat64, tyFloat128, tyUInt, tyUInt8, tyUInt16, tyUInt32,
  tyUInt64, tyOwned, tySink, tyLent, tyVarargs, tyUncheckedArray, tyProxy,
  tyBuiltInTypeClass, tyUserTypeClass, tyUserTypeClassInst,
  tyCompositeTypeClass, tyInferred, tyAnd, tyOr, tyNot, tyAnything, tyStatic,
  tyFromExpr, tyOptDeprecated, tyVoid
  Source Edit
TTypeKinds = set[TTypeKind]
  Source Edit
TNodeFlag = enum
  nfNone, nfBase2, nfBase8, nfBase16, nfAllConst, nfTransf, nfNoRewrite, nfSem,
  nfLL, nfDotField, nfDotSetter, nfExplicitCall, nfExprCall, nfIsRef, nfIsPtr,
  nfPreventCg, nfBlockArg, nfFromTemplate, nfDefaultParam, nfDefaultRefsParam,
  nfExecuteOnReload
  Source Edit
TNodeFlags = set[TNodeFlag]
  Source Edit
TTypeFlag = enum
  tfVarargs, tfNoSideEffect, tfFinal, tfInheritable, tfHasOwned, tfEnumHasHoles,
  tfShallow, tfThread, tfFromGeneric, tfUnresolved, tfResolved, tfRetType,
  tfCapturesEnv, tfByCopy, tfByRef, tfIterator, tfPartial, tfNotNil,
  tfRequiresInit, tfNeedsFullInit, tfVarIsPtr, tfHasMeta, tfHasGCedMem,
  tfPacked, tfHasStatic, tfGenericTypeParam, tfImplicitTypeParam,
  tfInferrableStatic, tfConceptMatchedTypeSym, tfExplicit, tfWildcard,
  tfHasAsgn, tfBorrowDot, tfTriggersCompileTime, tfRefsAnonObj, tfCovariant,
  tfWeakCovariant, tfContravariant, tfCheckedForDestructor, tfAcyclic,
  tfIncompleteStruct, tfCompleteStruct, tfExplicitCallConv
  Source Edit
TTypeFlags = set[TTypeFlag]
  Source Edit
TSymKind = enum
  skUnknown, skConditional, skDynLib, skParam, skGenericParam, skTemp, skModule,
  skType, skVar, skLet, skConst, skResult, skProc, skFunc, skMethod, skIterator,
  skConverter, skMacro, skTemplate, skField, skEnumField, skForVar, skLabel,
  skStub, skPackage, skAlias
  Source Edit
TSymKinds = set[TSymKind]
  Source Edit
TMagic = enum
  mNone, 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, mInc, mDec, mOrd,
  mNew, mNewFinalize, mNewSeq, mNewSeqOfCap, mLengthOpenArray, mLengthStr,
  mLengthArray, mLengthSeq, mIncl, mExcl, mCard, mChr, mGCref, mGCunref, mAddI,
  mSubI, mMulI, mDivI, mModI, mSucc, mPred, mAddF64, mSubF64, mMulF64, mDivF64,
  mShrI, mShlI, mAshrI, mBitandI, mBitorI, mBitxorI, mMinI, mMaxI, mAddU, mSubU,
  mMulU, mDivU, mModU, mEqI, mLeI, mLtI, mEqF64, mLeF64, mLtF64, mLeU, mLtU,
  mEqEnum, mLeEnum, mLtEnum, mEqCh, mLeCh, mLtCh, mEqB, mLeB, mLtB, mEqRef,
  mLePtr, mLtPtr, mXor, mEqCString, mEqProc, mUnaryMinusI, mUnaryMinusI64,
  mAbsI, mNot, mUnaryPlusI, mBitnotI, mUnaryPlusF64, mUnaryMinusF64, mCharToStr,
  mBoolToStr, mIntToStr, mInt64ToStr, mFloatToStr, mCStrToStr, mStrToStr,
  mEnumToStr, mAnd, mOr, mImplies, mIff, mExists, mForall, mOld, mEqStr, mLeStr,
  mLtStr, mEqSet, mLeSet, mLtSet, mMulSet, mPlusSet, mMinusSet, mConStrStr,
  mSlice, mDotDot, mFields, mFieldPairs, mOmpParFor, mAppendStrCh,
  mAppendStrStr, mAppendSeqElem, mInSet, mRepr, mExit, mSetLengthStr,
  mSetLengthSeq, mIsPartOf, mAstToStr, mParallel, mSwap, mIsNil, mArrToSeq,
  mNewString, mNewStringOfCap, mParseBiggestFloat, mMove, mWasMoved, mDestroy,
  mDefault, mUnown, mIsolate, mAccessEnv, mReset, mArray, mOpenArray, mRange,
  mSet, mSeq, mVarargs, mRef, mPtr, mVar, mDistinct, mVoid, mTuple, mOrdinal,
  mInt, mInt8, mInt16, mInt32, mInt64, mUInt, mUInt8, mUInt16, mUInt32, mUInt64,
  mFloat, mFloat32, mFloat64, mFloat128, mBool, mChar, mString, mCstring,
  mPointer, mNil, mExpr, mStmt, mTypeDesc, mVoidType, mPNimrodNode, mSpawn,
  mDeepCopy, mIsMainModule, mCompileDate, mCompileTime, mProcCall, mCpuEndian,
  mHostOS, mHostCPU, mBuildOS, mBuildCPU, mAppType, mCompileOption,
  mCompileOptionArg, mNLen, mNChild, mNSetChild, mNAdd, mNAddMultiple, mNDel,
  mNKind, mNSymKind, mNccValue, mNccInc, mNcsAdd, mNcsIncl, mNcsLen, mNcsAt,
  mNctPut, mNctLen, mNctGet, mNctHasNext, mNctNext, mNIntVal, mNFloatVal,
  mNSymbol, mNIdent, mNGetType, mNStrVal, mNSetIntVal, mNSetFloatVal,
  mNSetSymbol, mNSetIdent, mNSetType, mNSetStrVal, mNLineInfo, mNNewNimNode,
  mNCopyNimNode, mNCopyNimTree, mStrToIdent, mNSigHash, mNSizeOf, mNBindSym,
  mNCallSite, mEqIdent, mEqNimrodNode, mSameNodeType, mGetImpl, mNGenSym,
  mNHint, mNWarning, mNError, mInstantiationInfo, mGetTypeInfo, mGetTypeInfoV2,
  mNimvm, mIntDefine, mStrDefine, mBoolDefine, mRunnableExamples, mException,
  mBuiltinType, mSymOwner, mUncheckedArray, mGetImplTransf,
  mSymIsInstantiationOf, mNodeId
  Source Edit
PNode = ref TNode
  Source Edit
TNodeSeq = seq[PNode]
  Source Edit
PType = ref TType
  Source Edit
PSym = ref TSym
  Source Edit
TNode {...}{.final, acyclic.} = object
  when defined(useNodeIds):
      id*: int

  typ*: PType
  info*: TLineInfo
  flags*: TNodeFlags
  case kind*: TNodeKind
  of nkCharLit .. nkUInt64Lit:
      intVal*: BiggestInt

  of nkFloatLit .. nkFloat128Lit:
      floatVal*: BiggestFloat

  of nkStrLit .. nkTripleStrLit:
      strVal*: string

  of nkSym:
      sym*: PSym

  of nkIdent:
      ident*: PIdent

  else:
      sons*: TNodeSeq

  comment*: string
  Source Edit
TStrTable = object
  counter*: int
  data*: seq[PSym]
  Source Edit
TLocKind = enum
  locNone, locTemp, locLocalVar, locGlobalVar, locParam, locField, locExpr,
  locProc, locData, locCall, locOther
  Source Edit
TLocFlag = enum
  lfIndirect, lfFullExternalName, lfNoDeepCopy, lfNoDecl, lfDynamicLib,
  lfExportLib, lfHeader, lfImportCompilerProc, lfSingleUse, lfEnforceDeref,
  lfPrepareForMutation
  Source Edit
TStorageLoc = enum
  OnUnknown, OnStatic, OnStack, OnHeap
  Source Edit
TLocFlags = set[TLocFlag]
  Source Edit
TLoc = object
  k*: TLocKind
  storage*: TStorageLoc
  flags*: TLocFlags
  lode*: PNode
  r*: Rope
  Source Edit
TLibKind = enum
  libHeader, libDynamic
  Source Edit
TLib = object
  kind*: TLibKind
  generated*: bool
  isOverriden*: bool
  name*: Rope
  path*: PNode
  Source Edit
CompilesId = int
id that is used for the caching logic within system.compiles. See the seminst module.   Source Edit
TInstantiation = object
  sym*: PSym
  concreteTypes*: seq[PType]
  compilesId*: CompilesId
  Source Edit
PInstantiation = ref TInstantiation
  Source Edit
TScope = object
  depthLevel*: int
  symbols*: TStrTable
  parent*: PScope
  Source Edit
PScope = ref TScope
  Source Edit
PLib = ref TLib
  Source Edit
TSym {...}{.acyclic.} = object of TIdObj
  case kind*: TSymKind
  of skType, skGenericParam:
      typeInstCache*: seq[PType]

  of routineKinds:
      procInstCache*: seq[PInstantiation]
      gcUnsafetyReason*: PSym
      transformedBody*: PNode

  of skModule, skPackage:
      usedGenerics*: seq[PInstantiation]
      tab*: TStrTable

  of skLet, skVar, skField, skForVar:
      guard*: PSym
      bitsize*: int
      alignment*: int

  else:
    nil
  magic*: TMagic
  typ*: PType
  name*: PIdent
  info*: TLineInfo
  owner*: PSym
  flags*: TSymFlags
  ast*: PNode
  options*: TOptions
  position*: int
  offset*: int
  loc*: TLoc
  annex*: PLib
  when hasFFI:
      cname*: string

  constraint*: PNode
  when defined(nimsuggest):
      allUsages*: seq[TLineInfo]

  
  Source Edit
TTypeSeq = seq[PType]
  Source Edit
TLockLevel = distinct int16
  Source Edit
TTypeAttachedOp = enum
  attachedDestructor, attachedAsgn, attachedSink, attachedTrace,
  attachedDispose, attachedDeepCopy
as usual, order is important here   Source Edit
TType {...}{.acyclic.} = object of TIdObj
  kind*: TTypeKind
  callConv*: TCallingConvention
  flags*: TTypeFlags
  sons*: TTypeSeq
  n*: PNode
  owner*: PSym
  sym*: PSym
  attachedOps*: array[TTypeAttachedOp, PSym]
  methods*: seq[(int, PSym)]
  size*: BiggestInt
  align*: int16
  paddingAtEnd*: int16
  lockLevel*: TLockLevel
  loc*: TLoc
  typeInst*: PType
  uniqueId*: int
  Source Edit
TPair = object
  key*, val*: RootRef
  Source Edit
TPairSeq = seq[TPair]
  Source Edit
TIdPair = object
  key*: PIdObj
  val*: RootRef
  Source Edit
TIdPairSeq = seq[TIdPair]
  Source Edit
TIdTable = object
  counter*: int
  data*: TIdPairSeq
  Source Edit
TIdNodePair = object
  key*: PIdObj
  val*: PNode
  Source Edit
TIdNodePairSeq = seq[TIdNodePair]
  Source Edit
TIdNodeTable = object
  counter*: int
  data*: TIdNodePairSeq
  Source Edit
TNodePair = object
  h*: Hash
  key*: PNode
  val*: int
  Source Edit
TNodePairSeq = seq[TNodePair]
  Source Edit
TNodeTable = object
  counter*: int
  data*: TNodePairSeq
  Source Edit
TObjectSeq = seq[RootRef]
  Source Edit
TObjectSet = object
  counter*: int
  data*: TObjectSeq
  Source Edit
TImplication = enum
  impUnknown, impNo, impYes
  Source Edit

Vars

eqTypeFlags = {tfIterator, tfNotNil, tfVarIsPtr, tfGcSafe, tfNoSideEffect}
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}.   Source Edit
ggDebug: bool
convenience switch for trying out things   Source Edit

Consts

CallingConvToStr: array[TCallingConvention, string] = ["nimcall", "stdcall",
    "cdecl", "safecall", "syscall", "inline", "noinline", "fastcall",
    "thiscall", "closure", "noconv"]
  Source Edit
sfNoInit = sfMainModule
  Source Edit
sfAllUntyped = sfVolatile
  Source Edit
sfDirty = sfPure
  Source Edit
sfAnon = sfDiscardable
  Source Edit
sfNoForward = sfRegister
  Source Edit
sfReorder = sfForward
  Source Edit
sfCompileToCpp = sfInfixCall
  Source Edit
sfCompileToObjc = sfNamedParamCall
  Source Edit
sfExperimental = sfOverriden
  Source Edit
sfGoto = sfOverriden
  Source Edit
sfWrittenTo = sfBorrow
  Source Edit
sfEscapes = sfProcvar
  Source Edit
sfBase = sfDiscriminant
  Source Edit
sfIsSelf = sfOverriden
  Source Edit
sfCustomPragma = sfRegister
  Source Edit
nkWhen = nkWhenStmt
  Source Edit
nkWhenExpr = nkWhenStmt
  Source Edit
nkEffectList = nkArgList
  Source Edit
exceptionEffects = 0
  Source Edit
requiresEffects = 1
  Source Edit
ensuresEffects = 2
  Source Edit
tagEffects = 3
  Source Edit
pragmasEffects = 4
  Source Edit
effectListLen = 5
  Source Edit
nkLastBlockStmts = {nkRaiseStmt, nkReturnStmt, nkBreakStmt, nkContinueStmt}
  Source Edit
tyPureObject = tyTuple
  Source Edit
GcTypeKinds = {tyRef, tySequence, tyString}
  Source Edit
tyError = tyProxy
  Source Edit
tyUnknown = tyFromExpr
  Source Edit
tyUnknownTypes = {tyProxy, tyFromExpr}
  Source Edit
tyTypeClasses = {tyBuiltInTypeClass, tyCompositeTypeClass, tyUserTypeClass,
                 tyUserTypeClassInst, tyAnd, tyOr, tyNot, tyAnything}
  Source Edit
tyMetaTypes = {tyUntyped, tyTypeDesc, tyGenericParam,
               tyBuiltInTypeClass..tyCompositeTypeClass, tyAnd..tyAnything}
  Source Edit
tyUserTypeClasses = {tyUserTypeClass, tyUserTypeClassInst}
  Source Edit
abstractVarRange = {tyGenericInst, tyRange, tyVar, tyDistinct, tyOrdinal,
                    tyTypeDesc, tyAlias, tyInferred, tySink, tyOwned}
  Source Edit
routineKinds = {skProc, skFunc, skMethod, skIterator, skConverter, skMacro,
                skTemplate}
  Source Edit
tfUnion = tfNoSideEffect
  Source Edit
tfGcSafe = tfThread
  Source Edit
tfObjHasKids = tfEnumHasHoles
  Source Edit
tfReturnsNew = tfInheritable
  Source Edit
skError = skUnknown
  Source Edit
ctfeWhitelist = {mNone, mSucc, mPred, mInc, mDec, mOrd, mLengthOpenArray,
                 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, mAddU, mSubU, mMulU,
                 mDivU, mModU, mEqI, mLeI, mLtI, mEqF64, mLeF64, mLtF64, mLeU,
                 mLtU, mEqEnum, mLeEnum, mLtEnum, mEqCh, mLeCh, mLtCh, mEqB,
                 mLeB, mLtB, mEqRef, mEqProc, mLePtr, mLtPtr, mEqCString, mXor,
                 mUnaryMinusI, mUnaryMinusI64, mAbsI, mNot, mUnaryPlusI,
                 mBitnotI, mUnaryPlusF64, mUnaryMinusF64, mCharToStr,
                 mBoolToStr, mIntToStr, mInt64ToStr, mFloatToStr, mCStrToStr,
                 mStrToStr, mEnumToStr, mAnd, mOr, mEqStr, mLeStr, mLtStr,
                 mEqSet, mLeSet, mLtSet, mMulSet, mPlusSet, mMinusSet,
                 mConStrStr, mAppendStrCh, mAppendStrStr, mAppendSeqElem,
                 mInSet, mRepr}
  Source Edit
OverloadableSyms = {skProc, skFunc, skMethod, skIterator, skConverter, skModule,
                    skTemplate, skMacro}
  Source Edit
GenericTypes: TTypeKinds = {tyGenericInvocation, tyGenericBody, tyGenericParam}
  Source Edit
StructuralEquivTypes: TTypeKinds = {tyNil, tyTuple, tyArray, tySet, tyRange,
                                    tyPtr, tyRef, tyVar, tyLent, tySequence,
                                    tyProc, tyOpenArray, tyVarargs}
  Source Edit
ConcreteTypes: TTypeKinds = {tyBool, tyChar, tyEnum, tyArray, tyObject, tySet,
                             tyTuple, tyRange, tyPtr, tyRef, tyVar, tyLent,
                             tySequence, tyProc, tyPointer, tyOpenArray,
                             tyString, tyCString, tyInt..tyInt64,
                             tyFloat..tyFloat128, tyUInt..tyUInt64}
  Source Edit
IntegralTypes = {tyBool, tyChar, tyEnum, tyInt..tyInt64, tyFloat..tyFloat128,
                 tyUInt..tyUInt64}
  Source Edit
ConstantDataTypes: TTypeKinds = {tyArray, tySet, tyTuple, tySequence}
  Source Edit
NilableTypes: TTypeKinds = {tyPointer, tyCString, tyRef, tyPtr, tyProc, tyProxy}
  Source Edit
PtrLikeKinds: TTypeKinds = {tyPointer, tyPtr}
  Source Edit
ExportableSymKinds = {skVar, skConst, skProc, skFunc, skMethod, skType,
                      skIterator, skMacro, skTemplate, skConverter, skEnumField,
                      skLet, skStub, skAlias}
  Source Edit
PersistentNodeFlags: TNodeFlags = {nfBase2, nfBase8, nfBase16, nfDotSetter,
                                   nfDotField, nfIsRef, nfIsPtr, nfPreventCg,
                                   nfLL, nfFromTemplate, nfDefaultRefsParam,
                                   nfExecuteOnReload}
  Source Edit
namePos = 0
  Source Edit
patternPos = 1
  Source Edit
genericParamsPos = 2
  Source Edit
paramsPos = 3
  Source Edit
pragmasPos = 4
  Source Edit
miscPos = 5
  Source Edit
bodyPos = 6
  Source Edit
resultPos = 7
  Source Edit
dispatcherPos = 8
  Source Edit
nfAllFieldsSet = nfBase2
  Source Edit
nkCallKinds = {nkCall, nkInfix, nkPrefix, nkPostfix, nkCommand, nkCallStrLit,
               nkHiddenCallConv}
  Source Edit
nkIdentKinds = {nkIdent, nkSym, nkAccQuoted, nkOpenSymChoice, nkClosedSymChoice}
  Source Edit
nkPragmaCallKinds = {nkExprColonExpr, nkCall, nkCallStrLit}
  Source Edit
nkLiterals = {nkCharLit..nkTripleStrLit}
  Source Edit
nkFloatLiterals = {nkFloatLit..nkFloat128Lit}
  Source Edit
nkLambdaKinds = {nkLambda, nkDo}
  Source Edit
declarativeDefs = {nkProcDef, nkFuncDef, nkMethodDef, nkIteratorDef,
                   nkConverterDef}
  Source Edit
routineDefs = {nkProcDef..nkIteratorDef, nkFuncDef}
  Source Edit
procDefs = {nkLambda..nkDo, nkProcDef..nkConverterDef, nkIteratorDef, nkFuncDef}
  Source Edit
nkSymChoices = {nkClosedSymChoice, nkOpenSymChoice}
  Source Edit
nkStrKinds = {nkStrLit..nkTripleStrLit}
  Source Edit
skLocalVars = {skVar, skLet, skForVar, skParam, skResult}
  Source Edit
skProcKinds = {skProc, skFunc, skTemplate, skMacro, skIterator, skMethod,
               skConverter}
  Source Edit
GrowthFactor = 2
  Source Edit
StartSize = 8
  Source Edit
UnspecifiedLockLevel = -1'i16
  Source Edit
MaxLockLevel = 1000'i16
  Source Edit
UnknownLockLevel = 1001'i16
  Source Edit
AttachedOpToStr: array[TTypeAttachedOp, string] = ["=destroy", "=copy", "=sink",
    "=trace", "=dispose", "=deepcopy"]
  Source Edit

Procs

proc getnimblePkg(a: PSym): PSym {...}{.raises: [], tags: [].}
  Source Edit
proc getnimblePkgId(a: PSym): int {...}{.raises: [], tags: [].}
  Source Edit
proc isCallExpr(n: PNode): bool {...}{.raises: [], tags: [].}
  Source Edit
proc len(n: Indexable): int {...}{.inline.}
  Source Edit
proc safeLen(n: PNode): int {...}{.inline, raises: [], tags: [].}
works even for leaves.   Source Edit
proc safeArrLen(n: PNode): int {...}{.inline, raises: [], tags: [].}
works for array-like objects (strings passed as openArray in VM).   Source Edit
proc add(father, son: Indexable)
  Source Edit
proc newNode(kind: TNodeKind): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc newNodeI(kind: TNodeKind; info: TLineInfo): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc newNodeI(kind: TNodeKind; info: TLineInfo; children: int): PNode {...}{.
    raises: [], tags: [].}
  Source Edit
proc newNodeIT(kind: TNodeKind; info: TLineInfo; typ: PType): PNode {...}{.
    raises: [], tags: [].}
  Source Edit
proc newTree(kind: TNodeKind; children: varargs[PNode]): PNode {...}{.raises: [],
    tags: [].}
  Source Edit
proc newTreeI(kind: TNodeKind; info: TLineInfo; children: varargs[PNode]): PNode {...}{.
    raises: [], tags: [].}
  Source Edit
proc newTreeIT(kind: TNodeKind; info: TLineInfo; typ: PType;
               children: varargs[PNode]): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc newSym(symKind: TSymKind; name: PIdent; owner: PSym; info: TLineInfo;
            options: TOptions = {}): PSym {...}{.raises: [], tags: [].}
  Source Edit
proc astdef(s: PSym): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc isMetaType(t: PType): bool {...}{.raises: [], tags: [].}
  Source Edit
proc isUnresolvedStatic(t: PType): bool {...}{.raises: [], tags: [].}
  Source Edit
proc linkTo(t: PType; s: PSym): PType {...}{.discardable, raises: [], tags: [].}
  Source Edit
proc linkTo(s: PSym; t: PType): PSym {...}{.discardable, raises: [], tags: [].}
  Source Edit
proc appendToModule(m: PSym; n: PNode) {...}{.raises: [], tags: [].}
The compiler will use this internally to add nodes that will be appended to the module after the sem pass   Source Edit
proc copyStrTable(dest: var TStrTable; src: TStrTable) {...}{.raises: [], tags: [].}
  Source Edit
proc copyIdTable(dest: var TIdTable; src: TIdTable) {...}{.raises: [], tags: [].}
  Source Edit
proc copyObjectSet(dest: var TObjectSet; src: TObjectSet) {...}{.raises: [], tags: [].}
  Source Edit
proc discardSons(father: PNode) {...}{.raises: [], tags: [].}
  Source Edit
proc withInfo(n: PNode; info: TLineInfo): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc newIdentNode(ident: PIdent; info: TLineInfo): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc newSymNode(sym: PSym): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc newSymNode(sym: PSym; info: TLineInfo): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc newIntNode(kind: TNodeKind; intVal: BiggestInt): PNode {...}{.raises: [],
    tags: [].}
  Source Edit
proc newIntNode(kind: TNodeKind; intVal: Int128): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc lastSon(n: Indexable): Indexable
  Source Edit
proc skipTypes(t: PType; kinds: TTypeKinds): PType {...}{.raises: [], tags: [].}
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!   Source Edit
proc newIntTypeNode(intVal: BiggestInt; typ: PType): PNode {...}{.raises: [],
    tags: [].}
  Source Edit
proc newIntTypeNode(intVal: Int128; typ: PType): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc newFloatNode(kind: TNodeKind; floatVal: BiggestFloat): PNode {...}{.raises: [],
    tags: [].}
  Source Edit
proc newStrNode(kind: TNodeKind; strVal: string): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc newStrNode(strVal: string; info: TLineInfo): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc newProcNode(kind: TNodeKind; info: TLineInfo; body: PNode; params, name,
    pattern, genericParams, pragmas, exceptions: PNode): PNode {...}{.raises: [],
    tags: [].}
  Source Edit
proc `$`(x: TLockLevel): string {...}{.raises: [], tags: [].}
  Source Edit
proc `$`(s: PSym): string {...}{.raises: [], tags: [].}
  Source Edit
proc newType(kind: TTypeKind; owner: PSym): PType {...}{.raises: [], tags: [].}
  Source Edit
proc newSons(father: Indexable; length: int)
  Source Edit
proc assignType(dest, src: PType) {...}{.raises: [], tags: [].}
  Source Edit
proc copyType(t: PType; owner: PSym; keepId: bool): PType {...}{.raises: [], tags: [].}
  Source Edit
proc exactReplica(t: PType): PType {...}{.raises: [], tags: [].}
  Source Edit
proc copySym(s: PSym): PSym {...}{.raises: [], tags: [].}
  Source Edit
proc createModuleAlias(s: PSym; newIdent: PIdent; info: TLineInfo;
                       options: TOptions): PSym {...}{.raises: [], tags: [].}
  Source Edit
proc initStrTable(x: var TStrTable) {...}{.raises: [], tags: [].}
  Source Edit
proc newStrTable(): TStrTable {...}{.raises: [], tags: [].}
  Source Edit
proc initIdTable(x: var TIdTable) {...}{.raises: [], tags: [].}
  Source Edit
proc newIdTable(): TIdTable {...}{.raises: [], tags: [].}
  Source Edit
proc resetIdTable(x: var TIdTable) {...}{.raises: [], tags: [].}
  Source Edit
proc initObjectSet(x: var TObjectSet) {...}{.raises: [], tags: [].}
  Source Edit
proc initIdNodeTable(x: var TIdNodeTable) {...}{.raises: [], tags: [].}
  Source Edit
proc initNodeTable(x: var TNodeTable) {...}{.raises: [], tags: [].}
  Source Edit
proc skipTypes(t: PType; kinds: TTypeKinds; maxIters: int): PType {...}{.raises: [],
    tags: [].}
  Source Edit
proc skipTypesOrNil(t: PType; kinds: TTypeKinds): PType {...}{.raises: [], tags: [].}
same as skipTypes but handles 'nil'   Source Edit
proc isGCedMem(t: PType): bool {...}{.inline, raises: [], tags: [].}
  Source Edit
proc propagateToOwner(owner, elem: PType; propagateHasAsgn = true) {...}{.raises: [],
    tags: [].}
  Source Edit
proc rawAddSon(father, son: PType; propagateHasAsgn = true) {...}{.raises: [],
    tags: [].}
  Source Edit
proc rawAddSonNoPropagationOfTypeFlags(father, son: PType) {...}{.raises: [],
    tags: [].}
  Source Edit
proc addSonNilAllowed(father, son: PNode) {...}{.raises: [], tags: [].}
  Source Edit
proc delSon(father: PNode; idx: int) {...}{.raises: [], tags: [].}
  Source Edit
proc copyNode(src: PNode): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc transitionSonsKind(n: PNode; kind: range[nkComesFrom .. nkTupleConstr]) {...}{.
    raises: [], tags: [].}
  Source Edit
proc transitionIntKind(n: PNode; kind: range[nkCharLit .. nkUInt64Lit]) {...}{.
    raises: [], tags: [].}
  Source Edit
proc transitionNoneToSym(n: PNode) {...}{.raises: [], tags: [].}
  Source Edit
proc transitionGenericParamToType(s: PSym) {...}{.raises: [], tags: [].}
  Source Edit
proc transitionRoutineSymKind(s: PSym; kind: range[skProc .. skTemplate]) {...}{.
    raises: [], tags: [].}
  Source Edit
proc transitionToLet(s: PSym) {...}{.raises: [], tags: [].}
  Source Edit
proc shallowCopy(src: PNode): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc copyTree(src: PNode): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc copyTreeWithoutNode(src, skippedNode: PNode): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc hasSonWith(n: PNode; kind: TNodeKind): bool {...}{.raises: [], tags: [].}
  Source Edit
proc hasNilSon(n: PNode): bool {...}{.raises: [], tags: [].}
  Source Edit
proc containsNode(n: PNode; kinds: TNodeKinds): bool {...}{.raises: [], tags: [].}
  Source Edit
proc hasSubnodeWith(n: PNode; kind: TNodeKind): bool {...}{.raises: [], tags: [].}
  Source Edit
proc getInt(a: PNode): Int128 {...}{.raises: [ERecoverableError], tags: [].}
  Source Edit
proc getInt64(a: PNode): int64 {...}{.deprecated: "use getInt",
                                 raises: [ERecoverableError], tags: [].}
Deprecated: use getInt
  Source Edit
proc getFloat(a: PNode): BiggestFloat {...}{.raises: [ERecoverableError], tags: [].}
  Source Edit
proc getStr(a: PNode): string {...}{.raises: [ERecoverableError], tags: [].}
  Source Edit
proc getStrOrChar(a: PNode): string {...}{.raises: [ERecoverableError], tags: [].}
  Source Edit
proc isGenericRoutine(s: PSym): bool {...}{.raises: [], tags: [].}
  Source Edit
proc skipGenericOwner(s: PSym): PSym {...}{.raises: [], tags: [].}
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).   Source Edit
proc originatingModule(s: PSym): PSym {...}{.raises: [], tags: [].}
  Source Edit
proc isRoutine(s: PSym): bool {...}{.inline, raises: [], tags: [].}
  Source Edit
proc isCompileTimeProc(s: PSym): bool {...}{.inline, raises: [], tags: [].}
  Source Edit
proc isRunnableExamples(n: PNode): bool {...}{.raises: [], tags: [].}
  Source Edit
proc requiredParams(s: PSym): int {...}{.raises: [], tags: [].}
  Source Edit
proc hasPattern(s: PSym): bool {...}{.inline, raises: [], tags: [].}
  Source Edit
proc isAtom(n: PNode): bool {...}{.inline, raises: [], tags: [].}
  Source Edit
proc isEmptyType(t: PType): bool {...}{.inline, raises: [], tags: [].}
'void' and 'stmt' types are often equivalent to 'nil' these days:   Source Edit
proc makeStmtList(n: PNode): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc skipStmtList(n: PNode): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc toVar(typ: PType; kind: TTypeKind): PType {...}{.raises: [], tags: [].}
If typ is not a tyVar then it is converted into a var <typ> and returned. Otherwise typ is simply returned as-is.   Source Edit
proc toRef(typ: PType): PType {...}{.raises: [], tags: [].}
If typ is a tyObject then it is converted into a ref <typ> and returned. Otherwise typ is simply returned as-is.   Source Edit
proc toObject(typ: PType): PType {...}{.raises: [], tags: [].}
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.   Source Edit
proc isImportedException(t: PType; conf: ConfigRef): bool {...}{.raises: [], tags: [].}
  Source Edit
proc isInfixAs(n: PNode): bool {...}{.raises: [], tags: [].}
  Source Edit
proc skipColon(n: PNode): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc findUnresolvedStatic(n: PNode): PNode {...}{.raises: [], tags: [].}
  Source Edit
proc hasDisabledAsgn(t: PType): bool {...}{.raises: [], tags: [].}
  Source Edit
proc isInlineIterator(typ: PType): bool {...}{.inline, raises: [], tags: [].}
  Source Edit
proc isClosureIterator(typ: PType): bool {...}{.inline, raises: [], tags: [].}
  Source Edit
proc isClosure(typ: PType): bool {...}{.inline, raises: [], tags: [].}
  Source Edit
proc isSinkParam(s: PSym): bool {...}{.inline, raises: [], tags: [].}
  Source Edit
proc isSinkType(t: PType): bool {...}{.inline, raises: [], tags: [].}
  Source Edit
proc newProcType(info: TLineInfo; owner: PSym): PType {...}{.raises: [], tags: [].}
  Source Edit
proc addParam(procType: PType; param: PSym) {...}{.raises: [], tags: [].}
  Source Edit
proc canRaiseConservative(fn: PNode): bool {...}{.raises: [], tags: [].}
  Source Edit
proc canRaise(fn: PNode): bool {...}{.raises: [], tags: [].}
  Source Edit
proc toHumanStr(kind: TSymKind): string {...}{.raises: [], tags: [].}
strips leading sk   Source Edit
proc toHumanStr(kind: TTypeKind): string {...}{.raises: [], tags: [].}
strips leading tk   Source Edit
proc skipAddr(n: PNode): PNode {...}{.inline, raises: [], tags: [].}
  Source Edit

Iterators

iterator items(n: PNode): PNode {...}{.raises: [], tags: [].}
  Source Edit
iterator pairs(n: PNode): tuple[i: int, n: PNode] {...}{.raises: [], tags: [].}
  Source Edit

Templates

template `[]`(n: Indexable; i: int): Indexable
  Source Edit
template `[]=`(n: Indexable; i: int; x: Indexable)
  Source Edit
template `[]`(n: Indexable; i: BackwardsIndex): Indexable
  Source Edit
template `[]=`(n: Indexable; i: BackwardsIndex; x: Indexable)
  Source Edit
template previouslyInferred(t: PType): PType
  Source Edit
template fileIdx(c: PSym): FileIndex
  Source Edit
template filename(c: PSym): string
  Source Edit
template transitionSymKindCommon(k: TSymKind)
  Source Edit
template hasDestructor(t: PType): bool
  Source Edit
template incompleteType(t: PType): bool
  Source Edit
template typeCompleted(s: PSym)
  Source Edit
template getBody(s: PSym): PNode
  Source Edit
template detailedInfo(sym: PSym): string
  Source Edit
template destructor(t: PType): PSym
  Source Edit
template assignment(t: PType): PSym
  Source Edit
template asink(t: PType): PSym
  Source Edit