X-Git-Url: http://gitweb.michael.orlitzky.com/?p=dead%2Fharbl.git;a=blobdiff_plain;f=src%2FIPv4Pattern.hs;h=8c605ff97cbfb8881301298897da51b88bb8edae;hp=55403205aa3996914b1b4d9314f68636434ad1c6;hb=3beaa57bb0853ef3ab417a3f1bbbcddc2589cee4;hpb=9c0dbbefd192b1fe55181c33f7052c978d18cd38 diff --git a/src/IPv4Pattern.hs b/src/IPv4Pattern.hs index 5540320..8c605ff 100644 --- a/src/IPv4Pattern.hs +++ b/src/IPv4Pattern.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE FlexibleInstances #-} - -- | An IPv4 address pattern has four fields separated by ".". Each -- field is either a decimal number, or a sequence inside "[]" that -- contains one or more ";"-separated decimal numbers or @@ -23,34 +21,29 @@ -- v4sequence = v4seq_member | v4sequence ";" v4seq_member -- v4seq_member = v4octet | v4octet ".." v4octet -- -module IPv4Pattern +module IPv4Pattern ( + IPv4Pattern, + addresses, + ipv4pattern_tests, + v4pattern) where + import Test.Tasty ( TestTree, testGroup ) import Test.Tasty.HUnit ( (@?=), testCase ) -import Text.Parsec +import Text.Parsec ( + (<|>), + char, + digit, + many1, + parse, + string, + try, + unexpected ) import Text.Parsec.String ( Parser ) import Text.Read ( readMaybe ) - -class Pretty a where - -- | Obtain a pretty 'String' representation of the given thingy. - prettyshow :: a -> String - - -- | Pretty-print the given thingy. - pp :: a -> IO () - pp = putStrLn . prettyshow - - --- | Define a 'Pretty' instance for the result of 'parse'. This lets --- us pretty-print the result of a parse attempt without worrying --- about whether or not it failed. If the parse failed, you get the --- same output that you usually would. Otherwise we pretty-print the --- parsed value. --- -instance Pretty a => Pretty (Either ParseError a) where - prettyshow (Left err) = show err - prettyshow (Right v) = prettyshow v +import Pretty ( Pretty(..) ) -- * Octets @@ -64,7 +57,7 @@ newtype IPv4Octet = IPv4Octet Int instance Pretty IPv4Octet where - prettyshow (IPv4Octet x) = show x + pretty_show (IPv4Octet x) = show x -- | Parse an IPv4 octet, which should contain a string of digits. @@ -73,6 +66,8 @@ instance Pretty IPv4Octet where -- -- ==== _Examples_ -- +-- >>> import Text.Parsec ( parseTest ) +-- -- Standard octets are parsed correctly: -- -- >>> parseTest v4octet "0" @@ -108,7 +103,7 @@ v4octet = do -- to convert that to an Int! It will overflow rather than fail -- if the input is too big/small, so it should really always -- succeed. - Nothing -> unexpected "readMaybe failed on a sequence of digits!" + Nothing -> unexpected "v4octet: readMaybe failed on a sequence of digits!" -- If we got an Int, make sure it's actually a representation of -- an octet. @@ -135,9 +130,9 @@ data IPv4SequenceMember = instance Pretty IPv4SequenceMember where - prettyshow (IPv4SequenceMemberOctet octet) = prettyshow octet - prettyshow (IPv4SequenceMemberOctetRange octet1 octet2) = - (prettyshow octet1) ++ ".." ++ (prettyshow octet2) + pretty_show (IPv4SequenceMemberOctet octet) = pretty_show octet + pretty_show (IPv4SequenceMemberOctetRange octet1 octet2) = + (pretty_show octet1) ++ ".." ++ (pretty_show octet2) -- | Parse an IPv4 \"sequence member\". A sequence member is either an @@ -145,6 +140,8 @@ instance Pretty IPv4SequenceMember where -- -- ==== _Examples_ -- +-- >>> import Text.Parsec ( parseTest ) +-- -- >>> parseTest v4seq_member "127" -- IPv4SequenceMemberOctet (IPv4Octet 127) -- @@ -179,9 +176,9 @@ data IPv4Sequence = instance Pretty IPv4Sequence where - prettyshow (IPv4SequenceSingleMember member) = prettyshow member - prettyshow (IPv4SequenceOptions member subsequence) = - (prettyshow member) ++ ";" ++ (prettyshow subsequence) + pretty_show (IPv4SequenceSingleMember member) = pretty_show member + pretty_show (IPv4SequenceOptions member subsequence) = + (pretty_show member) ++ ";" ++ (pretty_show subsequence) -- | Parse an IPv4 \"sequence\". A sequence is whatever is allowed @@ -194,17 +191,18 @@ instance Pretty IPv4Sequence where -- -- ==== _Examples_ -- +-- >>> import Text.Parsec ( parseTest ) -- >>> parseTest v4sequence "1" -- IPv4SequenceSingleMember (IPv4SequenceMemberOctet (IPv4Octet 1)) -- --- >>> pp $ parse v4sequence "" "1..2" +-- >>> pretty_print $ parse v4sequence "" "1..2" -- 1..2 -- --- >>> pp $ parse v4sequence "" "1..2;8" +-- >>> pretty_print $ parse v4sequence "" "1..2;8" -- 1..2;8 -- v4sequence :: Parser IPv4Sequence -v4sequence = try both <|> just_one -- Maybe sepBy is appropriate here? +v4sequence = try both <|> just_one where both = do sm <- v4seq_member @@ -223,8 +221,8 @@ data IPv4Field = IPv4FieldOctet IPv4Octet | IPv4FieldSequence IPv4Sequence instance Pretty IPv4Field where - prettyshow (IPv4FieldOctet octet) = prettyshow octet - prettyshow (IPv4FieldSequence seq) = "[" ++ (prettyshow seq) ++ "]" + pretty_show (IPv4FieldOctet octet) = pretty_show octet + pretty_show (IPv4FieldSequence s) = "[" ++ (pretty_show s) ++ "]" -- | Parse an IPv4 \"field\", which is either a boring old octet, or a @@ -232,10 +230,11 @@ instance Pretty IPv4Field where -- -- ==== _Examples_ -- +-- >>> import Text.Parsec ( parseTest ) -- >>> parseTest v4field "127" -- IPv4FieldOctet (IPv4Octet 127) -- --- >>> pp $ parse v4field "" "[127]" +-- >>> pretty_print $ parse v4field "" "[127]" -- [127] -- v4field :: Parser IPv4Field @@ -259,13 +258,13 @@ data IPv4Pattern = instance Pretty IPv4Pattern where - prettyshow (IPv4Pattern f1 f2 f3 f4) = - (prettyshow f1) ++ "." - ++ (prettyshow f2) + pretty_show (IPv4Pattern f1 f2 f3 f4) = + (pretty_show f1) ++ "." + ++ (pretty_show f2) ++ "." - ++ (prettyshow f3) + ++ (pretty_show f3) ++ "." - ++ (prettyshow f4) + ++ (pretty_show f4) -- | Parse an ipv4 address pattern. This consists of four fields, @@ -276,17 +275,18 @@ instance Pretty IPv4Pattern where -- -- ==== _Examples_ -- --- >>> pp $ parse v4pattern "" "127.0.0.1" +-- >>> pretty_print $ parse v4pattern "" "127.0.0.1" -- 127.0.0.1 -- --- >>> pp $ parse v4pattern "" "127.0.[1..3].1" +-- >>> pretty_print $ parse v4pattern "" "127.0.[1..3].1" -- 127.0.[1..3].1 -- --- >>> pp $ parse v4pattern "" "127.0.[1..3;8].1" +-- >>> pretty_print $ parse v4pattern "" "127.0.[1..3;8].1" -- 127.0.[1..3;8].1 -- -- In the module intro, it is mentioned that this is invalid: -- +-- >>> import Text.Parsec ( parseTest ) -- >>> parseTest v4pattern "1.2.[3.4]" -- parse error at (line 1, column 7): -- unexpected "." @@ -295,7 +295,7 @@ instance Pretty IPv4Pattern where -- This one is /also/ invalid; however, we'll parse the valid part off -- the front of it: -- --- >>> pp $ parse v4pattern "" "1.2.3.3[6..9]" +-- >>> pretty_print $ parse v4pattern "" "1.2.3.3[6..9]" -- 1.2.3.3 -- v4pattern :: Parser IPv4Pattern @@ -420,6 +420,11 @@ addresses (IPv4Pattern field1 field2 field3 field4) = do -- * Tests +ipv4pattern_tests :: TestTree +ipv4pattern_tests = + testGroup "IPv4Pattern Tests" [ v4octet_tests ] + + v4octet_tests :: TestTree v4octet_tests = testGroup