]> gitweb.michael.orlitzky.com - dead/harbl.git/blob - src/IPv4Pattern.hs
Add more documentation and a pretty-printer to IPv4Pattern.
[dead/harbl.git] / src / IPv4Pattern.hs
1 {-# LANGUAGE FlexibleInstances #-}
2
3 -- | An IPv4 address pattern has four fields separated by ".". Each
4 -- field is either a decimal number, or a sequence inside "[]" that
5 -- contains one or more ";"-separated decimal numbers or
6 -- number..number ranges.
7 --
8 -- Thus, any pattern field can be a sequence inside "[]", but a "[]"
9 -- sequence cannot span multiple address fields, and a pattern field
10 -- cannot contain both a number and a "[]" sequence at the same
11 -- time.
12 --
13 -- This means that the pattern 1.2.[3.4] is not valid (the sequence
14 -- [3.4] cannot span two address fields) and the pattern
15 -- 1.2.3.3[6..9] is also not valid (the last field cannot be both
16 -- number 3 and sequence [6..9] at the same time).
17 --
18 -- The syntax for IPv4 patterns is as follows:
19 --
20 -- v4pattern = v4field "." v4field "." v4field "." v4field
21 -- v4field = v4octet | "[" v4sequence "]"
22 -- v4octet = any decimal number in the range 0 through 255
23 -- v4sequence = v4seq_member | v4sequence ";" v4seq_member
24 -- v4seq_member = v4octet | v4octet ".." v4octet
25 --
26 module IPv4Pattern
27 where
28
29 import Test.Tasty ( TestTree, testGroup )
30 import Test.Tasty.HUnit ( (@?=), testCase )
31 import Text.Parsec
32 import Text.Parsec.String ( Parser )
33 import Text.Read ( readMaybe )
34
35
36 class Pretty a where
37 -- | Obtain a pretty 'String' representation of the given thingy.
38 prettyshow :: a -> String
39
40 -- | Pretty-print the given thingy.
41 pp :: a -> IO ()
42 pp = putStrLn . prettyshow
43
44
45 -- | Define a 'Pretty' instance for the result of 'parse'. This lets
46 -- us pretty-print the result of a parse attempt without worrying
47 -- about whether or not it failed. If the parse failed, you get the
48 -- same output that you usually would. Otherwise we pretty-print the
49 -- parsed value.
50 --
51 instance Pretty a => Pretty (Either ParseError a) where
52 prettyshow (Left err) = show err
53 prettyshow (Right v) = prettyshow v
54
55
56 -- * Octets
57
58 -- | An ipv4 octet; that is, an integer between @0@ and @255@
59 -- inclusive. This is the data type corresponding to a \"v4octet\"
60 -- in the postscreen parser.
61 --
62 newtype IPv4Octet = IPv4Octet Int
63 deriving (Eq, Show)
64
65
66 instance Pretty IPv4Octet where
67 prettyshow (IPv4Octet x) = show x
68
69
70 -- | Parse an IPv4 octet, which should contain a string of digits.
71 -- Should fail if the parsed integer does not lie between @0@ and
72 -- @255@ inclusive.
73 --
74 -- ==== _Examples_
75 --
76 -- Standard octets are parsed correctly:
77 --
78 -- >>> parseTest v4octet "0"
79 -- IPv4Octet 0
80 --
81 -- >>> parseTest v4octet "127"
82 -- IPv4Octet 127
83 --
84 -- >>> parseTest v4octet "255"
85 -- IPv4Octet 255
86 --
87 -- Non-digit input throws an error:
88 --
89 -- >>> parseTest v4octet "Hello, World!"
90 -- parse error at (line 1, column 1):
91 -- unexpected "H"
92 -- expecting digit
93 --
94 -- If we're given an integer outside the range @0..255@ (i.e. not a
95 -- valid octet), we fail:
96 --
97 -- >>> parseTest v4octet "9000"
98 -- parse error at (line 1, column 5):
99 -- unexpected end of input
100 -- expecting digit
101 -- Octet "9000" must be between 0 and 255.
102 --
103 v4octet :: Parser IPv4Octet
104 v4octet = do
105 s <- many1 digit
106 case ( readMaybe s :: Maybe Int ) of
107 -- If "many1 digit" gives us a list of digits, we should be able
108 -- to convert that to an Int! It will overflow rather than fail
109 -- if the input is too big/small, so it should really always
110 -- succeed.
111 Nothing -> unexpected "readMaybe failed on a sequence of digits!"
112
113 -- If we got an Int, make sure it's actually a representation of
114 -- an octet.
115 Just k -> if 0 <= k && k <= 255
116 then return (IPv4Octet k)
117 else fail ("Octet \"" ++ (show k)
118 ++ "\" must be between 0 and 255.")
119
120
121
122
123 -- * Sequence members
124
125
126 -- | An ipv4 \"sequence member\". A sequence member is either an
127 -- integer (an octet) or a range of integers (contained in an
128 -- octet). This data type corresponds to \"v4seq_member\" in the
129 -- postscreen parser.
130 --
131 data IPv4SequenceMember =
132 IPv4SequenceMemberOctet IPv4Octet
133 | IPv4SequenceMemberOctetRange IPv4Octet IPv4Octet
134 deriving (Eq, Show)
135
136
137 instance Pretty IPv4SequenceMember where
138 prettyshow (IPv4SequenceMemberOctet octet) = prettyshow octet
139 prettyshow (IPv4SequenceMemberOctetRange octet1 octet2) =
140 (prettyshow octet1) ++ ".." ++ (prettyshow octet2)
141
142
143 -- | Parse an IPv4 \"sequence member\". A sequence member is either an
144 -- octet, or a start..end sequence (like an enumeration, in Haskell).
145 --
146 -- ==== _Examples_
147 --
148 -- >>> parseTest v4seq_member "127"
149 -- IPv4SequenceMemberOctet (IPv4Octet 127)
150 --
151 -- >>> parseTest v4seq_member "1..5"
152 -- IPv4SequenceMemberOctetRange (IPv4Octet 1) (IPv4Octet 5)
153 --
154 v4seq_member :: Parser IPv4SequenceMember
155 v4seq_member = try both <|> just_one
156 where
157 both = do
158 oct1 <- v4octet
159 _ <- string ".."
160 oct2 <- v4octet
161 return $ IPv4SequenceMemberOctetRange oct1 oct2
162
163 just_one = fmap IPv4SequenceMemberOctet v4octet
164
165
166
167 -- * Sequences
168
169 -- | An ipv4 \"sequence\". A sequence contains either a single
170 -- \"sequence member\" (see 'IPv4SequenceMember'), or a sequence
171 -- member along with another sequence. So, this is a potentially
172 -- recursive definition. This type corresponds to \"v4sequence\" in
173 -- the postscreen parser.
174 --
175 data IPv4Sequence =
176 IPv4SequenceSingleMember IPv4SequenceMember
177 | IPv4SequenceOptions IPv4SequenceMember IPv4Sequence
178 deriving (Eq, Show)
179
180
181 instance Pretty IPv4Sequence where
182 prettyshow (IPv4SequenceSingleMember member) = prettyshow member
183 prettyshow (IPv4SequenceOptions member subsequence) =
184 (prettyshow member) ++ ";" ++ (prettyshow subsequence)
185
186
187 -- | Parse an IPv4 \"sequence\". A sequence is whatever is allowed
188 -- within square brackets. Basically it can be three things:
189 --
190 -- * An octet (number).
191 -- * A range of addresses in start..end format.
192 -- * An alternative, separated by a semicolon, where each side
193 -- contains one of the previous two options.
194 --
195 -- ==== _Examples_
196 --
197 -- >>> parseTest v4sequence "1"
198 -- IPv4SequenceSingleMember (IPv4SequenceMemberOctet (IPv4Octet 1))
199 --
200 -- >>> pp $ parse v4sequence "" "1..2"
201 -- 1..2
202 --
203 -- >>> pp $ parse v4sequence "" "1..2;8"
204 -- 1..2;8
205 --
206 v4sequence :: Parser IPv4Sequence
207 v4sequence = try both <|> just_one -- Maybe sepBy is appropriate here?
208 where
209 both = do
210 sm <- v4seq_member
211 _ <- char ';'
212 s <- v4sequence
213 return $ IPv4SequenceOptions sm s
214
215 just_one = fmap IPv4SequenceSingleMember v4seq_member
216
217
218
219 -- * Fields
220
221 data IPv4Field = IPv4FieldOctet IPv4Octet | IPv4FieldSequence IPv4Sequence
222 deriving (Eq, Show)
223
224
225 instance Pretty IPv4Field where
226 prettyshow (IPv4FieldOctet octet) = prettyshow octet
227 prettyshow (IPv4FieldSequence seq) = "[" ++ (prettyshow seq) ++ "]"
228
229
230 -- | Parse an IPv4 \"field\", which is either a boring old octet, or a
231 -- 'v4sequence' within square brackets.
232 --
233 -- ==== _Examples_
234 --
235 -- >>> parseTest v4field "127"
236 -- IPv4FieldOctet (IPv4Octet 127)
237 --
238 -- >>> pp $ parse v4field "" "[127]"
239 -- [127]
240 --
241 v4field :: Parser IPv4Field
242 v4field = just_octet <|> brackets
243 where
244 just_octet = fmap IPv4FieldOctet v4octet
245
246 brackets = do
247 _ <- char '['
248 s <- v4sequence
249 _ <- char ']'
250 return $ IPv4FieldSequence s
251
252
253
254 -- * Patterns
255
256 data IPv4Pattern =
257 IPv4Pattern IPv4Field IPv4Field IPv4Field IPv4Field
258 deriving (Eq, Show)
259
260
261 instance Pretty IPv4Pattern where
262 prettyshow (IPv4Pattern f1 f2 f3 f4) =
263 (prettyshow f1) ++ "."
264 ++ (prettyshow f2)
265 ++ "."
266 ++ (prettyshow f3)
267 ++ "."
268 ++ (prettyshow f4)
269
270
271 -- | Parse an ipv4 address pattern. This consists of four fields,
272 -- separated by periods, where a field is either a simple octet or a
273 -- sequence.
274 --
275 -- See also: 'v4field', 'v4sequence'.
276 --
277 -- ==== _Examples_
278 --
279 -- >>> pp $ parse v4pattern "" "127.0.0.1"
280 -- 127.0.0.1
281 --
282 -- >>> pp $ parse v4pattern "" "127.0.[1..3].1"
283 -- 127.0.[1..3].1
284 --
285 -- >>> pp $ parse v4pattern "" "127.0.[1..3;8].1"
286 -- 127.0.[1..3;8].1
287 --
288 -- In the module intro, it is mentioned that this is invalid:
289 --
290 -- >>> parseTest v4pattern "1.2.[3.4]"
291 -- parse error at (line 1, column 7):
292 -- unexpected "."
293 -- expecting digit or "]"
294 --
295 -- This one is /also/ invalid; however, we'll parse the valid part off
296 -- the front of it:
297 --
298 -- >>> pp $ parse v4pattern "" "1.2.3.3[6..9]"
299 -- 1.2.3.3
300 --
301 v4pattern :: Parser IPv4Pattern
302 v4pattern = do
303 field1 <- v4field
304 _ <- char '.'
305 field2 <- v4field
306 _ <- char '.'
307 field3 <- v4field
308 _ <- char '.'
309 field4 <- v4field
310 return $ IPv4Pattern field1 field2 field3 field4
311
312
313
314 -- * Enumeration
315
316 -- | Enumerate the members of an 'IPv4SequenceMember'. A sequence
317 -- member is either an octet, which is easy to enumerate -- we just
318 -- print it -- or an octet range whose members can be enumerated
319 -- from least to greatest.
320 --
321 -- We enumerate strings instead of integers because the big picture
322 -- is that we will be listing out patterns of ipv4 addresses, and
323 -- those are represented as strings (dotted quad format).
324 --
325 -- ==== _Examples_
326 --
327 -- >>> let (Right r) = parse v4seq_member "" "127"
328 -- >>> sequence_members r
329 -- ["127"]
330 --
331 -- >>> let (Right r) = parse v4seq_member "" "127..135"
332 -- >>> sequence_members r
333 -- ["127","128","129","130","131","132","133","134","135"]
334 --
335 sequence_members :: IPv4SequenceMember -> [String]
336 sequence_members (IPv4SequenceMemberOctet (IPv4Octet i)) = [show i]
337 sequence_members (IPv4SequenceMemberOctetRange (IPv4Octet s) (IPv4Octet t)) =
338 [show x | x <- [s .. t]]
339
340
341 -- | Enumerate the members of an ipv4 sequence. These consist of
342 -- either a single sequence member (in which case we delegate to
343 -- 'sequence_members'), or an \"option\" which is enumerated
344 -- recursively.
345 --
346 -- ==== _Examples_
347 --
348 -- >>> let (Right r) = parse v4sequence "" "1"
349 -- >>> sequences r
350 -- ["1"]
351 --
352 -- >>> let (Right r) = parse v4sequence "" "1..2"
353 -- >>> sequences r
354 -- ["1","2"]
355 --
356 -- >>> let (Right r) = parse v4sequence "" "1..3;4;5..9"
357 -- >>> sequences r
358 -- ["1","2","3","4","5","6","7","8","9"]
359 --
360 sequences :: IPv4Sequence -> [String]
361 sequences (IPv4SequenceSingleMember sm) =
362 sequence_members sm
363 sequences (IPv4SequenceOptions sm s) =
364 (sequence_members sm) ++ (sequences s)
365
366
367 -- | Enumerate the members of an 'IPv4Field'. If the field contains a
368 -- single 'IPv4Octet', we simply 'show' it. Otherwise it contains an
369 -- 'IPv4FieldSequence', and we enumerate that recursively using
370 -- 'sequences'.
371 --
372 -- ==== _Examples_
373 --
374 -- >>> let (Right r) = parse v4field "" "1"
375 -- >>> fields r
376 -- ["1"]
377 --
378 -- >>> let (Right r) = parse v4field "" "[127..135]"
379 -- >>> fields r
380 -- ["127","128","129","130","131","132","133","134","135"]
381 --
382 fields :: IPv4Field -> [String]
383 fields (IPv4FieldOctet (IPv4Octet i)) = [show i]
384 fields (IPv4FieldSequence s) = sequences s
385
386
387 -- | Enumerate the addresses represented by a given 'IPv4Pattern'.
388 --
389 -- A pattern contains four fields, sepearated by period
390 -- characters. We want to list all possible combinations of
391 -- addresses where the first octet comes from the first field, the
392 -- second octet comes from the second field... and so on. To do
393 -- this, we take advantage of the List monad and the fact that
394 -- 'fields' returns a list of 'String's.
395 --
396 -- ==== _Examples_
397 --
398 -- A single address:
399 --
400 -- >>> let (Right r) = parse v4pattern "" "127.0.0.1"
401 -- >>> addresses r
402 -- ["127.0.0.1"]
403 --
404 -- Anything between 127.0.0.2 and 127.0.0.4, and either 127.0.0.10
405 -- or 127.0.0.11:
406 --
407 -- >>> let (Right r) = parse v4pattern "" "127.0.0.[2..4;10;11]"
408 -- >>> addresses r
409 -- ["127.0.0.2","127.0.0.3","127.0.0.4","127.0.0.10","127.0.0.11"]
410 --
411 addresses :: IPv4Pattern -> [String]
412 addresses (IPv4Pattern field1 field2 field3 field4) = do
413 f1 <- fields field1
414 f2 <- fields field2
415 f3 <- fields field3
416 f4 <- fields field4
417 return $ f1 ++ "." ++ f2 ++ "." ++ f3 ++ "." ++ f4
418
419
420
421 -- * Tests
422
423 v4octet_tests :: TestTree
424 v4octet_tests =
425 testGroup
426 "v4octet tests"
427 [ test_v4octet_single_digit_parsed ]
428
429 test_v4octet_single_digit_parsed :: TestTree
430 test_v4octet_single_digit_parsed =
431 testCase "a single digit is parsed as a v4octet" $ do
432 -- Whatever, it's a test.
433 let (Right actual) = parse v4octet "" "1"
434 let expected = IPv4Octet 1
435 actual @?= expected