-
Notifications
You must be signed in to change notification settings - Fork 1
/
ByteString.hs
184 lines (145 loc) · 8.41 KB
/
ByteString.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings #-}
module ByteString where
import Control.Lens
import Control.Lens.Regex.ByteString
import qualified Data.ByteString.Char8 as C8 hiding (index)
import Data.Char
import qualified Data.Map as M
import Test.Hspec
spec :: Spec
spec = do
describe "regex" $ do
xdescribe "pcre-heavy-compat" $ do
it "should handle crazy nested groups" $ do
"abcdefhijklm" ^? [regex|^(?:a(b(c)))(?:d(e(f)))(?:h(i(j)))(?:k(l(m)))$|] . matchAndGroups
`shouldBe` Just ("abcdefhijklm", ["bc", "c", "ef", "f", "ij", "j", "lm", "m"])
describe "match" $ do
describe "getting" $ do
it "should find one match" $ do
"abc" ^.. [regex|b|] . match
`shouldBe` ["b"]
it "should find many matches" $ do
"a b c" ^.. [regex|\w|] . match
`shouldBe` ["a", "b", "c"]
it "should fold" $ do
"a b c" ^. [regex|\w|] . match
`shouldBe` "abc"
it "should match with a group" $ do
"a b c" ^.. [regex|(\w)|] . match
`shouldBe` ["a", "b", "c"]
it "should match with many groups" $ do
"a b c" ^.. [regex|(\w) (\w)|] . match
`shouldBe` ["a b"]
it "should be greedy when overlapping" $ do
"abc" ^.. [regex|\w+|] . match
`shouldBe`["abc"]
it "should respect lazy modifiers" $ do
"abc" ^.. [regex|\w+?|] . match
`shouldBe`["a", "b", "c"]
describe "setting" $ do
it "should allow setting" $ do
("one two three" & [regex|two|] . match .~ "new")
`shouldBe` "one new three"
it "should allow setting many" $ do
("one <two> three" & [regex|\w+|] . match .~ "new")
`shouldBe` "new <new> new"
it "should allow mutating" $ do
("one two three" & [regex|two|] . match %~ (<> "!!"). C8.map toUpper)
`shouldBe` "one TWO!! three"
it "should allow mutating many" $ do
("one two three" & [regex|two|] . match %~ C8.map toUpper)
`shouldBe` "one TWO three"
describe "indexed" $ do
it "should allow folding with index" $ do
("one two three" ^.. ([regex|\w+|] <. match) . withIndex)
`shouldBe` [(0, "one"), (1, "two"), (2, "three")]
it "should allow getting with index" $ do
("one two three" ^.. [regex|\w+|] . index 1 . match)
`shouldBe` ["two"]
it "should allow setting with index" $ do
("one two three" & [regex|\w+|] <. match .@~ C8.pack . show)
`shouldBe` "0 1 2"
it "should allow mutating with index" $ do
("one two three" & [regex|\w+|] <. match %@~ \i s -> (C8.pack $ show i) <> ": " <> s)
`shouldBe` "0: one 1: two 2: three"
describe "groups" $ do
describe "getting" $ do
it "should get groups" $ do
"a b c" ^.. [regex|(\w)|] . groups
`shouldBe` [["a"], ["b"], ["c"]]
it "should get multiple groups" $ do
"raindrops on roses and whiskers on kittens" ^.. [regex|(\w+) on (\w+)|] . groups
`shouldBe` [["raindrops","roses"],["whiskers","kittens"]]
it "should allow getting a specific index" $ do
("one two three four" ^.. [regex|(\w+) (\w+)|] . groups . ix 1)
`shouldBe` ["two", "four"]
it "should handle weird group alternation" $ do
("AB" ^.. [regex|A(x)?(B)|] . groups `shouldBe` [["", "B"]])
("B" ^.. [regex|(A)|(B)|] . groups `shouldBe` [["", "B"]])
-- This behaviour is consistent with pcre-heavy
("A" ^.. [regex|(A)|(B)|] . groups `shouldBe` [["A"]])
describe "setting" $ do
it "should allow setting groups as a list" $ do
("one two three" & [regex|(\w+) (\w+)|] . groups .~ ["1", "2"])
`shouldBe` "1 2 three"
it "should allow editing when result list is the same length" $ do
("raindrops on roses and whiskers on kittens" & [regex|(\w+) on (\w+)|] . groups %~ reverse)
`shouldBe` "roses on raindrops and kittens on whiskers"
describe "group" $ do
it "should get a single group" $ do
"a:b c:d" ^.. [regex|(\w):(\w)|] . group 1
`shouldBe` ["b", "d"]
it "should set a single group" $ do
"a:b c:d" & [regex|(\w):(\w)|] . group 1 %~ C8.map toUpper
`shouldBe` "a:B c:D"
describe "traversed" $ do
it "should allow setting all group matches" $ do
("one two three" & [regex|(\w+) (\w+)|] . groups . traversed .~ "new")
`shouldBe` "new new three"
it "should allow mutating" $ do
("one two three four" & [regex|one (two) (three)|] . groups . traversed %~ (<> "!!") . C8.map toUpper)
`shouldBe` "one TWO!! THREE!! four"
it "should allow folding with index" $ do
("one two three four" ^.. [regex|(\w+) (\w+)|] . groups . traversed . withIndex)
`shouldBe` [(0, "one"), (1, "two"), (0, "three"), (1, "four")]
it "should allow setting with index" $ do
("one two three four" & [regex|(\w+) (\w+)|] . groups . traversed .@~ C8.pack . show)
`shouldBe` "0 1 0 1"
it "should allow mutating with index" $ do
("one two three four" & [regex|(\w+) (\w+)|] . groups . traversed %@~ \i s -> (C8.pack $ show i) <> ": " <> s)
`shouldBe` "0: one 1: two 0: three 1: four"
it "should compose indices with matches" $ do
("one two three four" ^.. ([regex|(\w+) (\w+)|] <.> groups . traversed) . withIndex)
`shouldBe` [((0, 0), "one"), ((0, 1), "two"), ((1, 0), "three"), ((1, 1), "four")]
describe "namedGroups" $ do
describe "getting" $ do
it "should get named groups" $ do
"a b c" ^.. [regex|(?<mygroup>\w)|] . namedGroups
`shouldBe` [M.fromList [("mygroup", "a")], M.fromList [("mygroup", "b")], M.fromList [("mygroup", "c")]]
it "should get multiple named groups" $ do
"raindrops on roses and whiskers on kittens" ^.. [regex|(?<one>\w+) on (?<two>\w+)|] . namedGroups
`shouldBe` [M.fromList [("one", "raindrops"), ("two", "roses")], M.fromList [("one", "whiskers"), ("two", "kittens")]]
it "should allow getting a specific named group" $ do
("raindrops on roses and whiskers on kittens" ^.. [regex|(?<one>\w+) on (?<two>\w+)|] . namedGroups . ix "two")
`shouldBe` ["roses", "kittens"]
it "should handle weird group alternation" $ do
("AB" ^.. [regex|A(?<opt>x)?(?<always>B)|] . namedGroups `shouldBe` [M.fromList [("opt", ""), ("always", "B")]])
("B" ^.. [regex|(?<a>A)|(?<b>B)|] . namedGroups `shouldBe` [M.fromList [("a", ""), ("b", "B")]])
-- This is the behaviour of pcre-heavy, it's a bit unfortunate
("A" ^.. [regex|(?<a>A)|(?<b>B)|] . namedGroups `shouldBe` [M.fromList [("a", "A")]])
describe "setting" $ do
it "should allow setting groups as a map" $ do
("one two three" & [regex|(?<a>\w+) (?<b>\w+)|] . namedGroups .~ M.fromList [("a", "1"), ("b", "2")])
`shouldBe` "1 2 three"
describe "namedGroup" $ do
it "should get a single named group" $ do
"a:b c:d" ^.. [regex|(?<before>\w):(?<after>\w)|] . namedGroup "after"
`shouldBe` ["b", "d"]
it "should set a single group" $ do
"a:b c:d" & [regex|(\w):(?<after>\w)|] . namedGroup "after" %~ C8.map toUpper
`shouldBe` "a:B c:D"
describe "matchAndGroups" $ do
it "should get match and groups" $ do
"raindrops on roses and whiskers on kittens" ^.. [regex|(\w+) on (\w+)|] . matchAndGroups
`shouldBe` [("raindrops on roses",["raindrops","roses"]),("whiskers on kittens",["whiskers","kittens"])]