{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Dino.Pretty where
import Prelude
import Data.Hashable (Hashable)
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HM
import Data.List (sortOn)
import Data.String (IsString)
import GHC.Generics (Generic)
import Text.PrettyPrint.ANSI.Leijen (Doc, Pretty (..), (<+>))
import qualified Text.PrettyPrint.ANSI.Leijen as PP
data Importance
= Unimportant
| Important
deriving (Eq, Show, Generic)
instance Semigroup Importance where
Unimportant <> Unimportant = Unimportant
_ <> _ = Important
instance Hashable Importance
unchanged :: Doc
unchanged = PP.magenta $ PP.text "*"
emphasize :: Importance -> Doc -> Doc
emphasize Unimportant = id
emphasize Important = PP.bold . PP.blue
underHeader ::
Doc
-> Doc
-> Doc
underHeader h d = h PP.<$> PP.space <+> PP.align d
verticalList :: Doc -> Doc -> Doc -> [Doc] -> Doc
verticalList l _ r [] = l <+> r
verticalList l sep r ds =
PP.vcat [c <+> PP.align d | (c, d) <- zip (l : repeat sep) ds] PP.<$> r
newtype Field = Field {unField :: String}
deriving (Eq, Ord, IsString, Hashable)
instance Show Field where
show = unField
instance Pretty Field where
pretty = PP.string . unField
prettyRecord :: (Show k, Ord k) => Importance -> HashMap k Doc -> Doc
prettyRecord imp =
verticalList PP.lbrace PP.comma PP.rbrace .
map prettyField . sortOn fst . HM.toList
where
prettyField (f, v) =
underHeader (emphasize imp (PP.string (show f)) <+> PP.string "=") v