123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626 |
- #
- #
- # The Nim Compiler
- # (c) Copyright 2013 Andreas Rumpf
- #
- # See the file "copying.txt", included in this
- # distribution, for details about the copyright.
- #
- # this module contains routines for accessing and iterating over types
- import
- intsets, ast, astalgo, trees, msgs, strutils, platform, renderer
- type
- TPreferedDesc* = enum
- preferName, preferDesc, preferExported, preferModuleInfo, preferGenericArg
- proc typeToString*(typ: PType; prefer: TPreferedDesc = preferName): string
- template `$`*(typ: PType): string = typeToString(typ)
- proc base*(t: PType): PType =
- result = t.sons[0]
- # ------------------- type iterator: ----------------------------------------
- type
- TTypeIter* = proc (t: PType, closure: RootRef): bool {.nimcall.} # true if iteration should stop
- TTypeMutator* = proc (t: PType, closure: RootRef): PType {.nimcall.} # copy t and mutate it
- TTypePredicate* = proc (t: PType): bool {.nimcall.}
- proc iterOverType*(t: PType, iter: TTypeIter, closure: RootRef): bool
- # Returns result of `iter`.
- proc mutateType*(t: PType, iter: TTypeMutator, closure: RootRef): PType
- # Returns result of `iter`.
- type
- TParamsEquality* = enum # they are equal, but their
- # identifiers or their return
- # type differ (i.e. they cannot be
- # overloaded)
- # this used to provide better error messages
- paramsNotEqual, # parameters are not equal
- paramsEqual, # parameters are equal
- paramsIncompatible
- proc equalParams*(a, b: PNode): TParamsEquality
- # returns whether the parameter lists of the procs a, b are exactly the same
- const
- # TODO: Remove tyTypeDesc from each abstractX and (where necessary)
- # replace with typedescX
- abstractPtrs* = {tyVar, tyPtr, tyRef, tyGenericInst, tyDistinct, tyOrdinal,
- tyTypeDesc, tyAlias, tyInferred}
- abstractVar* = {tyVar, tyGenericInst, tyDistinct, tyOrdinal, tyTypeDesc,
- tyAlias, tyInferred}
- abstractRange* = {tyGenericInst, tyRange, tyDistinct, tyOrdinal, tyTypeDesc,
- tyAlias, tyInferred}
- abstractVarRange* = {tyGenericInst, tyRange, tyVar, tyDistinct, tyOrdinal,
- tyTypeDesc, tyAlias, tyInferred}
- abstractInst* = {tyGenericInst, tyDistinct, tyOrdinal, tyTypeDesc, tyAlias,
- tyInferred}
- skipPtrs* = {tyVar, tyPtr, tyRef, tyGenericInst, tyTypeDesc, tyAlias,
- tyInferred}
- # typedescX is used if we're sure tyTypeDesc should be included (or skipped)
- typedescPtrs* = abstractPtrs + {tyTypeDesc}
- typedescInst* = abstractInst + {tyTypeDesc}
- type
- TTypeFieldResult* = enum
- frNone, # type has no object type field
- frHeader, # type has an object type field only in the header
- frEmbedded # type has an object type field somewhere embedded
- proc analyseObjectWithTypeField*(t: PType): TTypeFieldResult
- # this does a complex analysis whether a call to ``objectInit`` needs to be
- # made or intializing of the type field suffices or if there is no type field
- # at all in this type.
- proc invalidGenericInst*(f: PType): bool =
- result = f.kind == tyGenericInst and lastSon(f) == nil
- proc isPureObject*(typ: PType): bool =
- var t = typ
- while t.kind == tyObject and t.sons[0] != nil:
- t = t.sons[0].skipTypes(skipPtrs)
- result = t.sym != nil and sfPure in t.sym.flags
- proc getOrdValue*(n: PNode): BiggestInt =
- case n.kind
- of nkCharLit..nkUInt64Lit: result = n.intVal
- of nkNilLit: result = 0
- of nkHiddenStdConv: result = getOrdValue(n.sons[1])
- else:
- localError(n.info, errOrdinalTypeExpected)
- result = 0
- proc isIntLit*(t: PType): bool {.inline.} =
- result = t.kind == tyInt and t.n != nil and t.n.kind == nkIntLit
- proc isFloatLit*(t: PType): bool {.inline.} =
- result = t.kind == tyFloat and t.n != nil and t.n.kind == nkFloatLit
- proc getProcHeader*(sym: PSym; prefer: TPreferedDesc = preferName): string =
- result = sym.owner.name.s & '.' & sym.name.s & '('
- var n = sym.typ.n
- for i in countup(1, sonsLen(n) - 1):
- var p = n.sons[i]
- if p.kind == nkSym:
- add(result, p.sym.name.s)
- add(result, ": ")
- add(result, typeToString(p.sym.typ, prefer))
- if i != sonsLen(n)-1: add(result, ", ")
- else:
- internalError("getProcHeader")
- add(result, ')')
- if n.sons[0].typ != nil:
- result.add(": " & typeToString(n.sons[0].typ, prefer))
- result.add "[declared in "
- result.add($sym.info)
- result.add "]"
- proc elemType*(t: PType): PType =
- assert(t != nil)
- case t.kind
- of tyGenericInst, tyDistinct, tyAlias: result = elemType(lastSon(t))
- of tyArray: result = t.sons[1]
- else: result = t.lastSon
- assert(result != nil)
- proc isOrdinalType*(t: PType): bool =
- assert(t != nil)
- const
- # caution: uint, uint64 are no ordinal types!
- baseKinds = {tyChar,tyInt..tyInt64,tyUInt8..tyUInt32,tyBool,tyEnum}
- parentKinds = {tyRange, tyOrdinal, tyGenericInst, tyAlias, tyDistinct}
- t.kind in baseKinds or (t.kind in parentKinds and isOrdinalType(t.sons[0]))
- proc enumHasHoles*(t: PType): bool =
- var b = t
- while b.kind in {tyRange, tyGenericInst, tyAlias}: b = b.sons[0]
- result = b.kind == tyEnum and tfEnumHasHoles in b.flags
- proc iterOverTypeAux(marker: var IntSet, t: PType, iter: TTypeIter,
- closure: RootRef): bool
- proc iterOverNode(marker: var IntSet, n: PNode, iter: TTypeIter,
- closure: RootRef): bool =
- if n != nil:
- case n.kind
- of nkNone..nkNilLit:
- # a leaf
- result = iterOverTypeAux(marker, n.typ, iter, closure)
- else:
- for i in countup(0, sonsLen(n) - 1):
- result = iterOverNode(marker, n.sons[i], iter, closure)
- if result: return
- proc iterOverTypeAux(marker: var IntSet, t: PType, iter: TTypeIter,
- closure: RootRef): bool =
- result = false
- if t == nil: return
- result = iter(t, closure)
- if result: return
- if not containsOrIncl(marker, t.id):
- case t.kind
- of tyGenericInst, tyGenericBody, tyAlias, tyInferred:
- result = iterOverTypeAux(marker, lastSon(t), iter, closure)
- else:
- for i in countup(0, sonsLen(t) - 1):
- result = iterOverTypeAux(marker, t.sons[i], iter, closure)
- if result: return
- if t.n != nil: result = iterOverNode(marker, t.n, iter, closure)
- proc iterOverType(t: PType, iter: TTypeIter, closure: RootRef): bool =
- var marker = initIntSet()
- result = iterOverTypeAux(marker, t, iter, closure)
- proc searchTypeForAux(t: PType, predicate: TTypePredicate,
- marker: var IntSet): bool
- proc searchTypeNodeForAux(n: PNode, p: TTypePredicate,
- marker: var IntSet): bool =
- result = false
- case n.kind
- of nkRecList:
- for i in countup(0, sonsLen(n) - 1):
- result = searchTypeNodeForAux(n.sons[i], p, marker)
- if result: return
- of nkRecCase:
- assert(n.sons[0].kind == nkSym)
- result = searchTypeNodeForAux(n.sons[0], p, marker)
- if result: return
- for i in countup(1, sonsLen(n) - 1):
- case n.sons[i].kind
- of nkOfBranch, nkElse:
- result = searchTypeNodeForAux(lastSon(n.sons[i]), p, marker)
- if result: return
- else: internalError("searchTypeNodeForAux(record case branch)")
- of nkSym:
- result = searchTypeForAux(n.sym.typ, p, marker)
- else: internalError(n.info, "searchTypeNodeForAux()")
- proc searchTypeForAux(t: PType, predicate: TTypePredicate,
- marker: var IntSet): bool =
- # iterates over VALUE types!
- result = false
- if t == nil: return
- if containsOrIncl(marker, t.id): return
- result = predicate(t)
- if result: return
- case t.kind
- of tyObject:
- if t.sons[0] != nil:
- result = searchTypeForAux(t.sons[0].skipTypes(skipPtrs), predicate, marker)
- if not result: result = searchTypeNodeForAux(t.n, predicate, marker)
- of tyGenericInst, tyDistinct, tyAlias:
- result = searchTypeForAux(lastSon(t), predicate, marker)
- of tyArray, tySet, tyTuple:
- for i in countup(0, sonsLen(t) - 1):
- result = searchTypeForAux(t.sons[i], predicate, marker)
- if result: return
- else:
- discard
- proc searchTypeFor(t: PType, predicate: TTypePredicate): bool =
- var marker = initIntSet()
- result = searchTypeForAux(t, predicate, marker)
- proc isObjectPredicate(t: PType): bool =
- result = t.kind == tyObject
- proc containsObject*(t: PType): bool =
- result = searchTypeFor(t, isObjectPredicate)
- proc isObjectWithTypeFieldPredicate(t: PType): bool =
- result = t.kind == tyObject and t.sons[0] == nil and
- not (t.sym != nil and {sfPure, sfInfixCall} * t.sym.flags != {}) and
- tfFinal notin t.flags
- proc analyseObjectWithTypeFieldAux(t: PType,
- marker: var IntSet): TTypeFieldResult =
- var res: TTypeFieldResult
- result = frNone
- if t == nil: return
- case t.kind
- of tyObject:
- if (t.n != nil):
- if searchTypeNodeForAux(t.n, isObjectWithTypeFieldPredicate, marker):
- return frEmbedded
- for i in countup(0, sonsLen(t) - 1):
- var x = t.sons[i]
- if x != nil: x = x.skipTypes(skipPtrs)
- res = analyseObjectWithTypeFieldAux(x, marker)
- if res == frEmbedded:
- return frEmbedded
- if res == frHeader: result = frHeader
- if result == frNone:
- if isObjectWithTypeFieldPredicate(t): result = frHeader
- of tyGenericInst, tyDistinct, tyAlias:
- result = analyseObjectWithTypeFieldAux(lastSon(t), marker)
- of tyArray, tyTuple:
- for i in countup(0, sonsLen(t) - 1):
- res = analyseObjectWithTypeFieldAux(t.sons[i], marker)
- if res != frNone:
- return frEmbedded
- else:
- discard
- proc analyseObjectWithTypeField(t: PType): TTypeFieldResult =
- var marker = initIntSet()
- result = analyseObjectWithTypeFieldAux(t, marker)
- proc isGCRef(t: PType): bool =
- result = t.kind in GcTypeKinds or
- (t.kind == tyProc and t.callConv == ccClosure)
- proc containsGarbageCollectedRef*(typ: PType): bool =
- # returns true if typ contains a reference, sequence or string (all the
- # things that are garbage-collected)
- result = searchTypeFor(typ, isGCRef)
- proc isTyRef(t: PType): bool =
- result = t.kind == tyRef or (t.kind == tyProc and t.callConv == ccClosure)
- proc containsTyRef*(typ: PType): bool =
- # returns true if typ contains a 'ref'
- result = searchTypeFor(typ, isTyRef)
- proc isHiddenPointer(t: PType): bool =
- result = t.kind in {tyString, tySequence}
- proc containsHiddenPointer*(typ: PType): bool =
- # returns true if typ contains a string, table or sequence (all the things
- # that need to be copied deeply)
- result = searchTypeFor(typ, isHiddenPointer)
- proc canFormAcycleAux(marker: var IntSet, typ: PType, startId: int): bool
- proc canFormAcycleNode(marker: var IntSet, n: PNode, startId: int): bool =
- result = false
- if n != nil:
- result = canFormAcycleAux(marker, n.typ, startId)
- if not result:
- case n.kind
- of nkNone..nkNilLit:
- discard
- else:
- for i in countup(0, sonsLen(n) - 1):
- result = canFormAcycleNode(marker, n.sons[i], startId)
- if result: return
- proc canFormAcycleAux(marker: var IntSet, typ: PType, startId: int): bool =
- result = false
- if typ == nil: return
- if tfAcyclic in typ.flags: return
- var t = skipTypes(typ, abstractInst-{tyTypeDesc})
- if tfAcyclic in t.flags: return
- case t.kind
- of tyTuple, tyObject, tyRef, tySequence, tyArray, tyOpenArray, tyVarargs:
- if not containsOrIncl(marker, t.id):
- for i in countup(0, sonsLen(t) - 1):
- result = canFormAcycleAux(marker, t.sons[i], startId)
- if result: return
- if t.n != nil: result = canFormAcycleNode(marker, t.n, startId)
- else:
- result = t.id == startId
- # Inheritance can introduce cyclic types, however this is not relevant
- # as the type that is passed to 'new' is statically known!
- # er but we use it also for the write barrier ...
- if t.kind == tyObject and tfFinal notin t.flags:
- # damn inheritance may introduce cycles:
- result = true
- of tyProc: result = typ.callConv == ccClosure
- else: discard
- proc canFormAcycle*(typ: PType): bool =
- var marker = initIntSet()
- result = canFormAcycleAux(marker, typ, typ.id)
- proc mutateTypeAux(marker: var IntSet, t: PType, iter: TTypeMutator,
- closure: RootRef): PType
- proc mutateNode(marker: var IntSet, n: PNode, iter: TTypeMutator,
- closure: RootRef): PNode =
- result = nil
- if n != nil:
- result = copyNode(n)
- result.typ = mutateTypeAux(marker, n.typ, iter, closure)
- case n.kind
- of nkNone..nkNilLit:
- # a leaf
- discard
- else:
- for i in countup(0, sonsLen(n) - 1):
- addSon(result, mutateNode(marker, n.sons[i], iter, closure))
- proc mutateTypeAux(marker: var IntSet, t: PType, iter: TTypeMutator,
- closure: RootRef): PType =
- result = nil
- if t == nil: return
- result = iter(t, closure)
- if not containsOrIncl(marker, t.id):
- for i in countup(0, sonsLen(t) - 1):
- result.sons[i] = mutateTypeAux(marker, result.sons[i], iter, closure)
- if t.n != nil: result.n = mutateNode(marker, t.n, iter, closure)
- assert(result != nil)
- proc mutateType(t: PType, iter: TTypeMutator, closure: RootRef): PType =
- var marker = initIntSet()
- result = mutateTypeAux(marker, t, iter, closure)
- proc valueToString(a: PNode): string =
- case a.kind
- of nkCharLit..nkUInt64Lit: result = $a.intVal
- of nkFloatLit..nkFloat128Lit: result = $a.floatVal
- of nkStrLit..nkTripleStrLit: result = a.strVal
- else: result = "<invalid value>"
- proc rangeToStr(n: PNode): string =
- assert(n.kind == nkRange)
- result = valueToString(n.sons[0]) & ".." & valueToString(n.sons[1])
- const
- typeToStr: array[TTypeKind, string] = ["None", "bool", "Char", "empty",
- "Alias", "nil", "untyped", "typed", "typeDesc",
- "GenericInvocation", "GenericBody", "GenericInst", "GenericParam",
- "distinct $1", "enum", "ordinal[$1]", "array[$1, $2]", "object", "tuple",
- "set[$1]", "range[$1]", "ptr ", "ref ", "var ", "seq[$1]", "proc",
- "pointer", "OpenArray[$1]", "string", "CString", "Forward",
- "int", "int8", "int16", "int32", "int64",
- "float", "float32", "float64", "float128",
- "uint", "uint8", "uint16", "uint32", "uint64",
- "unused0", "unused1",
- "unused2", "varargs[$1]", "unused", "Error Type",
- "BuiltInTypeClass", "UserTypeClass",
- "UserTypeClassInst", "CompositeTypeClass", "inferred",
- "and", "or", "not", "any", "static", "TypeFromExpr", "FieldAccessor",
- "void"]
- const preferToResolveSymbols = {preferName, preferModuleInfo, preferGenericArg}
- template bindConcreteTypeToUserTypeClass*(tc, concrete: PType) =
- tc.sons.safeAdd concrete
- tc.flags.incl tfResolved
- # TODO: It would be a good idea to kill the special state of a resolved
- # concept by switching to tyAlias within the instantiated procs.
- # Currently, tyAlias is always skipped with lastSon, which means that
- # we can store information about the matched concept in another position.
- # Then builtInFieldAccess can be modified to properly read the derived
- # consts and types stored within the concept.
- template isResolvedUserTypeClass*(t: PType): bool =
- tfResolved in t.flags
- proc addTypeFlags(name: var string, typ: PType) {.inline.} =
- if tfNotNil in typ.flags: name.add(" not nil")
- proc typeToString(typ: PType, prefer: TPreferedDesc = preferName): string =
- var t = typ
- result = ""
- if t == nil: return
- if prefer in preferToResolveSymbols and t.sym != nil and
- sfAnon notin t.sym.flags:
- if t.kind == tyInt and isIntLit(t):
- result = t.sym.name.s & " literal(" & $t.n.intVal & ")"
- elif prefer == preferName or t.sym.owner.isNil:
- result = t.sym.name.s
- if t.kind == tyGenericParam and t.sons != nil and t.sonsLen > 0:
- result.add ": "
- var first = true
- for son in t.sons:
- if not first: result.add " or "
- result.add son.typeToString
- first = false
- else:
- result = t.sym.owner.name.s & '.' & t.sym.name.s
- result.addTypeFlags(t)
- return
- case t.kind
- of tyInt:
- if not isIntLit(t) or prefer == preferExported:
- result = typeToStr[t.kind]
- else:
- if prefer == preferGenericArg:
- result = $t.n.intVal
- else:
- result = "int literal(" & $t.n.intVal & ")"
- of tyGenericBody, tyGenericInst, tyGenericInvocation:
- result = typeToString(t.sons[0]) & '['
- for i in countup(1, sonsLen(t)-1-ord(t.kind != tyGenericInvocation)):
- if i > 1: add(result, ", ")
- add(result, typeToString(t.sons[i], preferGenericArg))
- add(result, ']')
- of tyTypeDesc:
- if t.sons[0].kind == tyNone: result = "typedesc"
- else: result = "type " & typeToString(t.sons[0])
- of tyStatic:
- internalAssert t.len > 0
- if prefer == preferGenericArg and t.n != nil:
- result = t.n.renderTree
- else:
- result = "static[" & typeToString(t.sons[0]) & "]"
- if t.n != nil: result.add "(" & renderTree(t.n) & ")"
- of tyUserTypeClass:
- internalAssert t.sym != nil and t.sym.owner != nil
- if t.isResolvedUserTypeClass: return typeToString(t.lastSon)
- return t.sym.owner.name.s
- of tyBuiltInTypeClass:
- result = case t.base.kind:
- of tyVar: "var"
- of tyRef: "ref"
- of tyPtr: "ptr"
- of tySequence: "seq"
- of tyArray: "array"
- of tySet: "set"
- of tyRange: "range"
- of tyDistinct: "distinct"
- of tyProc: "proc"
- of tyObject: "object"
- of tyTuple: "tuple"
- of tyOpenArray: "openarray"
- else: typeToStr[t.base.kind]
- of tyInferred:
- let concrete = t.previouslyInferred
- if concrete != nil: result = typeToString(concrete)
- else: result = "inferred[" & typeToString(t.base) & "]"
- of tyUserTypeClassInst:
- let body = t.base
- result = body.sym.name.s & "["
- for i in countup(1, sonsLen(t) - 2):
- if i > 1: add(result, ", ")
- add(result, typeToString(t.sons[i]))
- result.add "]"
- of tyAnd:
- result = typeToString(t.sons[0]) & " and " & typeToString(t.sons[1])
- of tyOr:
- result = typeToString(t.sons[0]) & " or " & typeToString(t.sons[1])
- of tyNot:
- result = "not " & typeToString(t.sons[0])
- of tyExpr:
- internalAssert t.len == 0
- result = "untyped"
- of tyFromExpr:
- result = renderTree(t.n)
- of tyArray:
- if t.sons[0].kind == tyRange:
- result = "array[" & rangeToStr(t.sons[0].n) & ", " &
- typeToString(t.sons[1]) & ']'
- else:
- result = "array[" & typeToString(t.sons[0]) & ", " &
- typeToString(t.sons[1]) & ']'
- of tySequence:
- result = "seq[" & typeToString(t.sons[0]) & ']'
- of tyOpt:
- result = "opt[" & typeToString(t.sons[0]) & ']'
- of tyOrdinal:
- result = "ordinal[" & typeToString(t.sons[0]) & ']'
- of tySet:
- result = "set[" & typeToString(t.sons[0]) & ']'
- of tyOpenArray:
- result = "openarray[" & typeToString(t.sons[0]) & ']'
- of tyDistinct:
- result = "distinct " & typeToString(t.sons[0],
- if prefer == preferModuleInfo: preferModuleInfo else: preferName)
- of tyTuple:
- # we iterate over t.sons here, because t.n may be nil
- if t.n != nil:
- result = "tuple["
- assert(sonsLen(t.n) == sonsLen(t))
- for i in countup(0, sonsLen(t.n) - 1):
- assert(t.n.sons[i].kind == nkSym)
- add(result, t.n.sons[i].sym.name.s & ": " & typeToString(t.sons[i]))
- if i < sonsLen(t.n) - 1: add(result, ", ")
- add(result, ']')
- elif sonsLen(t) == 0:
- result = "tuple[]"
- else:
- result = "("
- for i in countup(0, sonsLen(t) - 1):
- add(result, typeToString(t.sons[i]))
- if i < sonsLen(t) - 1: add(result, ", ")
- add(result, ')')
- of tyPtr, tyRef, tyVar:
- result = typeToStr[t.kind]
- if t.len >= 2:
- setLen(result, result.len-1)
- result.add '['
- for i in countup(0, sonsLen(t) - 1):
- add(result, typeToString(t.sons[i]))
- if i < sonsLen(t) - 1: add(result, ", ")
- result.add ']'
- else:
- result.add typeToString(t.sons[0])
- of tyRange:
- result = "range "
- if t.n != nil and t.n.kind == nkRange:
- result.add rangeToStr(t.n)
- if prefer != preferExported:
- result.add("(" & typeToString(t.sons[0]) & ")")
- of tyProc:
- result = if tfIterator in t.flags: "iterator " else: "proc "
- if tfUnresolved in t.flags: result.add "[*missing parameters*]"
- result.add "("
- for i in countup(1, sonsLen(t) - 1):
- if t.n != nil and i < t.n.len and t.n[i].kind == nkSym:
- add(result, t.n[i].sym.name.s)
- add(result, ": ")
- add(result, typeToString(t.sons[i]))
- if i < sonsLen(t) - 1: add(result, ", ")
- add(result, ')')
- if t.sons[0] != nil: add(result, ": " & typeToString(t.sons[0]))
- var prag = if t.callConv == ccDefault: "" else: CallingConvToStr[t.callConv]
- if tfNoSideEffect in t.flags:
- addSep(prag)
- add(prag, "noSideEffect")
- if tfThread in t.flags:
- addSep(prag)
- add(prag, "gcsafe")
- if t.lockLevel.ord != UnspecifiedLockLevel.ord:
- addSep(prag)
- add(prag, "locks: " & $t.lockLevel)
- if len(prag) != 0: add(result, "{." & prag & ".}")
- of tyVarargs:
- result = typeToStr[t.kind] % typeToString(t.sons[0])
- else:
- result = typeToStr[t.kind]
- result.addTypeFlags(t)
- proc firstOrd*(t: PType): BiggestInt =
- case t.kind
- of tyBool, tyChar, tySequence, tyOpenArray, tyString, tyVarargs, tyProxy:
- result = 0
- of tySet, tyVar: result = firstOrd(t.sons[0])
- of tyArray: result = firstOrd(t.sons[0])
- of tyRange:
- assert(t.n != nil) # range directly given:
- assert(t.n.kind == nkRange)
- result = getOrdValue(t.n.sons[0])
- of tyInt:
- if platform.intSize == 4: result = - (2147483646) - 2
- else: result = 0x8000000000000000'i64
- of tyInt8: result = - 128
- of tyInt16: result = - 32768
- of tyInt32: result = - 2147483646 - 2
- of tyInt64: result = 0x8000000000000000'i64
- of tyUInt..tyUInt64: result = 0
- of tyEnum:
- # if basetype <> nil then return firstOrd of basetype
- if sonsLen(t) > 0 and t.sons[0] != nil:
- result = firstOrd(t.sons[0])
- else:
- assert(t.n.sons[0].kind == nkSym)
- result = t.n.sons[0].sym.position
- of tyGenericInst, tyDistinct, tyTypeDesc, tyAlias:
- result = firstOrd(lastSon(t))
- of tyOrdinal:
- if t.len > 0: result = firstOrd(lastSon(t))
- else: internalError("invalid kind for first(" & $t.kind & ')')
- else:
- internalError("invalid kind for first(" & $t.kind & ')')
- result = 0
- proc lastOrd*(t: PType): BiggestInt =
- case t.kind
- of tyBool: result = 1
- of tyChar: result = 255
- of tySet, tyVar: result = lastOrd(t.sons[0])
- of tyArray: result = lastOrd(t.sons[0])
- of tyRange:
- assert(t.n != nil) # range directly given:
- assert(t.n.kind == nkRange)
- result = getOrdValue(t.n.sons[1])
- of tyInt:
- if platform.intSize == 4: result = 0x7FFFFFFF
- else: result = 0x7FFFFFFFFFFFFFFF'i64
- of tyInt8: result = 0x0000007F
- of tyInt16: result = 0x00007FFF
- of tyInt32: result = 0x7FFFFFFF
- of tyInt64: result = 0x7FFFFFFFFFFFFFFF'i64
- of tyUInt:
- if platform.intSize == 4: result = 0xFFFFFFFF
- else: result = 0x7FFFFFFFFFFFFFFF'i64
- of tyUInt8: result = 0xFF
- of tyUInt16: result = 0xFFFF
- of tyUInt32: result = 0xFFFFFFFF
- of tyUInt64: result = 0x7FFFFFFFFFFFFFFF'i64
- of tyEnum:
- assert(t.n.sons[sonsLen(t.n) - 1].kind == nkSym)
- result = t.n.sons[sonsLen(t.n) - 1].sym.position
- of tyGenericInst, tyDistinct, tyTypeDesc, tyAlias:
- result = lastOrd(lastSon(t))
- of tyProxy: result = 0
- of tyOrdinal:
- if t.len > 0: result = lastOrd(lastSon(t))
- else: internalError("invalid kind for last(" & $t.kind & ')')
- else:
- internalError("invalid kind for last(" & $t.kind & ')')
- result = 0
- proc lengthOrd*(t: PType): BiggestInt =
- case t.kind
- of tyInt64, tyInt32, tyInt: result = lastOrd(t)
- of tyDistinct: result = lengthOrd(t.sons[0])
- else:
- let last = lastOrd t
- let first = firstOrd t
- # XXX use a better overflow check here:
- if last == high(BiggestInt) and first <= 0:
- result = last
- else:
- result = lastOrd(t) - firstOrd(t) + 1
- # -------------- type equality -----------------------------------------------
- type
- TDistinctCompare* = enum ## how distinct types are to be compared
- dcEq, ## a and b should be the same type
- dcEqIgnoreDistinct, ## compare symmetrically: (distinct a) == b, a == b
- ## or a == (distinct b)
- dcEqOrDistinctOf ## a equals b or a is distinct of b
- TTypeCmpFlag* = enum
- IgnoreTupleFields ## NOTE: Only set this flag for backends!
- IgnoreCC
- ExactTypeDescValues
- ExactGenericParams
- ExactConstraints
- ExactGcSafety
- AllowCommonBase
- TTypeCmpFlags* = set[TTypeCmpFlag]
- TSameTypeClosure = object {.pure.}
- cmp: TDistinctCompare
- recCheck: int
- flags: TTypeCmpFlags
- s: seq[tuple[a,b: int]] # seq for a set as it's hopefully faster
- # (few elements expected)
- proc initSameTypeClosure: TSameTypeClosure =
- # we do the initialization lazily for performance (avoids memory allocations)
- discard
- proc containsOrIncl(c: var TSameTypeClosure, a, b: PType): bool =
- result = not isNil(c.s) and c.s.contains((a.id, b.id))
- if not result:
- if isNil(c.s): c.s = @[]
- c.s.add((a.id, b.id))
- proc sameTypeAux(x, y: PType, c: var TSameTypeClosure): bool
- proc sameTypeOrNilAux(a, b: PType, c: var TSameTypeClosure): bool =
- if a == b:
- result = true
- else:
- if a == nil or b == nil: result = false
- else: result = sameTypeAux(a, b, c)
- proc sameType*(a, b: PType, flags: TTypeCmpFlags = {}): bool =
- var c = initSameTypeClosure()
- c.flags = flags
- result = sameTypeAux(a, b, c)
- proc sameTypeOrNil*(a, b: PType, flags: TTypeCmpFlags = {}): bool =
- if a == b:
- result = true
- else:
- if a == nil or b == nil: result = false
- else: result = sameType(a, b, flags)
- proc equalParam(a, b: PSym): TParamsEquality =
- if sameTypeOrNil(a.typ, b.typ, {ExactTypeDescValues}) and
- exprStructuralEquivalent(a.constraint, b.constraint):
- if a.ast == b.ast:
- result = paramsEqual
- elif a.ast != nil and b.ast != nil:
- if exprStructuralEquivalent(a.ast, b.ast): result = paramsEqual
- else: result = paramsIncompatible
- elif a.ast != nil:
- result = paramsEqual
- elif b.ast != nil:
- result = paramsIncompatible
- else:
- result = paramsNotEqual
- proc sameConstraints(a, b: PNode): bool =
- if isNil(a) and isNil(b): return true
- internalAssert a.len == b.len
- for i in 1 .. <a.len:
- if not exprStructuralEquivalent(a[i].sym.constraint,
- b[i].sym.constraint):
- return false
- return true
- proc equalParams(a, b: PNode): TParamsEquality =
- result = paramsEqual
- var length = sonsLen(a)
- if length != sonsLen(b):
- result = paramsNotEqual
- else:
- for i in countup(1, length - 1):
- var m = a.sons[i].sym
- var n = b.sons[i].sym
- assert((m.kind == skParam) and (n.kind == skParam))
- case equalParam(m, n)
- of paramsNotEqual:
- return paramsNotEqual
- of paramsEqual:
- discard
- of paramsIncompatible:
- result = paramsIncompatible
- if (m.name.id != n.name.id):
- # BUGFIX
- return paramsNotEqual # paramsIncompatible;
- # continue traversal! If not equal, we can return immediately; else
- # it stays incompatible
- if not sameTypeOrNil(a.sons[0].typ, b.sons[0].typ, {ExactTypeDescValues}):
- if (a.sons[0].typ == nil) or (b.sons[0].typ == nil):
- result = paramsNotEqual # one proc has a result, the other not is OK
- else:
- result = paramsIncompatible # overloading by different
- # result types does not work
- proc sameTuple(a, b: PType, c: var TSameTypeClosure): bool =
- # two tuples are equivalent iff the names, types and positions are the same;
- # however, both types may not have any field names (t.n may be nil) which
- # complicates the matter a bit.
- if sonsLen(a) == sonsLen(b):
- result = true
- for i in countup(0, sonsLen(a) - 1):
- var x = a.sons[i]
- var y = b.sons[i]
- if IgnoreTupleFields in c.flags:
- x = skipTypes(x, {tyRange, tyGenericInst, tyAlias})
- y = skipTypes(y, {tyRange, tyGenericInst, tyAlias})
- result = sameTypeAux(x, y, c)
- if not result: return
- if a.n != nil and b.n != nil and IgnoreTupleFields notin c.flags:
- for i in countup(0, sonsLen(a.n) - 1):
- # check field names:
- if a.n.sons[i].kind == nkSym and b.n.sons[i].kind == nkSym:
- var x = a.n.sons[i].sym
- var y = b.n.sons[i].sym
- result = x.name.id == y.name.id
- if not result: break
- else: internalError(a.n.info, "sameTuple")
- elif a.n != b.n and (a.n == nil or b.n == nil) and IgnoreTupleFields notin c.flags:
- result = false
- template ifFastObjectTypeCheckFailed(a, b: PType, body: untyped) =
- if tfFromGeneric notin a.flags + b.flags:
- # fast case: id comparison suffices:
- result = a.id == b.id
- else:
- # expensive structural equality test; however due to the way generic and
- # objects work, if one of the types does **not** contain tfFromGeneric,
- # they cannot be equal. The check ``a.sym.id == b.sym.id`` checks
- # for the same origin and is essential because we don't want "pure"
- # structural type equivalence:
- #
- # type
- # TA[T] = object
- # TB[T] = object
- # --> TA[int] != TB[int]
- if tfFromGeneric in a.flags * b.flags and a.sym.id == b.sym.id:
- # ok, we need the expensive structural check
- body
- proc sameObjectTypes*(a, b: PType): bool =
- # specialized for efficiency (sigmatch uses it)
- ifFastObjectTypeCheckFailed(a, b):
- var c = initSameTypeClosure()
- result = sameTypeAux(a, b, c)
- proc sameDistinctTypes*(a, b: PType): bool {.inline.} =
- result = sameObjectTypes(a, b)
- proc sameEnumTypes*(a, b: PType): bool {.inline.} =
- result = a.id == b.id
- proc sameObjectTree(a, b: PNode, c: var TSameTypeClosure): bool =
- if a == b:
- result = true
- elif a != nil and b != nil and a.kind == b.kind:
- var x = a.typ
- var y = b.typ
- if IgnoreTupleFields in c.flags:
- if x != nil: x = skipTypes(x, {tyRange, tyGenericInst, tyAlias})
- if y != nil: y = skipTypes(y, {tyRange, tyGenericInst, tyAlias})
- if sameTypeOrNilAux(x, y, c):
- case a.kind
- of nkSym:
- # same symbol as string is enough:
- result = a.sym.name.id == b.sym.name.id
- of nkIdent: result = a.ident.id == b.ident.id
- of nkCharLit..nkInt64Lit: result = a.intVal == b.intVal
- of nkFloatLit..nkFloat64Lit: result = a.floatVal == b.floatVal
- of nkStrLit..nkTripleStrLit: result = a.strVal == b.strVal
- of nkEmpty, nkNilLit, nkType: result = true
- else:
- if sonsLen(a) == sonsLen(b):
- for i in countup(0, sonsLen(a) - 1):
- if not sameObjectTree(a.sons[i], b.sons[i], c): return
- result = true
- proc sameObjectStructures(a, b: PType, c: var TSameTypeClosure): bool =
- # check base types:
- if sonsLen(a) != sonsLen(b): return
- for i in countup(0, sonsLen(a) - 1):
- if not sameTypeOrNilAux(a.sons[i], b.sons[i], c): return
- if not sameObjectTree(a.n, b.n, c): return
- result = true
- proc sameChildrenAux(a, b: PType, c: var TSameTypeClosure): bool =
- if sonsLen(a) != sonsLen(b): return false
- result = true
- for i in countup(0, sonsLen(a) - 1):
- result = sameTypeOrNilAux(a.sons[i], b.sons[i], c)
- if not result: return
- proc isGenericAlias*(t: PType): bool =
- return t.kind == tyGenericInst and t.lastSon.kind == tyGenericInst
- proc skipGenericAlias*(t: PType): PType =
- return if t.isGenericAlias: t.lastSon else: t
- proc sameFlags*(a, b: PType): bool {.inline.} =
- result = eqTypeFlags*a.flags == eqTypeFlags*b.flags
- proc sameTypeAux(x, y: PType, c: var TSameTypeClosure): bool =
- template cycleCheck() =
- # believe it or not, the direct check for ``containsOrIncl(c, a, b)``
- # increases bootstrapping time from 2.4s to 3.3s on my laptop! So we cheat
- # again: Since the recursion check is only to not get caught in an endless
- # recursion, we use a counter and only if it's value is over some
- # threshold we perform the expensive exact cycle check:
- if c.recCheck < 3:
- inc c.recCheck
- else:
- if containsOrIncl(c, a, b): return true
- if x == y: return true
- var a = skipTypes(x, {tyGenericInst, tyAlias})
- var b = skipTypes(y, {tyGenericInst, tyAlias})
- assert(a != nil)
- assert(b != nil)
- if a.kind != b.kind:
- case c.cmp
- of dcEq: return false
- of dcEqIgnoreDistinct:
- while a.kind == tyDistinct: a = a.sons[0]
- while b.kind == tyDistinct: b = b.sons[0]
- if a.kind != b.kind: return false
- of dcEqOrDistinctOf:
- while a.kind == tyDistinct: a = a.sons[0]
- if a.kind != b.kind: return false
- # this is required by tunique_type but makes no sense really:
- if x.kind == tyGenericInst and IgnoreTupleFields notin c.flags:
- let
- lhs = x.skipGenericAlias
- rhs = y.skipGenericAlias
- if rhs.kind != tyGenericInst or lhs.base != rhs.base:
- return false
- for i in 1 .. lhs.len - 2:
- let ff = rhs.sons[i]
- let aa = lhs.sons[i]
- if not sameTypeAux(ff, aa, c): return false
- return true
- case a.kind
- of tyEmpty, tyChar, tyBool, tyNil, tyPointer, tyString, tyCString,
- tyInt..tyUInt64, tyStmt, tyExpr, tyVoid:
- result = sameFlags(a, b)
- of tyStatic, tyFromExpr:
- result = exprStructuralEquivalent(a.n, b.n) and sameFlags(a, b)
- if result and a.len == b.len and a.len == 1:
- cycleCheck()
- result = sameTypeAux(a.sons[0], b.sons[0], c)
- of tyObject:
- ifFastObjectTypeCheckFailed(a, b):
- cycleCheck()
- result = sameObjectStructures(a, b, c) and sameFlags(a, b)
- of tyDistinct:
- cycleCheck()
- if c.cmp == dcEq:
- if sameFlags(a, b):
- ifFastObjectTypeCheckFailed(a, b):
- result = sameTypeAux(a.sons[0], b.sons[0], c)
- else:
- result = sameTypeAux(a.sons[0], b.sons[0], c) and sameFlags(a, b)
- of tyEnum, tyForward:
- # XXX generic enums do not make much sense, but require structural checking
- result = a.id == b.id and sameFlags(a, b)
- of tyError:
- result = b.kind == tyError
- of tyTuple:
- cycleCheck()
- result = sameTuple(a, b, c) and sameFlags(a, b)
- of tyTypeDesc:
- if c.cmp == dcEqIgnoreDistinct: result = false
- elif ExactTypeDescValues in c.flags:
- cycleCheck()
- result = sameChildrenAux(x, y, c) and sameFlags(a, b)
- else:
- result = sameFlags(a, b)
- of tyGenericParam:
- result = sameChildrenAux(a, b, c) and sameFlags(a, b)
- if result and ExactGenericParams in c.flags:
- result = a.sym.position == b.sym.position
- of tyGenericInvocation, tyGenericBody, tySequence,
- tyOpenArray, tySet, tyRef, tyPtr, tyVar,
- tyArray, tyProc, tyVarargs, tyOrdinal, tyTypeClasses, tyOpt:
- cycleCheck()
- if a.kind == tyUserTypeClass and a.n != nil: return a.n == b.n
- result = sameChildrenAux(a, b, c) and sameFlags(a, b)
- if result and ExactGcSafety in c.flags:
- result = a.flags * {tfThread} == b.flags * {tfThread}
- if result and a.kind == tyProc:
- result = ((IgnoreCC in c.flags) or a.callConv == b.callConv) and
- ((ExactConstraints notin c.flags) or sameConstraints(a.n, b.n))
- of tyRange:
- cycleCheck()
- result = sameTypeOrNilAux(a.sons[0], b.sons[0], c) and
- sameValue(a.n.sons[0], b.n.sons[0]) and
- sameValue(a.n.sons[1], b.n.sons[1])
- of tyGenericInst, tyAlias, tyInferred:
- cycleCheck()
- result = sameTypeAux(a.lastSon, b.lastSon, c)
- of tyNone: result = false
- of tyUnused, tyOptAsRef, tyUnused1, tyUnused2: internalError("sameFlags")
- proc sameBackendType*(x, y: PType): bool =
- var c = initSameTypeClosure()
- c.flags.incl IgnoreTupleFields
- result = sameTypeAux(x, y, c)
- proc compareTypes*(x, y: PType,
- cmp: TDistinctCompare = dcEq,
- flags: TTypeCmpFlags = {}): bool =
- ## compares two type for equality (modulo type distinction)
- var c = initSameTypeClosure()
- c.cmp = cmp
- c.flags = flags
- if x == y: result = true
- elif x.isNil or y.isNil: result = false
- else: result = sameTypeAux(x, y, c)
- proc inheritanceDiff*(a, b: PType): int =
- # | returns: 0 iff `a` == `b`
- # | returns: -x iff `a` is the x'th direct superclass of `b`
- # | returns: +x iff `a` is the x'th direct subclass of `b`
- # | returns: `maxint` iff `a` and `b` are not compatible at all
- if a == b or a.kind == tyError or b.kind == tyError: return 0
- assert a.kind == tyObject
- assert b.kind == tyObject
- var x = a
- result = 0
- while x != nil:
- x = skipTypes(x, skipPtrs)
- if sameObjectTypes(x, b): return
- x = x.sons[0]
- dec(result)
- var y = b
- result = 0
- while y != nil:
- y = skipTypes(y, skipPtrs)
- if sameObjectTypes(y, a): return
- y = y.sons[0]
- inc(result)
- result = high(int)
- proc commonSuperclass*(a, b: PType): PType =
- # quick check: are they the same?
- if sameObjectTypes(a, b): return a
- # simple algorithm: we store all ancestors of 'a' in a ID-set and walk 'b'
- # up until the ID is found:
- assert a.kind == tyObject
- assert b.kind == tyObject
- var x = a
- var ancestors = initIntSet()
- while x != nil:
- x = skipTypes(x, skipPtrs)
- ancestors.incl(x.id)
- x = x.sons[0]
- var y = b
- while y != nil:
- y = skipTypes(y, skipPtrs)
- if ancestors.contains(y.id): return y
- y = y.sons[0]
- type
- TTypeAllowedFlag = enum
- taField,
- taHeap
- TTypeAllowedFlags = set[TTypeAllowedFlag]
- proc typeAllowedAux(marker: var IntSet, typ: PType, kind: TSymKind,
- flags: TTypeAllowedFlags = {}): PType
- proc typeAllowedNode(marker: var IntSet, n: PNode, kind: TSymKind,
- flags: TTypeAllowedFlags = {}): PType =
- if n != nil:
- result = typeAllowedAux(marker, n.typ, kind, flags)
- #if not result: debug(n.typ)
- if result == nil:
- case n.kind
- of nkNone..nkNilLit:
- discard
- else:
- if n.kind == nkRecCase and kind in {skProc, skFunc, skConst}:
- return n[0].typ
- for i in countup(0, sonsLen(n) - 1):
- let it = n.sons[i]
- result = typeAllowedNode(marker, it, kind, flags)
- if result != nil: break
- proc matchType*(a: PType, pattern: openArray[tuple[k:TTypeKind, i:int]],
- last: TTypeKind): bool =
- var a = a
- for k, i in pattern.items:
- if a.kind != k: return false
- if i >= a.sonsLen or a.sons[i] == nil: return false
- a = a.sons[i]
- result = a.kind == last
- proc typeAllowedAux(marker: var IntSet, typ: PType, kind: TSymKind,
- flags: TTypeAllowedFlags = {}): PType =
- assert(kind in {skVar, skLet, skConst, skProc, skFunc, skParam, skResult})
- # if we have already checked the type, return true, because we stop the
- # evaluation if something is wrong:
- result = nil
- if typ == nil: return
- if containsOrIncl(marker, typ.id): return
- var t = skipTypes(typ, abstractInst-{tyTypeDesc})
- case t.kind
- of tyVar:
- if kind in {skProc, skFunc, skConst}: return t
- var t2 = skipTypes(t.sons[0], abstractInst-{tyTypeDesc})
- case t2.kind
- of tyVar:
- if taHeap notin flags: result = t2 # ``var var`` is illegal on the heap
- of tyOpenArray:
- if kind != skParam: result = t
- else: result = typeAllowedAux(marker, t2, kind, flags)
- else:
- if kind notin {skParam, skResult}: result = t
- else: result = typeAllowedAux(marker, t2, kind, flags)
- of tyProc:
- if kind == skConst and t.callConv == ccClosure: return t
- for i in countup(1, sonsLen(t) - 1):
- result = typeAllowedAux(marker, t.sons[i], skParam, flags)
- if result != nil: break
- if result.isNil and t.sons[0] != nil:
- result = typeAllowedAux(marker, t.sons[0], skResult, flags)
- of tyTypeDesc:
- # XXX: This is still a horrible idea...
- result = nil
- of tyExpr, tyStmt, tyStatic:
- if kind notin {skParam, skResult}: result = t
- of tyVoid:
- if taField notin flags: result = t
- of tyTypeClasses:
- if not (tfGenericTypeParam in t.flags or taField notin flags): result = t
- of tyGenericBody, tyGenericParam, tyGenericInvocation,
- tyNone, tyForward, tyFromExpr:
- result = t
- of tyNil:
- if kind != skConst: result = t
- of tyString, tyBool, tyChar, tyEnum, tyInt..tyUInt64, tyCString, tyPointer:
- result = nil
- of tyOrdinal:
- if kind != skParam: result = t
- of tyGenericInst, tyDistinct, tyAlias, tyInferred:
- result = typeAllowedAux(marker, lastSon(t), kind, flags)
- of tyRange:
- if skipTypes(t.sons[0], abstractInst-{tyTypeDesc}).kind notin
- {tyChar, tyEnum, tyInt..tyFloat128, tyUInt8..tyUInt32}: result = t
- of tyOpenArray, tyVarargs:
- if kind != skParam: result = t
- else: result = typeAllowedAux(marker, t.sons[0], skVar, flags)
- of tySequence, tyOpt:
- if t.sons[0].kind != tyEmpty:
- result = typeAllowedAux(marker, t.sons[0], skVar, flags+{taHeap})
- of tyArray:
- if t.sons[1].kind != tyEmpty:
- result = typeAllowedAux(marker, t.sons[1], skVar, flags)
- of tyRef:
- if kind == skConst: result = t
- else: result = typeAllowedAux(marker, t.lastSon, skVar, flags+{taHeap})
- of tyPtr:
- result = typeAllowedAux(marker, t.lastSon, skVar, flags+{taHeap})
- of tySet:
- for i in countup(0, sonsLen(t) - 1):
- result = typeAllowedAux(marker, t.sons[i], kind, flags)
- if result != nil: break
- of tyObject, tyTuple:
- if kind in {skProc, skFunc, skConst} and
- t.kind == tyObject and t.sons[0] != nil: return t
- let flags = flags+{taField}
- for i in countup(0, sonsLen(t) - 1):
- result = typeAllowedAux(marker, t.sons[i], kind, flags)
- if result != nil: break
- if result.isNil and t.n != nil:
- result = typeAllowedNode(marker, t.n, kind, flags)
- of tyProxy, tyEmpty:
- # for now same as error node; we say it's a valid type as it should
- # prevent cascading errors:
- result = nil
- of tyUnused, tyOptAsRef, tyUnused1, tyUnused2: internalError("typeAllowedAux")
- proc typeAllowed*(t: PType, kind: TSymKind): PType =
- # returns 'nil' on success and otherwise the part of the type that is
- # wrong!
- var marker = initIntSet()
- result = typeAllowedAux(marker, t, kind, {})
- proc align(address, alignment: BiggestInt): BiggestInt =
- result = (address + (alignment - 1)) and not (alignment - 1)
- type
- OptKind* = enum ## What to map 'opt T' to internally.
- oBool ## opt[T] requires an additional 'bool' field
- oNil ## opt[T] has no overhead since 'nil'
- ## is available
- oEnum ## We can use some enum value that is not yet
- ## used for opt[T]
- oPtr ## opt[T] actually introduces a hidden pointer
- ## in order for the type recursion to work
- proc optKind*(typ: PType): OptKind =
- ## return true iff 'opt[T]' can be mapped to 'T' internally
- ## because we have a 'nil' value available:
- assert typ.kind == tyOpt
- case typ.sons[0].skipTypes(abstractInst).kind
- of tyRef, tyPtr, tyProc:
- result = oNil
- of tyArray, tyObject, tyTuple:
- result = oPtr
- of tyBool: result = oEnum
- of tyEnum:
- assert(typ.n.sons[0].kind == nkSym)
- if typ.n.sons[0].sym.position != low(int):
- result = oEnum
- else:
- result = oBool
- else:
- result = oBool
- proc optLowering*(typ: PType): PType =
- case optKind(typ)
- of oNil: result = typ.sons[0]
- of oPtr:
- result = newType(tyOptAsRef, typ.owner)
- result.rawAddSon typ.sons[0]
- of oBool:
- result = newType(tyTuple, typ.owner)
- result.rawAddSon newType(tyBool, typ.owner)
- result.rawAddSon typ.sons[0]
- of oEnum:
- if lastOrd(typ) + 1 < `shl`(BiggestInt(1), 32):
- result = newType(tyInt32, typ.owner)
- else:
- result = newType(tyInt64, typ.owner)
- proc optEnumValue*(typ: PType): BiggestInt =
- assert typ.kind == tyOpt
- assert optKind(typ) == oEnum
- let elem = typ.sons[0].skipTypes(abstractInst).kind
- if elem == tyBool:
- result = 2
- else:
- assert elem == tyEnum
- assert typ.n.sons[0].sym.position != low(int)
- result = typ.n.sons[0].sym.position - 1
- const
- szNonConcreteType* = -3
- szIllegalRecursion* = -2
- szUnknownSize* = -1
- proc computeSizeAux(typ: PType, a: var BiggestInt): BiggestInt
- proc computeRecSizeAux(n: PNode, a, currOffset: var BiggestInt): BiggestInt =
- var maxAlign, maxSize, b, res: BiggestInt
- case n.kind
- of nkRecCase:
- assert(n.sons[0].kind == nkSym)
- result = computeRecSizeAux(n.sons[0], a, currOffset)
- maxSize = 0
- maxAlign = 1
- for i in countup(1, sonsLen(n) - 1):
- case n.sons[i].kind
- of nkOfBranch, nkElse:
- res = computeRecSizeAux(lastSon(n.sons[i]), b, currOffset)
- if res < 0: return res
- maxSize = max(maxSize, res)
- maxAlign = max(maxAlign, b)
- else: internalError("computeRecSizeAux(record case branch)")
- currOffset = align(currOffset, maxAlign) + maxSize
- result = align(result, maxAlign) + maxSize
- a = maxAlign
- of nkRecList:
- result = 0
- maxAlign = 1
- for i in countup(0, sonsLen(n) - 1):
- res = computeRecSizeAux(n.sons[i], b, currOffset)
- if res < 0: return res
- currOffset = align(currOffset, b) + res
- result = align(result, b) + res
- if b > maxAlign: maxAlign = b
- a = maxAlign
- of nkSym:
- result = computeSizeAux(n.sym.typ, a)
- n.sym.offset = int(currOffset)
- else:
- a = 1
- result = szNonConcreteType
- proc computeSizeAux(typ: PType, a: var BiggestInt): BiggestInt =
- var res, maxAlign, length, currOffset: BiggestInt
- if typ.size == szIllegalRecursion:
- # we are already computing the size of the type
- # --> illegal recursion in type
- return szIllegalRecursion
- if typ.size >= 0:
- # size already computed
- result = typ.size
- a = typ.align
- return
- typ.size = szIllegalRecursion # mark as being computed
- case typ.kind
- of tyInt, tyUInt:
- result = intSize
- a = result
- of tyInt8, tyUInt8, tyBool, tyChar:
- result = 1
- a = result
- of tyInt16, tyUInt16:
- result = 2
- a = result
- of tyInt32, tyUInt32, tyFloat32:
- result = 4
- a = result
- of tyInt64, tyUInt64, tyFloat64:
- result = 8
- a = result
- of tyFloat128:
- result = 16
- a = result
- of tyFloat:
- result = floatSize
- a = result
- of tyProc:
- if typ.callConv == ccClosure: result = 2 * ptrSize
- else: result = ptrSize
- a = ptrSize
- of tyNil, tyCString, tyString, tySequence, tyPtr, tyRef, tyVar, tyOpenArray:
- let base = typ.lastSon
- if base == typ or (base.kind == tyTuple and base.size==szIllegalRecursion):
- result = szIllegalRecursion
- else: result = ptrSize
- a = result
- of tyArray:
- let elemSize = computeSizeAux(typ.sons[1], a)
- if elemSize < 0: return elemSize
- result = lengthOrd(typ.sons[0]) * elemSize
- of tyEnum:
- if firstOrd(typ) < 0:
- result = 4 # use signed int32
- else:
- length = lastOrd(typ) # BUGFIX: use lastOrd!
- if length + 1 < `shl`(1, 8): result = 1
- elif length + 1 < `shl`(1, 16): result = 2
- elif length + 1 < `shl`(BiggestInt(1), 32): result = 4
- else: result = 8
- a = result
- of tySet:
- if typ.sons[0].kind == tyGenericParam:
- result = szUnknownSize
- else:
- length = lengthOrd(typ.sons[0])
- if length <= 8: result = 1
- elif length <= 16: result = 2
- elif length <= 32: result = 4
- elif length <= 64: result = 8
- elif align(length, 8) mod 8 == 0: result = align(length, 8) div 8
- else: result = align(length, 8) div 8 + 1
- a = result
- of tyRange:
- result = computeSizeAux(typ.sons[0], a)
- of tyTuple:
- result = 0
- maxAlign = 1
- for i in countup(0, sonsLen(typ) - 1):
- res = computeSizeAux(typ.sons[i], a)
- if res < 0: return res
- maxAlign = max(maxAlign, a)
- result = align(result, a) + res
- result = align(result, maxAlign)
- a = maxAlign
- of tyObject:
- if typ.sons[0] != nil:
- result = computeSizeAux(typ.sons[0].skipTypes(skipPtrs), a)
- if result < 0: return
- maxAlign = a
- elif isObjectWithTypeFieldPredicate(typ):
- result = intSize
- maxAlign = result
- else:
- result = 0
- maxAlign = 1
- currOffset = result
- result = computeRecSizeAux(typ.n, a, currOffset)
- if result < 0: return
- if a < maxAlign: a = maxAlign
- result = align(result, a)
- of tyInferred:
- if typ.len > 1:
- result = computeSizeAux(typ.lastSon, a)
- of tyGenericInst, tyDistinct, tyGenericBody, tyAlias:
- result = computeSizeAux(lastSon(typ), a)
- of tyTypeClasses:
- result = if typ.isResolvedUserTypeClass: computeSizeAux(typ.lastSon, a)
- else: szUnknownSize
- of tyTypeDesc:
- result = computeSizeAux(typ.base, a)
- of tyForward: return szIllegalRecursion
- of tyStatic:
- result = if typ.n != nil: computeSizeAux(typ.lastSon, a)
- else: szUnknownSize
- of tyOpt:
- case optKind(typ)
- of oBool: result = computeSizeAux(lastSon(typ), a) + 1
- of oEnum:
- if lastOrd(typ) + 1 < `shl`(BiggestInt(1), 32): result = 4
- else: result = 8
- of oNil: result = computeSizeAux(lastSon(typ), a)
- of oPtr: result = ptrSize
- else:
- #internalError("computeSizeAux()")
- result = szUnknownSize
- typ.size = result
- typ.align = int16(a)
- proc computeSize*(typ: PType): BiggestInt =
- var a: BiggestInt = 1
- result = computeSizeAux(typ, a)
- proc getReturnType*(s: PSym): PType =
- # Obtains the return type of a iterator/proc/macro/template
- assert s.kind in skProcKinds
- result = s.typ.sons[0]
- proc getSize*(typ: PType): BiggestInt =
- result = computeSize(typ)
- if result < 0: internalError("getSize: " & $typ.kind)
- proc containsGenericTypeIter(t: PType, closure: RootRef): bool =
- case t.kind
- of tyStatic:
- return t.n == nil
- of tyTypeDesc:
- if t.base.kind == tyNone: return true
- if containsGenericTypeIter(t.base, closure): return true
- return false
- of GenericTypes + tyTypeClasses + {tyFromExpr}:
- return true
- else:
- return false
- proc containsGenericType*(t: PType): bool =
- result = iterOverType(t, containsGenericTypeIter, nil)
- proc baseOfDistinct*(t: PType): PType =
- if t.kind == tyDistinct:
- result = t.sons[0]
- else:
- result = copyType(t, t.owner, false)
- var parent: PType = nil
- var it = result
- while it.kind in {tyPtr, tyRef}:
- parent = it
- it = it.lastSon
- if it.kind == tyDistinct:
- internalAssert parent != nil
- parent.sons[0] = it.sons[0]
- proc safeInheritanceDiff*(a, b: PType): int =
- # same as inheritanceDiff but checks for tyError:
- if a.kind == tyError or b.kind == tyError:
- result = -1
- else:
- result = inheritanceDiff(a.skipTypes(skipPtrs), b.skipTypes(skipPtrs))
- proc compatibleEffectsAux(se, re: PNode): bool =
- if re.isNil: return false
- for r in items(re):
- block search:
- for s in items(se):
- if safeInheritanceDiff(r.typ, s.typ) <= 0:
- break search
- return false
- result = true
- type
- EffectsCompat* = enum
- efCompat
- efRaisesDiffer
- efRaisesUnknown
- efTagsDiffer
- efTagsUnknown
- efLockLevelsDiffer
- proc compatibleEffects*(formal, actual: PType): EffectsCompat =
- # for proc type compatibility checking:
- assert formal.kind == tyProc and actual.kind == tyProc
- internalAssert formal.n.sons[0].kind == nkEffectList
- internalAssert actual.n.sons[0].kind == nkEffectList
- var spec = formal.n.sons[0]
- if spec.len != 0:
- var real = actual.n.sons[0]
- let se = spec.sons[exceptionEffects]
- # if 'se.kind == nkArgList' it is no formal type really, but a
- # computed effect and as such no spec:
- # 'r.msgHandler = if isNil(msgHandler): defaultMsgHandler else: msgHandler'
- if not isNil(se) and se.kind != nkArgList:
- # spec requires some exception or tag, but we don't know anything:
- if real.len == 0: return efRaisesUnknown
- let res = compatibleEffectsAux(se, real.sons[exceptionEffects])
- if not res: return efRaisesDiffer
- let st = spec.sons[tagEffects]
- if not isNil(st) and st.kind != nkArgList:
- # spec requires some exception or tag, but we don't know anything:
- if real.len == 0: return efTagsUnknown
- let res = compatibleEffectsAux(st, real.sons[tagEffects])
- if not res: return efTagsDiffer
- if formal.lockLevel.ord < 0 or
- actual.lockLevel.ord <= formal.lockLevel.ord:
- result = efCompat
- else:
- result = efLockLevelsDiffer
- proc isCompileTimeOnly*(t: PType): bool {.inline.} =
- result = t.kind in {tyTypeDesc, tyStatic}
- proc containsCompileTimeOnly*(t: PType): bool =
- if isCompileTimeOnly(t): return true
- if t.sons != nil:
- for i in 0 .. <t.sonsLen:
- if t.sons[i] != nil and isCompileTimeOnly(t.sons[i]):
- return true
- return false
- type
- OrdinalType* = enum
- NoneLike, IntLike, FloatLike
- proc classify*(t: PType): OrdinalType =
- ## for convenient type checking:
- if t == nil:
- result = NoneLike
- else:
- case skipTypes(t, abstractVarRange).kind
- of tyFloat..tyFloat128: result = FloatLike
- of tyInt..tyInt64, tyUInt..tyUInt64, tyBool, tyChar, tyEnum:
- result = IntLike
- else: result = NoneLike
- proc skipConv*(n: PNode): PNode =
- result = n
- case n.kind
- of nkObjUpConv, nkObjDownConv, nkChckRange, nkChckRangeF, nkChckRange64:
- # only skip the conversion if it doesn't lose too important information
- # (see bug #1334)
- if n.sons[0].typ.classify == n.typ.classify:
- result = n.sons[0]
- of nkHiddenStdConv, nkHiddenSubConv, nkConv:
- if n.sons[1].typ.classify == n.typ.classify:
- result = n.sons[1]
- else: discard
- proc skipHidden*(n: PNode): PNode =
- result = n
- while true:
- case result.kind
- of nkHiddenStdConv, nkHiddenSubConv:
- if result.sons[1].typ.classify == result.typ.classify:
- result = result.sons[1]
- else: break
- of nkHiddenDeref, nkHiddenAddr:
- result = result.sons[0]
- else: break
- proc skipConvTakeType*(n: PNode): PNode =
- result = n.skipConv
- result.typ = n.typ
- proc isEmptyContainer*(t: PType): bool =
- case t.kind
- of tyExpr, tyNil: result = true
- of tyArray: result = t.sons[1].kind == tyEmpty
- of tySet, tySequence, tyOpenArray, tyVarargs:
- result = t.sons[0].kind == tyEmpty
- of tyGenericInst, tyAlias: result = isEmptyContainer(t.lastSon)
- else: result = false
- proc takeType*(formal, arg: PType): PType =
- # param: openArray[string] = []
- # [] is an array constructor of length 0 of type string!
- if arg.kind == tyNil:
- # and not (formal.kind == tyProc and formal.callConv == ccClosure):
- result = formal
- elif formal.kind in {tyOpenArray, tyVarargs, tySequence} and
- arg.isEmptyContainer:
- let a = copyType(arg.skipTypes({tyGenericInst, tyAlias}), arg.owner, keepId=false)
- a.sons[ord(arg.kind == tyArray)] = formal.sons[0]
- result = a
- elif formal.kind in {tyTuple, tySet} and arg.kind == formal.kind:
- result = formal
- else:
- result = arg
- proc skipHiddenSubConv*(n: PNode): PNode =
- if n.kind == nkHiddenSubConv:
- # param: openArray[string] = []
- # [] is an array constructor of length 0 of type string!
- let formal = n.typ
- result = n.sons[1]
- let arg = result.typ
- let dest = takeType(formal, arg)
- if dest == arg and formal.kind != tyExpr:
- #echo n.info, " came here for ", formal.typeToString
- result = n
- else:
- result = copyTree(result)
- result.typ = dest
- else:
- result = n
- proc typeMismatch*(info: TLineInfo, formal, actual: PType) =
- if formal.kind != tyError and actual.kind != tyError:
- let named = typeToString(formal)
- let desc = typeToString(formal, preferDesc)
- let x = if named == desc: named else: named & " = " & desc
- var msg = msgKindToString(errTypeMismatch) &
- typeToString(actual) & ") " &
- msgKindToString(errButExpectedX) % [x]
- if formal.kind == tyProc and actual.kind == tyProc:
- case compatibleEffects(formal, actual)
- of efCompat: discard
- of efRaisesDiffer:
- msg.add "\n.raise effects differ"
- of efRaisesUnknown:
- msg.add "\n.raise effect is 'can raise any'"
- of efTagsDiffer:
- msg.add "\n.tag effects differ"
- of efTagsUnknown:
- msg.add "\n.tag effect is 'any tag allowed'"
- of efLockLevelsDiffer:
- msg.add "\nlock levels differ"
- localError(info, errGenerated, msg)
|