]> gitweb.michael.orlitzky.com - dead/harbl.git/blobdiff - src/Network/DNS/RBL/Pretty.hs
Rename everything under the Network.DNS.RBL hierarchy.
[dead/harbl.git] / src / Network / DNS / RBL / Pretty.hs
diff --git a/src/Network/DNS/RBL/Pretty.hs b/src/Network/DNS/RBL/Pretty.hs
new file mode 100644 (file)
index 0000000..23a285c
--- /dev/null
@@ -0,0 +1,48 @@
+{-# 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 Network.DNS.RBL.Pretty ( 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
+
+
+-- | If we can pretty print something, we can pretty-print a list of
+--   them too.
+--
+instance (Pretty a) => Pretty [a] where
+  pretty_show l = show $ map pretty_show l
+
+
+-- | If we can pretty print something, we can pretty-print a pair of
+--   them too.
+--
+instance (Pretty a, Pretty b) => Pretty (a,b) where
+  pretty_show (x,y) = show (pretty_show x, pretty_show y)
+
+
+
+-- | 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