#if __GLASGOW_HASKELL__ >= 706
#endif
module Text.Printer
(
Printer(..)
, StringBuilder(..)
, buildString
, buildText
, buildLazyText
, AsciiBuilder(..)
, buildAscii
, buildLazyAscii
, Utf8Builder(..)
, buildUtf8
, buildLazyUtf8
, PrettyPrinter(..)
, renderPretty
, (<>)
, hcat
, fcat
, separate
, (<+>)
, hsep
, fsep
, list
, parens
, brackets
, braces
, angles
, squotes
, dquotes
, punctuateL
, punctuateR
, MultilinePrinter(..)
, lines
, newLine
, crlf
, LinePrinter(..)
, lfPrinter
, crlfPrinter
) where
import Prelude hiding (foldr, foldr1, print, lines)
#if __GLASGOW_HASKELL__ >= 706
import GHC.Generics (Generic)
#endif
import Data.Typeable (Typeable)
import Data.String (IsString(..))
import Data.Semigroup (Semigroup)
import qualified Data.Semigroup as S
import Data.Monoid (Monoid(..))
#if MIN_VERSION_base(4,5,0)
import Data.Monoid ((<>))
#endif
import Data.Foldable (Foldable(..), toList)
import Data.Traversable (Traversable, mapAccumL, mapAccumR)
import qualified Data.Text as TS
import qualified Data.Text.Encoding as TS
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import qualified Data.Text.Lazy.Builder as TB
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BS8
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BL8
import qualified Data.ByteString.Lazy.Builder as BB
import qualified Text.PrettyPrint as PP
class (IsString p, Semigroup p, Monoid p) ⇒ Printer p where
char ∷ Char → p
char c = string [c]
char7 ∷ Char → p
char7 = char
string ∷ String → p
string = fromString
string7 ∷ String → p
string7 = string
text ∷ TS.Text → p
text = string . TS.unpack
lazyText ∷ TL.Text → p
lazyText = string . TL.unpack
ascii ∷ BS.ByteString → p
ascii = string . BS8.unpack
lazyAscii ∷ BL.ByteString → p
lazyAscii = string . BL8.unpack
utf8 ∷ BS.ByteString → p
utf8 = text . TS.decodeUtf8
lazyUtf8 ∷ BL.ByteString → p
lazyUtf8 = lazyText . TL.decodeUtf8
instance Printer String where
newtype StringBuilder = StringBuilder { stringBuilder ∷ String → String }
deriving ( Typeable
#if __GLASGOW_HASKELL__ >= 706
, Generic
#endif
, Semigroup
, Monoid)
instance IsString StringBuilder where
fromString s = StringBuilder (s ++)
instance Printer StringBuilder where
char c = StringBuilder (c :)
buildString ∷ StringBuilder → String
buildString b = stringBuilder b ""
instance Printer TB.Builder where
char = TB.singleton
text = TB.fromText
lazyText = TB.fromLazyText
buildText ∷ TB.Builder → TS.Text
buildText = fold . TL.toChunks . buildLazyText
buildLazyText ∷ TB.Builder → TL.Text
buildLazyText = TB.toLazyText
newtype AsciiBuilder = AsciiBuilder { asciiBuilder ∷ BB.Builder }
deriving ( Typeable
#if __GLASGOW_HASKELL__ >= 706
, Generic
#endif
, Monoid)
instance IsString AsciiBuilder where
fromString = AsciiBuilder . BB.string7
instance Semigroup AsciiBuilder where
b₁ <> b₂ = AsciiBuilder $ asciiBuilder b₁ <> asciiBuilder b₂
stimes = S.stimesMonoid
instance Printer AsciiBuilder where
char = AsciiBuilder . BB.char7
ascii = AsciiBuilder . BB.byteString
lazyAscii = AsciiBuilder . BB.lazyByteString
utf8 = AsciiBuilder . BB.byteString
lazyUtf8 = AsciiBuilder . BB.lazyByteString
buildAscii ∷ AsciiBuilder → BS.ByteString
buildAscii = fold . BL.toChunks . buildLazyAscii
buildLazyAscii ∷ AsciiBuilder → BL.ByteString
buildLazyAscii = BB.toLazyByteString . asciiBuilder
newtype Utf8Builder = Utf8Builder { utf8Builder ∷ BB.Builder }
deriving ( Typeable
#if __GLASGOW_HASKELL__ >= 706
, Generic
#endif
, Monoid)
instance IsString Utf8Builder where
fromString = Utf8Builder . BB.stringUtf8
instance Semigroup Utf8Builder where
b₁ <> b₂ = Utf8Builder $ utf8Builder b₁ <> utf8Builder b₂
stimes = S.stimesMonoid
instance Printer Utf8Builder where
char = Utf8Builder . BB.charUtf8
char7 = Utf8Builder . BB.char7
string7 = Utf8Builder . BB.string7
text = Utf8Builder . BB.byteString . TS.encodeUtf8
lazyText = Utf8Builder . BB.lazyByteString . TL.encodeUtf8
ascii = Utf8Builder . BB.byteString
lazyAscii = Utf8Builder . BB.lazyByteString
utf8 = Utf8Builder . BB.byteString
lazyUtf8 = Utf8Builder . BB.lazyByteString
buildUtf8 ∷ Utf8Builder → BS.ByteString
buildUtf8 = fold . BL.toChunks . buildLazyUtf8
buildLazyUtf8 ∷ Utf8Builder → BL.ByteString
buildLazyUtf8 = BB.toLazyByteString . utf8Builder
newtype PrettyPrinter = PrettyPrinter { prettyPrinter ∷ PP.Doc }
deriving ( Typeable
#if __GLASGOW_HASKELL__ >= 706
, Generic
#endif
#if MIN_VERSION_pretty(1,1,0)
, IsString
# if MIN_VERSION_base(4,9,0)
, Semigroup
# endif
, Monoid
#endif
)
#if !MIN_VERSION_pretty(1,1,0)
instance IsString PrettyPrinter where
fromString = PrettyPrinter . PP.text
#endif
#if !MIN_VERSION_base(4,9,0) || !MIN_VERSION_pretty(1,1,0)
instance Semigroup PrettyPrinter where
p₁ <> p₂ = PrettyPrinter
$ (PP.<>) (prettyPrinter p₁) (prettyPrinter p₂)
stimes = S.stimesMonoid
#endif
#if !MIN_VERSION_pretty(1,1,0)
instance Monoid PrettyPrinter where
mempty = PP.empty
mappend = (S.<>)
#endif
instance Printer PrettyPrinter where
char = PrettyPrinter . PP.char
renderPretty ∷ PrettyPrinter → String
renderPretty = PP.render . prettyPrinter
#if !MIN_VERSION_base(4,5,0)
(<>) ∷ Monoid m ⇒ m → m → m
(<>) = mappend
#endif
hcat ∷ (Printer p, Foldable f) ⇒ f p → p
hcat = fold
fcat ∷ (Foldable f, Printer p) ⇒ (p → p → p) → f p → p
fcat c f = case toList f of
[] → mempty
ps → foldr1 c ps
separate ∷ Printer p
⇒ p
→ p → p → p
separate s x y = x <> s <> y
infixr 6 <+>
(<+>) ∷ Printer p ⇒ p → p → p
(<+>) = separate (char7 ' ')
hsep ∷ (Printer p, Foldable f) ⇒ f p → p
hsep = fcat (<+>)
fsep ∷ (Foldable f, Printer p) ⇒ p → f p → p
fsep = fcat . separate
list ∷ (Foldable f, Printer p) ⇒ f p → p
list = fsep (char7 ',')
parens ∷ Printer p ⇒ p → p
parens p = char7 '(' <> p <> char7 ')'
brackets ∷ Printer p ⇒ p → p
brackets p = char7 '[' <> p <> char7 ']'
braces ∷ Printer p ⇒ p → p
braces p = char7 '{' <> p <> char7 '}'
angles ∷ Printer p ⇒ p → p
angles p = char7 '<' <> p <> char7 '>'
squotes ∷ Printer p ⇒ p → p
squotes p = char7 '\'' <> p <> char7 '\''
dquotes ∷ Printer p ⇒ p → p
dquotes p = char7 '\"' <> p <> char7 '\"'
punctuateL ∷ (Traversable t, Printer p) ⇒ p → t p → t p
punctuateL p =
snd . mapAccumL (\f a → if f then (False, a) else (False, p <> a)) True
punctuateR ∷ (Traversable t, Printer p) ⇒ p → t p → t p
punctuateR p =
snd . mapAccumR (\l a → if l then (False, a) else (False, a <> p)) True
infixr 5 <->
class Printer p ⇒ MultilinePrinter p where
(<->) ∷ p → p → p
instance MultilinePrinter PrettyPrinter where
p₁ <-> p₂ = PrettyPrinter
$ (PP.$+$) (prettyPrinter p₁) (prettyPrinter p₂)
lines ∷ (MultilinePrinter p, Foldable f) ⇒ f p → p
lines = fcat (<->)
newLine ∷ Printer p ⇒ p
newLine = char '\n'
crlf ∷ Printer p ⇒ p
crlf = char '\r' <> char '\n'
newtype LinePrinter p = LinePrinter { linePrinter ∷ (p → p → p) → p }
deriving ( Typeable
#if __GLASGOW_HASKELL__ >= 706
, Generic
#endif
)
instance IsString p ⇒ IsString (LinePrinter p) where
fromString = LinePrinter . const . fromString
instance Semigroup p ⇒ Semigroup (LinePrinter p) where
x <> y = LinePrinter $ \l → linePrinter x l S.<> linePrinter y l
stimes n x = LinePrinter $ S.stimes n . linePrinter x
instance Monoid p ⇒ Monoid (LinePrinter p) where
mempty = LinePrinter $ const mempty
mappend x y = LinePrinter $ \l → mappend (linePrinter x l) (linePrinter y l)
mconcat xs = LinePrinter $ \l → mconcat (map (\x → linePrinter x l) xs)
instance Printer p ⇒ Printer (LinePrinter p) where
char = LinePrinter . const . char
char7 = LinePrinter . const . char7
string = LinePrinter . const . string
string7 = LinePrinter . const . string7
text = LinePrinter . const . text
lazyText = LinePrinter . const . lazyText
ascii = LinePrinter . const . ascii
lazyAscii = LinePrinter . const . lazyAscii
utf8 = LinePrinter . const . utf8
lazyUtf8 = LinePrinter . const . lazyUtf8
instance Printer p ⇒ MultilinePrinter (LinePrinter p) where
x <-> y = LinePrinter $ \l → l (linePrinter x l) (linePrinter y l)
lfPrinter ∷ Printer p ⇒ LinePrinter p → p
lfPrinter p = linePrinter p (separate newLine)
crlfPrinter ∷ Printer p ⇒ LinePrinter p → p
crlfPrinter p = linePrinter p (separate crlf)