{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeFamilies #-} module Descript.Misc.Build.Write.Print.PrimPrintable ( PrimPrintable (..) ) where import Descript.Misc.Build.Write.Print.APrint import Descript.Misc.Summary import Data.Ratio import Data.Monoid import Data.Text (Text) -- | A primitive value inside of an AST leaf which can be printed back -- into source text. Instances would implement 'Printable', but they -- don't have annotations, so they implement this instead. class (Summary a) => PrimPrintable a where -- | Prints the primitive value. pprim :: (APrint r) => a -> r instance PrimPrintable Char where pprim = plex . show instance PrimPrintable Int where pprim = plex . show instance PrimPrintable Integer where pprim = plex . show instance PrimPrintable Float where pprim = plex . show instance PrimPrintable Double where pprim = plex . show instance (a ~ Char) => PrimPrintable [a] where pprim = plex . show instance PrimPrintable Text where pprim = plex . show instance (PrimPrintable a) => PrimPrintable (Ratio a) where pprim x | denomPrint == "1" = numPrint | otherwise = numPrint <> "/" <> denomPrint -- Or just 'plex' everything? where numPrint = pprim $ numerator x denomPrint = pprim $ denominator x