{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, CPP #-}
module Language.Python.Common.Pretty (module TextPP, module Language.Python.Common.Pretty) where
#if __GLASGOW_HASKELL__ >= 803
import Prelude hiding ((<>))
#endif
import Text.PrettyPrint as TextPP
class Pretty a where
pretty :: a -> Doc
prettyText :: Pretty a => a -> String
prettyText = render . pretty
prettyPrefix :: Pretty a => Int -> a -> Doc
prettyPrefix maxLen x
| length fullText <= maxLen = pretty fullText
| otherwise = pretty (take maxLen fullText) <+> text "..."
where
fullText = prettyText x
instance Pretty String where
pretty s = text s
parensIf :: Pretty a => (a -> Bool) -> a -> Doc
parensIf test x = if test x then parens $ pretty x else pretty x
perhaps :: Pretty a => Maybe a -> Doc -> Doc
perhaps Nothing doc = empty
perhaps (Just {}) doc = doc
commaList :: Pretty a => [a] -> Doc
commaList = hsep . punctuate comma . map pretty
equalsList :: Pretty a => [a] -> Doc
equalsList = hsep . punctuate (space <> equals) . map pretty
instance Pretty Int where
pretty = int
instance Pretty Integer where
pretty = integer
instance Pretty Double where
pretty = double
instance Pretty Bool where
pretty True = text "True"
pretty False = text "False"
instance Pretty a => Pretty (Maybe a) where
pretty Nothing = empty
pretty (Just x) = pretty x