diff options
Diffstat (limited to 'tests/stdlib/nre')
-rw-r--r-- | tests/stdlib/nre/captures.nim | 64 | ||||
-rw-r--r-- | tests/stdlib/nre/escape.nim | 7 | ||||
-rw-r--r-- | tests/stdlib/nre/find.nim | 41 | ||||
-rw-r--r-- | tests/stdlib/nre/init.nim | 36 | ||||
-rw-r--r-- | tests/stdlib/nre/match.nim | 18 | ||||
-rw-r--r-- | tests/stdlib/nre/misc.nim | 16 | ||||
-rw-r--r-- | tests/stdlib/nre/optional_nonstrict.nim | 3 | ||||
-rw-r--r-- | tests/stdlib/nre/replace.nim | 22 | ||||
-rw-r--r-- | tests/stdlib/nre/split.nim | 53 |
9 files changed, 260 insertions, 0 deletions
diff --git a/tests/stdlib/nre/captures.nim b/tests/stdlib/nre/captures.nim new file mode 100644 index 000000000..acc141baf --- /dev/null +++ b/tests/stdlib/nre/captures.nim @@ -0,0 +1,64 @@ +import unittest, optional_nonstrict +include nre + +block: # captures + block: # map capture names to numbers + check(getNameToNumberTable(re("(?<v1>1(?<v2>2(?<v3>3))(?'v4'4))()")) == + { "v1" : 0, "v2" : 1, "v3" : 2, "v4" : 3 }.toTable()) + + block: # capture bounds are correct + let ex1 = re("([0-9])") + check("1 23".find(ex1).matchBounds == 0 .. 0) + check("1 23".find(ex1).captureBounds[0] == 0 .. 0) + check("1 23".find(ex1, 1).matchBounds == 2 .. 2) + check("1 23".find(ex1, 3).matchBounds == 3 .. 3) + + let ex2 = re("()()()()()()()()()()([0-9])") + check("824".find(ex2).captureBounds[0] == 0 .. -1) + check("824".find(ex2).captureBounds[10] == 0 .. 0) + + let ex3 = re("([0-9]+)") + check("824".find(ex3).captureBounds[0] == 0 .. 2) + + block: # named captures + let ex1 = "foobar".find(re("(?<foo>foo)(?<bar>bar)")) + check(ex1.captures["foo"] == "foo") + check(ex1.captures["bar"] == "bar") + + let ex2 = "foo".find(re("(?<foo>foo)(?<bar>bar)?")) + check("foo" in ex2.captureBounds) + check(ex2.captures["foo"] == "foo") + check(not ("bar" in ex2.captures)) + expect KeyError: + discard ex2.captures["bar"] + + block: # named capture bounds + let ex1 = "foo".find(re("(?<foo>foo)(?<bar>bar)?")) + check("foo" in ex1.captureBounds) + check(ex1.captureBounds["foo"] == 0..2) + check(not ("bar" in ex1.captures)) + expect KeyError: + discard ex1.captures["bar"] + + block: # capture count + let ex1 = re("(?<foo>foo)(?<bar>bar)?") + check(ex1.captureCount == 2) + check(ex1.captureNameId == {"foo" : 0, "bar" : 1}.toTable()) + + block: # named capture table + let ex1 = "foo".find(re("(?<foo>foo)(?<bar>bar)?")) + check(ex1.captures.toTable == {"foo" : "foo"}.toTable()) + check(ex1.captureBounds.toTable == {"foo" : 0..2}.toTable()) + + let ex2 = "foobar".find(re("(?<foo>foo)(?<bar>bar)?")) + check(ex2.captures.toTable == {"foo" : "foo", "bar" : "bar"}.toTable()) + + block: # capture sequence + let ex1 = "foo".find(re("(?<foo>foo)(?<bar>bar)?")) + check(ex1.captures.toSeq == @[some("foo"), none(string)]) + check(ex1.captureBounds.toSeq == @[some(0..2), none(Slice[int])]) + check(ex1.captures.toSeq(some("")) == @[some("foo"), some("")]) + + let ex2 = "foobar".find(re("(?<foo>foo)(?<bar>bar)?")) + check(ex2.captures.toSeq == @[some("foo"), some("bar")]) + diff --git a/tests/stdlib/nre/escape.nim b/tests/stdlib/nre/escape.nim new file mode 100644 index 000000000..5e7dc0c0e --- /dev/null +++ b/tests/stdlib/nre/escape.nim @@ -0,0 +1,7 @@ +import nre, unittest + +block: # escape strings + block: # escape strings + check("123".escapeRe() == "123") + check("[]".escapeRe() == r"\[\]") + check("()".escapeRe() == r"\(\)") diff --git a/tests/stdlib/nre/find.nim b/tests/stdlib/nre/find.nim new file mode 100644 index 000000000..7e7555d73 --- /dev/null +++ b/tests/stdlib/nre/find.nim @@ -0,0 +1,41 @@ +import unittest, sequtils +import nre except toSeq +import optional_nonstrict +import times, strutils + +block: # find + block: # find text + check("3213a".find(re"[a-z]").match == "a") + check(toSeq(findIter("1 2 3 4 5 6 7 8 ", re" ")).map( + proc (a: RegexMatch): string = a.match + ) == @[" ", " ", " ", " ", " ", " ", " ", " "]) + + block: # find bounds + check(toSeq(findIter("1 2 3 4 5 ", re" ")).map( + proc (a: RegexMatch): Slice[int] = a.matchBounds + ) == @[1..1, 3..3, 5..5, 7..7, 9..9]) + + block: # overlapping find + check("222".findAll(re"22") == @["22"]) + check("2222".findAll(re"22") == @["22", "22"]) + + block: # len 0 find + check("".findAll(re"\ ") == newSeq[string]()) + check("".findAll(re"") == @[""]) + check("abc".findAll(re"") == @["", "", "", ""]) + check("word word".findAll(re"\b") == @["", "", "", ""]) + check("word\r\lword".findAll(re"(*ANYCRLF)(?m)$") == @["", ""]) + check("слово слово".findAll(re"(*U)\b") == @["", "", "", ""]) + + block: # bail early + ## we expect nothing to be found and we should be bailing out early which means that + ## the timing difference between searching in small and large data should be well + ## within a tolerance margin + const small = 10 + const large = 1000 + var smallData = repeat("url.sequence = \"http://whatever.com/jwhrejrhrjrhrjhrrjhrjrhrjrh\" ", small) + var largeData = repeat("url.sequence = \"http://whatever.com/jwhrejrhrjrhrjhrrjhrjrhrjrh\" ", large) + var expression = re"^url.* = "(.*?)"" + + check(smallData.findAll(expression) == newSeq[string]()) + check(largeData.findAll(expression) == newSeq[string]()) diff --git a/tests/stdlib/nre/init.nim b/tests/stdlib/nre/init.nim new file mode 100644 index 000000000..f0c8e0a00 --- /dev/null +++ b/tests/stdlib/nre/init.nim @@ -0,0 +1,36 @@ +import unittest +include nre + +block: # Test NRE initialization + block: # correct initialization + check(re("[0-9]+") != nil) + check(re("(?i)[0-9]+") != nil) + + block: # options + check(extractOptions("(*NEVER_UTF)") == + ("", pcre.NEVER_UTF, true)) + check(extractOptions("(*UTF8)(*ANCHORED)(*UCP)z") == + ("(*UTF8)(*UCP)z", pcre.ANCHORED, true)) + check(extractOptions("(*ANCHORED)(*UTF8)(*JAVASCRIPT_COMPAT)z") == + ("(*UTF8)z", pcre.ANCHORED or pcre.JAVASCRIPT_COMPAT, true)) + + check(extractOptions("(*NO_STUDY)(") == ("(", 0, false)) + + check(extractOptions("(*LIMIT_MATCH=6)(*ANCHORED)z") == + ("(*LIMIT_MATCH=6)z", pcre.ANCHORED, true)) + + block: # incorrect options + for s in ["CR", "(CR", "(*CR", "(*abc)", "(*abc)CR", + "(?i)", + "(*LIMIT_MATCH=5", "(*NO_AUTO_POSSESS=5)"]: + let ss = s & "(*NEVER_UTF)" + check(extractOptions(ss) == (ss, 0, true)) + + block: # invalid regex + expect(SyntaxError): discard re("[0-9") + try: + discard re("[0-9") + except SyntaxError: + let ex = SyntaxError(getCurrentException()) + check(ex.pos == 4) + check(ex.pattern == "[0-9") diff --git a/tests/stdlib/nre/match.nim b/tests/stdlib/nre/match.nim new file mode 100644 index 000000000..7e09a4b2f --- /dev/null +++ b/tests/stdlib/nre/match.nim @@ -0,0 +1,18 @@ +include nre, unittest, optional_nonstrict + +block: # match + block: # upper bound must be inclusive + check("abc".match(re"abc", endpos = -1) == none(RegexMatch)) + check("abc".match(re"abc", endpos = 1) == none(RegexMatch)) + check("abc".match(re"abc", endpos = 2) != none(RegexMatch)) + + block: # match examples + check("abc".match(re"(\w)").captures[0] == "a") + check("abc".match(re"(?<letter>\w)").captures["letter"] == "a") + check("abc".match(re"(\w)\w").captures[-1] == "ab") + check("abc".match(re"(\w)").captureBounds[0] == 0 .. 0) + check("abc".match(re"").captureBounds[-1] == 0 .. -1) + check("abc".match(re"abc").captureBounds[-1] == 0 .. 2) + + block: # match test cases + check("123".match(re"").matchBounds == 0 .. -1) diff --git a/tests/stdlib/nre/misc.nim b/tests/stdlib/nre/misc.nim new file mode 100644 index 000000000..b7df08ee9 --- /dev/null +++ b/tests/stdlib/nre/misc.nim @@ -0,0 +1,16 @@ +import unittest, nre, strutils, optional_nonstrict + +block: # Misc tests + block: # unicode + check("".find(re"(*UTF8)").match == "") + check("перевірка".replace(re"(*U)\w", "") == "") + + block: # empty or non-empty match + check("abc".findAll(re"|.").join(":") == ":a::b::c:") + check("abc".findAll(re".|").join(":") == "a:b:c:") + + check("abc".replace(re"|.", "x") == "xxxxxxx") + check("abc".replace(re".|", "x") == "xxxx") + + check("abc".split(re"|.").join(":") == ":::::") + check("abc".split(re".|").join(":") == ":::") diff --git a/tests/stdlib/nre/optional_nonstrict.nim b/tests/stdlib/nre/optional_nonstrict.nim new file mode 100644 index 000000000..d13f4fab7 --- /dev/null +++ b/tests/stdlib/nre/optional_nonstrict.nim @@ -0,0 +1,3 @@ +import options +converter option2val*[T](val: Option[T]): T = + return val.get() diff --git a/tests/stdlib/nre/replace.nim b/tests/stdlib/nre/replace.nim new file mode 100644 index 000000000..5cf659f21 --- /dev/null +++ b/tests/stdlib/nre/replace.nim @@ -0,0 +1,22 @@ +include nre +import unittest + +block: # replace + block: # replace with 0-length strings + check("".replace(re"1", proc (v: RegexMatch): string = "1") == "") + check(" ".replace(re"", proc (v: RegexMatch): string = "1") == "1 1") + check("".replace(re"", proc (v: RegexMatch): string = "1") == "1") + + block: # regular replace + check("123".replace(re"\d", "foo") == "foofoofoo") + check("123".replace(re"(\d)", "$1$1") == "112233") + check("123".replace(re"(\d)(\d)", "$1$2") == "123") + check("123".replace(re"(\d)(\d)", "$#$#") == "123") + check("123".replace(re"(?<foo>\d)(\d)", "$foo$#$#") == "1123") + check("123".replace(re"(?<foo>\d)(\d)", "${foo}$#$#") == "1123") + + block: # replacing missing captures should throw instead of segfaulting + expect IndexDefect: discard "ab".replace(re"(a)|(b)", "$1$2") + expect IndexDefect: discard "b".replace(re"(a)?(b)", "$1$2") + expect KeyError: discard "b".replace(re"(a)?", "${foo}") + expect KeyError: discard "b".replace(re"(?<foo>a)?", "${foo}") diff --git a/tests/stdlib/nre/split.nim b/tests/stdlib/nre/split.nim new file mode 100644 index 000000000..3cd57bb82 --- /dev/null +++ b/tests/stdlib/nre/split.nim @@ -0,0 +1,53 @@ +import unittest, strutils +include nre + +block: # string splitting + block: # splitting strings + check("1 2 3 4 5 6 ".split(re" ") == @["1", "2", "3", "4", "5", "6", ""]) + check("1 2 ".split(re(" ")) == @["1", "", "2", "", ""]) + check("1 2".split(re(" ")) == @["1", "2"]) + check("foo".split(re("foo")) == @["", ""]) + check("".split(re"foo") == @[""]) + check("9".split(re"\son\s") == @["9"]) + + block: # captured patterns + check("12".split(re"(\d)") == @["", "1", "", "2", ""]) + + block: # maxsplit + check("123".split(re"", maxsplit = 2) == @["1", "23"]) + check("123".split(re"", maxsplit = 1) == @["123"]) + check("123".split(re"", maxsplit = -1) == @["1", "2", "3"]) + + block: # split with 0-length match + check("12345".split(re("")) == @["1", "2", "3", "4", "5"]) + check("".split(re"") == newSeq[string]()) + check("word word".split(re"\b") == @["word", " ", "word"]) + check("word\r\lword".split(re"(*ANYCRLF)(?m)$") == @["word", "\r\lword"]) + check("слово слово".split(re"(*U)(\b)") == @["", "слово", "", " ", "", "слово", ""]) + + block: # perl split tests + check("forty-two" .split(re"") .join(",") == "f,o,r,t,y,-,t,w,o") + check("forty-two" .split(re"", 3) .join(",") == "f,o,rty-two") + check("split this string" .split(re" ") .join(",") == "split,this,string") + check("split this string" .split(re" ", 2) .join(",") == "split,this string") + check("try$this$string" .split(re"\$") .join(",") == "try,this,string") + check("try$this$string" .split(re"\$", 2) .join(",") == "try,this$string") + check("comma, separated, values" .split(re", ") .join("|") == "comma|separated|values") + check("comma, separated, values" .split(re", ", 2) .join("|") == "comma|separated, values") + check("Perl6::Camelia::Test" .split(re"::") .join(",") == "Perl6,Camelia,Test") + check("Perl6::Camelia::Test" .split(re"::", 2) .join(",") == "Perl6,Camelia::Test") + check("split,me,please" .split(re",") .join("|") == "split|me|please") + check("split,me,please" .split(re",", 2) .join("|") == "split|me,please") + check("Hello World Goodbye Mars".split(re"\s+") .join(",") == "Hello,World,Goodbye,Mars") + check("Hello World Goodbye Mars".split(re"\s+", 3).join(",") == "Hello,World,Goodbye Mars") + check("Hello test" .split(re"(\s+)") .join(",") == "Hello, ,test") + check("this will be split" .split(re" ") .join(",") == "this,will,be,split") + check("this will be split" .split(re" ", 3) .join(",") == "this,will,be split") + check("a.b" .split(re"\.") .join(",") == "a,b") + check("" .split(re"") .len == 0) + check(":" .split(re"") .len == 1) + + block: # start position + check("abc".split(re"", start = 1) == @["b", "c"]) + check("abc".split(re"", start = 2) == @["c"]) + check("abc".split(re"", start = 3) == newSeq[string]()) |