{-# LANGUAGE Rank2Types #-} module Descript.Misc.Build.Write.Print.APrint ( APrint (..) , ppunc , pimpIf ) where import Data.List import Data.String -- | An abstract print - a stream of printed tokens. -- This abstracts over printing, allowing a single method to implement -- pretty prints, patches, reduced prints, and (in the future) prints -- with different style guidelines. class (Eq a, Monoid a, IsString a) => APrint a where -- | An "significant" block of text: a block of text which will be -- different for different occurrences of this node, like a symbol's -- string. -- -- This is different than 'ppunc' ('fromString'), which is an -- "insignificant" block of text: a block of text which will be the -- same for every occurrence of the node, like "?" at the end of a -- query or ", " between record properties (delimiters). plex :: String -> a -- | A piece of text which can sometimes be omitted, like a property -- key (could be implicit and resolved by index). The content doesn't -- /always/ have to be optional (if the property key is in the wrong -- position it can't be implicit). This is used to omit patches which -- are "parsed" from empty ranges of text (since the implicit content -- was obviously implicit). pimp :: a -> a -- | 'intercalate'. pintercal :: a -> [a] -> a pintercal sep = mconcat . intersperse sep -- An "insignificant" block of text: a block of text which will be the -- same for every occurrence of the node, like "?" at the end of a -- query or ", " between record properties (delimiters). This is an -- alias for 'fromString', but clearer. -- -- This is different than 'plex', a "significant" block of text: a block -- of text which will be different for different occurrences of this -- node, like a symbol's string. -- -- With 'OverloadedStrings' turned on, any string literal will be -- wrapped with 'ppunc' - -- -- > ppunc = fromString ppunc :: (APrint a) => String -> a ppunc = fromString -- | Marks the text implicit (can be omitted) if the given condition is -- true, otherwise returns the text as-is. pimpIf :: (APrint a) => Bool -> a -> a pimpIf True = pimp pimpIf False = id