diff options
-rwxr-xr-x | compiler/ccgtypes.nim | 9 | ||||
-rwxr-xr-x | compiler/nhashes.nim | 32 | ||||
-rwxr-xr-x | compiler/nimconf.nim | 90 | ||||
-rwxr-xr-x | compiler/pnimsyn.nim | 5 | ||||
-rwxr-xr-x | compiler/ropes.nim | 2 | ||||
-rwxr-xr-x | compiler/scanner.nim | 109 | ||||
-rwxr-xr-x | compiler/wordrecg.nim | 4 | ||||
-rwxr-xr-x | lib/pure/strutils.nim | 12 | ||||
-rwxr-xr-x | lib/system.nim | 6 | ||||
-rwxr-xr-x | lib/system/gc.nim | 6 | ||||
-rw-r--r-- | tests/accept/compile/ttempl4.nim | 8 |
11 files changed, 117 insertions, 166 deletions
diff --git a/compiler/ccgtypes.nim b/compiler/ccgtypes.nim index 1920da599..bea696c4e 100755 --- a/compiler/ccgtypes.nim +++ b/compiler/ccgtypes.nim @@ -513,14 +513,15 @@ proc genProcHeader(m: BModule, prc: PSym): PRope = rettype, params: PRope check: TIntSet # using static is needed for inline procs - if (prc.typ.callConv == ccInline): result = toRope("static ") - else: result = nil + if (prc.typ.callConv == ccInline): result = toRope"static " IntSetInit(check) fillLoc(prc.loc, locProc, prc.typ, mangleName(prc), OnUnknown) genProcParams(m, prc.typ, rettype, params, check) appf(result, "$1($2, $3)$4", [toRope(CallingConvToStr[prc.typ.callConv]), rettype, prc.loc.r, params]) +# ------------------ type info generation ------------------------------------- + proc genTypeInfo(m: BModule, typ: PType): PRope proc getNimNode(m: BModule): PRope = result = ropef("$1[$2]", [m.typeNodesName, toRope(m.typeNodes)]) @@ -743,10 +744,10 @@ proc genTypeInfo(m: BModule, typ: PType): PRope = [result, toRope(typeToString(t))]) if dataGenerated: return case t.kind - of tyEmpty: result = toRope("0") + of tyEmpty: result = toRope"0" of tyPointer, tyProc, tyBool, tyChar, tyCString, tyString, tyInt..tyFloat128, tyVar: - genTypeInfoAuxBase(gNimDat, t, result, toRope("0")) + genTypeInfoAuxBase(gNimDat, t, result, toRope"0") of tyRef, tyPtr, tySequence, tyRange: genTypeInfoAux(gNimDat, t, result) of tyArrayConstr, tyArray: genArrayInfo(gNimDat, t, result) of tySet: genSetInfo(gNimDat, t, result) diff --git a/compiler/nhashes.nim b/compiler/nhashes.nim index b9dd3670a..181f46d55 100755 --- a/compiler/nhashes.nim +++ b/compiler/nhashes.nim @@ -1,7 +1,7 @@ # # # The Nimrod Compiler -# (c) Copyright 2009 Andreas Rumpf +# (c) Copyright 2011 Andreas Rumpf # # See the file "copying.txt", included in this # distribution, for details about the copyright. @@ -20,29 +20,17 @@ type PHash* = ref THash THashFunc* = proc (str: cstring): THash -proc GetHash*(str: cstring): THash -proc GetHashCI*(str: cstring): THash -proc GetDataHash*(Data: Pointer, Size: int): THash -proc hashPtr*(p: Pointer): THash -proc GetHashStr*(s: string): THash -proc GetHashStrCI*(s: string): THash -proc getNormalizedHash*(s: string): THash - #function nextPowerOfTwo(x: int): int; -proc concHash*(h: THash, val: int): THash -proc finishHash*(h: THash): THash -# implementation - -proc concHash(h: THash, val: int): THash = +proc concHash*(h: THash, val: int): THash {.inline.} = result = h +% val result = result +% result shl 10 result = result xor (result shr 6) -proc finishHash(h: THash): THash = +proc finishHash*(h: THash): THash {.inline.} = result = h +% h shl 3 result = result xor (result shr 11) result = result +% result shl 15 -proc GetDataHash(Data: Pointer, Size: int): THash = +proc GetDataHash*(Data: Pointer, Size: int): THash = var h: THash p: cstring @@ -62,10 +50,10 @@ proc GetDataHash(Data: Pointer, Size: int): THash = h = h +% h shl 15 result = THash(h) -proc hashPtr(p: Pointer): THash = +proc hashPtr*(p: Pointer): THash = result = (cast[THash](p)) shr 3 # skip the alignment -proc GetHash(str: cstring): THash = +proc GetHash*(str: cstring): THash = var h: THash i: int @@ -81,7 +69,7 @@ proc GetHash(str: cstring): THash = h = h +% h shl 15 result = THash(h) -proc GetHashStr(s: string): THash = +proc GetHashStr*(s: string): THash = var h: THash h = 0 for i in countup(1, len(s)): @@ -93,7 +81,7 @@ proc GetHashStr(s: string): THash = h = h +% h shl 15 result = THash(h) -proc getNormalizedHash(s: string): THash = +proc getNormalizedHash*(s: string): THash = var h: THash c: Char @@ -112,7 +100,7 @@ proc getNormalizedHash(s: string): THash = h = h +% h shl 15 result = THash(h) -proc GetHashStrCI(s: string): THash = +proc GetHashStrCI*(s: string): THash = var h: THash c: Char @@ -129,7 +117,7 @@ proc GetHashStrCI(s: string): THash = h = h +% h shl 15 result = THash(h) -proc GetHashCI(str: cstring): THash = +proc GetHashCI*(str: cstring): THash = var h: THash c: Char diff --git a/compiler/nimconf.nim b/compiler/nimconf.nim index c41417fb1..31558fe74 100755 --- a/compiler/nimconf.nim +++ b/compiler/nimconf.nim @@ -13,18 +13,13 @@ import llstream, nversion, commands, os, strutils, msgs, platform, condsyms, scanner, options, idents, wordrecg -proc LoadConfig*(project: string) -proc LoadSpecialConfig*(configfilename: string) -# implementation # ---------------- configuration file parser ----------------------------- # we use Nimrod's scanner here to safe space and work proc ppGetTok(L: var TLexer, tok: PToken) = # simple filter - rawGetTok(L, tok[] ) - while (tok.tokType == tkInd) or (tok.tokType == tkSad) or - (tok.tokType == tkDed) or (tok.tokType == tkComment): - rawGetTok(L, tok[] ) + rawGetTok(L, tok[]) + while tok.tokType in {tkInd, tkSad, tkDed, tkComment}: rawGetTok(L, tok[]) proc parseExpr(L: var TLexer, tok: PToken): bool proc parseAtom(L: var TLexer, tok: PToken): bool = @@ -36,25 +31,22 @@ proc parseAtom(L: var TLexer, tok: PToken): bool = elif tok.ident.id == ord(wNot): ppGetTok(L, tok) result = not parseAtom(L, tok) - else: - result = isDefined(tok.ident) #condsyms.listSymbols(); - #writeln(tok.ident.s + ' has the value: ', result); + else: + result = isDefined(tok.ident) ppGetTok(L, tok) proc parseAndExpr(L: var TLexer, tok: PToken): bool = - var b: bool result = parseAtom(L, tok) while tok.ident.id == ord(wAnd): ppGetTok(L, tok) # skip "and" - b = parseAtom(L, tok) + var b = parseAtom(L, tok) result = result and b proc parseExpr(L: var TLexer, tok: PToken): bool = - var b: bool result = parseAndExpr(L, tok) while tok.ident.id == ord(wOr): ppGetTok(L, tok) # skip "or" - b = parseAndExpr(L, tok) + var b = parseAndExpr(L, tok) result = result or b proc EvalppIf(L: var TLexer, tok: PToken): bool = @@ -63,9 +55,8 @@ proc EvalppIf(L: var TLexer, tok: PToken): bool = if tok.tokType == tkColon: ppGetTok(L, tok) else: lexMessage(L, errTokenExpected, "\':\'") -var condStack: seq[bool] +var condStack: seq[bool] = @[] -condStack = @ [] proc doEnd(L: var TLexer, tok: PToken) = if high(condStack) < 0: lexMessage(L, errTokenExpected, "@if") ppGetTok(L, tok) # skip 'end' @@ -83,15 +74,13 @@ proc doElse(L: var TLexer, tok: PToken) = if condStack[high(condStack)]: jumpToDirective(L, tok, jdEndif) proc doElif(L: var TLexer, tok: PToken) = - var res: bool if high(condStack) < 0: lexMessage(L, errTokenExpected, "@if") - res = EvalppIf(L, tok) + var res = EvalppIf(L, tok) if condStack[high(condStack)] or not res: jumpToDirective(L, tok, jdElseEndif) else: condStack[high(condStack)] = true proc jumpToDirective(L: var TLexer, tok: PToken, dest: TJumpDest) = - var nestedIfs: int - nestedIfs = 0 + var nestedIfs = 0 while True: if (tok.ident != nil) and (tok.ident.s == "@"): ppGetTok(L, tok) @@ -120,42 +109,35 @@ proc jumpToDirective(L: var TLexer, tok: PToken, dest: TJumpDest) = ppGetTok(L, tok) proc parseDirective(L: var TLexer, tok: PToken) = - var - res: bool - key: string ppGetTok(L, tok) # skip @ case whichKeyword(tok.ident) of wIf: setlen(condStack, len(condStack) + 1) - res = EvalppIf(L, tok) + var res = EvalppIf(L, tok) condStack[high(condStack)] = res - if not res: - jumpToDirective(L, tok, jdElseEndif) - of wElif: - doElif(L, tok) - of wElse: - doElse(L, tok) - of wEnd: - doEnd(L, tok) + if not res: jumpToDirective(L, tok, jdElseEndif) + of wElif: doElif(L, tok) + of wElse: doElse(L, tok) + of wEnd: doEnd(L, tok) of wWrite: ppGetTok(L, tok) msgs.MsgWriteln(tokToStr(tok)) ppGetTok(L, tok) of wPutEnv: ppGetTok(L, tok) - key = tokToStr(tok) + var key = tokToStr(tok) ppGetTok(L, tok) os.putEnv(key, tokToStr(tok)) ppGetTok(L, tok) of wPrependEnv: ppGetTok(L, tok) - key = tokToStr(tok) + var key = tokToStr(tok) ppGetTok(L, tok) os.putEnv(key, tokToStr(tok) & os.getenv(key)) ppGetTok(L, tok) of wAppendenv: ppGetTok(L, tok) - key = tokToStr(tok) + var key = tokToStr(tok) ppGetTok(L, tok) os.putEnv(key, os.getenv(key) & tokToStr(tok)) ppGetTok(L, tok) @@ -163,24 +145,21 @@ proc parseDirective(L: var TLexer, tok: PToken) = proc confTok(L: var TLexer, tok: PToken) = ppGetTok(L, tok) - while (tok.ident != nil) and (tok.ident.s == "@"): + while tok.ident != nil and tok.ident.s == "@": parseDirective(L, tok) # else: give the token to the parser proc checkSymbol(L: TLexer, tok: PToken) = - if not (tok.tokType in {tkSymbol..pred(tkIntLit), tkStrLit..tkTripleStrLit}): + if tok.tokType notin {tkSymbol..pred(tkIntLit), tkStrLit..tkTripleStrLit}: lexMessage(L, errIdentifierExpected, tokToStr(tok)) proc parseAssignment(L: var TLexer, tok: PToken) = - var - s, val: string - info: TLineInfo - if (tok.ident.id == getIdent("-").id) or (tok.ident.id == getIdent("--").id): + if tok.ident.id == getIdent("-").id or tok.ident.id == getIdent("--").id: confTok(L, tok) # skip unnecessary prefix - info = getLineInfo(L) # safe for later in case of an error + var info = getLineInfo(L) # safe for later in case of an error checkSymbol(L, tok) - s = tokToStr(tok) + var s = tokToStr(tok) confTok(L, tok) # skip symbol - val = "" + var val = "" while tok.tokType == tkDot: add(s, '.') confTok(L, tok) @@ -197,14 +176,13 @@ proc parseAssignment(L: var TLexer, tok: PToken) = if tok.tokType == tkBracketRi: confTok(L, tok) else: lexMessage(L, errTokenExpected, "\']\'") add(val, ']') - if (tok.tokType == tkColon) or (tok.tokType == tkEquals): - if len(val) > 0: - add(val, ':') # BUGFIX + if tok.tokType in {tkColon, tkEquals}: + if len(val) > 0: add(val, ':') confTok(L, tok) # skip ':' or '=' checkSymbol(L, tok) add(val, tokToStr(tok)) confTok(L, tok) # skip symbol - while (tok.ident != nil) and (tok.ident.id == getIdent("&").id): + while tok.ident != nil and tok.ident.id == getIdent("&").id: confTok(L, tok) checkSymbol(L, tok) add(val, tokToStr(tok)) @@ -234,24 +212,22 @@ proc getConfigPath(filename: string): string = # try standard configuration file (installation did not distribute files # the UNIX way) result = joinPath([getPrefixDir(), "config", filename]) - if not ExistsFile(result): - result = "/etc/" & filename + if not ExistsFile(result): result = "/etc/" & filename -proc LoadSpecialConfig(configfilename: string) = - if not (optSkipConfigFile in gGlobalOptions): +proc LoadSpecialConfig*(configfilename: string) = + if optSkipConfigFile notin gGlobalOptions: readConfigFile(getConfigPath(configfilename)) -proc LoadConfig(project: string) = - var conffile, prefix: string +proc LoadConfig*(project: string) = # set default value (can be overwritten): if libpath == "": # choose default libpath: - prefix = getPrefixDir() + var prefix = getPrefixDir() if (prefix == "/usr"): libpath = "/usr/lib/nimrod" elif (prefix == "/usr/local"): libpath = "/usr/local/lib/nimrod" else: libpath = joinPath(prefix, "lib") LoadSpecialConfig("nimrod.cfg") # read project config file: - if not (optSkipProjConfigFile in gGlobalOptions) and (project != ""): - conffile = changeFileExt(project, "cfg") + if optSkipProjConfigFile notin gGlobalOptions and project != "": + var conffile = changeFileExt(project, "cfg") if existsFile(conffile): readConfigFile(conffile) diff --git a/compiler/pnimsyn.nim b/compiler/pnimsyn.nim index 990ca543d..80adc7824 100755 --- a/compiler/pnimsyn.nim +++ b/compiler/pnimsyn.nim @@ -44,7 +44,6 @@ proc newStrNodeP*(kind: TNodeKind, strVal: string, p: TParser): PNode proc newIdentNodeP*(ident: PIdent, p: TParser): PNode proc expectIdentOrKeyw*(p: TParser) proc ExpectIdent*(p: TParser) -proc expectIdentOrOpr*(p: TParser) proc parLineInfo*(p: TParser): TLineInfo proc Eat*(p: var TParser, TokType: TTokType) proc skipInd*(p: var TParser) @@ -101,10 +100,6 @@ proc ExpectIdent(p: TParser) = if p.tok.tokType != tkSymbol: lexMessage(p.lex[], errIdentifierExpected, tokToStr(p.tok)) -proc expectIdentOrOpr(p: TParser) = - if not (p.tok.tokType in tokOperators): - lexMessage(p.lex[], errOperatorExpected, tokToStr(p.tok)) - proc Eat(p: var TParser, TokType: TTokType) = if p.tok.TokType == TokType: getTok(p) else: lexMessage(p.lex[], errTokenExpected, TokTypeToStr[tokType]) diff --git a/compiler/ropes.nim b/compiler/ropes.nim index 62fdca4ae..9c4c5e700 100755 --- a/compiler/ropes.nim +++ b/compiler/ropes.nim @@ -274,7 +274,7 @@ proc app(a: var PRope, b: PRope) = a = con(a, b) proc app(a: var PRope, b: string) = a = con(a, b) proc prepend(a: var PRope, b: PRope) = a = con(b, a) -proc writeRope*(f: var tfile, c: PRope) = +proc writeRope*(f: TFile, c: PRope) = var stack = @[c] while len(stack) > 0: var it = pop(stack) diff --git a/compiler/scanner.nim b/compiler/scanner.nim index a14773773..f3d83480d 100755 --- a/compiler/scanner.nim +++ b/compiler/scanner.nim @@ -1,7 +1,7 @@ # # # The Nimrod Compiler -# (c) Copyright 2010 Andreas Rumpf +# (c) Copyright 2011 Andreas Rumpf # # See the file "copying.txt", included in this # distribution, for details about the copyright. @@ -25,27 +25,12 @@ const SymChars*: TCharSet = {'a'..'z', 'A'..'Z', '0'..'9', '\x80'..'\xFF'} SymStartChars*: TCharSet = {'a'..'z', 'A'..'Z', '\x80'..'\xFF'} OpChars*: TCharSet = {'+', '-', '*', '/', '\\', '<', '>', '!', '?', '^', '.', - '|', '=', '%', '&', '$', '@', '~', '\x80'..'\xFF'} + '|', '=', '%', '&', '$', '@', '~', ':', '\x80'..'\xFF'} type TTokType* = enum tkInvalid, tkEof, # order is important here! tkSymbol, # keywords: - #[[[cog - #from string import split, capitalize - #keywords = split(open("data/keywords.txt").read()) - #idents = "" - #strings = "" - #i = 1 - #for k in keywords: - # idents = idents + "tk" + capitalize(k) + ", " - # strings = strings + "'" + k + "', " - # if i % 4 == 0: - # idents = idents + "\n" - # strings = strings + "\n" - # i = i + 1 - #cog.out(idents) - #]]] tkAddr, tkAnd, tkAs, tkAsm, tkAtomic, tkBind, tkBlock, tkBreak, tkCase, tkCast, tkConst, tkContinue, tkConverter, tkDiscard, tkDistinct, tkDiv, tkElif, @@ -55,7 +40,7 @@ type tkMacro, tkMethod, tkMod, tkNil, tkNot, tkNotin, tkObject, tkOf, tkOr, tkOut, tkProc, tkPtr, tkRaise, tkRef, tkReturn, tkShl, tkShr, tkTemplate, tkTry, tkTuple, tkType, tkVar, tkWhen, tkWhile, tkWith, tkWithout, tkXor, - tkYield, #[[[end]]] + tkYield, # end of keywords tkIntLit, tkInt8Lit, tkInt16Lit, tkInt32Lit, tkInt64Lit, tkFloatLit, tkFloat32Lit, tkFloat64Lit, tkStrLit, tkRStrLit, tkTripleStrLit, tkGStrLit, tkGTripleStrLit, tkCharLit, tkParLe, tkParRi, tkBracketLe, @@ -63,8 +48,8 @@ type tkBracketDotLe, tkBracketDotRi, # [. and .] tkCurlyDotLe, tkCurlyDotRi, # {. and .} tkParDotLe, tkParDotRi, # (. and .) - tkComma, tkSemiColon, tkColon, tkEquals, tkDot, tkDotDot, tkHat, tkOpr, - tkComment, tkAccent, tkInd, tkSad, + tkComma, tkSemiColon, tkColon, tkColonColon, tkEquals, tkDot, tkDotDot, + tkHat, tkOpr, tkComment, tkAccent, tkInd, tkSad, tkDed, # pseudo token types used by the source renderers: tkSpaces, tkInfixOpr, tkPrefixOpr, tkPostfixOpr TTokTypes* = set[TTokType] @@ -72,13 +57,8 @@ type const tokKeywordLow* = succ(tkSymbol) tokKeywordHigh* = pred(tkIntLit) - tokOperators*: TTokTypes = {tkOpr, tkSymbol, tkBracketLe, tkBracketRi, tkIn, - tkIs, tkIsNot, tkEquals, tkDot, tkHat, tkNot, tkAnd, tkOr, tkXor, tkShl, - tkShr, tkDiv, tkMod, tkNotIn} TokTypeToStr*: array[TTokType, string] = ["tkInvalid", "[EOF]", - "tkSymbol", #[[[cog - #cog.out(strings) - #]]] + "tkSymbol", "addr", "and", "as", "asm", "atomic", "bind", "block", "break", "case", "cast", "const", "continue", "converter", "discard", "distinct", "div", "elif", @@ -88,11 +68,12 @@ const "macro", "method", "mod", "nil", "not", "notin", "object", "of", "or", "out", "proc", "ptr", "raise", "ref", "return", "shl", "shr", "template", "try", "tuple", "type", "var", "when", "while", "with", "without", "xor", - "yield", #[[[end]]] + "yield", "tkIntLit", "tkInt8Lit", "tkInt16Lit", "tkInt32Lit", "tkInt64Lit", "tkFloatLit", "tkFloat32Lit", "tkFloat64Lit", "tkStrLit", "tkRStrLit", "tkTripleStrLit", "tkGStrLit", "tkGTripleStrLit", "tkCharLit", "(", - ")", "[", "]", "{", "}", "[.", ".]", "{.", ".}", "(.", ".)", ",", ";", ":", + ")", "[", "]", "{", "}", "[.", ".]", "{.", ".}", "(.", ".)", ",", ";", + ":", "::", "=", ".", "..", "^", "tkOpr", "tkComment", "`", "[new indentation]", "[same indentation]", "[dedentation]", "tkSpaces", "tkInfixOpr", "tkPrefixOpr", "tkPostfixOpr"] @@ -414,8 +395,7 @@ proc handleHexChar(L: var TLexer, xi: var int) = of 'A'..'F': xi = (xi shl 4) or (ord(L.buf[L.bufpos]) - ord('A') + 10) inc(L.bufpos) - else: - nil + else: nil proc handleDecChars(L: var TLexer, xi: var int) = while L.buf[L.bufpos] in {'0'..'9'}: @@ -508,7 +488,7 @@ proc getString(L: var TLexer, tok: var TToken, rawMode: bool) = of CR, LF: pos = HandleCRLF(L, pos) buf = L.buf - tok.literal = tok.literal & tnl + add(tok.literal, tnl) of lexbase.EndOfFile: var line2 = L.linenumber L.LineNumber = line @@ -563,23 +543,17 @@ proc getSymbol(L: var TLexer, tok: var TToken) = var c = buf[pos] case c of 'a'..'z', '0'..'9', '\x80'..'\xFF': - h = h +% Ord(c) - h = h +% h shl 10 - h = h xor (h shr 6) + h = concHash(h, ord(c)) of 'A'..'Z': c = chr(ord(c) + (ord('a') - ord('A'))) # toLower() - h = h +% Ord(c) - h = h +% h shl 10 - h = h xor (h shr 6) + h = concHash(h, ord(c)) of '_': if buf[pos+1] notin SymChars: lexMessage(L, errInvalidToken, "_") break else: break Inc(pos) - h = h +% h shl 3 - h = h xor (h shr 11) - h = h +% h shl 15 + h = finishHash(h) tok.ident = getIdent(addr(L.buf[L.bufpos]), pos - L.bufpos, h) L.bufpos = pos if (tok.ident.id < ord(tokKeywordLow) - ord(tkSymbol)) or @@ -588,26 +562,24 @@ proc getSymbol(L: var TLexer, tok: var TToken) = else: tok.tokType = TTokType(tok.ident.id + ord(tkSymbol)) +proc endOperator(L: var TLexer, tok: var TToken, pos: int, + hash: THash) {.inline.} = + var h = finishHash(hash) + tok.ident = getIdent(addr(L.buf[L.bufpos]), pos - L.bufpos, h) + if (tok.ident.id < oprLow) or (tok.ident.id > oprHigh): tok.tokType = tkOpr + else: tok.tokType = TTokType(tok.ident.id - oprLow + ord(tkColon)) + L.bufpos = pos + proc getOperator(L: var TLexer, tok: var TToken) = var pos = L.bufpos var buf = L.buf var h: THash = 0 while true: var c = buf[pos] - if c in OpChars: - h = h +% Ord(c) - h = h +% h shl 10 - h = h xor (h shr 6) - else: - break + if c notin OpChars: break + h = concHash(h, Ord(c)) Inc(pos) - h = h +% h shl 3 - h = h xor (h shr 11) - h = h +% h shl 15 - tok.ident = getIdent(addr(L.buf[L.bufpos]), pos - L.bufpos, h) - if (tok.ident.id < oprLow) or (tok.ident.id > oprHigh): tok.tokType = tkOpr - else: tok.tokType = TTokType(tok.ident.id - oprLow + ord(tkColon)) - L.bufpos = pos + endOperator(L, tok, pos, h) proc handleIndentation(L: var TLexer, tok: var TToken, indent: int) = tok.indent = indent @@ -679,17 +651,17 @@ proc skip(L: var TLexer, tok: var TToken) = proc rawGetTok(L: var TLexer, tok: var TToken) = fillToken(tok) - if L.dedent > 0: + if L.dedent > 0: dec(L.dedent) if L.indentAhead >= 0: handleIndentation(L, tok, L.indentAhead) L.indentAhead = - 1 - else: + else: tok.tokType = tkDed - return + return skip(L, tok) # got an documentation comment or tkIndent, return that: - if tok.toktype != tkInvalid: return + if tok.toktype != tkInvalid: return var c = L.buf[L.bufpos] if c in SymStartChars - {'r', 'R', 'l'}: getSymbol(L, tok) @@ -699,10 +671,15 @@ proc rawGetTok(L: var TLexer, tok: var TToken) = case c of '#': scanComment(L, tok) - of ':': - tok.tokType = tkColon - inc(L.bufpos) - of ',': + of '*': + # '*:' is unfortunately a special case, because it is two tokens in + # 'var v*: int'. + if L.buf[L.bufpos+1] == ':' and L.buf[L.bufpos+2] notin OpChars: + var h = concHash(0, ord('*')) + endOperator(L, tok, L.bufpos+1, h) + else: + getOperator(L, tok) + of ',': tok.toktype = tkComma Inc(L.bufpos) of 'l': @@ -751,7 +728,7 @@ proc rawGetTok(L: var TLexer, tok: var TToken) = getOperator(L, tok) of '{': Inc(L.bufpos) - if (L.buf[L.bufPos] == '.') and (L.buf[L.bufPos + 1] != '.'): + if (L.buf[L.bufPos] == '.') and (L.buf[L.bufPos+1] != '.'): tok.toktype = tkCurlyDotLe Inc(L.bufpos) else: @@ -777,12 +754,12 @@ proc rawGetTok(L: var TLexer, tok: var TToken) = tok.tokType = tkCharLit getCharacter(L, tok) tok.tokType = tkCharLit - of lexbase.EndOfFile: - tok.toktype = tkEof - else: + else: if c in OpChars: getOperator(L, tok) - else: + elif c == lexbase.EndOfFile: + tok.toktype = tkEof + else: tok.literal = c & "" tok.tokType = tkInvalid lexMessage(L, errInvalidToken, c & " (\\" & $(ord(c)) & ')') diff --git a/compiler/wordrecg.nim b/compiler/wordrecg.nim index 8376fa01b..67c5b9542 100755 --- a/compiler/wordrecg.nim +++ b/compiler/wordrecg.nim @@ -32,7 +32,7 @@ type wShl, wShr, wTemplate, wTry, wTuple, wType, wVar, wWhen, wWhile, wWith, wWithout, wXor, wYield, - wColon, wEquals, wDot, wDotDot, wHat, wStar, wMinus, + wColon, wColonColon, wEquals, wDot, wDotDot, wHat, wStar, wMinus, wMagic, wTypeCheck, wFinal, wProfiler, wObjChecks, wImportc, wExportc, wExtern, wAlign, wNodecl, wPure, wVolatile, wRegister, wSideeffect, wHeader, @@ -78,7 +78,7 @@ const "try", "tuple", "type", "var", "when", "while", "with", "without", "xor", "yield", - ":", "=", ".", "..", "^", "*", "-", + ":", "::", "=", ".", "..", "^", "*", "-", "magic", "typecheck", "final", "profiler", "objchecks", "importc", "exportc", "extern", "align", "nodecl", "pure", "volatile", "register", "sideeffect", diff --git a/lib/pure/strutils.nim b/lib/pure/strutils.nim index de555917c..382eece7b 100755 --- a/lib/pure/strutils.nim +++ b/lib/pure/strutils.nim @@ -103,7 +103,7 @@ proc cmpIgnoreCase*(a, b: string): int {.noSideEffect, ## | 0 iff a == b ## | < 0 iff a < b ## | > 0 iff a > b - var i = 0 + var i = 0 var m = min(a.len, b.len) while i < m: result = ord(toLower(a[i])) - ord(toLower(b[i])) @@ -406,7 +406,7 @@ proc ParseInt*(s: string): int {.noSideEffect, procvar, ## Parses a decimal integer value contained in `s`. If `s` is not ## a valid integer, `EInvalidValue` is raised. var L = parseutils.parseInt(s, result, 0) - if L != s.len or L == 0: + if L != s.len or L == 0: raise newException(EInvalidValue, "invalid integer: " & s) proc ParseBiggestInt*(s: string): biggestInt {.noSideEffect, procvar, @@ -414,7 +414,7 @@ proc ParseBiggestInt*(s: string): biggestInt {.noSideEffect, procvar, ## Parses a decimal integer value contained in `s`. If `s` is not ## a valid integer, `EInvalidValue` is raised. var L = parseutils.parseBiggestInt(s, result, 0) - if L != s.len or L == 0: + if L != s.len or L == 0: raise newException(EInvalidValue, "invalid integer: " & s) proc ParseFloat*(s: string): float {.noSideEffect, procvar, @@ -423,7 +423,7 @@ proc ParseFloat*(s: string): float {.noSideEffect, procvar, ## a valid floating point number, `EInvalidValue` is raised. ``NAN``, ## ``INF``, ``-INF`` are also supported (case insensitive comparison). var L = parseutils.parseFloat(s, result, 0) - if L != s.len or L == 0: + if L != s.len or L == 0: raise newException(EInvalidValue, "invalid float: " & s) proc ParseHexInt*(s: string): int {.noSideEffect, procvar, @@ -952,7 +952,7 @@ type TFloatFormat* = enum ffDefault, ## use the shorter floating point notation ffDecimal, ## use decimal floating point notation - ffScientific ## use scientific notation (using ``e``) character + ffScientific ## use scientific notation (using ``e`` character) proc formatBiggestFloat*(f: BiggestFloat, format: TFloatFormat = ffDefault, precision = 16): string {.noSideEffect, @@ -1006,6 +1006,6 @@ when isMainModule: it goes""", 10, false) assert formatBiggestFloat(0.00000000001, ffDecimal, 11) == "0.00000000001" assert formatBiggestFloat(0.00000000001, ffScientific, 1) == "1.0e-11" - + assert "$# $3 $# $#" % ["a", "b", "c"] == "a c b c" diff --git a/lib/system.nim b/lib/system.nim index 8fc4493dd..6490ce416 100755 --- a/lib/system.nim +++ b/lib/system.nim @@ -650,13 +650,15 @@ proc setLen*[T](s: var seq[T], newlen: int) {. ## sets the length of `s` to `newlen`. ## ``T`` may be any sequence type. ## If the current length is greater than the new length, - ## ``s`` will be truncated. + ## ``s`` will be truncated. `s` cannot be nil! To initialize a sequence with + ## a size, use ``newSeq`` instead. proc setLen*(s: var string, newlen: int) {. magic: "SetLengthStr", noSideEffect.} ## sets the length of `s` to `newlen`. ## If the current length is greater than the new length, - ## ``s`` will be truncated. + ## ``s`` will be truncated. `s` cannot be nil! To initialize a string with + ## a size, use ``newString`` instead. proc newString*(len: int): string {. magic: "NewString", importc: "mnewString", noSideEffect.} diff --git a/lib/system/gc.nim b/lib/system/gc.nim index eb4811bf5..950b60c27 100755 --- a/lib/system/gc.nim +++ b/lib/system/gc.nim @@ -642,7 +642,11 @@ proc unmarkStackAndRegisters(gch: var TGcHeap) = var d = gch.decStack.d for i in 0..gch.decStack.len-1: assert isAllocatedPtr(allocator, d[i]) - decRef(d[i]) # OPT: cannot create a cycle! + # decRef(d[i]) inlined: cannot create a cycle + var c = d[i] + if atomicDec(c.refcount, rcIncrement) <% rcIncrement: + rtlAddZCT(c) + assert c.typ != nil gch.decStack.len = 0 proc collectCT(gch: var TGcHeap) = diff --git a/tests/accept/compile/ttempl4.nim b/tests/accept/compile/ttempl4.nim new file mode 100644 index 000000000..273605669 --- /dev/null +++ b/tests/accept/compile/ttempl4.nim @@ -0,0 +1,8 @@ + +template `:=`(name, val: expr): stmt = + var name = val + +ha := 1 +hu := "ta-da" +echo ha, hu + |