{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE Rank2Types #-} module Descript.Misc.Build.Write.Print.PrintText ( pprint , reprint , pprintF ) where import Descript.Misc.Build.Write.Print.Printable import Descript.Misc.Build.Write.Print.APrint import Descript.Misc.Build.Read.Parse import Descript.Misc.Loc import Descript.Misc.Ann import Data.String import Data.Text (Text) import qualified Data.Text as Text -- | Plain printed text. newtype PrintText = PrintText{ runPrintText :: Text } deriving (Eq, Monoid, IsString) instance APrint PrintText where plex = PrintText . Text.pack -- Same as 'ppunc' pimp = id pintercal (PrintText sep) = PrintText . Text.intercalate sep . map runPrintText -- | Pretty-prints the node. pprint :: (Printable a) => a an -> Text pprint = runPrintText . aprint -- | Pretty-prints the node, using the given function to print children. pprintRec :: (Printable a) => (forall b. (Printable b) => b an -> Text) -> a an -> Text pprintRec sub = runPrintText . aprintRec (PrintText . sub) -- | Converts the node back into source text. -- Will reuse the text the AST was derived from if it isn't tainted. -- Otherwise will print from scratch (like 'pprint'). reprint :: (Printable a) => Text -> a SrcAnn -> Text reprint src x | isTainted x = pprintRec (reprint src) x | otherwise = srcRange (getAnn x) `inText` src -- | Pretty-prints the nodes and concats them to form source text. Used -- for lexemes. pprintF :: (Foldable w, Printable a) => w (a an) -> Text pprintF = foldMap pprint