diff options
Diffstat (limited to 'lib')
-rw-r--r-- | lib/core/macros.nim | 5 | ||||
-rw-r--r-- | lib/impure/re.nim | 20 | ||||
-rw-r--r-- | lib/js/jsffi.nim | 22 | ||||
-rw-r--r-- | lib/nimbase.h | 2 | ||||
-rw-r--r-- | lib/packages/docutils/highlite.nim | 9 | ||||
-rw-r--r-- | lib/packages/docutils/rst.nim | 13 | ||||
-rw-r--r-- | lib/packages/docutils/rstgen.nim | 24 | ||||
-rw-r--r-- | lib/pure/asynchttpserver.nim | 5 | ||||
-rw-r--r-- | lib/pure/htmlgen.nim | 4 | ||||
-rw-r--r-- | lib/pure/json.nim | 162 | ||||
-rw-r--r-- | lib/pure/mimetypes.nim | 9 | ||||
-rw-r--r-- | lib/pure/ospaths.nim | 15 | ||||
-rw-r--r-- | lib/pure/osproc.nim | 8 | ||||
-rw-r--r-- | lib/pure/strutils.nim | 104 | ||||
-rw-r--r-- | lib/pure/unicode.nim | 12 | ||||
-rw-r--r-- | lib/system.nim | 30 |
16 files changed, 306 insertions, 138 deletions
diff --git a/lib/core/macros.nim b/lib/core/macros.nim index ebc9f7714..ee6c1a09f 100644 --- a/lib/core/macros.nim +++ b/lib/core/macros.nim @@ -1226,3 +1226,8 @@ when not defined(booting): macro payload: untyped {.gensym.} = result = parseStmt(e) payload() + +macro unpackVarargs*(callee: untyped; args: varargs[untyped]): untyped = + result = newCall(callee) + for i in 0 ..< args.len: + result.add args[i] diff --git a/lib/impure/re.nim b/lib/impure/re.nim index 24fc83366..c7f8f336b 100644 --- a/lib/impure/re.nim +++ b/lib/impure/re.nim @@ -49,9 +49,6 @@ type RegexError* = object of ValueError ## is raised if the pattern is no valid regular expression. -{.deprecated: [TRegexFlag: RegexFlag, TRegexDesc: RegexDesc, TRegex: Regex, - EInvalidRegEx: RegexError].} - proc raiseInvalidRegex(msg: string) {.noinline, noreturn.} = var e: ref RegexError new(e) @@ -470,8 +467,8 @@ proc replacef*(s: string, sub: Regex, by: string): string = prev = match.last + 1 add(result, substr(s, prev)) -proc parallelReplace*(s: string, subs: openArray[ - tuple[pattern: Regex, repl: string]]): string = +proc multiReplace*(s: string, subs: openArray[ + tuple[pattern: Regex, repl: string]]): string = ## Returns a modified copy of ``s`` with the substitutions in ``subs`` ## applied in parallel. result = "" @@ -490,13 +487,20 @@ proc parallelReplace*(s: string, subs: openArray[ # copy the rest: add(result, substr(s, i)) +proc parallelReplace*(s: string, subs: openArray[ + tuple[pattern: Regex, repl: string]]): string {.deprecated.} = + ## Returns a modified copy of ``s`` with the substitutions in ``subs`` + ## applied in parallel. + ## **Deprecated since version 0.18.0**: Use ``multiReplace`` instead. + result = multiReplace(s, subs) + proc transformFile*(infile, outfile: string, subs: openArray[tuple[pattern: Regex, repl: string]]) = ## reads in the file ``infile``, performs a parallel replacement (calls ## ``parallelReplace``) and writes back to ``outfile``. Raises ``IOError`` if an ## error occurs. This is supposed to be used for quick scripting. var x = readFile(infile).string - writeFile(outfile, x.parallelReplace(subs)) + writeFile(outfile, x.multiReplace(subs)) iterator split*(s: string, sep: Regex): string = ## Splits the string ``s`` into substrings. @@ -579,12 +583,12 @@ const ## common regular expressions ## describes an URL when isMainModule: - doAssert match("(a b c)", re"\( .* \)") + doAssert match("(a b c)", rex"\( .* \)") doAssert match("WHiLe", re("while", {reIgnoreCase})) doAssert "0158787".match(re"\d+") doAssert "ABC 0232".match(re"\w+\s+\d+") - doAssert "ABC".match(re"\d+ | \w+") + doAssert "ABC".match(rex"\d+ | \w+") {.push warnings:off.} doAssert matchLen("key", re(reIdentifier)) == 3 diff --git a/lib/js/jsffi.nim b/lib/js/jsffi.nim index 13eb1e759..f34efe9a2 100644 --- a/lib/js/jsffi.nim +++ b/lib/js/jsffi.nim @@ -177,7 +177,7 @@ proc `==`*(x, y: JsRoot): bool {. importcpp: "(# === #)" .} ## and not strings or numbers, this is a *comparison of references*. {. experimental .} -macro `.`*(obj: JsObject, field: static[cstring]): JsObject = +macro `.`*(obj: JsObject, field: untyped): JsObject = ## Experimental dot accessor (get) for type JsObject. ## Returns the value of a property of name `field` from a JsObject `x`. ## @@ -196,14 +196,14 @@ macro `.`*(obj: JsObject, field: static[cstring]): JsObject = helper(`obj`) else: if not mangledNames.hasKey($field): - mangledNames[$field] = $mangleJsName(field) + mangledNames[$field] = $mangleJsName($field) let importString = "#." & mangledNames[$field] result = quote do: proc helper(o: JsObject): JsObject {. importcpp: `importString`, gensym .} helper(`obj`) -macro `.=`*(obj: JsObject, field: static[cstring], value: untyped): untyped = +macro `.=`*(obj: JsObject, field, value: untyped): untyped = ## Experimental dot accessor (set) for type JsObject. ## Sets the value of a property of name `field` in a JsObject `x` to `value`. if validJsName($field): @@ -214,7 +214,7 @@ macro `.=`*(obj: JsObject, field: static[cstring], value: untyped): untyped = helper(`obj`, `value`) else: if not mangledNames.hasKey($field): - mangledNames[$field] = $mangleJsName(field) + mangledNames[$field] = $mangleJsName($field) let importString = "#." & mangledNames[$field] & " = #" result = quote do: proc helper(o: JsObject, v: auto) @@ -222,7 +222,7 @@ macro `.=`*(obj: JsObject, field: static[cstring], value: untyped): untyped = helper(`obj`, `value`) macro `.()`*(obj: JsObject, - field: static[cstring], + field: untyped, args: varargs[JsObject, jsFromAst]): JsObject = ## Experimental "method call" operator for type JsObject. ## Takes the name of a method of the JavaScript object (`field`) and calls @@ -245,7 +245,7 @@ macro `.()`*(obj: JsObject, importString = "#." & $field & "(@)" else: if not mangledNames.hasKey($field): - mangledNames[$field] = $mangleJsName(field) + mangledNames[$field] = $mangleJsName($field) importString = "#." & mangledNames[$field] & "(@)" result = quote: proc helper(o: JsObject): JsObject @@ -257,7 +257,7 @@ macro `.()`*(obj: JsObject, result[1].add args[idx].copyNimTree macro `.`*[K: string | cstring, V](obj: JsAssoc[K, V], - field: static[cstring]): V = + field: untyped): V = ## Experimental dot accessor (get) for type JsAssoc. ## Returns the value of a property of name `field` from a JsObject `x`. var importString: string @@ -265,7 +265,7 @@ macro `.`*[K: string | cstring, V](obj: JsAssoc[K, V], importString = "#." & $field else: if not mangledNames.hasKey($field): - mangledNames[$field] = $mangleJsName(field) + mangledNames[$field] = $mangleJsName($field) importString = "#." & mangledNames[$field] result = quote do: proc helper(o: type(`obj`)): `obj`.V @@ -273,7 +273,7 @@ macro `.`*[K: string | cstring, V](obj: JsAssoc[K, V], helper(`obj`) macro `.=`*[K: string | cstring, V](obj: JsAssoc[K, V], - field: static[cstring], + field: untyped, value: V): untyped = ## Experimental dot accessor (set) for type JsAssoc. ## Sets the value of a property of name `field` in a JsObject `x` to `value`. @@ -282,7 +282,7 @@ macro `.=`*[K: string | cstring, V](obj: JsAssoc[K, V], importString = "#." & $field & " = #" else: if not mangledNames.hasKey($field): - mangledNames[$field] = $mangleJsName(field) + mangledNames[$field] = $mangleJsName($field) importString = "#." & mangledNames[$field] & " = #" result = quote do: proc helper(o: type(`obj`), v: `obj`.V) @@ -290,7 +290,7 @@ macro `.=`*[K: string | cstring, V](obj: JsAssoc[K, V], helper(`obj`, `value`) macro `.()`*[K: string | cstring, V: proc](obj: JsAssoc[K, V], - field: static[cstring], + field: untyped, args: varargs[untyped]): auto = ## Experimental "method call" operator for type JsAssoc. ## Takes the name of a method of the JavaScript object (`field`) and calls diff --git a/lib/nimbase.h b/lib/nimbase.h index 76192713b..ac2cc097c 100644 --- a/lib/nimbase.h +++ b/lib/nimbase.h @@ -70,7 +70,7 @@ __clang__ #if defined(_MSC_VER) # pragma warning(disable: 4005 4100 4101 4189 4191 4200 4244 4293 4296 4309) # pragma warning(disable: 4310 4365 4456 4477 4514 4574 4611 4668 4702 4706) -# pragma warning(disable: 4710 4711 4774 4800 4820 4996 4090) +# pragma warning(disable: 4710 4711 4774 4800 4820 4996 4090 4297) #endif /* ------------------------------------------------------------------------- */ diff --git a/lib/packages/docutils/highlite.nim b/lib/packages/docutils/highlite.nim index 70369b001..2a58854a6 100644 --- a/lib/packages/docutils/highlite.nim +++ b/lib/packages/docutils/highlite.nim @@ -31,14 +31,12 @@ type state: TokenClass SourceLanguage* = enum - langNone, langNim, langNimrod, langCpp, langCsharp, langC, langJava, + langNone, langNim, langCpp, langCsharp, langC, langJava, langYaml -{.deprecated: [TSourceLanguage: SourceLanguage, TTokenClass: TokenClass, - TGeneralTokenizer: GeneralTokenizer].} const sourceLanguageToStr*: array[SourceLanguage, string] = ["none", - "Nim", "Nimrod", "C++", "C#", "C", "Java", "Yaml"] + "Nim", "C++", "C#", "C", "Java", "Yaml"] tokenClassToStr*: array[TokenClass, string] = ["Eof", "None", "Whitespace", "DecNumber", "BinNumber", "HexNumber", "OctNumber", "FloatNumber", "Identifier", "Keyword", "StringLit", "LongStringLit", "CharLit", @@ -398,7 +396,6 @@ type TokenizerFlag = enum hasPreprocessor, hasNestedComments TokenizerFlags = set[TokenizerFlag] -{.deprecated: [TTokenizerFlag: TokenizerFlag, TTokenizerFlags: TokenizerFlags].} proc clikeNextToken(g: var GeneralTokenizer, keywords: openArray[string], flags: TokenizerFlags) = @@ -888,7 +885,7 @@ proc yamlNextToken(g: var GeneralTokenizer) = proc getNextToken*(g: var GeneralTokenizer, lang: SourceLanguage) = case lang of langNone: assert false - of langNim, langNimrod: nimNextToken(g) + of langNim: nimNextToken(g) of langCpp: cppNextToken(g) of langCsharp: csharpNextToken(g) of langC: cNextToken(g) diff --git a/lib/packages/docutils/rst.nim b/lib/packages/docutils/rst.nim index 53699166f..223fc836a 100644 --- a/lib/packages/docutils/rst.nim +++ b/lib/packages/docutils/rst.nim @@ -45,8 +45,6 @@ type MsgHandler* = proc (filename: string, line, col: int, msgKind: MsgKind, arg: string) {.nimcall.} ## what to do in case of an error FindFileHandler* = proc (filename: string): string {.nimcall.} -{.deprecated: [TRstParseOptions: RstParseOptions, TRstParseOption: RstParseOption, - TMsgKind: MsgKind].} const messages: array[MsgKind, string] = [ @@ -127,8 +125,6 @@ type bufpos*: int line*, col*, baseIndent*: int skipPounds*: bool -{.deprecated: [TTokType: TokType, TToken: Token, TTokenSeq: TokenSeq, - TLexer: Lexer].} proc getThing(L: var Lexer, tok: var Token, s: set[char]) = tok.kind = tkWord @@ -288,10 +284,6 @@ type hasToc*: bool EParseError* = object of ValueError -{.deprecated: [TLevelMap: LevelMap, TSubstitution: Substitution, - TSharedState: SharedState, TRstParser: RstParser, - TMsgHandler: MsgHandler, TFindFileHandler: FindFileHandler, - TMsgClass: MsgClass].} proc whichMsgClass*(k: MsgKind): MsgClass = ## returns which message class `k` belongs to. @@ -341,11 +333,6 @@ proc rstMessage(p: RstParser, msgKind: MsgKind) = p.col + p.tok[p.idx].col, msgKind, p.tok[p.idx].symbol) -when false: - proc corrupt(p: RstParser) = - assert p.indentStack[0] == 0 - for i in 1 .. high(p.indentStack): assert p.indentStack[i] < 1_000 - proc currInd(p: RstParser): int = result = p.indentStack[high(p.indentStack)] diff --git a/lib/packages/docutils/rstgen.nim b/lib/packages/docutils/rstgen.nim index f156c440b..e6c95b59e 100644 --- a/lib/packages/docutils/rstgen.nim +++ b/lib/packages/docutils/rstgen.nim @@ -61,6 +61,9 @@ type seenIndexTerms: Table[string, int] ## \ ## Keeps count of same text index terms to generate different identifiers ## for hyperlinks. See renderIndexTerm proc for details. + id*: int ## A counter useful for generating IDs. + onTestSnippet*: proc (d: var RstGenerator; filename, cmd: string; status: int; + content: string) PDoc = var RstGenerator ## Alias to type less. @@ -69,8 +72,9 @@ type startLine: int ## The starting line of the code block, by default 1. langStr: string ## Input string used to specify the language. lang: SourceLanguage ## Type of highlighting, by default none. -{.deprecated: [TRstGenerator: RstGenerator, TTocEntry: TocEntry, - TOutputTarget: OutputTarget, TMetaEnum: MetaEnum].} + filename: string + testCmd: string + status: int proc init(p: var CodeBlockParams) = ## Default initialisation of CodeBlockParams to sane values. @@ -133,6 +137,7 @@ proc initRstGenerator*(g: var RstGenerator, target: OutputTarget, g.options = options g.findFile = findFile g.currentSection = "" + g.id = 0 let fileParts = filename.splitFile if fileParts.ext == ".nim": g.currentSection = "Module " & fileParts.name @@ -368,7 +373,6 @@ type ## ## The value indexed by this IndexEntry is a sequence with the real index ## entries found in the ``.idx`` file. -{.deprecated: [TIndexEntry: IndexEntry, TIndexedDocs: IndexedDocs].} proc cmp(a, b: IndexEntry): int = ## Sorts two ``IndexEntry`` first by `keyword` field, then by `link`. @@ -823,13 +827,20 @@ proc parseCodeBlockField(d: PDoc, n: PRstNode, params: var CodeBlockParams) = var number: int if parseInt(n.getFieldValue, number) > 0: params.startLine = number - of "file": + of "file", "filename": # The ``file`` option is a Nim extension to the official spec, it acts # like it would for other directives like ``raw`` or ``cvs-table``. This # field is dealt with in ``rst.nim`` which replaces the existing block with # the referenced file, so we only need to ignore it here to avoid incorrect # warning messages. - discard + params.filename = n.getFieldValue.strip + of "test": + params.testCmd = n.getFieldValue.strip + if params.testCmd.len == 0: params.testCmd = "nim c -r $1" + of "status": + var status: int + if parseInt(n.getFieldValue, status) > 0: + params.status = status of "default-language": params.langStr = n.getFieldValue.strip params.lang = params.langStr.getSourceLanguage @@ -901,6 +912,9 @@ proc renderCodeBlock(d: PDoc, n: PRstNode, result: var string) = var m = n.sons[2].sons[0] assert m.kind == rnLeaf + if params.testCmd.len > 0 and d.onTestSnippet != nil: + d.onTestSnippet(d, params.filename, params.testCmd, params.status, m.text) + let (blockStart, blockEnd) = buildLinesHTMLTable(d, params, m.text) dispA(d.target, result, blockStart, "\\begin{rstpre}\n", []) diff --git a/lib/pure/asynchttpserver.nim b/lib/pure/asynchttpserver.nim index 433931c9d..ba1615651 100644 --- a/lib/pure/asynchttpserver.nim +++ b/lib/pure/asynchttpserver.nim @@ -275,10 +275,7 @@ proc processClient(server: AsyncHttpServer, client: AsyncSocket, address: string lineFut.mget() = newStringOfCap(80) while not client.isClosed: - try: - await processRequest(server, request, client, address, lineFut, callback) - except: - asyncCheck request.mget().respondError(Http500) + await processRequest(server, request, client, address, lineFut, callback) proc serve*(server: AsyncHttpServer, port: Port, callback: proc (request: Request): Future[void] {.closure,gcsafe.}, diff --git a/lib/pure/htmlgen.nim b/lib/pure/htmlgen.nim index ad199a215..c0934a45b 100644 --- a/lib/pure/htmlgen.nim +++ b/lib/pure/htmlgen.nim @@ -59,8 +59,8 @@ proc xmlCheckedTag*(e: NimNode, tag: string, optAttr = "", reqAttr = "", # copy the attributes; when iterating over them these lists # will be modified, so that each attribute is only given one value - var req = split(reqAttr) - var opt = split(optAttr) + var req = splitWhitespace(reqAttr) + var opt = splitWhitespace(optAttr) result = newNimNode(nnkBracket, e) result.add(newStrLitNode("<")) result.add(newStrLitNode(tag)) diff --git a/lib/pure/json.nim b/lib/pure/json.nim index cea485c43..b5b84863a 100644 --- a/lib/pure/json.nim +++ b/lib/pure/json.nim @@ -1346,6 +1346,16 @@ proc createJsonIndexer(jsonNode: NimNode, indexNode ) +proc transformJsonIndexer(jsonNode: NimNode): NimNode = + case jsonNode.kind + of nnkBracketExpr: + result = newNimNode(nnkCurlyExpr) + else: + result = jsonNode.copy() + + for child in jsonNode: + result.add(transformJsonIndexer(child)) + template verifyJsonKind(node: JsonNode, kinds: set[JsonNodeKind], ast: string) = if node.kind notin kinds: @@ -1524,6 +1534,35 @@ proc processObjField(field, jsonNode: NimNode): seq[NimNode] = doAssert result.len > 0 +proc processFields(obj: NimNode, + jsonNode: NimNode): seq[NimNode] {.compileTime.} = + ## Process all the fields of an ``ObjectTy`` and any of its + ## parent type's fields (via inheritance). + result = @[] + case obj.kind + of nnkObjectTy: + expectKind(obj[2], nnkRecList) + for field in obj[2]: + let nodes = processObjField(field, jsonNode) + result.add(nodes) + + # process parent type fields + case obj[1].kind + of nnkBracketExpr: + assert $obj[1][0] == "ref" + result.add(processFields(getType(obj[1][1]), jsonNode)) + of nnkSym: + result.add(processFields(getType(obj[1]), jsonNode)) + else: + discard + of nnkTupleTy: + for identDefs in obj: + expectKind(identDefs, nnkIdentDefs) + let nodes = processObjField(identDefs[0], jsonNode) + result.add(nodes) + else: + doAssert false, "Unable to process field type: " & $obj.kind + proc processType(typeName: NimNode, obj: NimNode, jsonNode: NimNode, isRef: bool): NimNode {.compileTime.} = ## Process a type such as ``Sym "float"`` or ``ObjectTy ...``. @@ -1533,20 +1572,21 @@ proc processType(typeName: NimNode, obj: NimNode, ## .. code-block::plain ## ObjectTy ## Empty - ## Empty + ## InheritanceInformation ## RecList ## Sym "events" case obj.kind - of nnkObjectTy: + of nnkObjectTy, nnkTupleTy: # Create object constructor. - result = newNimNode(nnkObjConstr) - result.add(typeName) # Name of the type to construct. + result = + if obj.kind == nnkObjectTy: newNimNode(nnkObjConstr) + else: newNimNode(nnkPar) - # Process each object field and add it as an exprColonExpr - expectKind(obj[2], nnkRecList) - for field in obj[2]: - let nodes = processObjField(field, jsonNode) - result.add(nodes) + if obj.kind == nnkObjectTy: + result.add(typeName) # Name of the type to construct. + + # Process each object/tuple field and add it as an exprColonExpr + result.add(processFields(obj, jsonNode)) # Object might be null. So we need to check for that. if isRef: @@ -1569,25 +1609,14 @@ proc processType(typeName: NimNode, obj: NimNode, `getEnumCall` ) of nnkSym: - case ($typeName).normalize - of "float": - result = quote do: - ( - verifyJsonKind(`jsonNode`, {JFloat, JInt}, astToStr(`jsonNode`)); - if `jsonNode`.kind == JFloat: `jsonNode`.fnum else: `jsonNode`.num.float - ) + let name = ($typeName).normalize + case name of "string": result = quote do: ( verifyJsonKind(`jsonNode`, {JString, JNull}, astToStr(`jsonNode`)); if `jsonNode`.kind == JNull: nil else: `jsonNode`.str ) - of "int": - result = quote do: - ( - verifyJsonKind(`jsonNode`, {JInt}, astToStr(`jsonNode`)); - `jsonNode`.num.int - ) of "biggestint": result = quote do: ( @@ -1601,12 +1630,36 @@ proc processType(typeName: NimNode, obj: NimNode, `jsonNode`.bval ) else: - doAssert false, "Unable to process nnkSym " & $typeName + if name.startsWith("int") or name.startsWith("uint"): + result = quote do: + ( + verifyJsonKind(`jsonNode`, {JInt}, astToStr(`jsonNode`)); + `jsonNode`.num.`obj` + ) + elif name.startsWith("float"): + result = quote do: + ( + verifyJsonKind(`jsonNode`, {JInt, JFloat}, astToStr(`jsonNode`)); + if `jsonNode`.kind == JFloat: `jsonNode`.fnum.`obj` else: `jsonNode`.num.`obj` + ) + else: + doAssert false, "Unable to process nnkSym " & $typeName else: doAssert false, "Unable to process type: " & $obj.kind doAssert(not result.isNil(), "processType not initialised.") +import options +proc workaroundMacroNone[T](): Option[T] = + none(T) + +proc depth(n: NimNode, current = 0): int = + result = 1 + for child in n: + let d = 1 + child.depth(current + 1) + if d > result: + result = d + proc createConstructor(typeSym, jsonNode: NimNode): NimNode = ## Accepts a type description, i.e. "ref Type", "seq[Type]", "Type" etc. ## @@ -1616,10 +1669,50 @@ proc createConstructor(typeSym, jsonNode: NimNode): NimNode = # echo("--createConsuctor-- \n", treeRepr(typeSym)) # echo() + if depth(jsonNode) > 150: + error("The `to` macro does not support ref objects with cycles.", jsonNode) + case typeSym.kind of nnkBracketExpr: var bracketName = ($typeSym[0]).normalize case bracketName + of "option": + # TODO: Would be good to verify that this is Option[T] from + # options module I suppose. + let lenientJsonNode = transformJsonIndexer(jsonNode) + + let optionGeneric = typeSym[1] + let value = createConstructor(typeSym[1], jsonNode) + let workaround = bindSym("workaroundMacroNone") # TODO: Nim Bug: This shouldn't be necessary. + + result = quote do: + ( + if `lenientJsonNode`.isNil: `workaround`[`optionGeneric`]() else: some[`optionGeneric`](`value`) + ) + of "table", "orderedtable": + let tableKeyType = typeSym[1] + if ($tableKeyType).cmpIgnoreStyle("string") != 0: + error("JSON doesn't support keys of type " & $tableKeyType) + let tableValueType = typeSym[2] + + let forLoopKey = genSym(nskForVar, "key") + let indexerNode = createJsonIndexer(jsonNode, forLoopKey) + let constructorNode = createConstructor(tableValueType, indexerNode) + + let tableInit = + if bracketName == "table": + bindSym("initTable") + else: + bindSym("initOrderedTable") + + # Create a statement expression containing a for loop. + result = quote do: + ( + var map = `tableInit`[`tableKeyType`, `tableValueType`](); + verifyJsonKind(`jsonNode`, {JObject}, astToStr(`jsonNode`)); + for `forLoopKey` in keys(`jsonNode`.fields): map[`forLoopKey`] = `constructorNode`; + map + ) of "ref": # Ref type. var typeName = $typeSym[1] @@ -1663,12 +1756,23 @@ proc createConstructor(typeSym, jsonNode: NimNode): NimNode = let obj = getType(typeSym) result = processType(typeSym, obj, jsonNode, false) of nnkSym: + # Handle JsonNode. + if ($typeSym).cmpIgnoreStyle("jsonnode") == 0: + return jsonNode + + # Handle all other types. let obj = getType(typeSym) if obj.kind == nnkBracketExpr: # When `Sym "Foo"` turns out to be a `ref object`. result = createConstructor(obj, jsonNode) else: result = processType(typeSym, obj, jsonNode, false) + of nnkTupleTy: + result = processType(typeSym, typeSym, jsonNode, false) + of nnkPar: + # TODO: The fact that `jsonNode` here works to give a good line number + # is weird. Specifying typeSym should work but doesn't. + error("Use a named tuple instead of: " & $toStrLit(typeSym), jsonNode) else: doAssert false, "Unable to create constructor for: " & $typeSym.kind @@ -1796,10 +1900,18 @@ macro to*(node: JsonNode, T: typedesc): untyped = expectKind(typeNode, nnkBracketExpr) doAssert(($typeNode[0]).normalize == "typedesc") - result = createConstructor(typeNode[1], node) + # Create `temp` variable to store the result in case the user calls this + # on `parseJson` (see bug #6604). + result = newNimNode(nnkStmtListExpr) + let temp = genSym(nskLet, "temp") + result.add quote do: + let `temp` = `node` + + let constructor = createConstructor(typeNode[1], temp) # TODO: Rename postProcessValue and move it (?) - result = postProcessValue(result) + result.add(postProcessValue(constructor)) + # echo(treeRepr(result)) # echo(toStrLit(result)) when false: diff --git a/lib/pure/mimetypes.nim b/lib/pure/mimetypes.nim index 1e315afb4..b397ef47b 100644 --- a/lib/pure/mimetypes.nim +++ b/lib/pure/mimetypes.nim @@ -491,6 +491,8 @@ const mimes* = { "vrml": "x-world/x-vrml", "wrl": "x-world/x-vrml"} +from strutils import startsWith + proc newMimetypes*(): MimeDB = ## Creates a new Mimetypes database. The database will contain the most ## common mimetypes. @@ -498,8 +500,11 @@ proc newMimetypes*(): MimeDB = proc getMimetype*(mimedb: MimeDB, ext: string, default = "text/plain"): string = ## Gets mimetype which corresponds to ``ext``. Returns ``default`` if ``ext`` - ## could not be found. - result = mimedb.mimes.getOrDefault(ext) + ## could not be found. ``ext`` can start with an optional dot which is ignored. + if ext.startsWith("."): + result = mimedb.mimes.getOrDefault(ext.substr(1)) + else: + result = mimedb.mimes.getOrDefault(ext) if result == "": return default diff --git a/lib/pure/ospaths.nim b/lib/pure/ospaths.nim index c3bd399db..0d638abb9 100644 --- a/lib/pure/ospaths.nim +++ b/lib/pure/ospaths.nim @@ -602,14 +602,13 @@ proc quoteShellPosix*(s: string): string {.noSideEffect, rtl, extern: "nosp$1".} else: return "'" & s.replace("'", "'\"'\"'") & "'" -proc quoteShell*(s: string): string {.noSideEffect, rtl, extern: "nosp$1".} = - ## Quote ``s``, so it can be safely passed to shell. - when defined(Windows): - return quoteShellWindows(s) - elif defined(posix): - return quoteShellPosix(s) - else: - {.error:"quoteShell is not supported on your system".} +when defined(windows) or defined(posix): + proc quoteShell*(s: string): string {.noSideEffect, rtl, extern: "nosp$1".} = + ## Quote ``s``, so it can be safely passed to shell. + when defined(windows): + return quoteShellWindows(s) + else: + return quoteShellPosix(s) when isMainModule: assert quoteShellWindows("aaa") == "aaa" diff --git a/lib/pure/osproc.nim b/lib/pure/osproc.nim index 29f0380a3..5440ceb67 100644 --- a/lib/pure/osproc.nim +++ b/lib/pure/osproc.nim @@ -344,6 +344,8 @@ when not defined(useNimRtl): elif not running(p): break close(p) +template streamAccess(p) = + assert poParentStreams notin p.options, "API usage error: stream access not allowed when you use poParentStreams" when defined(Windows) and not defined(useNimRtl): # We need to implement a handle stream for Windows: @@ -604,12 +606,15 @@ when defined(Windows) and not defined(useNimRtl): return res proc inputStream(p: Process): Stream = + streamAccess(p) result = newFileHandleStream(p.inHandle) proc outputStream(p: Process): Stream = + streamAccess(p) result = newFileHandleStream(p.outHandle) proc errorStream(p: Process): Stream = + streamAccess(p) result = newFileHandleStream(p.errHandle) proc execCmd(command: string): int = @@ -1178,16 +1183,19 @@ elif not defined(useNimRtl): stream = newFileStream(f) proc inputStream(p: Process): Stream = + streamAccess(p) if p.inStream == nil: createStream(p.inStream, p.inHandle, fmWrite) return p.inStream proc outputStream(p: Process): Stream = + streamAccess(p) if p.outStream == nil: createStream(p.outStream, p.outHandle, fmRead) return p.outStream proc errorStream(p: Process): Stream = + streamAccess(p) if p.errStream == nil: createStream(p.errStream, p.errHandle, fmRead) return p.errStream diff --git a/lib/pure/strutils.nim b/lib/pure/strutils.nim index 4ac40d8b4..62ceaa2e8 100644 --- a/lib/pure/strutils.nim +++ b/lib/pure/strutils.nim @@ -32,10 +32,6 @@ when defined(nimOldSplit): else: {.pragma: deprecatedSplit.} -type - CharSet* {.deprecated.} = set[char] # for compatibility with Nim -{.deprecated: [TCharSet: CharSet].} - const Whitespace* = {' ', '\t', '\v', '\r', '\l', '\f'} ## All the characters that count as whitespace. @@ -78,40 +74,40 @@ proc isAlphaAscii*(c: char): bool {.noSideEffect, procvar, return c in Letters proc isAlphaNumeric*(c: char): bool {.noSideEffect, procvar, - rtl, extern: "nsuIsAlphaNumericChar".}= + rtl, extern: "nsuIsAlphaNumericChar".} = ## Checks whether or not `c` is alphanumeric. ## ## This checks a-z, A-Z, 0-9 ASCII characters only. - return c in Letters or c in Digits + return c in Letters+Digits proc isDigit*(c: char): bool {.noSideEffect, procvar, - rtl, extern: "nsuIsDigitChar".}= + rtl, extern: "nsuIsDigitChar".} = ## Checks whether or not `c` is a number. ## ## This checks 0-9 ASCII characters only. return c in Digits proc isSpaceAscii*(c: char): bool {.noSideEffect, procvar, - rtl, extern: "nsuIsSpaceAsciiChar".}= + rtl, extern: "nsuIsSpaceAsciiChar".} = ## Checks whether or not `c` is a whitespace character. return c in Whitespace proc isLowerAscii*(c: char): bool {.noSideEffect, procvar, - rtl, extern: "nsuIsLowerAsciiChar".}= + rtl, extern: "nsuIsLowerAsciiChar".} = ## Checks whether or not `c` is a lower case character. ## ## This checks ASCII characters only. return c in {'a'..'z'} proc isUpperAscii*(c: char): bool {.noSideEffect, procvar, - rtl, extern: "nsuIsUpperAsciiChar".}= + rtl, extern: "nsuIsUpperAsciiChar".} = ## Checks whether or not `c` is an upper case character. ## ## This checks ASCII characters only. return c in {'A'..'Z'} proc isAlphaAscii*(s: string): bool {.noSideEffect, procvar, - rtl, extern: "nsuIsAlphaAsciiStr".}= + rtl, extern: "nsuIsAlphaAsciiStr".} = ## Checks whether or not `s` is alphabetical. ## ## This checks a-z, A-Z ASCII characters only. @@ -123,10 +119,10 @@ proc isAlphaAscii*(s: string): bool {.noSideEffect, procvar, result = true for c in s: - result = c.isAlphaAscii() and result + if not c.isAlphaAscii(): return false proc isAlphaNumeric*(s: string): bool {.noSideEffect, procvar, - rtl, extern: "nsuIsAlphaNumericStr".}= + rtl, extern: "nsuIsAlphaNumericStr".} = ## Checks whether or not `s` is alphanumeric. ## ## This checks a-z, A-Z, 0-9 ASCII characters only. @@ -142,7 +138,7 @@ proc isAlphaNumeric*(s: string): bool {.noSideEffect, procvar, return false proc isDigit*(s: string): bool {.noSideEffect, procvar, - rtl, extern: "nsuIsDigitStr".}= + rtl, extern: "nsuIsDigitStr".} = ## Checks whether or not `s` is a numeric value. ## ## This checks 0-9 ASCII characters only. @@ -158,7 +154,7 @@ proc isDigit*(s: string): bool {.noSideEffect, procvar, return false proc isSpaceAscii*(s: string): bool {.noSideEffect, procvar, - rtl, extern: "nsuIsSpaceAsciiStr".}= + rtl, extern: "nsuIsSpaceAsciiStr".} = ## Checks whether or not `s` is completely whitespace. ## ## Returns true if all characters in `s` are whitespace @@ -172,7 +168,7 @@ proc isSpaceAscii*(s: string): bool {.noSideEffect, procvar, return false proc isLowerAscii*(s: string): bool {.noSideEffect, procvar, - rtl, extern: "nsuIsLowerAsciiStr".}= + rtl, extern: "nsuIsLowerAsciiStr".} = ## Checks whether or not `s` contains all lower case characters. ## ## This checks ASCII characters only. @@ -187,7 +183,7 @@ proc isLowerAscii*(s: string): bool {.noSideEffect, procvar, true proc isUpperAscii*(s: string): bool {.noSideEffect, procvar, - rtl, extern: "nsuIsUpperAsciiStr".}= + rtl, extern: "nsuIsUpperAsciiStr".} = ## Checks whether or not `s` contains all upper case characters. ## ## This checks ASCII characters only. @@ -506,16 +502,15 @@ template splitCommon(s, sep, maxsplit, sepLen) = var last = 0 var splits = maxsplit - if len(s) > 0: - while last <= len(s): - var first = last - while last < len(s) and not stringHasSep(s, last, sep): - inc(last) - if splits == 0: last = len(s) - yield substr(s, first, last-1) - if splits == 0: break - dec(splits) - inc(last, sepLen) + while last <= len(s): + var first = last + while last < len(s) and not stringHasSep(s, last, sep): + inc(last) + if splits == 0: last = len(s) + yield substr(s, first, last-1) + if splits == 0: break + dec(splits) + inc(last, sepLen) template oldSplit(s, seps, maxsplit) = var last = 0 @@ -673,30 +668,29 @@ template rsplitCommon(s, sep, maxsplit, sepLen) = splits = maxsplit startPos = 0 - if len(s) > 0: - # go to -1 in order to get separators at the beginning - while first >= -1: - while first >= 0 and not stringHasSep(s, first, sep): - dec(first) + # go to -1 in order to get separators at the beginning + while first >= -1: + while first >= 0 and not stringHasSep(s, first, sep): + dec(first) - if splits == 0: - # No more splits means set first to the beginning - first = -1 + if splits == 0: + # No more splits means set first to the beginning + first = -1 - if first == -1: - startPos = 0 - else: - startPos = first + sepLen + if first == -1: + startPos = 0 + else: + startPos = first + sepLen - yield substr(s, startPos, last) + yield substr(s, startPos, last) - if splits == 0: - break + if splits == 0: + break - dec(splits) - dec(first) + dec(splits) + dec(first) - last = first + last = first iterator rsplit*(s: string, seps: set[char] = Whitespace, maxsplit: int = -1): string = @@ -824,12 +818,18 @@ proc split*(s: string, seps: set[char] = Whitespace, maxsplit: int = -1): seq[st noSideEffect, rtl, extern: "nsuSplitCharSet".} = ## The same as the `split iterator <#split.i,string,set[char],int>`_, but is a ## proc that returns a sequence of substrings. + runnableExamples: + doAssert "a,b;c".split({',', ';'}) == @["a", "b", "c"] + doAssert "".split({' '}) == @[""] accumulateResult(split(s, seps, maxsplit)) proc split*(s: string, sep: char, maxsplit: int = -1): seq[string] {.noSideEffect, rtl, extern: "nsuSplitChar".} = ## The same as the `split iterator <#split.i,string,char,int>`_, but is a proc ## that returns a sequence of substrings. + runnableExamples: + doAssert "a,b,c".split(',') == @["a", "b", "c"] + doAssert "".split(' ') == @[""] accumulateResult(split(s, sep, maxsplit)) proc split*(s: string, sep: string, maxsplit: int = -1): seq[string] {.noSideEffect, @@ -838,6 +838,13 @@ proc split*(s: string, sep: string, maxsplit: int = -1): seq[string] {.noSideEff ## ## Substrings are separated by the string `sep`. This is a wrapper around the ## `split iterator <#split.i,string,string,int>`_. + runnableExamples: + doAssert "a,b,c".split(",") == @["a", "b", "c"] + doAssert "a man a plan a canal panama".split("a ") == @["", "man ", "plan ", "canal panama"] + doAssert "".split("Elon Musk") == @[""] + doAssert "a largely spaced sentence".split(" ") == @["a", "", "largely", "", "", "", "spaced", "sentence"] + + doAssert "a largely spaced sentence".split(" ", maxsplit=1) == @["a", " largely spaced sentence"] doAssert(sep.len > 0) accumulateResult(split(s, sep, maxsplit)) @@ -906,6 +913,13 @@ proc rsplit*(s: string, sep: string, maxsplit: int = -1): seq[string] ## .. code-block:: nim ## @["Root#Object#Method", "Index"] ## + runnableExamples: + doAssert "a largely spaced sentence".rsplit(" ", maxsplit=1) == @["a largely spaced", "sentence"] + + doAssert "a,b,c".rsplit(",") == @["a", "b", "c"] + doAssert "a man a plan a canal panama".rsplit("a ") == @["", "man ", "plan ", "canal panama"] + doAssert "".rsplit("Elon Musk") == @[""] + doAssert "a largely spaced sentence".rsplit(" ") == @["a", "", "largely", "", "", "", "spaced", "sentence"] accumulateResult(rsplit(s, sep, maxsplit)) result.reverse() diff --git a/lib/pure/unicode.nim b/lib/pure/unicode.nim index 7d9c3108b..257c620f7 100644 --- a/lib/pure/unicode.nim +++ b/lib/pure/unicode.nim @@ -293,33 +293,33 @@ proc runeSubStr*(s: string, pos:int, len:int = int.high): string = if pos < 0: let (o, rl) = runeReverseOffset(s, -pos) if len >= rl: - result = s[o.. s.len-1] + result = s.substr(o, s.len-1) elif len < 0: let e = rl + len if e < 0: result = "" else: - result = s[o.. runeOffset(s, e-(rl+pos) , o)-1] + result = s.substr(o, runeOffset(s, e-(rl+pos) , o)-1) else: - result = s[o.. runeOffset(s, len, o)-1] + result = s.substr(o, runeOffset(s, len, o)-1) else: let o = runeOffset(s, pos) if o < 0: result = "" elif len == int.high: - result = s[o.. s.len-1] + result = s.substr(o, s.len-1) elif len < 0: let (e, rl) = runeReverseOffset(s, -len) discard rl if e <= 0: result = "" else: - result = s[o.. e-1] + result = s.substr(o, e-1) else: var e = runeOffset(s, len, o) if e < 0: e = s.len - result = s[o.. e-1] + result = s.substr(o, e-1) const alphaRanges = [ diff --git a/lib/system.nim b/lib/system.nim index 323ff00e6..b9f01c306 100644 --- a/lib/system.nim +++ b/lib/system.nim @@ -1439,7 +1439,11 @@ const ## is the value that should be passed to `quit <#quit>`_ to indicate ## failure. -var programResult* {.exportc: "nim_program_result".}: int +when defined(nodejs): + var programResult* {.importc: "process.exitCode".}: int + programResult = 0 +else: + var programResult* {.exportc: "nim_program_result".}: int ## modify this variable to specify the exit code of the program ## under normal circumstances. When the program is terminated ## prematurely using ``quit``, this value is ignored. @@ -3525,7 +3529,10 @@ when hasAlloc or defined(nimscript): ## .. code-block:: nim ## var s = "abcdef" ## assert s[1..3] == "bcd" - result = s.substr(s ^^ x.a, s ^^ x.b) + let a = s ^^ x.a + let L = (s ^^ x.b) - a + 1 + result = newString(L) + for i in 0 ..< L: result[i] = s[i + a] proc `[]=`*[T, U](s: var string, x: HSlice[T, U], b: string) = ## slice assignment for strings. If @@ -3752,6 +3759,7 @@ template assert*(cond: bool, msg = "") = ## that ``AssertionError`` is hidden from the effect system, so it doesn't ## produce ``{.raises: [AssertionError].}``. This exception is only supposed ## to be caught by unit testing frameworks. + ## ## The compiler may not generate any code at all for ``assert`` if it is ## advised to do so through the ``-d:release`` or ``--assertions:off`` ## `command line switches <nimc.html#command-line-switches>`_. @@ -4009,3 +4017,21 @@ when defined(nimHasRunnableExamples): else: template runnableExamples*(body: untyped) = discard + +template doAssertRaises*(exception, code: untyped): typed = + ## Raises ``AssertionError`` if specified ``code`` does not raise the + ## specified exception. + runnableExamples: + doAssertRaises(ValueError): + raise newException(ValueError, "Hello World") + + try: + block: + code + raiseAssert(astToStr(exception) & " wasn't raised by:\n" & astToStr(code)) + except exception: + discard + except Exception as exc: + raiseAssert(astToStr(exception) & + " wasn't raised, another error was raised instead by:\n"& + astToStr(code)) \ No newline at end of file |