-{-# 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
import Test.Tasty ( TestTree, testGroup )
import Test.Tasty.HUnit ( (@?=), testCase )
import Text.Parsec (
- ParseError,
(<|>),
char,
digit,
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
-- * Octets
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.
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
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
-- >>> 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
instance Pretty IPv4Field where
- prettyshow (IPv4FieldOctet octet) = prettyshow octet
- prettyshow (IPv4FieldSequence s) = "[" ++ (prettyshow s) ++ "]"
+ 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
-- >>> parseTest v4field "127"
-- IPv4FieldOctet (IPv4Octet 127)
--
--- >>> pp $ parse v4field "" "[127]"
+-- >>> pretty_print $ parse v4field "" "[127]"
-- [127]
--
v4field :: Parser IPv4Field
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,
--
-- ==== _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:
-- 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
--- /dev/null
+{-# LANGUAGE FlexibleInstances #-}
+
+-- | A typeclass for pretty-printing. Types that wish to be
+-- pretty-printed should make themselves an instance of the 'Pretty'
+-- class. The only class function that they need to implement is
+-- 'pretty_show', which turns the thing into a string in a nice
+-- way. The 'pretty_print' function then prints the result of
+-- 'pretty_show' by default.
+--
+module Pretty
+where
+
+import Text.Parsec ( ParseError )
+
+
+class Pretty a where
+ -- | Obtain a pretty 'String' representation of the given thingy.
+ pretty_show :: a -> String
+
+ -- | Pretty-print the given thingy.
+ pretty_print :: a -> IO ()
+ pretty_print = putStrLn . pretty_show
+
+
+-- | 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
+ pretty_show (Left err) = show err
+ pretty_show (Right v) = pretty_show v