diff options
author | Oscar Campbell <oscar@campbell.nu> | 2015-06-07 13:17:06 +0200 |
---|---|---|
committer | Oscar Campbell <oscar@campbell.nu> | 2015-06-07 13:17:06 +0200 |
commit | f0b6c03b2686aca85670cd35f84c6b0bdc3ff23d (patch) | |
tree | d0b0357ac4398d68f1067f33b9dac03fe7b308d2 /compiler | |
parent | 0a810fd10f81e11e6b738a18ff18e62c89479436 (diff) | |
parent | 858cdd0b05df4846fb40a3263f05e54438995e99 (diff) | |
download | Nim-f0b6c03b2686aca85670cd35f84c6b0bdc3ff23d.tar.gz |
Merge branch 'devel' into bugfix-2858-testament-sources-system-wide
Diffstat (limited to 'compiler')
-rw-r--r-- | compiler/ast.nim | 3 | ||||
-rw-r--r-- | compiler/ccgexprs.nim | 2 | ||||
-rw-r--r-- | compiler/cgen.nim | 2 | ||||
-rw-r--r-- | compiler/lambdalifting.nim | 6 | ||||
-rw-r--r-- | compiler/msgs.nim | 6 | ||||
-rw-r--r-- | compiler/nimfix/nimfix.nim | 14 | ||||
-rw-r--r-- | compiler/nimfix/pretty.nim | 20 | ||||
-rw-r--r-- | compiler/nimfix/prettybase.nim | 7 | ||||
-rw-r--r-- | compiler/nimsuggest/nimsuggest.nim | 328 | ||||
-rw-r--r-- | compiler/nimsuggest/nimsuggest.nim.cfg | 17 | ||||
-rw-r--r-- | compiler/parser.nim | 14 | ||||
-rw-r--r-- | compiler/patterns.nim | 4 | ||||
-rw-r--r-- | compiler/plugins/locals/locals.nim | 3 | ||||
-rw-r--r-- | compiler/pragmas.nim | 4 | ||||
-rw-r--r-- | compiler/semcall.nim | 5 | ||||
-rw-r--r-- | compiler/sempass2.nim | 10 | ||||
-rw-r--r-- | compiler/semstmts.nim | 2 | ||||
-rw-r--r-- | compiler/wordrecg.nim | 4 |
18 files changed, 73 insertions, 378 deletions
diff --git a/compiler/ast.nim b/compiler/ast.nim index 044f21341..c141352cb 100644 --- a/compiler/ast.nim +++ b/compiler/ast.nim @@ -423,6 +423,7 @@ type # but unfortunately it has measurable impact for compilation # efficiency nfTransf, # node has been transformed + nfNoRewrite # node should not be transformed anymore nfSem # node has been checked for semantics nfLL # node has gone through lambda lifting nfDotField # the call can use a dot operator @@ -1345,7 +1346,7 @@ proc propagateToOwner*(owner, elem: PType) = owner.flags.incl tfHasAsgn if owner.kind notin {tyProc, tyGenericInst, tyGenericBody, - tyGenericInvocation}: + tyGenericInvocation, tyPtr}: let elemB = elem.skipTypes({tyGenericInst}) if elemB.isGCedMem or tfHasGCedMem in elemB.flags: # for simplicity, we propagate this flag even to generics. We then diff --git a/compiler/ccgexprs.nim b/compiler/ccgexprs.nim index 05a3602d1..64902c3fc 100644 --- a/compiler/ccgexprs.nim +++ b/compiler/ccgexprs.nim @@ -2150,7 +2150,7 @@ proc genNamedConstExpr(p: BProc, n: PNode): Rope = proc genConstSimpleList(p: BProc, n: PNode): Rope = var length = sonsLen(n) result = rope("{") - for i in countup(0, length - 2): + for i in countup(ord(n.kind == nkObjConstr), length - 2): addf(result, "$1,$n", [genNamedConstExpr(p, n.sons[i])]) if length > 0: add(result, genNamedConstExpr(p, n.sons[length - 1])) addf(result, "}$n", []) diff --git a/compiler/cgen.nim b/compiler/cgen.nim index 4b0bac28a..91877833a 100644 --- a/compiler/cgen.nim +++ b/compiler/cgen.nim @@ -721,6 +721,8 @@ proc genProcPrototype(m: BModule, sym: PSym) = getTypeDesc(m, sym.loc.t), mangleDynLibProc(sym))) elif not containsOrIncl(m.declaredProtos, sym.id): var header = genProcHeader(m, sym) + if sfNoReturn in sym.flags and hasDeclspec in extccomp.CC[cCompiler].props: + header = "__declspec(noreturn) " & header if sym.typ.callConv != ccInline and crossesCppBoundary(m, sym): header = "extern \"C\" " & header if sfPure in sym.flags and hasAttribute in CC[cCompiler].props: diff --git a/compiler/lambdalifting.nim b/compiler/lambdalifting.nim index c68bc352c..69b45c980 100644 --- a/compiler/lambdalifting.nim +++ b/compiler/lambdalifting.nim @@ -946,7 +946,11 @@ proc transformOuterProc(o: POuterContext, n: PNode; it: TIter): PNode = proc liftLambdas*(fn: PSym, body: PNode): PNode = # XXX gCmd == cmdCompileToJS does not suffice! The compiletime stuff needs # the transformation even when compiling to JS ... - if body.kind == nkEmpty or gCmd == cmdCompileToJS or + + # However we can do lifting for the stuff which is *only* compiletime. + let isCompileTime = sfCompileTime in fn.flags or fn.kind == skMacro + + if body.kind == nkEmpty or (gCmd == cmdCompileToJS and not isCompileTime) or fn.skipGenericOwner.kind != skModule: # ignore forward declaration: result = body diff --git a/compiler/msgs.nim b/compiler/msgs.nim index e97032db4..81a62371e 100644 --- a/compiler/msgs.nim +++ b/compiler/msgs.nim @@ -34,7 +34,9 @@ type errNoneSpeedOrSizeExpectedButXFound, errGuiConsoleOrLibExpectedButXFound, errUnknownOS, errUnknownCPU, errGenOutExpectedButXFound, errArgsNeedRunOption, errInvalidMultipleAsgn, errColonOrEqualsExpected, - errExprExpected, errUndeclaredIdentifier, errUseQualifier, errTypeExpected, + errExprExpected, errUndeclaredIdentifier, errUndeclaredField, + errUndeclaredRoutine, errUseQualifier, + errTypeExpected, errSystemNeeds, errExecutionOfProgramFailed, errNotOverloadable, errInvalidArgForX, errStmtHasNoEffect, errXExpectsTypeOrValue, errXExpectsArrayType, errIteratorCannotBeInstantiated, errExprXAmbiguous, @@ -190,6 +192,8 @@ const errColonOrEqualsExpected: "\':\' or \'=\' expected, but found \'$1\'", errExprExpected: "expression expected, but found \'$1\'", errUndeclaredIdentifier: "undeclared identifier: \'$1\'", + errUndeclaredField: "undeclared field: \'$1\'", + errUndeclaredRoutine: "attempting to call undeclared routine: \'$1\'", errUseQualifier: "ambiguous identifier: \'$1\' -- use a qualifier", errTypeExpected: "type expected", errSystemNeeds: "system module needs \'$1\'", diff --git a/compiler/nimfix/nimfix.nim b/compiler/nimfix/nimfix.nim index 8caa23ee3..3641aec36 100644 --- a/compiler/nimfix/nimfix.nim +++ b/compiler/nimfix/nimfix.nim @@ -10,8 +10,10 @@ ## Nimfix is a tool that helps to convert old-style Nimrod code to Nim code. import strutils, os, parseopt -import options, commands, modules, sem, passes, passaux, pretty, msgs, nimconf, - extccomp, condsyms, lists +import compiler/options, compiler/commands, compiler/modules, compiler/sem, + compiler/passes, compiler/passaux, compiler/nimfix/pretty, + compiler/msgs, compiler/nimconf, + compiler/extccomp, compiler/condsyms, compiler/lists const Usage = """ Nimfix - Tool to patch Nim code @@ -24,7 +26,7 @@ Options: --wholeProject overwrite every processed file. --checkExtern:on|off style check also extern names --styleCheck:on|off|auto performs style checking for identifiers - and suggests an alternative spelling; + and suggests an alternative spelling; 'auto' corrects the spelling. --bestEffort try to fix the code even when there are errors. @@ -48,11 +50,11 @@ proc processCmdLine*(pass: TCmdLinePass, cmd: string) = var p = parseopt.initOptParser(cmd) var argsCount = 0 gOnlyMainfile = true - while true: + while true: parseopt.next(p) case p.kind - of cmdEnd: break - of cmdLongoption, cmdShortOption: + of cmdEnd: break + of cmdLongoption, cmdShortOption: case p.key.normalize of "overwritefiles": case p.val.normalize diff --git a/compiler/nimfix/pretty.nim b/compiler/nimfix/pretty.nim index d2d5b5e83..1123afb9e 100644 --- a/compiler/nimfix/pretty.nim +++ b/compiler/nimfix/pretty.nim @@ -10,9 +10,11 @@ ## This module implements the code "prettifier". This is part of the toolchain ## to convert Nim code into a consistent style. -import - strutils, os, options, ast, astalgo, msgs, ropes, idents, - intsets, strtabs, semdata, prettybase +import + strutils, os, intsets, strtabs + +import compiler/options, compiler/ast, compiler/astalgo, compiler/msgs, + compiler/semdata, compiler/nimfix/prettybase, compiler/ropes, compiler/idents type StyleCheck* {.pure.} = enum None, Warn, Auto @@ -92,7 +94,7 @@ proc beautifyName(s: string, k: TSymKind): string = proc replaceInFile(info: TLineInfo; newName: string) = loadFile(info) - + let line = gSourceFiles[info.fileIndex].lines[info.line-1] var first = min(info.col.int, line.len) if first < 0: return @@ -100,18 +102,18 @@ proc replaceInFile(info: TLineInfo; newName: string) = while first > 0 and line[first-1] in prettybase.Letters: dec first if first < 0: return if line[first] == '`': inc first - + let last = first+identLen(line, first)-1 if differ(line, first, last, newName): - # last-first+1 != newName.len or - var x = line.substr(0, first-1) & newName & line.substr(last+1) + # last-first+1 != newName.len or + var x = line.substr(0, first-1) & newName & line.substr(last+1) system.shallowCopy(gSourceFiles[info.fileIndex].lines[info.line-1], x) gSourceFiles[info.fileIndex].dirty = true proc checkStyle(info: TLineInfo, s: string, k: TSymKind; sym: PSym) = let beau = beautifyName(s, k) if s != beau: - if gStyleCheck == StyleCheck.Auto: + if gStyleCheck == StyleCheck.Auto: sym.name = getIdent(beau) replaceInFile(info, beau) else: @@ -137,7 +139,7 @@ proc styleCheckUseImpl(info: TLineInfo; s: PSym) = if info.fileIndex < 0: return # we simply convert it to what it looks like in the definition # for consistency - + # operators stay as they are: if s.kind in {skResult, skTemp} or s.name.s[0] notin prettybase.Letters: return diff --git a/compiler/nimfix/prettybase.nim b/compiler/nimfix/prettybase.nim index 5130d1863..0f17cbcb1 100644 --- a/compiler/nimfix/prettybase.nim +++ b/compiler/nimfix/prettybase.nim @@ -7,7 +7,8 @@ # distribution, for details about the copyright. # -import ast, msgs, strutils, idents, lexbase, streams +import strutils, lexbase, streams +import compiler/ast, compiler/msgs, compiler/idents from os import splitFile type @@ -39,7 +40,7 @@ proc loadFile*(info: TLineInfo) = var pos = lex.bufpos while true: case lex.buf[pos] - of '\c': + of '\c': gSourceFiles[i].newline = "\c\L" break of '\L', '\0': @@ -70,7 +71,7 @@ proc replaceDeprecated*(info: TLineInfo; oldSym, newSym: PIdent) = while first > 0 and line[first-1] in Letters: dec first if first < 0: return if line[first] == '`': inc first - + let last = first+identLen(line, first)-1 if cmpIgnoreStyle(line[first..last], oldSym.s) == 0: var x = line.substr(0, first-1) & newSym.s & line.substr(last+1) diff --git a/compiler/nimsuggest/nimsuggest.nim b/compiler/nimsuggest/nimsuggest.nim index 2c785d118..2be368d68 100644 --- a/compiler/nimsuggest/nimsuggest.nim +++ b/compiler/nimsuggest/nimsuggest.nim @@ -7,330 +7,6 @@ # distribution, for details about the copyright. # -## Nimsuggest is a tool that helps to give editors IDE like capabilities. +## Nimsuggest has been moved to https://github.com/nim-lang/nimsuggest -import strutils, os, parseopt, parseutils, sequtils, net -# Do NOT import suggest. It will lead to wierd bugs with -# suggestionResultHook, because suggest.nim is included by sigmatch. -# So we import that one instead. -import options, commands, modules, sem, passes, passaux, msgs, nimconf, - extccomp, condsyms, lists, net, rdstdin, sexp, sigmatch, ast - -when defined(windows): - import winlean -else: - import posix - -const Usage = """ -Nimsuggest - Tool to give every editor IDE like capabilities for Nim -Usage: - nimsuggest [options] projectfile.nim - -Options: - --port:PORT port, by default 6000 - --address:HOST binds to that address, by default "" - --stdin read commands from stdin and write results to - stdout instead of using sockets - --epc use emacs epc mode - -The server then listens to the connection and takes line-based commands. - -In addition, all command line options of Nim that do not affect code generation -are supported. -""" -type - Mode = enum mstdin, mtcp, mepc - -var - gPort = 6000.Port - gAddress = "" - gMode: Mode - -const - seps = {':', ';', ' ', '\t'} - Help = "usage: sug|con|def|use file.nim[;dirtyfile.nim]:line:col\n"& - "type 'quit' to quit\n" & - "type 'debug' to toggle debug mode on/off\n" & - "type 'terse' to toggle terse mode on/off" - -type - EUnexpectedCommand = object of Exception - -proc parseQuoted(cmd: string; outp: var string; start: int): int = - var i = start - i += skipWhitespace(cmd, i) - if cmd[i] == '"': - i += parseUntil(cmd, outp, '"', i+1)+2 - else: - i += parseUntil(cmd, outp, seps, i) - result = i - -proc sexp(s: IdeCmd): SexpNode = sexp($s) - -proc sexp(s: TSymKind): SexpNode = sexp($s) - -proc sexp(s: Suggest): SexpNode = - # If you change the oder here, make sure to change it over in - # nim-mode.el too. - result = convertSexp([ - s.section, - s.symkind, - s.qualifiedPath.map(newSString), - s.filePath, - s.forth, - s.line, - s.column, - s.doc - ]) - -proc sexp(s: seq[Suggest]): SexpNode = - result = newSList() - for sug in s: - result.add(sexp(sug)) - -proc listEPC(): SexpNode = - let - argspecs = sexp("file line column dirtyfile".split(" ").map(newSSymbol)) - docstring = sexp("line starts at 1, column at 0, dirtyfile is optional") - result = newSList() - for command in ["sug", "con", "def", "use"]: - let - cmd = sexp(command) - methodDesc = newSList() - methodDesc.add(cmd) - methodDesc.add(argspecs) - methodDesc.add(docstring) - result.add(methodDesc) - -proc execute(cmd: IdeCmd, file, dirtyfile: string, line, col: int) = - gIdeCmd = cmd - if cmd == ideUse: - modules.resetAllModules() - var isKnownFile = true - let dirtyIdx = file.fileInfoIdx(isKnownFile) - - if dirtyfile.len != 0: msgs.setDirtyFile(dirtyIdx, dirtyfile) - else: msgs.setDirtyFile(dirtyIdx, nil) - - resetModule dirtyIdx - if dirtyIdx != gProjectMainIdx: - resetModule gProjectMainIdx - - gTrackPos = newLineInfo(dirtyIdx, line, col) - gErrorCounter = 0 - if not isKnownFile: - compileProject() - compileProject(dirtyIdx) - -proc executeEPC(cmd: IdeCmd, args: SexpNode) = - let - file = args[0].getStr - line = args[1].getNum - column = args[2].getNum - var dirtyfile = "" - if len(args) > 3: - dirtyfile = args[3].getStr(nil) - execute(cmd, file, dirtyfile, int(line), int(column)) - -proc returnEPC(socket: var Socket, uid: BiggestInt, s: SexpNode, return_symbol = "return") = - let response = $convertSexp([newSSymbol(return_symbol), uid, s]) - socket.send(toHex(len(response), 6)) - socket.send(response) - -proc connectToNextFreePort(server: Socket, host: string, start = 30000): int = - result = start - while true: - try: - server.bindaddr(Port(result), host) - return - except OsError: - when defined(windows): - let checkFor = WSAEADDRINUSE.OSErrorCode - else: - let checkFor = EADDRINUSE.OSErrorCode - if osLastError() != checkFor: - raise getCurrentException() - else: - result += 1 - -proc parseCmdLine(cmd: string) = - template toggle(sw) = - if sw in gGlobalOptions: - excl(gGlobalOptions, sw) - else: - incl(gGlobalOptions, sw) - return - - template err() = - echo Help - return - - var opc = "" - var i = parseIdent(cmd, opc, 0) - case opc.normalize - of "sug": gIdeCmd = ideSug - of "con": gIdeCmd = ideCon - of "def": gIdeCmd = ideDef - of "use": gIdeCmd = ideUse - of "quit": quit() - of "debug": toggle optIdeDebug - of "terse": toggle optIdeTerse - else: err() - var dirtyfile = "" - var orig = "" - i = parseQuoted(cmd, orig, i) - if cmd[i] == ';': - i = parseQuoted(cmd, dirtyfile, i+1) - i += skipWhile(cmd, seps, i) - var line = -1 - var col = 0 - i += parseInt(cmd, line, i) - i += skipWhile(cmd, seps, i) - i += parseInt(cmd, col, i) - - execute(gIdeCmd, orig, dirtyfile, line, col-1) - -proc serve() = - case gMode: - of mstdin: - echo Help - var line = "" - while readLineFromStdin("> ", line): - parseCmdLine line - echo "" - flushFile(stdout) - of mtcp: - var server = newSocket() - server.bindAddr(gPort, gAddress) - var inp = "".TaintedString - server.listen() - - while true: - var stdoutSocket = newSocket() - msgs.writelnHook = proc (line: string) = - stdoutSocket.send(line & "\c\L") - - accept(server, stdoutSocket) - - stdoutSocket.readLine(inp) - parseCmdLine inp.string - - stdoutSocket.send("\c\L") - stdoutSocket.close() - of mepc: - var server = newSocket() - let port = connectToNextFreePort(server, "localhost") - var inp = "".TaintedString - server.listen() - echo(port) - var client = newSocket() - # Wait for connection - accept(server, client) - while true: - var sizeHex = "" - if client.recv(sizeHex, 6) != 6: - raise newException(ValueError, "didn't get all the hexbytes") - var size = 0 - if parseHex(sizeHex, size) == 0: - raise newException(ValueError, "invalid size hex: " & $sizeHex) - var messageBuffer = "" - if client.recv(messageBuffer, size) != size: - raise newException(ValueError, "didn't get all the bytes") - let - message = parseSexp($messageBuffer) - messageType = message[0].getSymbol - case messageType: - of "call": - var results: seq[Suggest] = @[] - suggestionResultHook = proc (s: Suggest) = - results.add(s) - - let - uid = message[1].getNum - cmd = parseIdeCmd(message[2].getSymbol) - args = message[3] - executeEPC(cmd, args) - returnEPC(client, uid, sexp(results)) - of "return": - raise newException(EUnexpectedCommand, "no return expected") - of "return-error": - raise newException(EUnexpectedCommand, "no return expected") - of "epc-error": - stderr.writeln("recieved epc error: " & $messageBuffer) - raise newException(IOError, "epc error") - of "methods": - returnEPC(client, message[1].getNum, listEPC()) - else: - raise newException(EUnexpectedCommand, "unexpected call: " & messageType) - -proc mainCommand = - registerPass verbosePass - registerPass semPass - gCmd = cmdIdeTools - incl gGlobalOptions, optCaasEnabled - isServing = true - wantMainModule() - appendStr(searchPaths, options.libpath) - if gProjectFull.len != 0: - # current path is always looked first for modules - prependStr(searchPaths, gProjectPath) - - # do not stop after the first error: - msgs.gErrorMax = high(int) - compileProject() - serve() - -proc processCmdLine*(pass: TCmdLinePass, cmd: string) = - var p = parseopt.initOptParser(cmd) - while true: - parseopt.next(p) - case p.kind - of cmdEnd: break - of cmdLongoption, cmdShortOption: - case p.key.normalize - of "port": - gPort = parseInt(p.val).Port - gMode = mtcp - of "address": - gAddress = p.val - gMode = mtcp - of "stdin": gMode = mstdin - of "epc": - gMode = mepc - gVerbosity = 0 # Port number gotta be first. - else: processSwitch(pass, p) - of cmdArgument: - options.gProjectName = unixToNativePath(p.key) - # if processArgument(pass, p, argsCount): break - -proc handleCmdLine() = - if paramCount() == 0: - stdout.writeln(Usage) - else: - processCmdLine(passCmd1, "") - if gProjectName != "": - try: - gProjectFull = canonicalizePath(gProjectName) - except OSError: - gProjectFull = gProjectName - var p = splitFile(gProjectFull) - gProjectPath = p.dir - gProjectName = p.name - else: - gProjectPath = getCurrentDir() - loadConfigs(DefaultConfig) # load all config files - # now process command line arguments again, because some options in the - # command line can overwite the config file's settings - extccomp.initVars() - processCmdLine(passCmd2, "") - mainCommand() - -when false: - proc quitCalled() {.noconv.} = - writeStackTrace() - - addQuitProc(quitCalled) - -condsyms.initDefines() -defineSymbol "nimsuggest" -handleCmdline() +{.error: "This project has moved to the following repo: https://github.com/nim-lang/nimsuggest".} diff --git a/compiler/nimsuggest/nimsuggest.nim.cfg b/compiler/nimsuggest/nimsuggest.nim.cfg deleted file mode 100644 index acca17396..000000000 --- a/compiler/nimsuggest/nimsuggest.nim.cfg +++ /dev/null @@ -1,17 +0,0 @@ -# Special configuration file for the Nim project - -gc:markAndSweep - -hint[XDeclaredButNotUsed]:off -path:"$projectPath/../.." - -path:"$lib/packages/docutils" -path:"../../compiler" - -define:useStdoutAsStdmsg -define:nimsuggest - -cs:partial -#define:useNodeIds -define:booting -#define:noDocgen diff --git a/compiler/parser.nim b/compiler/parser.nim index 0d2ba7cfc..05b4df13d 100644 --- a/compiler/parser.nim +++ b/compiler/parser.nim @@ -64,6 +64,7 @@ proc setBaseFlags*(n: PNode, base: TNumericalBase) proc parseSymbol*(p: var TParser, allowNil = false): PNode proc parseTry(p: var TParser; isExpr: bool): PNode proc parseCase(p: var TParser): PNode +proc parseStmtPragma(p: var TParser): PNode # implementation proc getTok(p: var TParser) = @@ -499,10 +500,13 @@ proc parsePar(p: var TParser): PNode = #| parKeyw = 'discard' | 'include' | 'if' | 'while' | 'case' | 'try' #| | 'finally' | 'except' | 'for' | 'block' | 'const' | 'let' #| | 'when' | 'var' | 'mixin' - #| par = '(' optInd (&parKeyw complexOrSimpleStmt ^+ ';' - #| | simpleExpr ('=' expr (';' complexOrSimpleStmt ^+ ';' )? )? - #| | (':' expr)? (',' (exprColonEqExpr comma?)*)? )? - #| optPar ')' + #| par = '(' optInd + #| ( &parKeyw complexOrSimpleStmt ^+ ';' + #| | ';' complexOrSimpleStmt ^+ ';' + #| | pragmaStmt + #| | simpleExpr ( ('=' expr (';' complexOrSimpleStmt ^+ ';' )? ) + #| | (':' expr (',' exprColonEqExpr ^+ ',' )? ) ) ) + #| optPar ')' # # unfortunately it's ambiguous: (expr: expr) vs (exprStmt); however a # leading ';' could be used to enforce a 'stmt' context ... @@ -521,6 +525,8 @@ proc parsePar(p: var TParser): PNode = getTok(p) optInd(p, result) semiStmtList(p, result) + elif p.tok.tokType == tkCurlyDotLe: + result.add(parseStmtPragma(p)) elif p.tok.tokType != tkParRi: var a = simpleExpr(p) if p.tok.tokType == tkEquals: diff --git a/compiler/patterns.nim b/compiler/patterns.nim index 368b0b37b..3f8b05940 100644 --- a/compiler/patterns.nim +++ b/compiler/patterns.nim @@ -130,7 +130,9 @@ proc matchNested(c: PPatternContext, p, n: PNode, rpn: bool): bool = proc matches(c: PPatternContext, p, n: PNode): bool = # hidden conversions (?) - if isPatternParam(c, p): + if nfNoRewrite in n.flags: + result = false + elif isPatternParam(c, p): result = bindOrCheck(c, p.sym, n) elif n.kind == nkSym and p.kind == nkIdent: result = p.ident.id == n.sym.name.id diff --git a/compiler/plugins/locals/locals.nim b/compiler/plugins/locals/locals.nim index d89149f33..59e3d677d 100644 --- a/compiler/plugins/locals/locals.nim +++ b/compiler/plugins/locals/locals.nim @@ -9,7 +9,8 @@ ## The builtin 'system.locals' implemented as a plugin. -import plugins, ast, astalgo, magicsys, lookups, semdata, lowerings +import compiler/plugins, compiler/ast, compiler/astalgo, compiler/magicsys, + compiler/lookups, compiler/semdata, compiler/lowerings proc semLocals(c: PContext, n: PNode): PNode = var counter = 0 diff --git a/compiler/pragmas.nim b/compiler/pragmas.nim index c048d78e9..6f37fe756 100644 --- a/compiler/pragmas.nim +++ b/compiler/pragmas.nim @@ -37,7 +37,7 @@ const wImportc, wExportc, wNodecl, wMagic, wDeprecated, wBorrow, wExtern, wImportCpp, wImportObjC, wError, wDiscardable, wGensym, wInject, wRaises, wTags, wLocks, wGcSafe} - exprPragmas* = {wLine, wLocks} + exprPragmas* = {wLine, wLocks, wNoRewrite} stmtPragmas* = {wChecks, wObjChecks, wFieldChecks, wRangechecks, wBoundchecks, wOverflowchecks, wNilchecks, wAssertions, wWarnings, wHints, wLinedir, wStacktrace, wLinetrace, wOptimization, wHint, wWarning, wError, @@ -859,6 +859,8 @@ proc singlePragma(c: PContext, sym: PSym, n: PNode, i: int, c.module.flags.incl sfExperimental else: localError(it.info, "'experimental' pragma only valid as toplevel statement") + of wNoRewrite: + noVal(it) else: invalidPragma(it) else: invalidPragma(it) else: processNote(c, it) diff --git a/compiler/semcall.nim b/compiler/semcall.nim index c48e761e3..571504c3a 100644 --- a/compiler/semcall.nim +++ b/compiler/semcall.nim @@ -209,7 +209,10 @@ proc resolveOverloads(c: PContext, n, orig: PNode, pickBest(callOp) if overloadsState == csEmpty and result.state == csEmpty: - localError(n.info, errUndeclaredIdentifier, considerQuotedIdent(f).s) + if nfDotField in n.flags and nfExplicitCall notin n.flags: + localError(n.info, errUndeclaredField, considerQuotedIdent(f).s) + else: + localError(n.info, errUndeclaredRoutine, considerQuotedIdent(f).s) return elif result.state != csMatch: if nfExprCall in n.flags: diff --git a/compiler/sempass2.nim b/compiler/sempass2.nim index adf03be64..12c4a7c7b 100644 --- a/compiler/sempass2.nim +++ b/compiler/sempass2.nim @@ -207,9 +207,9 @@ proc markGcUnsafe(a: PEffects; reason: PNode) = a.owner.gcUnsafetyReason = newSym(skUnknown, getIdent("<unknown>"), a.owner, reason.info) -proc listGcUnsafety(s: PSym; onlyWarning: bool) = +proc listGcUnsafety(s: PSym; onlyWarning: bool; cycleCheck: var IntSet) = let u = s.gcUnsafetyReason - if u != nil: + if u != nil and not cycleCheck.containsOrIncl(u.id): let msgKind = if onlyWarning: warnGcUnsafe2 else: errGenerated if u.kind in {skLet, skVar}: message(s.info, msgKind, @@ -218,7 +218,7 @@ proc listGcUnsafety(s: PSym; onlyWarning: bool) = elif u.kind in routineKinds: # recursive call *always* produces only a warning so the full error # message is printed: - listGcUnsafety(u, true) + listGcUnsafety(u, true, cycleCheck) message(s.info, msgKind, "'$#' is not GC-safe as it calls '$#'" % [s.name.s, u.name.s]) @@ -227,6 +227,10 @@ proc listGcUnsafety(s: PSym; onlyWarning: bool) = message(u.info, msgKind, "'$#' is not GC-safe as it performs an indirect call here" % s.name.s) +proc listGcUnsafety(s: PSym; onlyWarning: bool) = + var cycleCheck = initIntSet() + listGcUnsafety(s, onlyWarning, cycleCheck) + proc useVar(a: PEffects, n: PNode) = let s = n.sym if isLocalVar(a, s): diff --git a/compiler/semstmts.nim b/compiler/semstmts.nim index c355a5bf1..43cdca866 100644 --- a/compiler/semstmts.nim +++ b/compiler/semstmts.nim @@ -1268,6 +1268,8 @@ proc semPragmaBlock(c: PContext, n: PNode): PNode = of wLocks: result = n result.typ = n.sons[1].typ + of wNoRewrite: + incl(result.flags, nfNoRewrite) else: discard proc semStaticStmt(c: PContext, n: PNode): PNode = diff --git a/compiler/wordrecg.nim b/compiler/wordrecg.nim index 63fd995c4..deb12536f 100644 --- a/compiler/wordrecg.nim +++ b/compiler/wordrecg.nim @@ -55,7 +55,7 @@ type wFloatchecks, wNanChecks, wInfChecks, wAssertions, wPatterns, wWarnings, wHints, wOptimization, wRaises, wWrites, wReads, wSize, wEffects, wTags, - wDeadCodeElim, wSafecode, wNoForward, + wDeadCodeElim, wSafecode, wNoForward, wNoRewrite, wPragma, wCompileTime, wNoInit, wPassc, wPassl, wBorrow, wDiscardable, @@ -139,7 +139,7 @@ const "assertions", "patterns", "warnings", "hints", "optimization", "raises", "writes", "reads", "size", "effects", "tags", - "deadcodeelim", "safecode", "noforward", + "deadcodeelim", "safecode", "noforward", "norewrite", "pragma", "compiletime", "noinit", "passc", "passl", "borrow", "discardable", "fieldchecks", |