ast

Search:
Group by:
Source   Edit  

Types

CompilesId = int
id that is used for the caching logic within system.compiles. See the seminst module. Source   Edit  
IdGenerator = ref object
  module*: int32
  symId*: int32
  typeId*: int32
  sealed*: bool
  disambTable*: CountTable[PIdent]
Source   Edit  
ItemId = object
  module*: int32
  item*: int32
Source   Edit  
PIdObj = ref TIdObj
Source   Edit  
PLib = ref TLib
Source   Edit  
PNode = ref TNode
Source   Edit  
PScope = ref TScope
Source   Edit  
PSym = ref TSym
Source   Edit  
PType = ref TType
Source   Edit  
TCallingConvention = enum
  ccNimCall = "nimcall", ccStdCall = "stdcall", ccCDecl = "cdecl",
  ccSafeCall = "safecall", ccSysCall = "syscall", ccInline = "inline",
  ccNoInline = "noinline", ccFastCall = "fastcall", ccThisCall = "thiscall",
  ccClosure = "closure", ccNoConvention = "noconv"
Source   Edit  
TIdNodePair = object
  key*: PIdObj
  val*: PNode
Source   Edit  
TIdNodeTable = object
  counter*: int
  data*: TIdNodePairSeq
Source   Edit  
TIdObj {.acyclic.} = object of RootObj
  itemId*: ItemId
Source   Edit  
TIdPair = object
  key*: PIdObj
  val*: RootRef
Source   Edit  
TIdPairSeq = seq[TIdPair]
Source   Edit  
TIdTable = object
  counter*: int
  data*: TIdPairSeq
Source   Edit  
TImplication = enum
  impUnknown, impNo, impYes
Source   Edit  
TInstantiation = object
  sym*: PSym
  concreteTypes*: seq[PType]
  compilesId*: CompilesId
Source   Edit  
TLib = object
  kind*: TLibKind
  generated*: bool
  isOverridden*: bool
  name*: Rope
  path*: PNode
Source   Edit  
TLibKind = enum
  libHeader, libDynamic
Source   Edit  
TLoc = object
  k*: TLocKind
  storage*: TStorageLoc
  flags*: TLocFlags
  lode*: PNode
  r*: Rope
Source   Edit  
TLocFlag = enum
  lfIndirect, lfNoDeepCopy, lfNoDecl, lfDynamicLib, lfExportLib, lfHeader,
  lfImportCompilerProc, lfSingleUse, lfEnforceDeref, lfPrepareForMutation
Source   Edit  
TLocFlags = set[TLocFlag]
Source   Edit  
TLocKind = enum
  locNone, locTemp, locLocalVar, locGlobalVar, locParam, locField, locExpr,
  locProc, locData, locCall, locOther
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,
  mOpenArrayToSeq, mNewString, mNewStringOfCap, mParseBiggestFloat, mMove,
  mEnsureMove, mWasMoved, mDup, mDestroy, mTrace, mDefault, mUnown, mFinished,
  mIsolate, mAccessEnv, mAccessTypeField, mReset, mArray, mOpenArray, mRange,
  mSet, mSeq, mVarargs, mRef, mPtr, mVar, mDistinct, mVoid, mTuple, mOrdinal,
  mIterableType, 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, 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, mGenericDefine,
  mRunnableExamples, mException, mBuiltinType, mSymOwner, mUncheckedArray,
  mGetImplTransf, mSymIsInstantiationOf, mNodeId, mPrivateAccess, mZeroDefault
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

  when defined(nimsuggest):
      endInfo*: TLineInfo

  
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, nfLastRead, nfFirstWrite, nfHasComment, nfSkipFieldChecking
Source   Edit  
TNodeFlags = set[TNodeFlag]
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, nkOutTy, nkDistinctTy, nkProcTy, nkIteratorTy, nkSinkAsgn,
  nkEnumTy, nkEnumFieldDef, nkArgList, nkPattern, nkHiddenTryStmt, nkClosure,
  nkGotoState, nkState, nkBreakState, nkFuncDef, nkTupleConstr, nkError,
  nkModuleRef, nkReplayAction, nkNilRodNode
Source   Edit  
TNodeKinds = set[TNodeKind]
Source   Edit  
TNodePair = object
  h*: Hash
  key*: PNode
  val*: int
Source   Edit  
TNodeSeq = seq[PNode]
Source   Edit  
TNodeTable = object
  counter*: int
  data*: TNodePairSeq
Source   Edit  
TObjectSeq = seq[RootRef]
Source   Edit  
TObjectSet = object
  counter*: int
  data*: TObjectSeq
Source   Edit  
TPair = object
  key*, val*: RootRef
Source   Edit  
TPairSeq = seq[TPair]
Source   Edit  
TScope {.acyclic.} = object
  depthLevel*: int
  symbols*: TStrTable
  parent*: PScope
  allowPrivateAccess*: seq[PSym]
Source   Edit  
TStorageLoc = enum
  OnUnknown, OnStatic, OnStack, OnHeap
Source   Edit  
TStrTable = object
  counter*: int
  data*: seq[PSym]
Source   Edit  
TSym {.acyclic.} = object of TIdObj
  case kind*: TSymKind
  of routineKinds:
      gcUnsafetyReason*: PSym
      transformedBody*: PNode

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

  else:
    nil
  magic*: TMagic
  typ*: PType
  name*: PIdent
  info*: TLineInfo
  when defined(nimsuggest):
      endInfo*: TLineInfo
      hasUserSpecifiedType*: bool

  owner*: PSym
  flags*: TSymFlags
  ast*: PNode
  options*: TOptions
  position*: int
  offset*: int32
  disamb*: int32
  loc*: TLoc
  annex*: PLib
  when hasFFI:
      cname*: string

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

  
Source   Edit  
TSymFlag = enum
  sfUsed, sfExported, sfFromGeneric, sfGlobal, sfForward, sfWasForwarded,
  sfImportc, sfExportc, sfMangleCpp, sfVolatile, sfRegister, sfPure,
  sfNoSideEffect, sfSideEffect, sfMainModule, sfSystemModule, sfNoReturn,
  sfAddrTaken, sfCompilerProc, sfEscapes, sfDiscriminant, sfRequiresInit,
  sfDeprecated, sfExplain, sfError, sfShadowed, sfThread, sfCppNonPod,
  sfCompileTime, sfConstructor, sfDispatcher, sfBorrow, sfInfixCall,
  sfNamedParamCall, sfDiscardable, sfOverridden, sfCallsite, sfGenSym,
  sfNonReloadable, sfGeneratedOp, sfTemplateParam, sfCursor,
  sfInjectDestructors, sfNeverRaises, sfSystemRaisesDefect,
  sfUsedInFinallyOrExcept, sfSingleUsedTemp, sfNoalias, sfEffectsDelayed,
  sfGeneratedType, sfVirtual, sfByCopy, sfCodegenDecl
Source   Edit  
TSymFlags = set[TSymFlag]
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
Source   Edit  
TSymKinds = set[TSymKind]
Source   Edit  
TType {.acyclic.} = object of TIdObj
  kind*: TTypeKind
  callConv*: TCallingConvention
  flags*: TTypeFlags
  sons*: TTypeSeq
  n*: PNode
  owner*: PSym
  sym*: PSym
  size*: BiggestInt
  align*: int16
  paddingAtEnd*: int16
  loc*: TLoc
  typeInst*: PType
  uniqueId*: ItemId
Source   Edit  
TTypeAttachedOp = enum
  attachedWasMoved, attachedDestructor, attachedAsgn, attachedDup, attachedSink,
  attachedTrace, attachedDeepCopy
as usual, order is important here 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, tfIsConstructor,
  tfEffectSystemWorkaround, tfIsOutParam, tfSendable
Source   Edit  
TTypeFlags = set[TTypeFlag]
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, tyConcept, tyVoid, tyIterable
Source   Edit  
TTypeKinds = set[TTypeKind]
Source   Edit  
TTypeSeq = seq[PType]
Source   Edit  

Vars

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

Consts

abstractInst = {tyGenericInst, tyDistinct, tyOrdinal, tyTypeDesc, tyAlias,
                tyInferred, tySink, tyOwned}
Source   Edit  
abstractVarRange = {tyGenericInst, tyRange, tyVar, tyDistinct, tyOrdinal,
                    tyTypeDesc, tyAlias, tyInferred, tySink, tyOwned}
Source   Edit  
AttachedOpToStr: array[TTypeAttachedOp, string] = ["=wasMoved", "=destroy",
    "=copy", "=dup", "=sink", "=trace", "=deepcopy"]
Source   Edit  
bodyPos = 6
Source   Edit  
callableDefs = {nkLambda..nkDo, nkProcDef..nkIteratorDef, nkFuncDef}
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  
ConstantDataTypes: TTypeKinds = {tyArray, tySet, tyTuple, tySequence}
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, mOpenArrayToSeq}
Source   Edit  
declarativeDefs = {nkProcDef, nkFuncDef, nkMethodDef, nkIteratorDef,
                   nkConverterDef}
Source   Edit  
defaultOffset = -1
Source   Edit  
dispatcherPos = 8
Source   Edit  
effectListLen = 6
Source   Edit  
ensuresEffects = 2
Source   Edit  
ExportableSymKinds = {skType..skConst, skProc..skTemplate, skEnumField, skStub}
Source   Edit  
GcTypeKinds = {tyRef, tySequence, tyString}
Source   Edit  
generatedMagics = {mNone, mIsolate, mFinished, mOpenArrayToSeq}
magics that are generated as normal procs in the backend Source   Edit  
GenericTypes: TTypeKinds = {tyGenericInvocation, tyGenericBody, tyGenericParam}
Source   Edit  
GrowthFactor = 2
Source   Edit  
IntegralTypes = {tyBool, tyChar, tyEnum, tyInt..tyInt64, tyFloat..tyFloat128,
                 tyUInt..tyUInt64}
Source   Edit  
miscPos = 5
Source   Edit  
namePos = 0
Source   Edit  
nfAllFieldsSet = nfBase2
Source   Edit  
NilableTypes: TTypeKinds = {tyPointer, tyCstring, tyRef, tyPtr, tyProc, tyProxy}
Source   Edit  
nkCallKinds = {nkCall, nkInfix, nkPrefix, nkPostfix, nkCommand, nkCallStrLit,
               nkHiddenCallConv}
Source   Edit  
nkEffectList = nkArgList
Source   Edit  
nkFloatLiterals = {nkFloatLit..nkFloat128Lit}
Source   Edit  
nkIdentKinds = {nkIdent, nkSym, nkAccQuoted, nkOpenSymChoice, nkClosedSymChoice}
Source   Edit  
nkLambdaKinds = {nkLambda, nkDo}
Source   Edit  
nkLastBlockStmts = {nkRaiseStmt, nkReturnStmt, nkBreakStmt, nkContinueStmt}
Source   Edit  
nkLiterals = {nkCharLit..nkTripleStrLit}
Source   Edit  
nkPragmaCallKinds = {nkExprColonExpr, nkCall, nkCallStrLit}
Source   Edit  
nkStrKinds = {nkStrLit..nkTripleStrLit}
Source   Edit  
nkSymChoices = {nkClosedSymChoice, nkOpenSymChoice}
Source   Edit  
nkWhen = nkWhenStmt
Source   Edit  
nkWhenExpr = nkWhenStmt
Source   Edit  
nodesToIgnoreSet = {nkNone..nkIdent, nkType..nkNilLit, nkTypeSection, nkProcDef,
                    nkConverterDef, nkMethodDef, nkIteratorDef, nkMacroDef,
                    nkTemplateDef, nkLambda, nkDo, nkFuncDef, nkConstSection,
                    nkConstDef, nkIncludeStmt, nkImportStmt, nkExportStmt,
                    nkPragma, nkCommentStmt, nkBreakState, nkTypeOfExpr,
                    nkMixinStmt, nkBindStmt}
Source   Edit  
OverloadableSyms = {skProc, skFunc, skMethod, skIterator, skConverter, skModule,
                    skTemplate, skMacro, skEnumField}
Source   Edit  
PackageModuleId = -3'i32
Source   Edit  
paramsPos = 3
Source   Edit  
patternPos = 1
Source   Edit  
PersistentNodeFlags: TNodeFlags = {nfBase2, nfBase8, nfBase16, nfDotSetter,
                                   nfDotField, nfIsRef, nfIsPtr, nfPreventCg,
                                   nfLL, nfFromTemplate, nfDefaultRefsParam,
                                   nfExecuteOnReload, nfLastRead, nfFirstWrite,
                                   nfSkipFieldChecking}
Source   Edit  
pragmasEffects = 4
Source   Edit  
pragmasPos = 4
Source   Edit  
procDefs = {nkLambda..nkDo, nkProcDef..nkConverterDef, nkIteratorDef, nkFuncDef}
Source   Edit  
PtrLikeKinds: TTypeKinds = {tyPointer, tyPtr}
Source   Edit  
resultPos = 7
Source   Edit  
routineDefs = {nkProcDef..nkIteratorDef, nkFuncDef}
Source   Edit  
routineKinds = {skProc, skFunc, skMethod, skIterator, skConverter, skMacro,
                skTemplate}
Source   Edit  
sfAllUntyped = sfVolatile
Source   Edit  
sfAnon = sfDiscardable
Source   Edit  
sfBase = sfDiscriminant
Source   Edit  
sfCompileToCpp = sfInfixCall
Source   Edit  
sfCompileToObjc = sfNamedParamCall
Source   Edit  
sfCustomPragma = sfRegister
Source   Edit  
sfDirty = sfPure
Source   Edit  
sfExperimental = sfOverridden
Source   Edit  
sfGoto = sfOverridden
Source   Edit  
sfNoForward = sfRegister
Source   Edit  
sfNoInit = sfMainModule
Source   Edit  
sfReorder = sfForward
Source   Edit  
sfTemplateRedefinition = sfExportc
Source   Edit  
sfWrittenTo = sfBorrow
Source   Edit  
skError = skUnknown
Source   Edit  
skLocalVars = {skVar, skLet, skForVar, skParam, skResult}
Source   Edit  
skProcKinds = {skProc, skFunc, skTemplate, skMacro, skIterator, skMethod,
               skConverter}
Source   Edit  
StartSize = 8
Source   Edit  
StructuralEquivTypes: TTypeKinds = {tyNil, tyTuple, tyArray, tySet, tyRange,
                                    tyPtr, tyRef, tyVar, tyLent, tySequence,
                                    tyProc, tyOpenArray, tyVarargs}
Source   Edit  
tagEffects = 3
Source   Edit  
tfGcSafe = tfThread
Source   Edit  
tfObjHasKids = tfEnumHasHoles
Source   Edit  
tfReturnsNew = tfInheritable
Source   Edit  
tfUnion = tfNoSideEffect
Source   Edit  
tyError = tyProxy
Source   Edit  
tyMetaTypes = {tyUntyped, tyTypeDesc, tyGenericParam,
               tyBuiltInTypeClass..tyCompositeTypeClass, tyAnd..tyAnything}
Source   Edit  
tyPureObject = tyTuple
Source   Edit  
tyTypeClasses = {tyBuiltInTypeClass, tyCompositeTypeClass, tyUserTypeClass,
                 tyUserTypeClassInst, tyAnd, tyOr, tyNot, tyAnything}
Source   Edit  
tyUnknown = tyFromExpr
Source   Edit  
tyUnknownTypes = {tyProxy, tyFromExpr}
Source   Edit  
tyUserTypeClasses = {tyUserTypeClass, tyUserTypeClassInst}
Source   Edit  

Procs

proc `$`(s: PSym): string {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc `$`(x: ItemId): string {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc `==`(a, b: ItemId): bool {.inline, ...raises: [], tags: [], forbids: [].}
Source   Edit  
proc add(father, son: Indexable)
Source   Edit  
proc addAllowNil(father, son: Indexable) {.inline.}
Source   Edit  
proc addParam(procType: PType; param: PSym) {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc addSonNilAllowed(father, son: PNode) {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc appendToModule(m: PSym; n: PNode) {....raises: [], tags: [], forbids: [].}
The compiler will use this internally to add nodes that will be appended to the module after the sem pass Source   Edit  
proc assignType(dest, src: PType) {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc astdef(s: PSym): PNode {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc canRaise(fn: PNode): bool {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc canRaiseConservative(fn: PNode): bool {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc comment(n: PNode): string {....raises: [KeyError], tags: [], forbids: [].}
Source   Edit  
proc comment=(n: PNode; a: string) {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc containsNode(n: PNode; kinds: TNodeKinds): bool {....raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc copyIdTable(dest: var TIdTable; src: TIdTable) {....raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc copyNode(src: PNode): PNode {....raises: [KeyError], tags: [], forbids: [].}
Source   Edit  
proc copyObjectSet(dest: var TObjectSet; src: TObjectSet) {....raises: [],
    tags: [], forbids: [].}
Source   Edit  
proc copyStrTable(dest: var TStrTable; src: TStrTable) {....raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc copySym(s: PSym; idgen: IdGenerator): PSym {....raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc copyTree(src: PNode): PNode {....raises: [KeyError], tags: [], forbids: [].}
Source   Edit  
proc copyTreeWithoutNode(src, skippedNode: PNode): PNode {....raises: [KeyError],
    tags: [], forbids: [].}
Source   Edit  
proc copyType(t: PType; id: ItemId; owner: PSym): PType {....raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc createModuleAlias(s: PSym; idgen: IdGenerator; newIdent: PIdent;
                       info: TLineInfo; options: TOptions): PSym {....raises: [],
    tags: [], forbids: [].}
Source   Edit  
proc delSon(father: PNode; idx: int) {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc discardSons(father: PNode) {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc exactReplica(t: PType): PType {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc extractPragma(s: PSym): PNode {....raises: [], tags: [], forbids: [].}
gets the pragma node of routine/type/var/let/const symbol s Source   Edit  
proc findUnresolvedStatic(n: PNode): PNode {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc getDeclPragma(n: PNode): PNode {....raises: [], tags: [], forbids: [].}
return the nkPragma node for declaration n, or nil if no pragma was found. Currently only supports routineDefs + {nkTypeDef}. Source   Edit  
proc getFloat(a: PNode): BiggestFloat {....raises: [ERecoverableError], tags: [],
                                        forbids: [].}
Source   Edit  
proc getInt(a: PNode): Int128 {....raises: [ERecoverableError], tags: [],
                                forbids: [].}
Source   Edit  
proc getInt64(a: PNode): int64 {....deprecated: "use getInt",
                                 raises: [ERecoverableError], tags: [],
                                 forbids: [].}
Deprecated: use getInt
Source   Edit  
proc getPIdent(a: PNode): PIdent {.inline, ...raises: [], tags: [], forbids: [].}
Returns underlying PIdent for {nkSym, nkIdent}, or nil. Source   Edit  
proc getStr(a: PNode): string {....raises: [ERecoverableError], tags: [],
                                forbids: [].}
Source   Edit  
proc getStrOrChar(a: PNode): string {....raises: [ERecoverableError], tags: [],
                                      forbids: [].}
Source   Edit  
proc hash(x: ItemId): Hash {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc hasNilSon(n: PNode): bool {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc hasPattern(s: PSym): bool {.inline, ...raises: [], tags: [], forbids: [].}
Source   Edit  
proc hasSonWith(n: PNode; kind: TNodeKind): bool {....raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc hasSubnodeWith(n: PNode; kind: TNodeKind): bool {....raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc idGeneratorForPackage(nextIdWillBe: int32): IdGenerator {....raises: [],
    tags: [], forbids: [].}
Source   Edit  
proc idGeneratorFromModule(m: PSym): IdGenerator {....raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc initIdNodeTable(x: var TIdNodeTable) {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc initIdTable(x: var TIdTable) {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc initNodeTable(x: var TNodeTable) {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc initObjectSet(x: var TObjectSet) {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc initStrTable(x: var TStrTable) {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc isAtom(n: PNode): bool {.inline, ...raises: [], tags: [], forbids: [].}
Source   Edit  
proc isCallExpr(n: PNode): bool {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc isClosure(typ: PType): bool {.inline, ...raises: [], tags: [], forbids: [].}
Source   Edit  
proc isClosureIterator(typ: PType): bool {.inline, ...raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc isCompileTimeProc(s: PSym): bool {.inline, ...raises: [], tags: [],
                                        forbids: [].}
Source   Edit  
proc isEmptyType(t: PType): bool {.inline, ...raises: [], tags: [], forbids: [].}
'void' and 'typed' types are often equivalent to 'nil' these days: Source   Edit  
proc isGCedMem(t: PType): bool {.inline, ...raises: [], tags: [], forbids: [].}
Source   Edit  
proc isGenericParams(n: PNode): bool {.inline, ...raises: [], tags: [], forbids: [].}
used to judge whether a node is generic params. Source   Edit  
proc isGenericRoutine(n: PNode): bool {.inline, ...raises: [], tags: [],
                                        forbids: [].}
Source   Edit  
proc isGenericRoutine(s: PSym): bool {.inline, ...raises: [], tags: [], forbids: [].}

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
Source   Edit  
proc isGenericRoutineStrict(s: PSym): bool {.inline, ...raises: [], tags: [],
    forbids: [].}
determines if this symbol represents a generic routine the unusual name is so it doesn't collide and eventually replaces isGenericRoutine Source   Edit  
proc isImportedException(t: PType; conf: ConfigRef): bool {....raises: [],
    tags: [], forbids: [].}
Source   Edit  
proc isInfixAs(n: PNode): bool {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc isInlineIterator(typ: PType): bool {.inline, ...raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc isIterator(typ: PType): bool {.inline, ...raises: [], tags: [], forbids: [].}
Source   Edit  
proc isMetaType(t: PType): bool {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc isNewStyleConcept(n: PNode): bool {.inline, ...raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc isOutParam(t: PType): bool {.inline, ...raises: [], tags: [], forbids: [].}
Source   Edit  
proc isRoutine(s: PSym): bool {.inline, ...raises: [], tags: [], forbids: [].}
Source   Edit  
proc isSinkParam(s: PSym): bool {.inline, ...raises: [], tags: [], forbids: [].}
Source   Edit  
proc isSinkType(t: PType): bool {.inline, ...raises: [], tags: [], forbids: [].}
Source   Edit  
proc isUnresolvedStatic(t: PType): bool {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc lastSon(n: Indexable): Indexable
Source   Edit  
proc len(n: Indexable): int {.inline.}
Source   Edit  
proc linkTo(s: PSym; t: PType): PSym {.discardable, ...raises: [], tags: [],
                                       forbids: [].}
Source   Edit  
proc linkTo(t: PType; s: PSym): PType {.discardable, ...raises: [], tags: [],
                                        forbids: [].}
Source   Edit  
proc makeStmtList(n: PNode): PNode {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc newFloatNode(kind: TNodeKind; floatVal: BiggestFloat): PNode {....raises: [],
    tags: [], forbids: [].}
Source   Edit  
proc newIdentNode(ident: PIdent; info: TLineInfo): PNode {....raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc newIdTable(): TIdTable {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc newIntNode(kind: TNodeKind; intVal: BiggestInt): PNode {....raises: [],
    tags: [], forbids: [].}
Source   Edit  
proc newIntNode(kind: TNodeKind; intVal: Int128): PNode {....raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc newIntTypeNode(intVal: BiggestInt; typ: PType): PNode {....raises: [],
    tags: [], forbids: [].}
Source   Edit  
proc newIntTypeNode(intVal: Int128; typ: PType): PNode {....raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc newNode(kind: TNodeKind): PNode {....raises: [], tags: [], forbids: [].}
new node with unknown line info, no type, and no children Source   Edit  
proc newNodeI(kind: TNodeKind; info: TLineInfo): PNode {....raises: [], tags: [],
    forbids: [].}
new node with line info, no type, and no children Source   Edit  
proc newNodeI(kind: TNodeKind; info: TLineInfo; children: int): PNode {.
    ...raises: [], tags: [], forbids: [].}
new node with line info, type, and children Source   Edit  
proc newNodeIT(kind: TNodeKind; info: TLineInfo; typ: PType): PNode {.
    ...raises: [], tags: [], forbids: [].}
new node with line info, type, and no children Source   Edit  
proc newProcNode(kind: TNodeKind; info: TLineInfo; body: PNode; params, name,
    pattern, genericParams, pragmas, exceptions: PNode): PNode {....raises: [],
    tags: [], forbids: [].}
Source   Edit  
proc newProcType(info: TLineInfo; id: ItemId; owner: PSym): PType {....raises: [],
    tags: [], forbids: [].}
Source   Edit  
proc newSons(father: Indexable; length: int)
Source   Edit  
proc newStrNode(kind: TNodeKind; strVal: string): PNode {....raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc newStrNode(strVal: string; info: TLineInfo): PNode {....raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc newStrTable(): TStrTable {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc newSym(symKind: TSymKind; name: PIdent; idgen: IdGenerator; owner: PSym;
            info: TLineInfo; options: TOptions = {}): PSym {....raises: [],
    tags: [], forbids: [].}
Source   Edit  
proc newSymNode(sym: PSym): PNode {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc newSymNode(sym: PSym; info: TLineInfo): PNode {....raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc newTree(kind: TNodeKind; children: varargs[PNode]): PNode {....raises: [],
    tags: [], forbids: [].}
Source   Edit  
proc newTreeI(kind: TNodeKind; info: TLineInfo; children: varargs[PNode]): PNode {.
    ...raises: [], tags: [], forbids: [].}
Source   Edit  
proc newTreeIT(kind: TNodeKind; info: TLineInfo; typ: PType;
               children: varargs[PNode]): PNode {....raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc newType(kind: TTypeKind; id: ItemId; owner: PSym): PType {....raises: [],
    tags: [], forbids: [].}
Source   Edit  
proc nextSymId(x: IdGenerator): ItemId {.inline, ...raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc nextTypeId(x: IdGenerator): ItemId {.inline, ...raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc originatingModule(s: PSym): PSym {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc propagateToOwner(owner, elem: PType; propagateHasAsgn = true) {....raises: [],
    tags: [], forbids: [].}
Source   Edit  
proc rawAddSon(father, son: PType; propagateHasAsgn = true) {....raises: [],
    tags: [], forbids: [].}
Source   Edit  
proc rawAddSonNoPropagationOfTypeFlags(father, son: PType) {....raises: [],
    tags: [], forbids: [].}
Source   Edit  
proc resetIdTable(x: var TIdTable) {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc safeArrLen(n: PNode): int {.inline, ...raises: [], tags: [], forbids: [].}
works for array-like objects (strings passed as openArray in VM). Source   Edit  
proc safeLen(n: PNode): int {.inline, ...raises: [], tags: [], forbids: [].}
works even for leaves. Source   Edit  
proc setInfoRecursive(n: PNode; info: TLineInfo) {....raises: [], tags: [],
    forbids: [].}
set line info recursively Source   Edit  
proc setUseIc(useIc: bool) {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc shallowCopy(src: PNode): PNode {....raises: [KeyError], tags: [], forbids: [].}
Source   Edit  
proc skipAddr(n: PNode): PNode {.inline, ...raises: [], tags: [], forbids: [].}
Source   Edit  
proc skipColon(n: PNode): PNode {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc skipGenericOwner(s: PSym): PSym {....raises: [], tags: [], forbids: [].}
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 skipPragmaExpr(n: PNode): PNode {....raises: [], tags: [], forbids: [].}
if pragma expr, give the node the pragmas are applied to, otherwise give node itself Source   Edit  
proc skipStmtList(n: PNode): PNode {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc skipTypes(t: PType; kinds: TTypeKinds): PType {....raises: [], tags: [],
    forbids: [].}
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 skipTypes(t: PType; kinds: TTypeKinds; maxIters: int): PType {....raises: [],
    tags: [], forbids: [].}
Source   Edit  
proc skipTypesOrNil(t: PType; kinds: TTypeKinds): PType {....raises: [], tags: [],
    forbids: [].}
same as skipTypes but handles 'nil' Source   Edit  
proc toHumanStr(kind: TSymKind): string {....raises: [], tags: [], forbids: [].}
strips leading sk Source   Edit  
proc toHumanStr(kind: TTypeKind): string {....raises: [], tags: [], forbids: [].}
strips leading tk Source   Edit  
proc toObject(typ: PType): PType {....raises: [], tags: [], forbids: [].}
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 toObjectFromRefPtrGeneric(typ: PType): PType {....raises: [], tags: [],
    forbids: [].}
Source   Edit  
proc toRef(typ: PType; idgen: IdGenerator): PType {....raises: [], tags: [],
    forbids: [].}
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 toVar(typ: PType; kind: TTypeKind; idgen: IdGenerator): PType {....raises: [],
    tags: [], forbids: [].}
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 transitionGenericParamToType(s: PSym) {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc transitionIntKind(n: PNode; kind: range[nkCharLit .. nkUInt64Lit]) {.
    ...raises: [], tags: [], forbids: [].}
Source   Edit  
proc transitionIntToFloatKind(n: PNode; kind: range[nkFloatLit .. nkFloat128Lit]) {.
    ...raises: [], tags: [], forbids: [].}
Source   Edit  
proc transitionNoneToSym(n: PNode) {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc transitionRoutineSymKind(s: PSym; kind: range[skProc .. skTemplate]) {.
    ...raises: [], tags: [], forbids: [].}
Source   Edit  
proc transitionSonsKind(n: PNode; kind: range[nkComesFrom .. nkTupleConstr]) {.
    ...raises: [], tags: [], forbids: [].}
Source   Edit  
proc transitionToLet(s: PSym) {....raises: [], tags: [], forbids: [].}
Source   Edit  
proc withInfo(n: PNode; info: TLineInfo): PNode {....raises: [], tags: [],
    forbids: [].}
Source   Edit  

Iterators

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

Templates

template `[]`(n: Indexable; i: BackwardsIndex): Indexable
Source   Edit  
template `[]`(n: Indexable; i: int): Indexable
Source   Edit  
template `[]=`(n: Indexable; i: BackwardsIndex; x: Indexable)
Source   Edit  
template `[]=`(n: Indexable; i: int; x: Indexable)
Source   Edit  
template detailedInfo(sym: PSym): string
Source   Edit  
template fileIdx(c: PSym): FileIndex
Source   Edit  
template filename(c: PSym): string
Source   Edit  
template hasDestructor(t: PType): bool
Source   Edit  
template id(a: PIdObj): int
Source   Edit  
template incompleteType(t: PType): bool
Source   Edit  
template previouslyInferred(t: PType): PType
Source   Edit  
template typeCompleted(s: PSym)
Source   Edit