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 | |
parent | 0a810fd10f81e11e6b738a18ff18e62c89479436 (diff) | |
parent | 858cdd0b05df4846fb40a3263f05e54438995e99 (diff) | |
download | Nim-f0b6c03b2686aca85670cd35f84c6b0bdc3ff23d.tar.gz |
Merge branch 'devel' into bugfix-2858-testament-sources-system-wide
46 files changed, 344 insertions, 1226 deletions
diff --git a/bootstrap.sh b/bootstrap.sh index ade74a9aa..ade74a9aa 100644..100755 --- a/bootstrap.sh +++ b/bootstrap.sh diff --git a/compiler.nimble b/compiler.nimble index 52eb4083b..9d39af502 100644 --- a/compiler.nimble +++ b/compiler.nimble @@ -1,6 +1,6 @@ [Package] name = "compiler" -version = "0.10.3" +version = "0.11.3" author = "Andreas Rumpf" description = "Compiler package providing the compiler sources as a library." license = "MIT" @@ -8,4 +8,4 @@ license = "MIT" InstallDirs = "doc, compiler" [Deps] -Requires: "nim >= 0.10.3" +Requires: "nim >= 0.11.3" 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", diff --git a/doc/exception_hierarchy_fragment.txt b/doc/exception_hierarchy_fragment.txt index f4a419fc4..a02d9ccef 100644 --- a/doc/exception_hierarchy_fragment.txt +++ b/doc/exception_hierarchy_fragment.txt @@ -11,8 +11,8 @@ * `FloatInvalidOpError <system.html#FloatInvalidOpError>`_ * `FloatOverflowError <system.html#FloatOverflowError>`_ * `FloatUnderflowError <system.html#FloatUnderflowError>`_ - * `FieldError <system.html#InvalidFieldError>`_ - * `IndexError <system.html#InvalidIndexError>`_ + * `FieldError <system.html#FieldError>`_ + * `IndexError <system.html#IndexError>`_ * `ObjectAssignmentError <system.html#ObjectAssignmentError>`_ * `ObjectConversionError <system.html#ObjectConversionError>`_ * `ValueError <system.html#ValueError>`_ diff --git a/doc/manual/procs.txt b/doc/manual/procs.txt index 38e343686..23b5e4d1e 100644 --- a/doc/manual/procs.txt +++ b/doc/manual/procs.txt @@ -404,7 +404,7 @@ dispatch. result.a = a result.b = b -echo eval(newPlus(newPlus(newLit(1), newLit(2)), newLit(4))) + echo eval(newPlus(newPlus(newLit(1), newLit(2)), newLit(4))) In the example the constructors ``newLit`` and ``newPlus`` are procs because they should use static binding, but ``eval`` is a method because it diff --git a/lib/core/typeinfo.nim b/lib/core/typeinfo.nim index d7fa2ec9b..ab150b2a4 100644 --- a/lib/core/typeinfo.nim +++ b/lib/core/typeinfo.nim @@ -340,6 +340,8 @@ proc `[]`*(x: Any, fieldName: string): Any = if n != nil: result.value = x.value +!! n.offset result.rawType = n.typ + elif x.rawType.kind == tyObject and x.rawType.base != nil: + return `[]`(TAny(value: x.value, rawType: x.rawType.base), fieldName) else: raise newException(ValueError, "invalid field name: " & fieldName) diff --git a/lib/impure/zipfiles.nim b/lib/impure/zipfiles.nim index d66d7d7f3..d8903f5c1 100644 --- a/lib/impure/zipfiles.nim +++ b/lib/impure/zipfiles.nim @@ -114,7 +114,7 @@ type atEnd: bool PZipFileStream* = - ref ZipFileStream ## a reader stream of a file within a zip archive + ref TZipFileStream ## a reader stream of a file within a zip archive proc fsClose(s: Stream) = zip_fclose(PZipFileStream(s).f) proc fsAtEnd(s: Stream): bool = PZipFileStream(s).atEnd diff --git a/lib/pure/algorithm.nim b/lib/pure/algorithm.nim index 0eafb316a..c9f779018 100644 --- a/lib/pure/algorithm.nim +++ b/lib/pure/algorithm.nim @@ -99,16 +99,13 @@ proc lowerBound*[T](a: openArray[T], key: T, cmp: proc(x,y: T): int {.closure.}) ## arr.insert(4, arr.lowerBound(4)) ## `after running the above arr is `[1,2,3,4,5,6,7,8,9]` result = a.low - var pos = result - var count, step: int - count = a.high - a.low + 1 + var count = a.high - a.low + 1 + var step, pos: int while count != 0: - pos = result step = count div 2 - pos += step + pos = result + step if cmp(a[pos], key) < 0: - pos.inc - result = pos + result = pos + 1 count -= step + 1 else: count = step @@ -331,3 +328,16 @@ proc prevPermutation*[T](x: var openarray[T]): bool {.discardable.} = swap x[i-1], x[j] result = true + +when isMainModule: + # Tests for lowerBound + var arr = @[1,2,3,5,6,7,8,9] + assert arr.lowerBound(0) == 0 + assert arr.lowerBound(4) == 3 + assert arr.lowerBound(5) == 3 + assert arr.lowerBound(10) == 8 + arr = @[1,5,10] + assert arr.lowerBound(4) == 1 + assert arr.lowerBound(5) == 1 + assert arr.lowerBound(6) == 2 + diff --git a/lib/pure/asyncnet.nim b/lib/pure/asyncnet.nim index d44e5d31f..01c28a13a 100644 --- a/lib/pure/asyncnet.nim +++ b/lib/pure/asyncnet.nim @@ -91,13 +91,13 @@ type # TODO: Save AF, domain etc info and reuse it in procs which need it like connect. -proc newAsyncSocket*(fd: AsyncFD, isBuff: bool): AsyncSocket = +proc newAsyncSocket*(fd: AsyncFD, buffered = true): AsyncSocket = ## Creates a new ``AsyncSocket`` based on the supplied params. assert fd != osInvalidSocket.AsyncFD new(result) result.fd = fd.SocketHandle - result.isBuffered = isBuff - if isBuff: + result.isBuffered = buffered + if buffered: result.currPos = 0 proc newAsyncSocket*(domain: Domain = AF_INET, typ: SockType = SOCK_STREAM, diff --git a/lib/pure/concurrency/cpuload.nim b/lib/pure/concurrency/cpuload.nim index 1f3f54056..22598b5c9 100644 --- a/lib/pure/concurrency/cpuload.nim +++ b/lib/pure/concurrency/cpuload.nim @@ -13,7 +13,7 @@ when defined(windows): import winlean, os, strutils, math - proc `-`(a, b: TFILETIME): int64 = a.rdFileTime - b.rdFileTime + proc `-`(a, b: FILETIME): int64 = a.rdFileTime - b.rdFileTime elif defined(linux): from cpuinfo import countProcessors @@ -25,16 +25,16 @@ type ThreadPoolState* = object when defined(windows): - prevSysKernel, prevSysUser, prevProcKernel, prevProcUser: TFILETIME + prevSysKernel, prevSysUser, prevProcKernel, prevProcUser: FILETIME calls*: int proc advice*(s: var ThreadPoolState): ThreadPoolAdvice = when defined(windows): var sysIdle, sysKernel, sysUser, - procCreation, procExit, procKernel, procUser: TFILETIME + procCreation, procExit, procKernel, procUser: FILETIME if getSystemTimes(sysIdle, sysKernel, sysUser) == 0 or - getProcessTimes(Handle(-1), procCreation, procExit, + getProcessTimes(Handle(-1), procCreation, procExit, procKernel, procUser) == 0: return doNothing if s.calls > 0: @@ -57,7 +57,7 @@ proc advice*(s: var ThreadPoolState): ThreadPoolAdvice = s.prevProcKernel = procKernel s.prevProcUser = procUser elif defined(linux): - proc fscanf(c: File, frmt: cstring) {.varargs, importc, + proc fscanf(c: File, frmt: cstring) {.varargs, importc, header: "<stdio.h>".} var f = open("/proc/loadavg") diff --git a/lib/pure/fsmonitor.nim b/lib/pure/fsmonitor.nim index 83779eb9c..229df80b5 100644 --- a/lib/pure/fsmonitor.nim +++ b/lib/pure/fsmonitor.nim @@ -108,7 +108,7 @@ proc del*(monitor: FSMonitor, wd: cint) = proc getEvent(m: FSMonitor, fd: cint): seq[MonitorEvent] = result = @[] - let size = (sizeof(TINotifyEvent)+2000)*MaxEvents + let size = (sizeof(INotifyEvent)+2000)*MaxEvents var buffer = newString(size) let le = read(fd, addr(buffer[0]), size) @@ -117,7 +117,7 @@ proc getEvent(m: FSMonitor, fd: cint): seq[MonitorEvent] = var i = 0 while i < le: - var event = cast[ptr TINotifyEvent](addr(buffer[i])) + var event = cast[ptr INotifyEvent](addr(buffer[i])) var mev: MonitorEvent mev.wd = event.wd if event.len.int != 0: @@ -129,7 +129,7 @@ proc getEvent(m: FSMonitor, fd: cint): seq[MonitorEvent] = if (event.mask.int and IN_MOVED_FROM) != 0: # Moved from event, add to m's collection movedFrom.add(event.cookie.cint, (mev.wd, mev.name)) - inc(i, sizeof(TINotifyEvent) + event.len.int) + inc(i, sizeof(INotifyEvent) + event.len.int) continue elif (event.mask.int and IN_MOVED_TO) != 0: mev.kind = MonitorMoved @@ -159,7 +159,7 @@ proc getEvent(m: FSMonitor, fd: cint): seq[MonitorEvent] = mev.fullname = "" result.add(mev) - inc(i, sizeof(TINotifyEvent) + event.len.int) + inc(i, sizeof(INotifyEvent) + event.len.int) # If movedFrom events have not been matched with a moveTo. File has # been moved to an unwatched location, emit a MonitorDelete. diff --git a/lib/pure/net.nim b/lib/pure/net.nim index 49ca12098..9ce0669bc 100644 --- a/lib/pure/net.nim +++ b/lib/pure/net.nim @@ -119,13 +119,13 @@ proc toOSFlags*(socketFlags: set[SocketFlag]): cint = result = result or MSG_PEEK of SocketFlag.SafeDisconn: continue -proc newSocket(fd: SocketHandle, isBuff: bool): Socket = +proc newSocket*(fd: SocketHandle, buffered = true): Socket = ## Creates a new socket as specified by the params. assert fd != osInvalidSocket new(result) result.fd = fd - result.isBuffered = isBuff - if isBuff: + result.isBuffered = buffered + if buffered: result.currPos = 0 proc newSocket*(domain, typ, protocol: cint, buffered = true): Socket = diff --git a/lib/pure/sexp.nim b/lib/pure/sexp.nim deleted file mode 100644 index be6188c9e..000000000 --- a/lib/pure/sexp.nim +++ /dev/null @@ -1,698 +0,0 @@ -# -# -# Nim's Runtime Library -# (c) Copyright 2015 Andreas Rumpf, Dominik Picheta -# -# See the file "copying.txt", included in this -# distribution, for details about the copyright. -# - -import - hashes, strutils, lexbase, streams, unicode, macros - -type - SexpEventKind* = enum ## enumeration of all events that may occur when parsing - sexpError, ## an error occurred during parsing - sexpEof, ## end of file reached - sexpString, ## a string literal - sexpSymbol, ## a symbol - sexpInt, ## an integer literal - sexpFloat, ## a float literal - sexpNil, ## the value ``nil`` - sexpDot, ## the dot to separate car/cdr - sexpListStart, ## start of a list: the ``(`` token - sexpListEnd, ## end of a list: the ``)`` token - - TokKind = enum # must be synchronized with SexpEventKind! - tkError, - tkEof, - tkString, - tkSymbol, - tkInt, - tkFloat, - tkNil, - tkDot, - tkParensLe, - tkParensRi - tkSpace - - SexpError* = enum ## enumeration that lists all errors that can occur - errNone, ## no error - errInvalidToken, ## invalid token - errParensRiExpected, ## ``)`` expected - errQuoteExpected, ## ``"`` expected - errEofExpected, ## EOF expected - - SexpParser* = object of BaseLexer ## the parser object. - a: string - tok: TokKind - kind: SexpEventKind - err: SexpError -{.deprecated: [TTokKind: TokKind].} - -const - errorMessages: array [SexpError, string] = [ - "no error", - "invalid token", - "')' expected", - "'\"' or \"'\" expected", - "EOF expected", - ] - tokToStr: array [TokKind, string] = [ - "invalid token", - "EOF", - "string literal", - "symbol", - "int literal", - "float literal", - "nil", - ".", - "(", ")", "space" - ] - -proc close*(my: var SexpParser) {.inline.} = - ## closes the parser `my` and its associated input stream. - lexbase.close(my) - -proc str*(my: SexpParser): string {.inline.} = - ## returns the character data for the events: ``sexpInt``, ``sexpFloat``, - ## ``sexpString`` - assert(my.kind in {sexpInt, sexpFloat, sexpString}) - result = my.a - -proc getInt*(my: SexpParser): BiggestInt {.inline.} = - ## returns the number for the event: ``sexpInt`` - assert(my.kind == sexpInt) - result = parseBiggestInt(my.a) - -proc getFloat*(my: SexpParser): float {.inline.} = - ## returns the number for the event: ``sexpFloat`` - assert(my.kind == sexpFloat) - result = parseFloat(my.a) - -proc kind*(my: SexpParser): SexpEventKind {.inline.} = - ## returns the current event type for the SEXP parser - result = my.kind - -proc getColumn*(my: SexpParser): int {.inline.} = - ## get the current column the parser has arrived at. - result = getColNumber(my, my.bufpos) - -proc getLine*(my: SexpParser): int {.inline.} = - ## get the current line the parser has arrived at. - result = my.lineNumber - -proc errorMsg*(my: SexpParser): string = - ## returns a helpful error message for the event ``sexpError`` - assert(my.kind == sexpError) - result = "($1, $2) Error: $3" % [$getLine(my), $getColumn(my), errorMessages[my.err]] - -proc errorMsgExpected*(my: SexpParser, e: string): string = - ## returns an error message "`e` expected" in the same format as the - ## other error messages - result = "($1, $2) Error: $3" % [$getLine(my), $getColumn(my), e & " expected"] - -proc handleHexChar(c: char, x: var int): bool = - result = true # Success - case c - of '0'..'9': x = (x shl 4) or (ord(c) - ord('0')) - of 'a'..'f': x = (x shl 4) or (ord(c) - ord('a') + 10) - of 'A'..'F': x = (x shl 4) or (ord(c) - ord('A') + 10) - else: result = false # error - -proc parseString(my: var SexpParser): TokKind = - result = tkString - var pos = my.bufpos + 1 - var buf = my.buf - while true: - case buf[pos] - of '\0': - my.err = errQuoteExpected - result = tkError - break - of '"': - inc(pos) - break - of '\\': - case buf[pos+1] - of '\\', '"', '\'', '/': - add(my.a, buf[pos+1]) - inc(pos, 2) - of 'b': - add(my.a, '\b') - inc(pos, 2) - of 'f': - add(my.a, '\f') - inc(pos, 2) - of 'n': - add(my.a, '\L') - inc(pos, 2) - of 'r': - add(my.a, '\C') - inc(pos, 2) - of 't': - add(my.a, '\t') - inc(pos, 2) - of 'u': - inc(pos, 2) - var r: int - if handleHexChar(buf[pos], r): inc(pos) - if handleHexChar(buf[pos], r): inc(pos) - if handleHexChar(buf[pos], r): inc(pos) - if handleHexChar(buf[pos], r): inc(pos) - add(my.a, toUTF8(Rune(r))) - else: - # don't bother with the error - add(my.a, buf[pos]) - inc(pos) - of '\c': - pos = lexbase.handleCR(my, pos) - buf = my.buf - add(my.a, '\c') - of '\L': - pos = lexbase.handleLF(my, pos) - buf = my.buf - add(my.a, '\L') - else: - add(my.a, buf[pos]) - inc(pos) - my.bufpos = pos # store back - -proc parseNumber(my: var SexpParser) = - var pos = my.bufpos - var buf = my.buf - if buf[pos] == '-': - add(my.a, '-') - inc(pos) - if buf[pos] == '.': - add(my.a, "0.") - inc(pos) - else: - while buf[pos] in Digits: - add(my.a, buf[pos]) - inc(pos) - if buf[pos] == '.': - add(my.a, '.') - inc(pos) - # digits after the dot: - while buf[pos] in Digits: - add(my.a, buf[pos]) - inc(pos) - if buf[pos] in {'E', 'e'}: - add(my.a, buf[pos]) - inc(pos) - if buf[pos] in {'+', '-'}: - add(my.a, buf[pos]) - inc(pos) - while buf[pos] in Digits: - add(my.a, buf[pos]) - inc(pos) - my.bufpos = pos - -proc parseSymbol(my: var SexpParser) = - var pos = my.bufpos - var buf = my.buf - if buf[pos] in IdentStartChars: - while buf[pos] in IdentChars: - add(my.a, buf[pos]) - inc(pos) - my.bufpos = pos - -proc getTok(my: var SexpParser): TokKind = - setLen(my.a, 0) - case my.buf[my.bufpos] - of '-', '0'..'9': # numbers that start with a . are not parsed - # correctly. - parseNumber(my) - if {'.', 'e', 'E'} in my.a: - result = tkFloat - else: - result = tkInt - of '"': #" # gotta fix nim-mode - result = parseString(my) - of '(': - inc(my.bufpos) - result = tkParensLe - of ')': - inc(my.bufpos) - result = tkParensRi - of '\0': - result = tkEof - of 'a'..'z', 'A'..'Z', '_': - parseSymbol(my) - if my.a == "nil": - result = tkNil - else: - result = tkSymbol - of ' ': - result = tkSpace - inc(my.bufpos) - of '.': - result = tkDot - inc(my.bufpos) - else: - inc(my.bufpos) - result = tkError - my.tok = result - -# ------------- higher level interface --------------------------------------- - -type - SexpNodeKind* = enum ## possible SEXP node types - SNil, - SInt, - SFloat, - SString, - SSymbol, - SList, - SCons - - SexpNode* = ref SexpNodeObj ## SEXP node - SexpNodeObj* {.acyclic.} = object - case kind*: SexpNodeKind - of SString: - str*: string - of SSymbol: - symbol*: string - of SInt: - num*: BiggestInt - of SFloat: - fnum*: float - of SList: - elems*: seq[SexpNode] - of SCons: - car: SexpNode - cdr: SexpNode - of SNil: - discard - - Cons = tuple[car: SexpNode, cdr: SexpNode] - - SexpParsingError* = object of ValueError ## is raised for a SEXP error - -proc raiseParseErr*(p: SexpParser, msg: string) {.noinline, noreturn.} = - ## raises an `ESexpParsingError` exception. - raise newException(SexpParsingError, errorMsgExpected(p, msg)) - -proc newSString*(s: string): SexpNode {.procvar.}= - ## Creates a new `SString SexpNode`. - new(result) - result.kind = SString - result.str = s - -proc newSStringMove(s: string): SexpNode = - new(result) - result.kind = SString - shallowCopy(result.str, s) - -proc newSInt*(n: BiggestInt): SexpNode {.procvar.} = - ## Creates a new `SInt SexpNode`. - new(result) - result.kind = SInt - result.num = n - -proc newSFloat*(n: float): SexpNode {.procvar.} = - ## Creates a new `SFloat SexpNode`. - new(result) - result.kind = SFloat - result.fnum = n - -proc newSNil*(): SexpNode {.procvar.} = - ## Creates a new `SNil SexpNode`. - new(result) - -proc newSCons*(car, cdr: SexpNode): SexpNode {.procvar.} = - ## Creates a new `SCons SexpNode` - new(result) - result.kind = SCons - result.car = car - result.cdr = cdr - -proc newSList*(): SexpNode {.procvar.} = - ## Creates a new `SList SexpNode` - new(result) - result.kind = SList - result.elems = @[] - -proc newSSymbol*(s: string): SexpNode {.procvar.} = - new(result) - result.kind = SSymbol - result.symbol = s - -proc newSSymbolMove(s: string): SexpNode = - new(result) - result.kind = SSymbol - shallowCopy(result.symbol, s) - -proc getStr*(n: SexpNode, default: string = ""): string = - ## Retrieves the string value of a `SString SexpNode`. - ## - ## Returns ``default`` if ``n`` is not a ``SString``. - if n.kind != SString: return default - else: return n.str - -proc getNum*(n: SexpNode, default: BiggestInt = 0): BiggestInt = - ## Retrieves the int value of a `SInt SexpNode`. - ## - ## Returns ``default`` if ``n`` is not a ``SInt``. - if n.kind != SInt: return default - else: return n.num - -proc getFNum*(n: SexpNode, default: float = 0.0): float = - ## Retrieves the float value of a `SFloat SexpNode`. - ## - ## Returns ``default`` if ``n`` is not a ``SFloat``. - if n.kind != SFloat: return default - else: return n.fnum - -proc getSymbol*(n: SexpNode, default: string = ""): string = - ## Retrieves the int value of a `SList SexpNode`. - ## - ## Returns ``default`` if ``n`` is not a ``SList``. - if n.kind != SSymbol: return default - else: return n.symbol - -proc getElems*(n: SexpNode, default: seq[SexpNode] = @[]): seq[SexpNode] = - ## Retrieves the int value of a `SList SexpNode`. - ## - ## Returns ``default`` if ``n`` is not a ``SList``. - if n.kind == SNil: return @[] - elif n.kind != SList: return default - else: return n.elems - -proc getCons*(n: SexpNode, defaults: Cons = (newSNil(), newSNil())): Cons = - ## Retrieves the cons value of a `SList SexpNode`. - ## - ## Returns ``default`` if ``n`` is not a ``SList``. - if n.kind == SCons: return (n.car, n.cdr) - elif n.kind == SList: return (n.elems[0], n.elems[1]) - else: return defaults - -proc sexp*(s: string): SexpNode = - ## Generic constructor for SEXP data. Creates a new `SString SexpNode`. - new(result) - result.kind = SString - result.str = s - -proc sexp*(n: BiggestInt): SexpNode = - ## Generic constructor for SEXP data. Creates a new `SInt SexpNode`. - new(result) - result.kind = SInt - result.num = n - -proc sexp*(n: float): SexpNode = - ## Generic constructor for SEXP data. Creates a new `SFloat SexpNode`. - new(result) - result.kind = SFloat - result.fnum = n - -proc sexp*(b: bool): SexpNode = - ## Generic constructor for SEXP data. Creates a new `SSymbol - ## SexpNode` with value t or `SNil SexpNode`. - new(result) - if b: - result.kind = SSymbol - result.symbol = "t" - else: - result.kind = SNil - -proc sexp*(elements: openArray[SexpNode]): SexpNode = - ## Generic constructor for SEXP data. Creates a new `SList SexpNode` - new(result) - result.kind = SList - newSeq(result.elems, elements.len) - for i, p in pairs(elements): result.elems[i] = p - -proc sexp*(s: SexpNode): SexpNode = - result = s - -proc toSexp(x: NimNode): NimNode {.compiletime.} = - case x.kind - of nnkBracket: - result = newNimNode(nnkBracket) - for i in 0 .. <x.len: - result.add(toSexp(x[i])) - - else: - result = x - - result = prefix(result, "sexp") - -macro convertSexp*(x: expr): expr = - ## Convert an expression to a SexpNode directly, without having to specify - ## `%` for every element. - result = toSexp(x) - -proc `==`* (a,b: SexpNode): bool = - ## Check two nodes for equality - if a.isNil: - if b.isNil: return true - return false - elif b.isNil or a.kind != b.kind: - return false - else: - return case a.kind - of SString: - a.str == b.str - of SInt: - a.num == b.num - of SFloat: - a.fnum == b.fnum - of SNil: - true - of SList: - a.elems == b.elems - of SSymbol: - a.symbol == b.symbol - of SCons: - a.car == b.car and a.cdr == b.cdr - -proc hash* (n:SexpNode): Hash = - ## Compute the hash for a SEXP node - case n.kind - of SList: - result = hash(n.elems) - of SInt: - result = hash(n.num) - of SFloat: - result = hash(n.fnum) - of SString: - result = hash(n.str) - of SNil: - result = hash(0) - of SSymbol: - result = hash(n.symbol) - of SCons: - result = hash(n.car) !& hash(n.cdr) - -proc len*(n: SexpNode): int = - ## If `n` is a `SList`, it returns the number of elements. - ## If `n` is a `JObject`, it returns the number of pairs. - ## Else it returns 0. - case n.kind - of SList: result = n.elems.len - else: discard - -proc `[]`*(node: SexpNode, index: int): SexpNode = - ## Gets the node at `index` in a List. Result is undefined if `index` - ## is out of bounds - assert(not isNil(node)) - assert(node.kind == SList) - return node.elems[index] - -proc add*(father, child: SexpNode) = - ## Adds `child` to a SList node `father`. - assert father.kind == SList - father.elems.add(child) - -# ------------- pretty printing ---------------------------------------------- - -proc indent(s: var string, i: int) = - s.add(spaces(i)) - -proc newIndent(curr, indent: int, ml: bool): int = - if ml: return curr + indent - else: return indent - -proc nl(s: var string, ml: bool) = - if ml: s.add("\n") - -proc escapeJson*(s: string): string = - ## Converts a string `s` to its JSON representation. - result = newStringOfCap(s.len + s.len shr 3) - result.add("\"") - for x in runes(s): - var r = int(x) - if r >= 32 and r <= 127: - var c = chr(r) - case c - of '"': result.add("\\\"") #" # gotta fix nim-mode - of '\\': result.add("\\\\") - else: result.add(c) - else: - result.add("\\u") - result.add(toHex(r, 4)) - result.add("\"") - -proc copy*(p: SexpNode): SexpNode = - ## Performs a deep copy of `a`. - case p.kind - of SString: - result = newSString(p.str) - of SInt: - result = newSInt(p.num) - of SFloat: - result = newSFloat(p.fnum) - of SNil: - result = newSNil() - of SSymbol: - result = newSSymbol(p.symbol) - of SList: - result = newSList() - for i in items(p.elems): - result.elems.add(copy(i)) - of SCons: - result = newSCons(copy(p.car), copy(p.cdr)) - -proc toPretty(result: var string, node: SexpNode, indent = 2, ml = true, - lstArr = false, currIndent = 0) = - case node.kind - of SString: - if lstArr: result.indent(currIndent) - result.add(escapeJson(node.str)) - of SInt: - if lstArr: result.indent(currIndent) - result.add($node.num) - of SFloat: - if lstArr: result.indent(currIndent) - result.add($node.fnum) - of SNil: - if lstArr: result.indent(currIndent) - result.add("nil") - of SSymbol: - if lstArr: result.indent(currIndent) - result.add($node.symbol) - of SList: - if lstArr: result.indent(currIndent) - if len(node.elems) != 0: - result.add("(") - result.nl(ml) - for i in 0..len(node.elems)-1: - if i > 0: - result.add(" ") - result.nl(ml) # New Line - toPretty(result, node.elems[i], indent, ml, - true, newIndent(currIndent, indent, ml)) - result.nl(ml) - result.indent(currIndent) - result.add(")") - else: result.add("nil") - of SCons: - if lstArr: result.indent(currIndent) - result.add("(") - toPretty(result, node.car, indent, ml, - true, newIndent(currIndent, indent, ml)) - result.add(" . ") - toPretty(result, node.cdr, indent, ml, - true, newIndent(currIndent, indent, ml)) - result.add(")") - -proc pretty*(node: SexpNode, indent = 2): string = - ## Converts `node` to its Sexp Representation, with indentation and - ## on multiple lines. - result = "" - toPretty(result, node, indent) - -proc `$`*(node: SexpNode): string = - ## Converts `node` to its SEXP Representation on one line. - result = "" - toPretty(result, node, 0, false) - -iterator items*(node: SexpNode): SexpNode = - ## Iterator for the items of `node`. `node` has to be a SList. - assert node.kind == SList - for i in items(node.elems): - yield i - -iterator mitems*(node: var SexpNode): var SexpNode = - ## Iterator for the items of `node`. `node` has to be a SList. Items can be - ## modified. - assert node.kind == SList - for i in mitems(node.elems): - yield i - -proc eat(p: var SexpParser, tok: TokKind) = - if p.tok == tok: discard getTok(p) - else: raiseParseErr(p, tokToStr[tok]) - -proc parseSexp(p: var SexpParser): SexpNode = - ## Parses SEXP from a SEXP Parser `p`. - case p.tok - of tkString: - # we capture 'p.a' here, so we need to give it a fresh buffer afterwards: - result = newSStringMove(p.a) - p.a = "" - discard getTok(p) - of tkInt: - result = newSInt(parseBiggestInt(p.a)) - discard getTok(p) - of tkFloat: - result = newSFloat(parseFloat(p.a)) - discard getTok(p) - of tkNil: - result = newSNil() - discard getTok(p) - of tkSymbol: - result = newSSymbolMove(p.a) - p.a = "" - discard getTok(p) - of tkParensLe: - result = newSList() - discard getTok(p) - while p.tok notin {tkParensRi, tkDot}: - result.add(parseSexp(p)) - if p.tok != tkSpace: break - discard getTok(p) - if p.tok == tkDot: - eat(p, tkDot) - eat(p, tkSpace) - result.add(parseSexp(p)) - result = newSCons(result[0], result[1]) - eat(p, tkParensRi) - of tkSpace, tkDot, tkError, tkParensRi, tkEof: - raiseParseErr(p, "(") - -proc open*(my: var SexpParser, input: Stream) = - ## initializes the parser with an input stream. - lexbase.open(my, input) - my.kind = sexpError - my.a = "" - -proc parseSexp*(s: Stream): SexpNode = - ## Parses from a buffer `s` into a `SexpNode`. - var p: SexpParser - p.open(s) - discard getTok(p) # read first token - result = p.parseSexp() - p.close() - -proc parseSexp*(buffer: string): SexpNode = - ## Parses Sexp from `buffer`. - result = parseSexp(newStringStream(buffer)) - -when isMainModule: - let testSexp = parseSexp("""(1 (98 2) nil (2) foobar "foo" 9.234)""") - assert(testSexp[0].getNum == 1) - assert(testSexp[1][0].getNum == 98) - assert(testSexp[2].getElems == @[]) - assert(testSexp[4].getSymbol == "foobar") - assert(testSexp[5].getStr == "foo") - - let alist = parseSexp("""((1 . 2) (2 . "foo"))""") - assert(alist[0].getCons.car.getNum == 1) - assert(alist[0].getCons.cdr.getNum == 2) - assert(alist[1].getCons.cdr.getStr == "foo") - - # Generator: - var j = convertSexp([true, false, "foobar", [1, 2, "baz"]]) - assert($j == """(t nil "foobar" (1 2 "baz"))""") diff --git a/lib/pure/unittest.nim b/lib/pure/unittest.nim index 092b1fba2..dbbd3cabc 100644 --- a/lib/pure/unittest.nim +++ b/lib/pure/unittest.nim @@ -99,8 +99,9 @@ template test*(name: expr, body: stmt): stmt {.immediate, dirty.} = body except: - checkpoint("Unhandled exception: " & getCurrentExceptionMsg()) - echo getCurrentException().getStackTrace() + when not defined(js): + checkpoint("Unhandled exception: " & getCurrentExceptionMsg()) + echo getCurrentException().getStackTrace() fail() finally: @@ -114,9 +115,7 @@ proc checkpoint*(msg: string) = template fail* = bind checkpoints for msg in items(checkpoints): - # this used to be 'echo' which now breaks due to a bug. XXX will revisit - # this issue later. - stdout.writeln msg + echo msg when not defined(ECMAScript): if abortOnError: quit(1) diff --git a/lib/system/arithm.nim b/lib/system/arithm.nim index ef153417c..907907e24 100644 --- a/lib/system/arithm.nim +++ b/lib/system/arithm.nim @@ -17,17 +17,114 @@ proc raiseOverflow {.compilerproc, noinline.} = proc raiseDivByZero {.compilerproc, noinline.} = sysFatal(DivByZeroError, "division by zero") -proc addInt64(a, b: int64): int64 {.compilerProc, inline.} = - result = a +% b - if (result xor a) >= int64(0) or (result xor b) >= int64(0): - return result - raiseOverflow() +when defined(builtinOverflow): +# Builtin compiler functions for improved performance + when sizeof(clong) == 8: + proc addInt64Overflow[T: int64|int](a, b: T, c: var T): bool {. + importc: "__builtin_saddl_overflow", nodecl, nosideeffect.} -proc subInt64(a, b: int64): int64 {.compilerProc, inline.} = - result = a -% b - if (result xor a) >= int64(0) or (result xor not b) >= int64(0): - return result - raiseOverflow() + proc subInt64Overflow[T: int64|int](a, b: T, c: var T): bool {. + importc: "__builtin_ssubl_overflow", nodecl, nosideeffect.} + + proc mulInt64Overflow[T: int64|int](a, b: T, c: var T): bool {. + importc: "__builtin_smull_overflow", nodecl, nosideeffect.} + + elif sizeof(clonglong) == 8: + proc addInt64Overflow[T: int64|int](a, b: T, c: var T): bool {. + importc: "__builtin_saddll_overflow", nodecl, nosideeffect.} + + proc subInt64Overflow[T: int64|int](a, b: T, c: var T): bool {. + importc: "__builtin_ssubll_overflow", nodecl, nosideeffect.} + + proc mulInt64Overflow[T: int64|int](a, b: T, c: var T): bool {. + importc: "__builtin_smulll_overflow", nodecl, nosideeffect.} + + when sizeof(int) == 8: + proc addIntOverflow(a, b: int, c: var int): bool {.inline.} = + addInt64Overflow(a, b, c) + + proc subIntOverflow(a, b: int, c: var int): bool {.inline.} = + subInt64Overflow(a, b, c) + + proc mulIntOverflow(a, b: int, c: var int): bool {.inline.} = + mulInt64Overflow(a, b, c) + + elif sizeof(int) == 4 and sizeof(cint) == 4: + proc addIntOverflow(a, b: int, c: var int): bool {. + importc: "__builtin_sadd_overflow", nodecl, nosideeffect.} + + proc subIntOverflow(a, b: int, c: var int): bool {. + importc: "__builtin_ssub_overflow", nodecl, nosideeffect.} + + proc mulIntOverflow(a, b: int, c: var int): bool {. + importc: "__builtin_smul_overflow", nodecl, nosideeffect.} + + proc addInt64(a, b: int64): int64 {.compilerProc, inline.} = + if addInt64Overflow(a, b, result): + raiseOverflow() + + proc subInt64(a, b: int64): int64 {.compilerProc, inline.} = + if subInt64Overflow(a, b, result): + raiseOverflow() + + proc mulInt64(a, b: int64): int64 {.compilerproc, inline.} = + if mulInt64Overflow(a, b, result): + raiseOverflow() +else: + proc addInt64(a, b: int64): int64 {.compilerProc, inline.} = + result = a +% b + if (result xor a) >= int64(0) or (result xor b) >= int64(0): + return result + raiseOverflow() + + proc subInt64(a, b: int64): int64 {.compilerProc, inline.} = + result = a -% b + if (result xor a) >= int64(0) or (result xor not b) >= int64(0): + return result + raiseOverflow() + + # + # This code has been inspired by Python's source code. + # The native int product x*y is either exactly right or *way* off, being + # just the last n bits of the true product, where n is the number of bits + # in an int (the delivered product is the true product plus i*2**n for + # some integer i). + # + # The native float64 product x*y is subject to three + # rounding errors: on a sizeof(int)==8 box, each cast to double can lose + # info, and even on a sizeof(int)==4 box, the multiplication can lose info. + # But, unlike the native int product, it's not in *range* trouble: even + # if sizeof(int)==32 (256-bit ints), the product easily fits in the + # dynamic range of a float64. So the leading 50 (or so) bits of the float64 + # product are correct. + # + # We check these two ways against each other, and declare victory if they're + # approximately the same. Else, because the native int product is the only + # one that can lose catastrophic amounts of information, it's the native int + # product that must have overflowed. + # + proc mulInt64(a, b: int64): int64 {.compilerproc.} = + var + resAsFloat, floatProd: float64 + result = a *% b + floatProd = toBiggestFloat(a) # conversion + floatProd = floatProd * toBiggestFloat(b) + resAsFloat = toBiggestFloat(result) + + # Fast path for normal case: small multiplicands, and no info + # is lost in either method. + if resAsFloat == floatProd: return result + + # Somebody somewhere lost info. Close enough, or way off? Note + # that a != 0 and b != 0 (else resAsFloat == floatProd == 0). + # The difference either is or isn't significant compared to the + # true value (of which floatProd is a good approximation). + + # abs(diff)/abs(prod) <= 1/32 iff + # 32 * abs(diff) <= abs(prod) -- 5 good bits is "close enough" + if 32.0 * abs(resAsFloat - floatProd) <= abs(floatProd): + return result + raiseOverflow() proc negInt64(a: int64): int64 {.compilerProc, inline.} = if a != low(int64): return -a @@ -51,50 +148,6 @@ proc modInt64(a, b: int64): int64 {.compilerProc, inline.} = raiseDivByZero() return a mod b -# -# This code has been inspired by Python's source code. -# The native int product x*y is either exactly right or *way* off, being -# just the last n bits of the true product, where n is the number of bits -# in an int (the delivered product is the true product plus i*2**n for -# some integer i). -# -# The native float64 product x*y is subject to three -# rounding errors: on a sizeof(int)==8 box, each cast to double can lose -# info, and even on a sizeof(int)==4 box, the multiplication can lose info. -# But, unlike the native int product, it's not in *range* trouble: even -# if sizeof(int)==32 (256-bit ints), the product easily fits in the -# dynamic range of a float64. So the leading 50 (or so) bits of the float64 -# product are correct. -# -# We check these two ways against each other, and declare victory if they're -# approximately the same. Else, because the native int product is the only -# one that can lose catastrophic amounts of information, it's the native int -# product that must have overflowed. -# -proc mulInt64(a, b: int64): int64 {.compilerproc.} = - var - resAsFloat, floatProd: float64 - result = a *% b - floatProd = toBiggestFloat(a) # conversion - floatProd = floatProd * toBiggestFloat(b) - resAsFloat = toBiggestFloat(result) - - # Fast path for normal case: small multiplicands, and no info - # is lost in either method. - if resAsFloat == floatProd: return result - - # Somebody somewhere lost info. Close enough, or way off? Note - # that a != 0 and b != 0 (else resAsFloat == floatProd == 0). - # The difference either is or isn't significant compared to the - # true value (of which floatProd is a good approximation). - - # abs(diff)/abs(prod) <= 1/32 iff - # 32 * abs(diff) <= abs(prod) -- 5 good bits is "close enough" - if 32.0 * abs(resAsFloat - floatProd) <= abs(floatProd): - return result - raiseOverflow() - - proc absInt(a: int): int {.compilerProc, inline.} = if a != low(int): if a >= 0: return a @@ -246,6 +299,21 @@ elif false: # asmVersion and (defined(gcc) or defined(llvm_gcc)): :"%edx" """ +when not declared(addInt) and defined(builtinOverflow): + proc addInt(a, b: int): int {.compilerProc, inline.} = + if addIntOverflow(a, b, result): + raiseOverflow() + +when not declared(subInt) and defined(builtinOverflow): + proc subInt(a, b: int): int {.compilerProc, inline.} = + if subIntOverflow(a, b, result): + raiseOverflow() + +when not declared(mulInt) and defined(builtinOverflow): + proc mulInt(a, b: int): int {.compilerProc, inline.} = + if mulIntOverflow(a, b, result): + raiseOverflow() + # Platform independent versions of the above (slower!) when not declared(addInt): proc addInt(a, b: int): int {.compilerProc, inline.} = diff --git a/lib/system/gc_ms.nim b/lib/system/gc_ms.nim index aab28eba2..ee80c61e9 100644 --- a/lib/system/gc_ms.nim +++ b/lib/system/gc_ms.nim @@ -58,7 +58,7 @@ type stat: GcStat additionalRoots: CellSeq # dummy roots for GC_ref/unref {.deprecated: [TWalkOp: WalkOp, TFinalizer: Finalizer, TGcStat: GcStat, - TGlobalMarkerProc: GlobalMarkerProc, TGcHeap, GcHeap].} + TGlobalMarkerProc: GlobalMarkerProc, TGcHeap: GcHeap].} var gch {.rtlThreadVar.}: GcHeap diff --git a/lib/windows/winlean.nim b/lib/windows/winlean.nim index 39f2be61d..9f04bab35 100644 --- a/lib/windows/winlean.nim +++ b/lib/windows/winlean.nim @@ -690,6 +690,7 @@ const ERROR_IO_PENDING* = 997 # a.k.a WSA_IO_PENDING FILE_FLAG_OVERLAPPED* = 1073741824 WSAECONNABORTED* = 10053 + WSAEADDRINUSE* = 10048 WSAECONNRESET* = 10054 WSAEDISCON* = 10101 WSAENETRESET* = 10052 diff --git a/lib/wrappers/libffi/libffi.nim b/lib/wrappers/libffi/libffi.nim index d7e11a20c..34b91f8c7 100644 --- a/lib/wrappers/libffi/libffi.nim +++ b/lib/wrappers/libffi/libffi.nim @@ -60,7 +60,7 @@ else: type Arg* = int SArg* = int -{deprecated: [TArg: Arg, TSArg: SArg].} +{.deprecated: [TArg: Arg, TSArg: SArg].} when defined(windows) and defined(x86): type diff --git a/lib/wrappers/readline/readline.nim b/lib/wrappers/readline/readline.nim index 4173a0e0f..652808576 100644 --- a/lib/wrappers/readline/readline.nim +++ b/lib/wrappers/readline/readline.nim @@ -29,7 +29,7 @@ elif defined(macosx): else: const readlineDll* = "libreadline.so.6(|.0)" -# mangle "'TCommandFunc'" TCommandFunc +# mangle "'CommandFunc'" CommandFunc # mangle TvcpFunc TvcpFunc import rltypedefs @@ -80,7 +80,7 @@ const type KEYMAP_ENTRY*{.pure, final.} = object typ*: char - function*: TCommandFunc + function*: CommandFunc {.deprecated: [TKEYMAP_ENTRY: KEYMAP_ENTRY].} @@ -243,7 +243,7 @@ when not defined(macosx): type FUNMAP*{.pure, final.} = object name*: cstring - function*: TCommandFunc + function*: CommandFunc {.deprecated: [TFUNMAP: FUNMAP].} @@ -610,31 +610,31 @@ proc discard_argument*(): cint{.cdecl, importc: "rl_discard_argument", dynlib: readlineDll.} # Utility functions to bind keys to readline commands. -proc add_defun*(a2: cstring, a3: TCommandFunc, a4: cint): cint{.cdecl, +proc add_defun*(a2: cstring, a3: CommandFunc, a4: cint): cint{.cdecl, importc: "rl_add_defun", dynlib: readlineDll.} -proc bind_key*(a2: cint, a3: TCommandFunc): cint{.cdecl, +proc bind_key*(a2: cint, a3: CommandFunc): cint{.cdecl, importc: "rl_bind_key", dynlib: readlineDll.} -proc bind_key_in_map*(a2: cint, a3: TCommandFunc, a4: PKeymap): cint{.cdecl, +proc bind_key_in_map*(a2: cint, a3: CommandFunc, a4: PKeymap): cint{.cdecl, importc: "rl_bind_key_in_map", dynlib: readlineDll.} proc unbind_key*(a2: cint): cint{.cdecl, importc: "rl_unbind_key", dynlib: readlineDll.} proc unbind_key_in_map*(a2: cint, a3: PKeymap): cint{.cdecl, importc: "rl_unbind_key_in_map", dynlib: readlineDll.} -proc bind_key_if_unbound*(a2: cint, a3: TCommandFunc): cint{.cdecl, +proc bind_key_if_unbound*(a2: cint, a3: CommandFunc): cint{.cdecl, importc: "rl_bind_key_if_unbound", dynlib: readlineDll.} -proc bind_key_if_unbound_in_map*(a2: cint, a3: TCommandFunc, a4: PKeymap): cint{. +proc bind_key_if_unbound_in_map*(a2: cint, a3: CommandFunc, a4: PKeymap): cint{. cdecl, importc: "rl_bind_key_if_unbound_in_map", dynlib: readlineDll.} -proc unbind_function_in_map*(a2: TCommandFunc, a3: PKeymap): cint{.cdecl, +proc unbind_function_in_map*(a2: CommandFunc, a3: PKeymap): cint{.cdecl, importc: "rl_unbind_function_in_map", dynlib: readlineDll.} proc unbind_command_in_map*(a2: cstring, a3: PKeymap): cint{.cdecl, importc: "rl_unbind_command_in_map", dynlib: readlineDll.} -proc bind_keyseq*(a2: cstring, a3: TCommandFunc): cint{.cdecl, +proc bind_keyseq*(a2: cstring, a3: CommandFunc): cint{.cdecl, importc: "rl_bind_keyseq", dynlib: readlineDll.} -proc bind_keyseq_in_map*(a2: cstring, a3: TCommandFunc, a4: PKeymap): cint{. +proc bind_keyseq_in_map*(a2: cstring, a3: CommandFunc, a4: PKeymap): cint{. cdecl, importc: "rl_bind_keyseq_in_map", dynlib: readlineDll.} -proc bind_keyseq_if_unbound*(a2: cstring, a3: TCommandFunc): cint{.cdecl, +proc bind_keyseq_if_unbound*(a2: cstring, a3: CommandFunc): cint{.cdecl, importc: "rl_bind_keyseq_if_unbound", dynlib: readlineDll.} -proc bind_keyseq_if_unbound_in_map*(a2: cstring, a3: TCommandFunc, +proc bind_keyseq_if_unbound_in_map*(a2: cstring, a3: CommandFunc, a4: PKeymap): cint{.cdecl, importc: "rl_bind_keyseq_if_unbound_in_map", dynlib: readlineDll.} proc generic_bind*(a2: cint, a3: cstring, a4: cstring, a5: PKeymap): cint{. @@ -645,7 +645,7 @@ proc variable_bind*(a2: cstring, a3: cstring): cint{.cdecl, importc: "rl_variable_bind", dynlib: readlineDll.} # Backwards compatibility, use rl_bind_keyseq_in_map instead. -proc set_key*(a2: cstring, a3: TCommandFunc, a4: PKeymap): cint{.cdecl, +proc set_key*(a2: cstring, a3: CommandFunc, a4: PKeymap): cint{.cdecl, importc: "rl_set_key", dynlib: readlineDll.} # Backwards compatibility, use rl_generic_bind instead. @@ -657,15 +657,15 @@ proc translate_keyseq*(a2: cstring, a3: cstring, a4: ptr cint): cint{.cdecl, importc: "rl_translate_keyseq", dynlib: readlineDll.} proc untranslate_keyseq*(a2: cint): cstring{.cdecl, importc: "rl_untranslate_keyseq", dynlib: readlineDll.} -proc named_function*(a2: cstring): TCommandFunc{.cdecl, +proc named_function*(a2: cstring): CommandFunc{.cdecl, importc: "rl_named_function", dynlib: readlineDll.} -proc function_of_keyseq*(a2: cstring, a3: PKeymap, a4: ptr cint): TCommandFunc{. +proc function_of_keyseq*(a2: cstring, a3: PKeymap, a4: ptr cint): CommandFunc{. cdecl, importc: "rl_function_of_keyseq", dynlib: readlineDll.} proc list_funmap_names*(){.cdecl, importc: "rl_list_funmap_names", dynlib: readlineDll.} -proc invoking_keyseqs_in_map*(a2: TCommandFunc, a3: PKeymap): cstringArray{. +proc invoking_keyseqs_in_map*(a2: CommandFunc, a3: PKeymap): cstringArray{. cdecl, importc: "rl_invoking_keyseqs_in_map", dynlib: readlineDll.} -proc invoking_keyseqs*(a2: TCommandFunc): cstringArray{.cdecl, +proc invoking_keyseqs*(a2: CommandFunc): cstringArray{.cdecl, importc: "rl_invoking_keyseqs", dynlib: readlineDll.} proc function_dumper*(a2: cint){.cdecl, importc: "rl_function_dumper", dynlib: readlineDll.} @@ -688,7 +688,7 @@ proc get_keymap_name_from_edit_mode*(): cstring{.cdecl, importc: "rl_get_keymap_name_from_edit_mode", dynlib: readlineDll.} # Functions for manipulating the funmap, which maps command names to functions. -proc add_funmap_entry*(a2: cstring, a3: TCommandFunc): cint{.cdecl, +proc add_funmap_entry*(a2: cstring, a3: CommandFunc): cint{.cdecl, importc: "rl_add_funmap_entry", dynlib: readlineDll.} proc funmap_names*(): cstringArray{.cdecl, importc: "rl_funmap_names", dynlib: readlineDll.} @@ -828,7 +828,7 @@ proc username_completion_function*(a2: cstring, a3: cint): cstring{.cdecl, importc: "rl_username_completion_function", dynlib: readlineDll.} proc filename_completion_function*(a2: cstring, a3: cint): cstring{.cdecl, importc: "rl_filename_completion_function", dynlib: readlineDll.} -proc completion_mode*(a2: TCommandFunc): cint{.cdecl, +proc completion_mode*(a2: CommandFunc): cint{.cdecl, importc: "rl_completion_mode", dynlib: readlineDll.} # **************************************************************** # @@ -883,7 +883,7 @@ when false: # The current value of the numeric argument specified by the user. var numeric_arg*{.importc: "rl_numeric_arg", dynlib: readlineDll.}: cint # The address of the last command function Readline executed. - var last_func*{.importc: "rl_last_func", dynlib: readlineDll.}: TCommandFunc + var last_func*{.importc: "rl_last_func", dynlib: readlineDll.}: CommandFunc # The name of the terminal to use. var terminal_name*{.importc: "rl_terminal_name", dynlib: readlineDll.}: cstring # The input and output streams. @@ -1186,7 +1186,7 @@ type rlstate*: cint done*: cint kmap*: PKeymap # input state - lastfunc*: TCommandFunc + lastfunc*: CommandFunc insmode*: cint edmode*: cint kseqlen*: cint diff --git a/lib/wrappers/sdl/sdl.nim b/lib/wrappers/sdl/sdl.nim index 707c65a53..376de8e08 100644 --- a/lib/wrappers/sdl/sdl.nim +++ b/lib/wrappers/sdl/sdl.nim @@ -775,7 +775,7 @@ type Arg*{.final.} = object buf*: array[0..ERR_MAX_STRLEN - 1, int8] - Perror* = ptr Terror + Perror* = ptr Error Error*{.final.} = object # This is a numeric value corresponding to the current error # SDL_rwops.h types # This is the read/write operation structure -- very basic @@ -814,7 +814,7 @@ type theType*: cint mem*: Mem - RWops* = RWops # SDL_timer.h types + # SDL_timer.h types # Function prototype for the timer callback function TimerCallback* = proc (interval: int32): int32{.cdecl.} NewTimerCallback* = proc (interval: int32, param: pointer): int32{.cdecl.} @@ -950,8 +950,8 @@ type EventAction* = enum # Application visibility event structure ADDEVENT, PEEKEVENT, GETEVENT - PActiveEvent* = ptr ActiveEvent - ActiveEvent*{.final.} = object # SDL_ACTIVEEVENT + PActiveEvent* = ptr TActiveEvent + TActiveEvent*{.final.} = object # SDL_ACTIVEEVENT # Keyboard event structure kind*: EventKind gain*: byte # Whether given states were gained or lost (1/0) @@ -1032,8 +1032,8 @@ type w*: cint # New width h*: cint # New height - PUserEvent* = ptr UserEvent - UserEvent*{.final.} = object # SDL_USEREVENT through SDL_NUMEVENTS-1 + PUserEvent* = ptr TUserEvent + TUserEvent*{.final.} = object # SDL_USEREVENT through SDL_NUMEVENTS-1 kind*: EventKind code*: cint # User defined event code data1*: pointer # User defined data pointer @@ -1044,7 +1044,7 @@ type TWrite: Write, TBool: Bool, TUInt8Array: UInt8Array, TGrabMode: GrabMode, Terrorcode: Errorcode, TStdio: Stdio, TMem: Mem, TSeek: Seek, TRead: Read, TClose: Close, - TTimerCallback: TimerCallback, TNewTimerCallback: NewTimerCallabck, + TTimerCallback: TimerCallback, TNewTimerCallback: NewTimerCallback, TTimerID: TimerID, TAudioSpecCallback: AudioSpecCallback, TAudioSpec: AudioSpec, TAudioCVTFilter: AudioCVTFilter, TAudioCVTFilterArray: AudioCVTFilterArray, TAudioCVT: AudioCVT, @@ -1053,16 +1053,19 @@ type TJoystick: Joystick, TJoyAxisEvent: JoyAxisEvent, TRWops: RWops, TJoyBallEvent: JoyBallEvent, TJoyHatEvent: JoyHatEvent, TJoyButtonEvent: JoyButtonEvent, TBallDelta: BallDelta, - Tversion: Version, TMod: Mod, TActiveEvent: ActiveEvent, + Tversion: Version, TMod: Mod, + # TActiveEvent: ActiveEvent, # Naming conflict when we drop the `T` TMouseMotionEvent: MouseMotionEvent, TMouseButtonEvent: MouseButtonEvent, - TResizeEvent: ResizeEvent, TUserEvent: UserEvent].} + TResizeEvent: ResizeEvent, + # TUserEvent: UserEvent # Naming conflict when we drop the `T` + ].} -when defined(Unix): +when defined(Unix): type #These are the various supported subsystems under UNIX SysWm* = enum SYSWM_X11 {.deprecated: [TSysWm: SysWm].} -when defined(WINDOWS): +when defined(WINDOWS): type PSysWMmsg* = ptr SysWMmsg SysWMmsg*{.final.} = object @@ -1136,8 +1139,8 @@ else: {.deprecated: [TSysWMinfo: SysWMinfo].} type - PSysWMEvent* = ptr SysWMEvent - SysWMEvent*{.final.} = object + PSysWMEvent* = ptr TSysWMEvent + TSysWMEvent*{.final.} = object kind*: EventKind msg*: PSysWMmsg @@ -1172,12 +1175,12 @@ type PColorArray* = ptr ColorArray ColorArray* = array[0..65000, Color] - PPalette* = ptr TPalette + PPalette* = ptr Palette Palette*{.final.} = object # Everything in the pixel format structure is read-only ncolors*: int colors*: PColorArray - PPixelFormat* = ptr TPixelFormat + PPixelFormat* = ptr PixelFormat PixelFormat*{.final.} = object # The structure passed to the low level blit functions palette*: PPalette bitsPerPixel*: byte @@ -1254,10 +1257,10 @@ type hwOverlay*: int32 # This will be set to 1 if the overlay is hardware accelerated. GLAttr* = enum - GL_RED_SIZE, GL_GREEN_SIZE, GL_BLUE_SIZE, GL_ALPHA_SIZE, GL_BUFFER_SIZE, - GL_DOUBLEBUFFER, GL_DEPTH_SIZE, GL_STENCIL_SIZE, GL_ACCUM_RED_SIZE, - GL_ACCUM_GREEN_SIZE, GL_ACCUM_BLUE_SIZE, GL_ACCUM_ALPHA_SIZE, GL_STEREO, - GL_MULTISAMPLEBUFFERS, GL_MULTISAMPLESAMPLES, GL_ACCELERATED_VISUAL, + GL_RED_SIZE, GL_GREEN_SIZE, GL_BLUE_SIZE, GL_ALPHA_SIZE, GL_BUFFER_SIZE, + GL_DOUBLEBUFFER, GL_DEPTH_SIZE, GL_STENCIL_SIZE, GL_ACCUM_RED_SIZE, + GL_ACCUM_GREEN_SIZE, GL_ACCUM_BLUE_SIZE, GL_ACCUM_ALPHA_SIZE, GL_STEREO, + GL_MULTISAMPLEBUFFERS, GL_MULTISAMPLESAMPLES, GL_ACCELERATED_VISUAL, GL_SWAP_CONTROL PCursor* = ptr Cursor Cursor*{.final.} = object # SDL_mutex.h types @@ -1269,7 +1272,8 @@ type wmCursor*: pointer # Window-manager cursor {.deprecated: [TRect: Rect, TSurface: Surface, TEvent: Event, TColor: Color, TEventFilter: EventFilter, TColorArray: ColorArray, - TSysWMEvent: SysWMEvent, TExposeEvent: ExposeEvent, + # TSysWMEvent: SysWMEvent, # Naming conflict when we drop the `T` + TExposeEvent: ExposeEvent, TQuitEvent: QuitEvent, TPalette: Palette, TPixelFormat: PixelFormat, TBlitInfo: BlitInfo, TBlit: Blit, TVideoInfo: VideoInfo, TOverlay: Overlay, TGLAttr: GLAttr, TCursor: Cursor].} @@ -1285,11 +1289,11 @@ type Cond*{.final.} = object # SDL_thread.h types {.deprecated: [TCond: Cond, TSem: Sem, TMutex: Mutex, Tsemaphore: Semaphore].} -when defined(WINDOWS): +when defined(WINDOWS): type SYS_ThreadHandle* = Handle {.deprecated: [TSYS_ThreadHandle: SYS_ThreadHandle].} -when defined(Unix): +when defined(Unix): type SYS_ThreadHandle* = pointer {.deprecated: [TSYS_ThreadHandle: SYS_ThreadHandle].} @@ -1300,7 +1304,7 @@ type # This is the system-independent thread info struc threadid*: int32 handle*: SYS_ThreadHandle status*: int - errbuf*: Terror + errbuf*: Error data*: pointer PKeyStateArr* = ptr KeyStateArr @@ -2211,7 +2215,7 @@ proc glLoadLibrary*(filename: cstring): int{.cdecl, proc glGetProcAddress*(procname: cstring): pointer{.cdecl, importc: "SDL_GL_GetProcAddress", dynlib: LibName.} # Set an attribute of the OpenGL subsystem before intialization. -proc glSetAttribute*(attr: TGLAttr, value: int): int{.cdecl, +proc glSetAttribute*(attr: GLAttr, value: int): int{.cdecl, importc: "SDL_GL_SetAttribute", dynlib: LibName.} # Get an attribute of the OpenGL subsystem from the windowing # interface, such as glX. This is of course different from getting @@ -2220,7 +2224,7 @@ proc glSetAttribute*(attr: TGLAttr, value: int): int{.cdecl, # # Developers should track the values they pass into SDL_GL_SetAttribute # themselves if they want to retrieve these values. -proc glGetAttribute*(attr: TGLAttr, value: var int): int{.cdecl, +proc glGetAttribute*(attr: GLAttr, value: var int): int{.cdecl, importc: "SDL_GL_GetAttribute", dynlib: LibName.} # Swap the OpenGL buffers, if double-buffering is supported. proc glSwapBuffers*(){.cdecl, importc: "SDL_GL_SwapBuffers", dynlib: LibName.} @@ -2267,7 +2271,7 @@ proc wmToggleFullScreen*(surface: PSurface): int{.cdecl, # Grabbing means that the mouse is confined to the application window, # and nearly all keyboard input is passed directly to the application, # and not interpreted by a window manager, if any. -proc wmGrabInput*(mode: TGrabMode): GrabMode{.cdecl, +proc wmGrabInput*(mode: GrabMode): GrabMode{.cdecl, importc: "SDL_WM_GrabInput", dynlib: LibName.} #------------------------------------------------------------------------------ # mouse-routines diff --git a/tests/enum/tenumitems.nim b/tests/enum/tenumitems.nim index 04737fa9e..38233aad7 100644 --- a/tests/enum/tenumitems.nim +++ b/tests/enum/tenumitems.nim @@ -1,6 +1,6 @@ discard """ line: 7 - errormsg: "undeclared identifier: 'items'" + errormsg: "attempting to call undeclared routine: 'items'" """ type a = enum b,c,d diff --git a/tests/js/tunittests.nim b/tests/js/tunittests.nim index 8a264a5e0..4b09c99a9 100644 --- a/tests/js/tunittests.nim +++ b/tests/js/tunittests.nim @@ -1,10 +1,7 @@ discard """ - disabled: "true" + output: '''[OK] >:)''' """ -# Unittest uses lambdalifting at compile-time which we disable for the JS -# codegen! So this cannot and will not work for quite some time. - import unittest suite "Bacon": diff --git a/tests/misc/tissue710.nim b/tests/misc/tissue710.nim index ecfdf653e..3b6d3e5f3 100644 --- a/tests/misc/tissue710.nim +++ b/tests/misc/tissue710.nim @@ -1,7 +1,7 @@ discard """ file: "tissue710.nim" line: 8 - errorMsg: "undeclared identifier: '||'" + errorMsg: "attempting to call undeclared routine: '||'" """ var sum = 0 for x in 3..1000: diff --git a/tests/misc/tnoop.nim b/tests/misc/tnoop.nim index 10c2eb2ec..1e3fbe6cf 100644 --- a/tests/misc/tnoop.nim +++ b/tests/misc/tnoop.nim @@ -1,7 +1,7 @@ discard """ file: "tnoop.nim" line: 11 - errormsg: "undeclared identifier: 'a'" + errormsg: "attempting to call undeclared routine: 'a'" """ diff --git a/tests/modules/topaque.nim b/tests/modules/topaque.nim index f0587c959..84e2388bc 100644 --- a/tests/modules/topaque.nim +++ b/tests/modules/topaque.nim @@ -1,16 +1,16 @@ discard """ file: "topaque.nim" line: 16 - errormsg: "undeclared identifier: \'buffer\'" + errormsg: "undeclared field: \'buffer\'" """ # Test the new opaque types -import +import mopaque - + var L: TLexer - + L.filename = "ha" L.line = 34 L.buffer[0] = '\0' #ERROR_MSG undeclared field: 'buffer' diff --git a/tests/parallel/tptr_to_ref.nim b/tests/parallel/tptr_to_ref.nim new file mode 100644 index 000000000..66d618481 --- /dev/null +++ b/tests/parallel/tptr_to_ref.nim @@ -0,0 +1,26 @@ +# bug #2854 + +import locks, threadpool, osproc + +const MAX_WORKERS = 10 + +type + Killer = object + lock: Lock + bailed {.guard: lock.}: bool + processes {.guard: lock.}: array[0..MAX_WORKERS-1, foreign ptr Process] + +template hold(lock: Lock, body: stmt) = + lock.acquire + defer: lock.release + {.locks: [lock].}: + body + +proc initKiller*(): Killer = + initLock(result.lock) + result.lock.hold: + result.bailed = false + for i, _ in result.processes: + result.processes[i] = nil + +var killer = initKiller() diff --git a/tests/tuples/twrongtupleaccess.nim b/tests/tuples/twrongtupleaccess.nim index 1a9ae64a2..b1684b097 100644 --- a/tests/tuples/twrongtupleaccess.nim +++ b/tests/tuples/twrongtupleaccess.nim @@ -1,7 +1,7 @@ discard """ file: "twrongtupleaccess.nim" line: 9 - errormsg: "undeclared identifier: \'setBLAH\'" + errormsg: "attempting to call undeclared routine: \'setBLAH\'" """ # Bugfix diff --git a/tests/vm/tconstobj.nim b/tests/vm/tconstobj.nim new file mode 100644 index 000000000..414708945 --- /dev/null +++ b/tests/vm/tconstobj.nim @@ -0,0 +1,14 @@ +discard """ + output: '''(name: hello)''' +""" + +# bug #2774 + +type Foo = object + name: string + +const fooArray = [ + Foo(name: "hello") +] + +echo fooArray[0] diff --git a/tools/niminst/niminst.nim b/tools/niminst/niminst.nim index 99befa92d..253543a50 100644 --- a/tools/niminst/niminst.nim +++ b/tools/niminst/niminst.nim @@ -538,7 +538,7 @@ when haveZipLib: var n = "$#.zip" % proj if c.outdir.len == 0: n = "build" / n else: n = c.outdir / n - var z: TZipArchive + var z: ZipArchive if open(z, n, fmWrite): addFile(z, proj / buildBatFile32, "build" / buildBatFile32) addFile(z, proj / buildBatFile64, "build" / buildBatFile64) |