{-# LANGUAGE CPP, FlexibleInstances, TypeSynonymInstances #-}
module Test.Framework.Pretty (
Pretty(..), (<=>),
module Text.PrettyPrint
)
where
#if MIN_VERSION_base(4,11,0)
import Text.PrettyPrint hiding ((<>))
#else
import Text.PrettyPrint
#endif
class Pretty a where
pretty :: a -> Doc
prettyList :: [a] -> Doc
prettyList [a]
l =
Char -> Doc
char Char
'[' Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> [Doc] -> Doc
vcat (Doc -> [Doc] -> [Doc]
punctuate Doc
comma ((a -> Doc) -> [a] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map a -> Doc
forall a. Pretty a => a -> Doc
pretty [a]
l)) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Char -> Doc
char Char
']'
showPretty :: a -> String
showPretty = Doc -> String
render (Doc -> String) -> (a -> Doc) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Doc
forall a. Pretty a => a -> Doc
pretty
instance Pretty Char where
pretty :: Char -> Doc
pretty = Char -> Doc
char
prettyList :: String -> Doc
prettyList String
s = String -> Doc
text String
s
instance Pretty a => Pretty [a] where
pretty :: [a] -> Doc
pretty = [a] -> Doc
forall a. Pretty a => [a] -> Doc
prettyList
instance Pretty Int where
pretty :: Int -> Doc
pretty = Int -> Doc
int
instance Pretty Bool where
pretty :: Bool -> Doc
pretty = String -> Doc
text (String -> Doc) -> (Bool -> String) -> Bool -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> String
forall a. Show a => a -> String
show
(<=>) :: Doc -> Doc -> Doc
Doc
d1 <=> :: Doc -> Doc -> Doc
<=> Doc
d2 = Doc
d1 Doc -> Doc -> Doc
<+> Doc
equals Doc -> Doc -> Doc
<+> Doc
d2