summary refs log tree commit diff stats
path: root/compiler/modules.nim
blob: fb194074164cf6401742d58a0d4c527a0a22abf5 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
#
#
#           The Nimrod Compiler
#        (c) Copyright 2014 Andreas Rumpf
#
#    See the file "copying.txt", included in this
#    distribution, for details about the copyright.
#

## implements the module handling

import
  ast, astalgo, magicsys, crc, rodread, msgs, cgendata, sigmatch, options, 
  idents, os, lexer, idgen, passes, syntaxes

type
  TNeedRecompile* = enum Maybe, No, Yes, Probing, Recompiled
  TCrcStatus* = enum crcNotTaken, crcCached, crcHasChanged, crcNotChanged

  TModuleInMemory* = object
    compiledAt*: float
    crc*: TCrc32
    deps*: seq[int32] ## XXX: slurped files are currently not tracked
    needsRecompile*: TNeedRecompile
    crcStatus*: TCrcStatus

var
  gCompiledModules: seq[PSym] = @[]
  gMemCacheData*: seq[TModuleInMemory] = @[]
    ## XXX: we should implement recycling of file IDs
    ## if the user keeps renaming modules, the file IDs will keep growing

proc getModule(fileIdx: int32): PSym =
  if fileIdx >= 0 and fileIdx < gCompiledModules.len:
    result = gCompiledModules[fileIdx]

template compiledAt(x: PSym): expr =
  gMemCacheData[x.position].compiledAt

template crc(x: PSym): expr =
  gMemCacheData[x.position].crc

proc crcChanged(fileIdx: int32): bool =
  internalAssert fileIdx >= 0 and fileIdx < gMemCacheData.len
  
  template updateStatus =
    gMemCacheData[fileIdx].crcStatus = if result: crcHasChanged
                                       else: crcNotChanged
    # echo "TESTING CRC: ", fileIdx.toFilename, " ", result
  
  case gMemCacheData[fileIdx].crcStatus:
  of crcHasChanged:
    result = true
  of crcNotChanged:
    result = false
  of crcCached:
    let newCrc = crcFromFile(fileIdx.toFilename)
    result = newCrc != gMemCacheData[fileIdx].crc
    gMemCacheData[fileIdx].crc = newCrc
    updateStatus()
  of crcNotTaken:
    gMemCacheData[fileIdx].crc = crcFromFile(fileIdx.toFilename)
    result = true
    updateStatus()

proc doCRC(fileIdx: int32) =
  if gMemCacheData[fileIdx].crcStatus == crcNotTaken:
    # echo "FIRST CRC: ", fileIdx.ToFilename
    gMemCacheData[fileIdx].crc = crcFromFile(fileIdx.toFilename)

proc addDep(x: PSym, dep: int32) =
  growCache gMemCacheData, dep
  gMemCacheData[x.position].deps.safeAdd(dep)

proc resetModule*(fileIdx: int32) =
  # echo "HARD RESETTING ", fileIdx.toFilename
  gMemCacheData[fileIdx].needsRecompile = Yes
  gCompiledModules[fileIdx] = nil
  cgendata.gModules[fileIdx] = nil
  resetSourceMap(fileIdx)

proc resetAllModules* =
  for i in 0..gCompiledModules.high:
    if gCompiledModules[i] != nil:
      resetModule(i.int32)
  resetPackageCache()
  # for m in cgenModules(): echo "CGEN MODULE FOUND"

proc checkDepMem(fileIdx: int32): TNeedRecompile =
  template markDirty =
    resetModule(fileIdx)
    return Yes

  if gMemCacheData[fileIdx].needsRecompile != Maybe:
    return gMemCacheData[fileIdx].needsRecompile

  if optForceFullMake in gGlobalOptions or
     crcChanged(fileIdx):
       markDirty
  
  if gMemCacheData[fileIdx].deps != nil:
    gMemCacheData[fileIdx].needsRecompile = Probing
    for dep in gMemCacheData[fileIdx].deps:
      let d = checkDepMem(dep)
      if d in {Yes, Recompiled}:
        # echo fileIdx.toFilename, " depends on ", dep.toFilename, " ", d
        markDirty
  
  gMemCacheData[fileIdx].needsRecompile = No
  return No

proc newModule(fileIdx: int32): PSym =
  # We cannot call ``newSym`` here, because we have to circumvent the ID
  # mechanism, which we do in order to assign each module a persistent ID. 
  new(result)
  result.id = - 1             # for better error checking
  result.kind = skModule
  let filename = fileIdx.toFilename
  result.name = getIdent(splitFile(filename).name)
  if not isNimrodIdentifier(result.name.s):
    rawMessage(errInvalidModuleName, result.name.s)
  
  result.info = newLineInfo(fileIdx, 1, 1)
  result.owner = newSym(skPackage, getIdent(getPackageName(filename)), nil,
                        result.info)
  result.position = fileIdx
  
  growCache gMemCacheData, fileIdx
  growCache gCompiledModules, fileIdx
  gCompiledModules[result.position] = result
  
  incl(result.flags, sfUsed)
  initStrTable(result.tab)
  strTableAdd(result.tab, result) # a module knows itself

proc compileModule*(fileIdx: int32, flags: TSymFlags): PSym =
  result = getModule(fileIdx)
  if result == nil:
    growCache gMemCacheData, fileIdx
    gMemCacheData[fileIdx].needsRecompile = Probing
    result = newModule(fileIdx)
    #var rd = handleSymbolFile(result)
    var rd: PRodReader
    result.flags = result.flags + flags
    if gCmd in {cmdCompileToC, cmdCompileToCpp, cmdCheck, cmdIdeTools}:
      rd = handleSymbolFile(result)
      if result.id < 0: 
        internalError("handleSymbolFile should have set the module\'s ID")
        return
    else:
      result.id = getID()
    processModule(result, nil, rd)
    if optCaasEnabled in gGlobalOptions:
      gMemCacheData[fileIdx].compiledAt = gLastCmdTime
      gMemCacheData[fileIdx].needsRecompile = Recompiled
      doCRC fileIdx
  else:
    if checkDepMem(fileIdx) == Yes:
      result = compileModule(fileIdx, flags)
    else:
      result = gCompiledModules[fileIdx]

proc importModule*(s: PSym, fileIdx: int32): PSym {.procvar.} =
  # this is called by the semantic checking phase
  result = compileModule(fileIdx, {})
  if optCaasEnabled in gGlobalOptions: addDep(s, fileIdx)
  if sfSystemModule in result.flags:
    localError(result.info, errAttemptToRedefine, result.name.s)

proc includeModule*(s: PSym, fileIdx: int32): PNode {.procvar.} =
  result = syntaxes.parseFile(fileIdx)
  if optCaasEnabled in gGlobalOptions:
    growCache gMemCacheData, fileIdx
    addDep(s, fileIdx)
    doCRC(fileIdx)

proc `==^`(a, b: string): bool =
  try:
    result = sameFile(a, b)
  except EOS:
    result = false

proc compileSystemModule* =
  if magicsys.systemModule == nil:
    systemFileIdx = fileInfoIdx(options.libpath/"system.nim")
    discard compileModule(systemFileIdx, {sfSystemModule})

proc compileProject*(projectFile = gProjectMainIdx) =
  let systemFileIdx = fileInfoIdx(options.libpath / "system.nim")
  if projectFile == systemFileIdx:
    discard compileModule(projectFile, {sfMainModule, sfSystemModule})
  else:
    compileSystemModule()
    discard compileModule(projectFile, {sfMainModule})

var stdinModule: PSym
proc makeStdinModule*(): PSym =
  if stdinModule == nil:
    stdinModule = newModule(fileInfoIdx"stdin")
    stdinModule.id = getID()
  result = stdinModule
ss="c"># checks if `t` contains the `key` (compared by the pointer value, not only # `key`'s id) proc idNodeTableGet*(t: TIdNodeTable, key: PIdObj): PNode proc idNodeTablePut*(t: var TIdNodeTable, key: PIdObj, val: PNode) # --------------------------------------------------------------------------- proc getSymFromList*(list: PNode, ident: PIdent, start: int = 0): PSym proc lookupInRecord*(n: PNode, field: PIdent): PSym proc getModule*(s: PSym): PSym proc mustRehash*(length, counter: int): bool proc nextTry*(h, maxHash: THash): THash {.inline.} # ------------- table[int, int] --------------------------------------------- const InvalidKey* = low(int) type TIIPair*{.final.} = object key*, val*: int TIIPairSeq* = seq[TIIPair] TIITable*{.final.} = object # table[int, int] counter*: int data*: TIIPairSeq proc initIiTable*(x: var TIITable) proc iiTableGet*(t: TIITable, key: int): int proc iiTablePut*(t: var TIITable, key, val: int) # implementation proc skipConvAndClosure*(n: PNode): PNode = result = n while true: case result.kind of nkObjUpConv, nkObjDownConv, nkChckRange, nkChckRangeF, nkChckRange64, nkClosure: result = result.sons[0] of nkHiddenStdConv, nkHiddenSubConv, nkConv: result = result.sons[1] else: break proc sameValue*(a, b: PNode): bool = result = false case a.kind of nkCharLit..nkUInt64Lit: if b.kind in {nkCharLit..nkUInt64Lit}: result = a.intVal == b.intVal of nkFloatLit..nkFloat64Lit: if b.kind in {nkFloatLit..nkFloat64Lit}: result = a.floatVal == b.floatVal of nkStrLit..nkTripleStrLit: if b.kind in {nkStrLit..nkTripleStrLit}: result = a.strVal == b.strVal else: # don't raise an internal error for 'nimrod check': #InternalError(a.info, "SameValue") discard proc leValue*(a, b: PNode): bool = # a <= b? result = false case a.kind of nkCharLit..nkUInt32Lit: if b.kind in {nkCharLit..nkUInt32Lit}: result = a.intVal <= b.intVal of nkFloatLit..nkFloat64Lit: if b.kind in {nkFloatLit..nkFloat64Lit}: result = a.floatVal <= b.floatVal of nkStrLit..nkTripleStrLit: if b.kind in {nkStrLit..nkTripleStrLit}: result = a.strVal <= b.strVal else: # don't raise an internal error for 'nimrod check': #InternalError(a.info, "leValue") discard proc weakLeValue*(a, b: PNode): TImplication = if a.kind notin nkLiterals or b.kind notin nkLiterals: result = impUnknown else: result = if leValue(a, b): impYes else: impNo proc lookupInRecord(n: PNode, field: PIdent): PSym = result = nil case n.kind of nkRecList: for i in countup(0, sonsLen(n) - 1): result = lookupInRecord(n.sons[i], field) if result != nil: return of nkRecCase: if (n.sons[0].kind != nkSym): internalError(n.info, "lookupInRecord") result = lookupInRecord(n.sons[0], field) if result != nil: return for i in countup(1, sonsLen(n) - 1): case n.sons[i].kind of nkOfBranch, nkElse: result = lookupInRecord(lastSon(n.sons[i]), field) if result != nil: return else: internalError(n.info, "lookupInRecord(record case branch)") of nkSym: if n.sym.name.id == field.id: result = n.sym else: internalError(n.info, "lookupInRecord()") proc getModule(s: PSym): PSym = result = s assert((result.kind == skModule) or (result.owner != result)) while result != nil and result.kind != skModule: result = result.owner proc getSymFromList(list: PNode, ident: PIdent, start: int = 0): PSym = for i in countup(start, sonsLen(list) - 1): if list.sons[i].kind == nkSym: result = list.sons[i].sym if result.name.id == ident.id: return else: internalError(list.info, "getSymFromList") result = nil proc hashNode(p: RootRef): THash = result = hash(cast[pointer](p)) proc mustRehash(length, counter: int): bool = assert(length > counter) result = (length * 2 < counter * 3) or (length - counter < 4) proc rspaces(x: int): Rope = # returns x spaces result = rope(spaces(x)) proc toYamlChar(c: char): string = case c of '\0'..'\x1F', '\x80'..'\xFF': result = "\\u" & strutils.toHex(ord(c), 4) of '\'', '\"', '\\': result = '\\' & c else: result = $c proc makeYamlString*(s: string): Rope = # We have to split long strings into many ropes. Otherwise # this could trigger InternalError(111). See the ropes module for # further information. const MaxLineLength = 64 result = nil var res = "\"" for i in countup(0, if s.isNil: -1 else: (len(s)-1)): if (i + 1) mod MaxLineLength == 0: add(res, '\"') add(res, "\n") add(result, rope(res)) res = "\"" # reset add(res, toYamlChar(s[i])) add(res, '\"') add(result, rope(res)) proc flagsToStr[T](flags: set[T]): Rope = if flags == {}: result = rope("[]") else: result = nil for x in items(flags): if result != nil: add(result, ", ") add(result, makeYamlString($x)) result = "[" & result & "]" proc lineInfoToStr(info: TLineInfo): Rope = result = "[$1, $2, $3]" % [makeYamlString(toFilename(info)), rope(toLinenumber(info)), rope(toColumn(info))] proc treeToYamlAux(n: PNode, marker: var IntSet, indent, maxRecDepth: int): Rope proc symToYamlAux(n: PSym, marker: var IntSet, indent, maxRecDepth: int): Rope proc typeToYamlAux(n: PType, marker: var IntSet, indent, maxRecDepth: int): Rope proc strTableToYaml(n: TStrTable, marker: var IntSet, indent: int, maxRecDepth: int): Rope = var istr = rspaces(indent + 2) result = rope("[") var mycount = 0 for i in countup(0, high(n.data)): if n.data[i] != nil: if mycount > 0: add(result, ",") addf(result, "$N$1$2", [istr, symToYamlAux(n.data[i], marker, indent + 2, maxRecDepth - 1)]) inc(mycount) if mycount > 0: addf(result, "$N$1", [rspaces(indent)]) add(result, "]") assert(mycount == n.counter) proc ropeConstr(indent: int, c: openArray[Rope]): Rope = # array of (name, value) pairs var istr = rspaces(indent + 2) result = rope("{") var i = 0 while i <= high(c): if i > 0: add(result, ",") addf(result, "$N$1\"$2\": $3", [istr, c[i], c[i + 1]]) inc(i, 2) addf(result, "$N$1}", [rspaces(indent)]) proc symToYamlAux(n: PSym, marker: var IntSet, indent: int, maxRecDepth: int): Rope = if n == nil: result = rope("null") elif containsOrIncl(marker, n.id): result = "\"$1 @$2\"" % [rope(n.name.s), rope( strutils.toHex(cast[ByteAddress](n), sizeof(n) * 2))] else: var ast = treeToYamlAux(n.ast, marker, indent + 2, maxRecDepth - 1) result = ropeConstr(indent, [rope("kind"), makeYamlString($n.kind), rope("name"), makeYamlString(n.name.s), rope("typ"), typeToYamlAux(n.typ, marker, indent + 2, maxRecDepth - 1), rope("info"), lineInfoToStr(n.info), rope("flags"), flagsToStr(n.flags), rope("magic"), makeYamlString($n.magic), rope("ast"), ast, rope("options"), flagsToStr(n.options), rope("position"), rope(n.position)]) proc typeToYamlAux(n: PType, marker: var IntSet, indent: int, maxRecDepth: int): Rope = if n == nil: result = rope("null") elif containsOrIncl(marker, n.id): result = "\"$1 @$2\"" % [rope($n.kind), rope( strutils.toHex(cast[ByteAddress](n), sizeof(n) * 2))] else: if sonsLen(n) > 0: result = rope("[") for i in countup(0, sonsLen(n) - 1): if i > 0: add(result, ",") addf(result, "$N$1$2", [rspaces(indent + 4), typeToYamlAux(n.sons[i], marker, indent + 4, maxRecDepth - 1)]) addf(result, "$N$1]", [rspaces(indent + 2)]) else: result = rope("null") result = ropeConstr(indent, [rope("kind"), makeYamlString($n.kind), rope("sym"), symToYamlAux(n.sym, marker, indent + 2, maxRecDepth - 1), rope("n"), treeToYamlAux(n.n, marker, indent + 2, maxRecDepth - 1), rope("flags"), flagsToStr(n.flags), rope("callconv"), makeYamlString(CallingConvToStr[n.callConv]), rope("size"), rope(n.size), rope("align"), rope(n.align), rope("sons"), result]) proc treeToYamlAux(n: PNode, marker: var IntSet, indent: int, maxRecDepth: int): Rope = if n == nil: result = rope("null") else: var istr = rspaces(indent + 2) result = "{$N$1\"kind\": $2" % [istr, makeYamlString($n.kind)] if maxRecDepth != 0: addf(result, ",$N$1\"info\": $2", [istr, lineInfoToStr(n.info)]) case n.kind of nkCharLit..nkInt64Lit: addf(result, ",$N$1\"intVal\": $2", [istr, rope(n.intVal)]) of nkFloatLit, nkFloat32Lit, nkFloat64Lit: addf(result, ",$N$1\"floatVal\": $2", [istr, rope(n.floatVal.toStrMaxPrecision)]) of nkStrLit..nkTripleStrLit: if n.strVal.isNil: addf(result, ",$N$1\"strVal\": null", [istr]) else: addf(result, ",$N$1\"strVal\": $2", [istr, makeYamlString(n.strVal)]) of nkSym: addf(result, ",$N$1\"sym\": $2", [istr, symToYamlAux(n.sym, marker, indent + 2, maxRecDepth)]) of nkIdent: if n.ident != nil: addf(result, ",$N$1\"ident\": $2", [istr, makeYamlString(n.ident.s)]) else: addf(result, ",$N$1\"ident\": null", [istr]) else: if sonsLen(n) > 0: addf(result, ",$N$1\"sons\": [", [istr]) for i in countup(0, sonsLen(n) - 1): if i > 0: add(result, ",") addf(result, "$N$1$2", [rspaces(indent + 4), treeToYamlAux(n.sons[i], marker, indent + 4, maxRecDepth - 1)]) addf(result, "$N$1]", [istr]) addf(result, ",$N$1\"typ\": $2", [istr, typeToYamlAux(n.typ, marker, indent + 2, maxRecDepth)]) addf(result, "$N$1}", [rspaces(indent)]) proc treeToYaml(n: PNode, indent: int = 0, maxRecDepth: int = - 1): Rope = var marker = initIntSet() result = treeToYamlAux(n, marker, indent, maxRecDepth) proc typeToYaml(n: PType, indent: int = 0, maxRecDepth: int = - 1): Rope = var marker = initIntSet() result = typeToYamlAux(n, marker, indent, maxRecDepth) proc symToYaml(n: PSym, indent: int = 0, maxRecDepth: int = - 1): Rope = var marker = initIntSet() result = symToYamlAux(n, marker, indent, maxRecDepth) proc debugTree*(n: PNode, indent: int, maxRecDepth: int; renderType=false): Rope proc debugType(n: PType, maxRecDepth=100): Rope = if n == nil: result = rope("null") else: result = rope($n.kind) if n.sym != nil: add(result, " ") add(result, n.sym.name.s) if n.kind in IntegralTypes and n.n != nil: add(result, ", node: ") add(result, debugTree(n.n, 2, maxRecDepth-1, renderType=true)) if (n.kind != tyString) and (sonsLen(n) > 0) and maxRecDepth != 0: add(result, "(") for i in countup(0, sonsLen(n) - 1): if i > 0: add(result, ", ") if n.sons[i] == nil: add(result, "null") else: add(result, debugType(n.sons[i], maxRecDepth-1)) if n.kind == tyObject and n.n != nil: add(result, ", node: ") add(result, debugTree(n.n, 2, maxRecDepth-1, renderType=true)) add(result, ")") proc debugTree(n: PNode, indent: int, maxRecDepth: int; renderType=false): Rope = if n == nil: result = rope("null") else: var istr = rspaces(indent + 2) result = "{$N$1\"kind\": $2" % [istr, makeYamlString($n.kind)] if maxRecDepth != 0: case n.kind of nkCharLit..nkUInt64Lit: addf(result, ",$N$1\"intVal\": $2", [istr, rope(n.intVal)]) of nkFloatLit, nkFloat32Lit, nkFloat64Lit: addf(result, ",$N$1\"floatVal\": $2", [istr, rope(n.floatVal.toStrMaxPrecision)]) of nkStrLit..nkTripleStrLit: if n.strVal.isNil: addf(result, ",$N$1\"strVal\": null", [istr]) else: addf(result, ",$N$1\"strVal\": $2", [istr, makeYamlString(n.strVal)]) of nkSym: addf(result, ",$N$1\"sym\": $2_$3", [istr, rope(n.sym.name.s), rope(n.sym.id)]) # [istr, symToYaml(n.sym, indent, maxRecDepth), # rope(n.sym.id)]) if renderType and n.sym.typ != nil: addf(result, ",$N$1\"typ\": $2", [istr, debugType(n.sym.typ, 2)]) of nkIdent: if n.ident != nil: addf(result, ",$N$1\"ident\": $2", [istr, makeYamlString(n.ident.s)]) else: addf(result, ",$N$1\"ident\": null", [istr]) else: if sonsLen(n) > 0: addf(result, ",$N$1\"sons\": [", [istr]) for i in countup(0, sonsLen(n) - 1): if i > 0: add(result, ",") addf(result, "$N$1$2", [rspaces(indent + 4), debugTree(n.sons[i], indent + 4, maxRecDepth - 1, renderType)]) addf(result, "$N$1]", [istr]) addf(result, ",$N$1\"info\": $2", [istr, lineInfoToStr(n.info)]) addf(result, "$N$1}", [rspaces(indent)]) proc debug(n: PSym) = if n == nil: msgWriteln("null") elif n.kind == skUnknown: msgWriteln("skUnknown") else: #writeln(stdout, $symToYaml(n, 0, 1)) msgWriteln("$1_$2: $3, $4, $5, $6" % [ n.name.s, $n.id, $flagsToStr(n.flags), $flagsToStr(n.loc.flags), $lineInfoToStr(n.info), $n.kind]) proc debug(n: PType) = msgWriteln($debugType(n)) proc debug(n: PNode) = msgWriteln($debugTree(n, 0, 100)) const EmptySeq = @[] proc nextTry(h, maxHash: THash): THash = result = ((5 * h) + 1) and maxHash # For any initial h in range(maxHash), repeating that maxHash times # generates each int in range(maxHash) exactly once (see any text on # random-number generation for proof). proc objectSetContains(t: TObjectSet, obj: RootRef): bool = # returns true whether n is in t var h: THash = hashNode(obj) and high(t.data) # start with real hash value while t.data[h] != nil: if t.data[h] == obj: return true h = nextTry(h, high(t.data)) result = false proc objectSetRawInsert(data: var TObjectSeq, obj: RootRef) = var h: THash = hashNode(obj) and high(data) while data[h] != nil: assert(data[h] != obj) h = nextTry(h, high(data)) assert(data[h] == nil) data[h] = obj proc objectSetEnlarge(t: var TObjectSet) = var n: TObjectSeq newSeq(n, len(t.data) * GrowthFactor) for i in countup(0, high(t.data)): if t.data[i] != nil: objectSetRawInsert(n, t.data[i]) swap(t.data, n) proc objectSetIncl(t: var TObjectSet, obj: RootRef) = if mustRehash(len(t.data), t.counter): objectSetEnlarge(t) objectSetRawInsert(t.data, obj) inc(t.counter) proc objectSetContainsOrIncl(t: var TObjectSet, obj: RootRef): bool = # returns true if obj is already in the string table: var h: THash = hashNode(obj) and high(t.data) while true: var it = t.data[h] if it == nil: break if it == obj: return true # found it h = nextTry(h, high(t.data)) if mustRehash(len(t.data), t.counter): objectSetEnlarge(t) objectSetRawInsert(t.data, obj) else: assert(t.data[h] == nil) t.data[h] = obj inc(t.counter) result = false proc tableRawGet(t: TTable, key: RootRef): int = var h: THash = hashNode(key) and high(t.data) # start with real hash value while t.data[h].key != nil: if t.data[h].key == key: return h h = nextTry(h, high(t.data)) result = -1 proc tableSearch(t: TTable, key, closure: RootRef, comparator: TCmpProc): RootRef = var h: THash = hashNode(key) and high(t.data) # start with real hash value while t.data[h].key != nil: if t.data[h].key == key: if comparator(t.data[h].val, closure): # BUGFIX 1 return t.data[h].val h = nextTry(h, high(t.data)) result = nil proc tableGet(t: TTable, key: RootRef): RootRef = var index = tableRawGet(t, key) if index >= 0: result = t.data[index].val else: result = nil proc tableRawInsert(data: var TPairSeq, key, val: RootRef) = var h: THash = hashNode(key) and high(data) while data[h].key != nil: assert(data[h].key != key) h = nextTry(h, high(data)) assert(data[h].key == nil) data[h].key = key data[h].val = val proc tableEnlarge(t: var TTable) = var n: TPairSeq newSeq(n, len(t.data) * GrowthFactor) for i in countup(0, high(t.data)): if t.data[i].key != nil: tableRawInsert(n, t.data[i].key, t.data[i].val) swap(t.data, n) proc tablePut(t: var TTable, key, val: RootRef) = var index = tableRawGet(t, key) if index >= 0: t.data[index].val = val else: if mustRehash(len(t.data), t.counter): tableEnlarge(t) tableRawInsert(t.data, key, val) inc(t.counter) proc strTableContains(t: TStrTable, n: PSym): bool = var h: THash = n.name.h and high(t.data) # start with real hash value while t.data[h] != nil: if (t.data[h] == n): return true h = nextTry(h, high(t.data)) result = false proc strTableRawInsert(data: var TSymSeq, n: PSym) = var h: THash = n.name.h and high(data) if sfImmediate notin n.flags: # fast path: while data[h] != nil: if data[h] == n: # allowed for 'export' feature: #InternalError(n.info, "StrTableRawInsert: " & n.name.s) return h = nextTry(h, high(data)) assert(data[h] == nil) data[h] = n else: # slow path; we have to ensure immediate symbols are preferred for # symbol lookups. # consider the chain: foo (immediate), foo, bar, bar (immediate) # then bar (immediate) gets replaced with foo (immediate) and the non # immediate foo is picked! Thus we need to replace it with the first # slot that has in fact the same identifier stored in it! var favPos = -1 while data[h] != nil: if data[h] == n: return if favPos < 0 and data[h].name.id == n.name.id: favPos = h h = nextTry(h, high(data)) assert(data[h] == nil) data[h] = n if favPos >= 0: swap data[h], data[favPos] proc symTabReplaceRaw(data: var TSymSeq, prevSym: PSym, newSym: PSym) = assert prevSym.name.h == newSym.name.h var h: THash = prevSym.name.h and high(data) while data[h] != nil: if data[h] == prevSym: data[h] = newSym return h = nextTry(h, high(data)) assert false proc symTabReplace*(t: var TStrTable, prevSym: PSym, newSym: PSym) = symTabReplaceRaw(t.data, prevSym, newSym) proc strTableEnlarge(t: var TStrTable) = var n: TSymSeq newSeq(n, len(t.data) * GrowthFactor) for i in countup(0, high(t.data)): if t.data[i] != nil: strTableRawInsert(n, t.data[i]) swap(t.data, n) proc strTableAdd(t: var TStrTable, n: PSym) = if mustRehash(len(t.data), t.counter): strTableEnlarge(t) strTableRawInsert(t.data, n) inc(t.counter) proc reallySameIdent(a, b: string): bool {.inline.} = when defined(nimfix): result = a[0] == b[0] else: result = true proc strTableIncl*(t: var TStrTable, n: PSym): bool {.discardable.} = # returns true if n is already in the string table: # It is essential that `n` is written nevertheless! # This way the newest redefinition is picked by the semantic analyses! assert n.name != nil var h: THash = n.name.h and high(t.data) var replaceSlot = -1 while true: var it = t.data[h] if it == nil: break # Semantic checking can happen multiple times thanks to templates # and overloading: (var x=@[]; x).mapIt(it). # So it is possible the very same sym is added multiple # times to the symbol table which we allow here with the 'it == n' check. if it.name.id == n.name.id and reallySameIdent(it.name.s, n.name.s): if it == n: return false replaceSlot = h h = nextTry(h, high(t.data)) if replaceSlot >= 0: t.data[replaceSlot] = n # overwrite it with newer definition! return true # found it elif mustRehash(len(t.data), t.counter): strTableEnlarge(t) strTableRawInsert(t.data, n) else: assert(t.data[h] == nil) t.data[h] = n inc(t.counter) result = false proc strTableGet(t: TStrTable, name: PIdent): PSym = var h: THash = name.h and high(t.data) while true: result = t.data[h] if result == nil: break if result.name.id == name.id: break h = nextTry(h, high(t.data)) proc initIdentIter(ti: var TIdentIter, tab: TStrTable, s: PIdent): PSym = ti.h = s.h ti.name = s if tab.counter == 0: result = nil else: result = nextIdentIter(ti, tab) proc nextIdentIter(ti: var TIdentIter, tab: TStrTable): PSym = var h = ti.h and high(tab.data) var start = h result = tab.data[h] while result != nil: if result.name.id == ti.name.id: break h = nextTry(h, high(tab.data)) if h == start: result = nil break result = tab.data[h] ti.h = nextTry(h, high(tab.data)) proc nextIdentExcluding*(ti: var TIdentIter, tab: TStrTable, excluding: IntSet): PSym = var h: THash = ti.h and high(tab.data) var start = h result = tab.data[h] while result != nil: if result.name.id == ti.name.id and not contains(excluding, result.id): break h = nextTry(h, high(tab.data)) if h == start: result = nil break result = tab.data[h] ti.h = nextTry(h, high(tab.data)) if result != nil and contains(excluding, result.id): result = nil proc firstIdentExcluding*(ti: var TIdentIter, tab: TStrTable, s: PIdent, excluding: IntSet): PSym = ti.h = s.h ti.name = s if tab.counter == 0: result = nil else: result = nextIdentExcluding(ti, tab, excluding) proc initTabIter(ti: var TTabIter, tab: TStrTable): PSym = ti.h = 0 # we start by zero ... if tab.counter == 0: result = nil # FIX 1: removed endless loop else: result = nextIter(ti, tab) proc nextIter(ti: var TTabIter, tab: TStrTable): PSym = result = nil while (ti.h <= high(tab.data)): result = tab.data[ti.h] inc(ti.h) # ... and increment by one always if result != nil: break iterator items*(tab: TStrTable): PSym = var it: TTabIter var s = initTabIter(it, tab) while s != nil: yield s s = nextIter(it, tab) proc hasEmptySlot(data: TIdPairSeq): bool = for h in countup(0, high(data)): if data[h].key == nil: return true result = false proc idTableRawGet(t: TIdTable, key: int): int = var h: THash h = key and high(t.data) # start with real hash value while t.data[h].key != nil: if t.data[h].key.id == key: return h h = nextTry(h, high(t.data)) result = - 1 proc idTableHasObjectAsKey(t: TIdTable, key: PIdObj): bool = var index = idTableRawGet(t, key.id) if index >= 0: result = t.data[index].key == key else: result = false proc idTableGet(t: TIdTable, key: PIdObj): RootRef = var index = idTableRawGet(t, key.id) if index >= 0: result = t.data[index].val else: result = nil proc idTableGet(t: TIdTable, key: int): RootRef = var index = idTableRawGet(t, key) if index >= 0: result = t.data[index].val else: result = nil iterator pairs*(t: TIdTable): tuple[key: int, value: RootRef] = for i in 0..high(t.data): if t.data[i].key != nil: yield (t.data[i].key.id, t.data[i].val) proc idTableRawInsert(data: var TIdPairSeq, key: PIdObj, val: RootRef) = var h: THash h = key.id and high(data) while data[h].key != nil: assert(data[h].key.id != key.id) h = nextTry(h, high(data)) assert(data[h].key == nil) data[h].key = key data[h].val = val proc idTablePut(t: var TIdTable, key: PIdObj, val: RootRef) = var index: int n: TIdPairSeq index = idTableRawGet(t, key.id) if index >= 0: assert(t.data[index].key != nil) t.data[index].val = val else: if mustRehash(len(t.data), t.counter): newSeq(n, len(t.data) * GrowthFactor) for i in countup(0, high(t.data)): if t.data[i].key != nil: idTableRawInsert(n, t.data[i].key, t.data[i].val) assert(hasEmptySlot(n)) swap(t.data, n) idTableRawInsert(t.data, key, val) inc(t.counter) iterator idTablePairs*(t: TIdTable): tuple[key: PIdObj, val: RootRef] = for i in 0 .. high(t.data): if not isNil(t.data[i].key): yield (t.data[i].key, t.data[i].val) proc idNodeTableRawGet(t: TIdNodeTable, key: PIdObj): int = var h: THash h = key.id and high(t.data) # start with real hash value while t.data[h].key != nil: if t.data[h].key.id == key.id: return h h = nextTry(h, high(t.data)) result = - 1 proc idNodeTableGet(t: TIdNodeTable, key: PIdObj): PNode = var index: int index = idNodeTableRawGet(t, key) if index >= 0: result = t.data[index].val else: result = nil proc idNodeTableGetLazy*(t: TIdNodeTable, key: PIdObj): PNode = if not isNil(t.data): result = idNodeTableGet(t, key) proc idNodeTableRawInsert(data: var TIdNodePairSeq, key: PIdObj, val: PNode) = var h: THash h = key.id and high(data) while data[h].key != nil: assert(data[h].key.id != key.id) h = nextTry(h, high(data)) assert(data[h].key == nil) data[h].key = key data[h].val = val proc idNodeTablePut(t: var TIdNodeTable, key: PIdObj, val: PNode) = var index = idNodeTableRawGet(t, key) if index >= 0: assert(t.data[index].key != nil) t.data[index].val = val else: if mustRehash(len(t.data), t.counter): var n: TIdNodePairSeq newSeq(n, len(t.data) * GrowthFactor) for i in countup(0, high(t.data)): if t.data[i].key != nil: idNodeTableRawInsert(n, t.data[i].key, t.data[i].val) swap(t.data, n) idNodeTableRawInsert(t.data, key, val) inc(t.counter) proc idNodeTablePutLazy*(t: var TIdNodeTable, key: PIdObj, val: PNode) = if isNil(t.data): initIdNodeTable(t) idNodeTablePut(t, key, val) iterator pairs*(t: TIdNodeTable): tuple[key: PIdObj, val: PNode] = for i in 0 .. high(t.data): if not isNil(t.data[i].key): yield (t.data[i].key, t.data[i].val) proc initIITable(x: var TIITable) = x.counter = 0 newSeq(x.data, StartSize) for i in countup(0, StartSize - 1): x.data[i].key = InvalidKey proc iiTableRawGet(t: TIITable, key: int): int = var h: THash h = key and high(t.data) # start with real hash value while t.data[h].key != InvalidKey: if t.data[h].key == key: return h h = nextTry(h, high(t.data)) result = -1 proc iiTableGet(t: TIITable, key: int): int = var index = iiTableRawGet(t, key) if index >= 0: result = t.data[index].val else: result = InvalidKey proc iiTableRawInsert(data: var TIIPairSeq, key, val: int) = var h: THash h = key and high(data) while data[h].key != InvalidKey: assert(data[h].key != key) h = nextTry(h, high(data)) assert(data[h].key == InvalidKey) data[h].key = key data[h].val = val proc iiTablePut(t: var TIITable, key, val: int) = var index = iiTableRawGet(t, key) if index >= 0: assert(t.data[index].key != InvalidKey) t.data[index].val = val else: if mustRehash(len(t.data), t.counter): var n: TIIPairSeq newSeq(n, len(t.data) * GrowthFactor) for i in countup(0, high(n)): n[i].key = InvalidKey for i in countup(0, high(t.data)): if t.data[i].key != InvalidKey: iiTableRawInsert(n, t.data[i].key, t.data[i].val) swap(t.data, n) iiTableRawInsert(t.data, key, val) inc(t.counter)