{-# LANGUAGE CPP #-}
{-# LANGUAGE UnicodeSyntax #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveDataTypeable #-}
#if __GLASGOW_HASKELL__ >= 706
{-# LANGUAGE DeriveGeneric #-}
#endif
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}

-- | Monoids with a homomorphism from 'String' to themselves.
module Text.Printer
  (
  -- * The class
    Printer(..)
  -- * Builders
  , StringBuilder(..)
  , buildString
  , buildText
  , buildLazyText
  , AsciiBuilder(..)
  , buildAscii
  , buildLazyAscii
  , Utf8Builder(..)
  , buildUtf8
  , buildLazyUtf8
  , PrettyPrinter(..)
  , renderPretty
  -- * Combinators
  , (<>)
  , hcat
  , fcat
  , separate
  , (<+>)
  , hsep
  , fsep
  , list
  , parens
  , brackets
  , braces
  , angles
  , squotes
  , dquotes
  , punctuateL
  , punctuateR
  -- * Multiline printers
  , 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
#if MIN_VERSION_bytestring(0,10,2)
import qualified Data.ByteString.Builder as BB
#else
import qualified Data.ByteString.Lazy.Builder as BB
#endif
import qualified Text.PrettyPrint as PP

-- | Text monoid. 'string' must be equivalent to 'fromString' and be a monoid
--   homomorphism, i.e. @'string' 'mempty' = 'mempty'@ and
--   @'mappend' ('string' /x/) ('string' /y/) = 'string' ('mappend' /x/ /y/)@.
--   Other operations must be monoid homomorphisms that are eqiuvalent (but
--   possibly faster) to the composition of 'string' and the corresponding
--   embedding, e.g. @'text' = 'string' . 'TS.unpack'@.
class (IsString p, Semigroup p, Monoid p)  Printer p where
  -- | Print a character. @'char' /c/@ must be equivalent to
  --   @'string' [/c/]@, but hopefully is faster.
  char  Char  p
  char Char
c = String -> p
forall p. Printer p => String -> p
string [Char
c]
  {-# INLINE char #-}
  -- | Print an ASCII character, can be faster than 'char'.
  char7  Char  p
  char7 = Char -> p
forall p. Printer p => Char -> p
char
  {-# INLINE char7 #-}
  -- | Print a string.
  string  String  p
  string = String -> p
forall a. IsString a => String -> a
fromString
  {-# INLINE string #-}
  -- | Print an ASCII string, can be faster than 'string'.
  string7  String  p
  string7 = String -> p
forall p. Printer p => String -> p
string
  {-# INLINE string7 #-}
  -- | Print a 'TS.Text'.
  text  TS.Text  p
  text = String -> p
forall p. Printer p => String -> p
string (String -> p) -> (Text -> String) -> Text -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
TS.unpack
  {-# INLINE text #-}
  -- | Print a lazy 'TL.Text'.
  lazyText  TL.Text  p
  lazyText = String -> p
forall p. Printer p => String -> p
string (String -> p) -> (Text -> String) -> Text -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
TL.unpack
  {-# INLINE lazyText #-}
  -- | Print an ASCII 'BS.ByteString'.
  ascii  BS.ByteString  p
  ascii = String -> p
forall p. Printer p => String -> p
string (String -> p) -> (ByteString -> String) -> ByteString -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
BS8.unpack
  {-# INLINE ascii #-}
  -- | Print a lazy ASCII 'BL.ByteString'.
  lazyAscii  BL.ByteString  p
  lazyAscii = String -> p
forall p. Printer p => String -> p
string (String -> p) -> (ByteString -> String) -> ByteString -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
BL8.unpack
  {-# INLINE lazyAscii #-}
  -- | Print a UTF-8 'BS.ByteString'.
  utf8  BS.ByteString  p
  utf8 = Text -> p
forall p. Printer p => Text -> p
text (Text -> p) -> (ByteString -> Text) -> ByteString -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
TS.decodeUtf8
  {-# INLINE utf8 #-}
  -- | Print a lazy UTF-8 'BL.ByteString'
  lazyUtf8  BL.ByteString  p
  lazyUtf8 = Text -> p
forall p. Printer p => Text -> p
lazyText (Text -> p) -> (ByteString -> Text) -> ByteString -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
TL.decodeUtf8
  {-# INLINE lazyUtf8 #-}

instance Printer String where

-- | A simple string builder as used by 'Show'.
newtype StringBuilder = StringBuilder { StringBuilder -> String -> String
stringBuilder  String  String }
                        deriving ( Typeable
#if __GLASGOW_HASKELL__ >= 706
                                 , (forall x. StringBuilder -> Rep StringBuilder x)
-> (forall x. Rep StringBuilder x -> StringBuilder)
-> Generic StringBuilder
forall x. Rep StringBuilder x -> StringBuilder
forall x. StringBuilder -> Rep StringBuilder x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StringBuilder x -> StringBuilder
$cfrom :: forall x. StringBuilder -> Rep StringBuilder x
Generic
#endif
                                 , b -> StringBuilder -> StringBuilder
NonEmpty StringBuilder -> StringBuilder
StringBuilder -> StringBuilder -> StringBuilder
(StringBuilder -> StringBuilder -> StringBuilder)
-> (NonEmpty StringBuilder -> StringBuilder)
-> (forall b. Integral b => b -> StringBuilder -> StringBuilder)
-> Semigroup StringBuilder
forall b. Integral b => b -> StringBuilder -> StringBuilder
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> StringBuilder -> StringBuilder
$cstimes :: forall b. Integral b => b -> StringBuilder -> StringBuilder
sconcat :: NonEmpty StringBuilder -> StringBuilder
$csconcat :: NonEmpty StringBuilder -> StringBuilder
<> :: StringBuilder -> StringBuilder -> StringBuilder
$c<> :: StringBuilder -> StringBuilder -> StringBuilder
Semigroup
                                 , Semigroup StringBuilder
StringBuilder
Semigroup StringBuilder
-> StringBuilder
-> (StringBuilder -> StringBuilder -> StringBuilder)
-> ([StringBuilder] -> StringBuilder)
-> Monoid StringBuilder
[StringBuilder] -> StringBuilder
StringBuilder -> StringBuilder -> StringBuilder
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [StringBuilder] -> StringBuilder
$cmconcat :: [StringBuilder] -> StringBuilder
mappend :: StringBuilder -> StringBuilder -> StringBuilder
$cmappend :: StringBuilder -> StringBuilder -> StringBuilder
mempty :: StringBuilder
$cmempty :: StringBuilder
$cp1Monoid :: Semigroup StringBuilder
Monoid)

instance IsString StringBuilder where
  fromString :: String -> StringBuilder
fromString String
s = (String -> String) -> StringBuilder
StringBuilder (String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++)
  {-# INLINE fromString #-}

instance Printer StringBuilder where
  char :: Char -> StringBuilder
char Char
c = (String -> String) -> StringBuilder
StringBuilder (Char
c Char -> String -> String
forall a. a -> [a] -> [a]
:)
  {-# INLINE char #-}

buildString  StringBuilder  String
buildString :: StringBuilder -> String
buildString StringBuilder
b = StringBuilder -> String -> String
stringBuilder StringBuilder
b String
""
{-# INLINE buildString #-}

instance Printer TB.Builder where
  char :: Char -> Builder
char = Char -> Builder
TB.singleton
  {-# INLINE char #-}
  text :: Text -> Builder
text = Text -> Builder
TB.fromText
  {-# INLINE text #-}
  lazyText :: Text -> Builder
lazyText = Text -> Builder
TB.fromLazyText
  {-# INLINE lazyText #-}

buildText  TB.Builder  TS.Text
buildText :: Builder -> Text
buildText = [Text] -> Text
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold ([Text] -> Text) -> (Builder -> [Text]) -> Builder -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
TL.toChunks (Text -> [Text]) -> (Builder -> Text) -> Builder -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
buildLazyText
{-# INLINE buildText #-}

buildLazyText  TB.Builder  TL.Text
buildLazyText :: Builder -> Text
buildLazyText = Builder -> Text
TB.toLazyText
{-# INLINE buildLazyText #-}

-- | Use this builder when you are sure that only ASCII characters
--   will get printed to it.
newtype AsciiBuilder = AsciiBuilder { AsciiBuilder -> Builder
asciiBuilder  BB.Builder }
                       deriving ( Typeable
#if __GLASGOW_HASKELL__ >= 706
                                , (forall x. AsciiBuilder -> Rep AsciiBuilder x)
-> (forall x. Rep AsciiBuilder x -> AsciiBuilder)
-> Generic AsciiBuilder
forall x. Rep AsciiBuilder x -> AsciiBuilder
forall x. AsciiBuilder -> Rep AsciiBuilder x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AsciiBuilder x -> AsciiBuilder
$cfrom :: forall x. AsciiBuilder -> Rep AsciiBuilder x
Generic
#endif
                                , Semigroup AsciiBuilder
AsciiBuilder
Semigroup AsciiBuilder
-> AsciiBuilder
-> (AsciiBuilder -> AsciiBuilder -> AsciiBuilder)
-> ([AsciiBuilder] -> AsciiBuilder)
-> Monoid AsciiBuilder
[AsciiBuilder] -> AsciiBuilder
AsciiBuilder -> AsciiBuilder -> AsciiBuilder
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [AsciiBuilder] -> AsciiBuilder
$cmconcat :: [AsciiBuilder] -> AsciiBuilder
mappend :: AsciiBuilder -> AsciiBuilder -> AsciiBuilder
$cmappend :: AsciiBuilder -> AsciiBuilder -> AsciiBuilder
mempty :: AsciiBuilder
$cmempty :: AsciiBuilder
$cp1Monoid :: Semigroup AsciiBuilder
Monoid)

instance IsString AsciiBuilder where
  fromString :: String -> AsciiBuilder
fromString = Builder -> AsciiBuilder
AsciiBuilder (Builder -> AsciiBuilder)
-> (String -> Builder) -> String -> AsciiBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Builder
BB.string7
  {-# INLINE fromString #-}

instance Semigroup AsciiBuilder where
  AsciiBuilder
b₁ <> :: AsciiBuilder -> AsciiBuilder -> AsciiBuilder
<> AsciiBuilder
b₂ = Builder -> AsciiBuilder
AsciiBuilder (Builder -> AsciiBuilder) -> Builder -> AsciiBuilder
forall a b. (a -> b) -> a -> b
$ AsciiBuilder -> Builder
asciiBuilder AsciiBuilder
b₁ Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> AsciiBuilder -> Builder
asciiBuilder AsciiBuilder
b₂
  {-# INLINE (<>) #-}
  stimes :: b -> AsciiBuilder -> AsciiBuilder
stimes = b -> AsciiBuilder -> AsciiBuilder
forall b a. (Integral b, Monoid a) => b -> a -> a
S.stimesMonoid
  {-# INLINE stimes #-}

instance Printer AsciiBuilder where
  char :: Char -> AsciiBuilder
char = Builder -> AsciiBuilder
AsciiBuilder (Builder -> AsciiBuilder)
-> (Char -> Builder) -> Char -> AsciiBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Builder
BB.char7
  {-# INLINE char #-}
  ascii :: ByteString -> AsciiBuilder
ascii = Builder -> AsciiBuilder
AsciiBuilder (Builder -> AsciiBuilder)
-> (ByteString -> Builder) -> ByteString -> AsciiBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
BB.byteString
  {-# INLINE ascii #-}
  lazyAscii :: ByteString -> AsciiBuilder
lazyAscii = Builder -> AsciiBuilder
AsciiBuilder (Builder -> AsciiBuilder)
-> (ByteString -> Builder) -> ByteString -> AsciiBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
BB.lazyByteString
  {-# INLINE lazyAscii #-}
  utf8 :: ByteString -> AsciiBuilder
utf8 = Builder -> AsciiBuilder
AsciiBuilder (Builder -> AsciiBuilder)
-> (ByteString -> Builder) -> ByteString -> AsciiBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
BB.byteString
  {-# INLINE utf8 #-}
  lazyUtf8 :: ByteString -> AsciiBuilder
lazyUtf8 = Builder -> AsciiBuilder
AsciiBuilder (Builder -> AsciiBuilder)
-> (ByteString -> Builder) -> ByteString -> AsciiBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
BB.lazyByteString
  {-# INLINE lazyUtf8 #-}

buildAscii  AsciiBuilder  BS.ByteString
buildAscii :: AsciiBuilder -> ByteString
buildAscii = [ByteString] -> ByteString
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold ([ByteString] -> ByteString)
-> (AsciiBuilder -> [ByteString]) -> AsciiBuilder -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
BL.toChunks (ByteString -> [ByteString])
-> (AsciiBuilder -> ByteString) -> AsciiBuilder -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AsciiBuilder -> ByteString
buildLazyAscii
{-# INLINE buildAscii #-}

buildLazyAscii  AsciiBuilder  BL.ByteString
buildLazyAscii :: AsciiBuilder -> ByteString
buildLazyAscii = Builder -> ByteString
BB.toLazyByteString (Builder -> ByteString)
-> (AsciiBuilder -> Builder) -> AsciiBuilder -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AsciiBuilder -> Builder
asciiBuilder
{-# INLINE buildLazyAscii #-}

-- | UTF-8 lazy 'BL.ByteString' builder.
newtype Utf8Builder = Utf8Builder { Utf8Builder -> Builder
utf8Builder  BB.Builder }
                      deriving ( Typeable
#if __GLASGOW_HASKELL__ >= 706
                               , (forall x. Utf8Builder -> Rep Utf8Builder x)
-> (forall x. Rep Utf8Builder x -> Utf8Builder)
-> Generic Utf8Builder
forall x. Rep Utf8Builder x -> Utf8Builder
forall x. Utf8Builder -> Rep Utf8Builder x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Utf8Builder x -> Utf8Builder
$cfrom :: forall x. Utf8Builder -> Rep Utf8Builder x
Generic
#endif
                               , Semigroup Utf8Builder
Utf8Builder
Semigroup Utf8Builder
-> Utf8Builder
-> (Utf8Builder -> Utf8Builder -> Utf8Builder)
-> ([Utf8Builder] -> Utf8Builder)
-> Monoid Utf8Builder
[Utf8Builder] -> Utf8Builder
Utf8Builder -> Utf8Builder -> Utf8Builder
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [Utf8Builder] -> Utf8Builder
$cmconcat :: [Utf8Builder] -> Utf8Builder
mappend :: Utf8Builder -> Utf8Builder -> Utf8Builder
$cmappend :: Utf8Builder -> Utf8Builder -> Utf8Builder
mempty :: Utf8Builder
$cmempty :: Utf8Builder
$cp1Monoid :: Semigroup Utf8Builder
Monoid)

instance IsString Utf8Builder where
  fromString :: String -> Utf8Builder
fromString = Builder -> Utf8Builder
Utf8Builder (Builder -> Utf8Builder)
-> (String -> Builder) -> String -> Utf8Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Builder
BB.stringUtf8
  {-# INLINE fromString #-}

instance Semigroup Utf8Builder where
  Utf8Builder
b₁ <> :: Utf8Builder -> Utf8Builder -> Utf8Builder
<> Utf8Builder
b₂ = Builder -> Utf8Builder
Utf8Builder (Builder -> Utf8Builder) -> Builder -> Utf8Builder
forall a b. (a -> b) -> a -> b
$ Utf8Builder -> Builder
utf8Builder Utf8Builder
b₁ Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Utf8Builder -> Builder
utf8Builder Utf8Builder
b₂
  {-# INLINE (<>) #-}
  stimes :: b -> Utf8Builder -> Utf8Builder
stimes = b -> Utf8Builder -> Utf8Builder
forall b a. (Integral b, Monoid a) => b -> a -> a
S.stimesMonoid
  {-# INLINE stimes #-}

instance Printer Utf8Builder where
  char :: Char -> Utf8Builder
char = Builder -> Utf8Builder
Utf8Builder (Builder -> Utf8Builder)
-> (Char -> Builder) -> Char -> Utf8Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Builder
BB.charUtf8
  {-# INLINE char #-}
  char7 :: Char -> Utf8Builder
char7 = Builder -> Utf8Builder
Utf8Builder (Builder -> Utf8Builder)
-> (Char -> Builder) -> Char -> Utf8Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Builder
BB.char7
  {-# INLINE char7 #-}
  string7 :: String -> Utf8Builder
string7 = Builder -> Utf8Builder
Utf8Builder (Builder -> Utf8Builder)
-> (String -> Builder) -> String -> Utf8Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Builder
BB.string7
  {-# INLINE string7 #-}
  text :: Text -> Utf8Builder
text = Builder -> Utf8Builder
Utf8Builder (Builder -> Utf8Builder)
-> (Text -> Builder) -> Text -> Utf8Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
BB.byteString (ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
TS.encodeUtf8
  {-# INLINE text #-}
  lazyText :: Text -> Utf8Builder
lazyText = Builder -> Utf8Builder
Utf8Builder (Builder -> Utf8Builder)
-> (Text -> Builder) -> Text -> Utf8Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
BB.lazyByteString (ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
TL.encodeUtf8
  {-# INLINE lazyText #-}
  ascii :: ByteString -> Utf8Builder
ascii = Builder -> Utf8Builder
Utf8Builder (Builder -> Utf8Builder)
-> (ByteString -> Builder) -> ByteString -> Utf8Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
BB.byteString
  {-# INLINE ascii #-}
  lazyAscii :: ByteString -> Utf8Builder
lazyAscii = Builder -> Utf8Builder
Utf8Builder (Builder -> Utf8Builder)
-> (ByteString -> Builder) -> ByteString -> Utf8Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
BB.lazyByteString
  {-# INLINE lazyAscii #-}
  utf8 :: ByteString -> Utf8Builder
utf8 = Builder -> Utf8Builder
Utf8Builder (Builder -> Utf8Builder)
-> (ByteString -> Builder) -> ByteString -> Utf8Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
BB.byteString
  {-# INLINE utf8 #-}
  lazyUtf8 :: ByteString -> Utf8Builder
lazyUtf8 = Builder -> Utf8Builder
Utf8Builder (Builder -> Utf8Builder)
-> (ByteString -> Builder) -> ByteString -> Utf8Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
BB.lazyByteString
  {-# INLINE lazyUtf8 #-}

buildUtf8  Utf8Builder  BS.ByteString
buildUtf8 :: Utf8Builder -> ByteString
buildUtf8 = [ByteString] -> ByteString
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold ([ByteString] -> ByteString)
-> (Utf8Builder -> [ByteString]) -> Utf8Builder -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
BL.toChunks (ByteString -> [ByteString])
-> (Utf8Builder -> ByteString) -> Utf8Builder -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Utf8Builder -> ByteString
buildLazyUtf8
{-# INLINE buildUtf8 #-}

buildLazyUtf8  Utf8Builder  BL.ByteString
buildLazyUtf8 :: Utf8Builder -> ByteString
buildLazyUtf8 = Builder -> ByteString
BB.toLazyByteString (Builder -> ByteString)
-> (Utf8Builder -> Builder) -> Utf8Builder -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Utf8Builder -> Builder
utf8Builder
{-# INLINE buildLazyUtf8 #-}

newtype PrettyPrinter = PrettyPrinter { PrettyPrinter -> Doc
prettyPrinter  PP.Doc }
                        deriving ( Typeable
#if __GLASGOW_HASKELL__ >= 706
                                 , (forall x. PrettyPrinter -> Rep PrettyPrinter x)
-> (forall x. Rep PrettyPrinter x -> PrettyPrinter)
-> Generic PrettyPrinter
forall x. Rep PrettyPrinter x -> PrettyPrinter
forall x. PrettyPrinter -> Rep PrettyPrinter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PrettyPrinter x -> PrettyPrinter
$cfrom :: forall x. PrettyPrinter -> Rep PrettyPrinter x
Generic
#endif
#if MIN_VERSION_pretty(1,1,0)
                                 , String -> PrettyPrinter
(String -> PrettyPrinter) -> IsString PrettyPrinter
forall a. (String -> a) -> IsString a
fromString :: String -> PrettyPrinter
$cfromString :: String -> PrettyPrinter
IsString
# if MIN_VERSION_base(4,9,0)
                                 , b -> PrettyPrinter -> PrettyPrinter
NonEmpty PrettyPrinter -> PrettyPrinter
PrettyPrinter -> PrettyPrinter -> PrettyPrinter
(PrettyPrinter -> PrettyPrinter -> PrettyPrinter)
-> (NonEmpty PrettyPrinter -> PrettyPrinter)
-> (forall b. Integral b => b -> PrettyPrinter -> PrettyPrinter)
-> Semigroup PrettyPrinter
forall b. Integral b => b -> PrettyPrinter -> PrettyPrinter
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> PrettyPrinter -> PrettyPrinter
$cstimes :: forall b. Integral b => b -> PrettyPrinter -> PrettyPrinter
sconcat :: NonEmpty PrettyPrinter -> PrettyPrinter
$csconcat :: NonEmpty PrettyPrinter -> PrettyPrinter
<> :: PrettyPrinter -> PrettyPrinter -> PrettyPrinter
$c<> :: PrettyPrinter -> PrettyPrinter -> PrettyPrinter
Semigroup
# endif
                                 , Semigroup PrettyPrinter
PrettyPrinter
Semigroup PrettyPrinter
-> PrettyPrinter
-> (PrettyPrinter -> PrettyPrinter -> PrettyPrinter)
-> ([PrettyPrinter] -> PrettyPrinter)
-> Monoid PrettyPrinter
[PrettyPrinter] -> PrettyPrinter
PrettyPrinter -> PrettyPrinter -> PrettyPrinter
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [PrettyPrinter] -> PrettyPrinter
$cmconcat :: [PrettyPrinter] -> PrettyPrinter
mappend :: PrettyPrinter -> PrettyPrinter -> PrettyPrinter
$cmappend :: PrettyPrinter -> PrettyPrinter -> PrettyPrinter
mempty :: PrettyPrinter
$cmempty :: PrettyPrinter
$cp1Monoid :: Semigroup PrettyPrinter
Monoid
#endif
                                 )

#if !MIN_VERSION_pretty(1,1,0)
instance IsString PrettyPrinter where
  fromString = PrettyPrinter . PP.text
  {-# INLINE fromString #-}
#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₂)
  {-# INLINE (<>) #-}
  stimes = S.stimesMonoid
  {-# INLINE stimes #-}
#endif

#if !MIN_VERSION_pretty(1,1,0)
instance Monoid PrettyPrinter where
  mempty = PP.empty
  {-# INLINE mempty #-}
  mappend = (S.<>)
  {-# INLINE mappend #-}
#endif

instance Printer PrettyPrinter where
  char :: Char -> PrettyPrinter
char = Doc -> PrettyPrinter
PrettyPrinter (Doc -> PrettyPrinter) -> (Char -> Doc) -> Char -> PrettyPrinter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Doc
PP.char
  {-# INLINE char #-}

-- | An alias for @'PP.render' . 'prettyPrinter'@
renderPretty  PrettyPrinter  String
renderPretty :: PrettyPrinter -> String
renderPretty = Doc -> String
PP.render (Doc -> String)
-> (PrettyPrinter -> Doc) -> PrettyPrinter -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PrettyPrinter -> Doc
prettyPrinter

#if !MIN_VERSION_base(4,5,0)
-- | An infix synonym for 'mappend'.
(<>)  Monoid m  m  m  m
(<>) = mappend
{-# INLINE (<>) #-}
#endif

-- | 'mconcat' for 'Foldable' data structures.
hcat  (Printer p, Foldable f)  f p  p
hcat :: f p -> p
hcat = f p -> p
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold
{-# INLINE hcat #-}

-- | Combine the items of a 'Foldable' data structure using the provided
--   function. If the data structure is empty, 'mempty' is returned.
fcat  (Foldable f, Printer p)  (p  p  p)  f p  p
fcat :: (p -> p -> p) -> f p -> p
fcat p -> p -> p
c f p
f = case f p -> [p]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList f p
f of
  []  p
forall a. Monoid a => a
mempty
  [p]
ps  (p -> p -> p) -> [p] -> p
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 p -> p -> p
c [p]
ps
{-# INLINABLE fcat #-}

-- | Concatenate two 'Printer's with a separator between them.
separate  Printer p
          p -- ^ The separator
          p  p  p
separate :: p -> p -> p -> p
separate p
s p
x p
y = p
x p -> p -> p
forall a. Semigroup a => a -> a -> a
<> p
s p -> p -> p
forall a. Semigroup a => a -> a -> a
<> p
y
{-# INLINE separate #-}

infixr 6 <+>

-- | Concatenate two 'Printer's with a space between them.
(<+>)  Printer p  p  p  p
<+> :: p -> p -> p
(<+>) = p -> p -> p -> p
forall p. Printer p => p -> p -> p -> p
separate (Char -> p
forall p. Printer p => Char -> p
char7 Char
' ')
{-# INLINE (<+>) #-}

-- | Concatenate the items of a 'Foldable' data structure
--   with spaces between them.
hsep  (Printer p, Foldable f)  f p  p
hsep :: f p -> p
hsep = (p -> p -> p) -> f p -> p
forall (f :: * -> *) p.
(Foldable f, Printer p) =>
(p -> p -> p) -> f p -> p
fcat p -> p -> p
forall p. Printer p => p -> p -> p
(<+>)
{-# INLINE hsep #-}

-- | A shorthand for @'fcat' . 'separate'@.
fsep  (Foldable f, Printer p)  p  f p  p
fsep :: p -> f p -> p
fsep = (p -> p -> p) -> f p -> p
forall (f :: * -> *) p.
(Foldable f, Printer p) =>
(p -> p -> p) -> f p -> p
fcat ((p -> p -> p) -> f p -> p) -> (p -> p -> p -> p) -> p -> f p -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p -> p -> p -> p
forall p. Printer p => p -> p -> p -> p
separate
{-# INLINE fsep #-}

-- | Concatenate the items of a 'Foldable' data structure with commas
--   between them.
--
-- @
--   'list' = 'fsep' ('char7' ',')
-- @
list  (Foldable f, Printer p)  f p  p
list :: f p -> p
list = p -> f p -> p
forall (f :: * -> *) p. (Foldable f, Printer p) => p -> f p -> p
fsep (Char -> p
forall p. Printer p => Char -> p
char7 Char
',')
{-# INLINE list #-}

-- | Enclose a 'Printer' with parentheses.
parens  Printer p  p  p
parens :: p -> p
parens p
p = Char -> p
forall p. Printer p => Char -> p
char7 Char
'(' p -> p -> p
forall a. Semigroup a => a -> a -> a
<> p
p p -> p -> p
forall a. Semigroup a => a -> a -> a
<> Char -> p
forall p. Printer p => Char -> p
char7 Char
')'
{-# INLINE parens #-}

-- | Enclose a 'Printer' with square brackets.
brackets  Printer p  p  p
brackets :: p -> p
brackets p
p = Char -> p
forall p. Printer p => Char -> p
char7 Char
'[' p -> p -> p
forall a. Semigroup a => a -> a -> a
<> p
p p -> p -> p
forall a. Semigroup a => a -> a -> a
<> Char -> p
forall p. Printer p => Char -> p
char7 Char
']'
{-# INLINE brackets #-}

-- | Enclose a 'Printer' with curly braces.
braces  Printer p  p  p
braces :: p -> p
braces p
p = Char -> p
forall p. Printer p => Char -> p
char7 Char
'{' p -> p -> p
forall a. Semigroup a => a -> a -> a
<> p
p p -> p -> p
forall a. Semigroup a => a -> a -> a
<> Char -> p
forall p. Printer p => Char -> p
char7 Char
'}'
{-# INLINE braces #-}

-- | Enclose a 'Printer' with angle brackets.
angles  Printer p  p  p
angles :: p -> p
angles p
p = Char -> p
forall p. Printer p => Char -> p
char7 Char
'<' p -> p -> p
forall a. Semigroup a => a -> a -> a
<> p
p p -> p -> p
forall a. Semigroup a => a -> a -> a
<> Char -> p
forall p. Printer p => Char -> p
char7 Char
'>'
{-# INLINE angles #-}

-- | Enclose a 'Printer' with single quotes.
squotes  Printer p  p  p
squotes :: p -> p
squotes p
p = Char -> p
forall p. Printer p => Char -> p
char7 Char
'\'' p -> p -> p
forall a. Semigroup a => a -> a -> a
<> p
p p -> p -> p
forall a. Semigroup a => a -> a -> a
<> Char -> p
forall p. Printer p => Char -> p
char7 Char
'\''
{-# INLINE squotes #-}

-- | Enclose a 'Printer' with double quotes.
dquotes  Printer p  p  p
dquotes :: p -> p
dquotes p
p  = Char -> p
forall p. Printer p => Char -> p
char7 Char
'\"' p -> p -> p
forall a. Semigroup a => a -> a -> a
<> p
p p -> p -> p
forall a. Semigroup a => a -> a -> a
<> Char -> p
forall p. Printer p => Char -> p
char7 Char
'\"'
{-# INLINE dquotes #-}

-- | Prepend all but the first element of a 'Traversable' with the
--   provided value, e.g.
--   @'punctuateL' /p/ [/x1/, /x2/, ..., /xN/] =
--      [/x1/, /p/ '<>' /x2/, ..., /p/ '<>' /xN/]@
punctuateL  (Traversable t, Printer p)  p  t p  t p
punctuateL :: p -> t p -> t p
punctuateL p
p =
  (Bool, t p) -> t p
forall a b. (a, b) -> b
snd ((Bool, t p) -> t p) -> (t p -> (Bool, t p)) -> t p -> t p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> p -> (Bool, p)) -> Bool -> t p -> (Bool, t p)
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumL (\Bool
f p
a  if Bool
f then (Bool
False, p
a) else (Bool
False, p
p p -> p -> p
forall a. Semigroup a => a -> a -> a
<> p
a)) Bool
True
{-# INLINE punctuateL #-}

-- | Append the provided value to all but the last element of a 'Traversable',
--   e.g. @'punctuateR' /p/ [/x1/, ..., /xN-1/, /xN/] =
--           [/x1/ '<>' /p/, ..., /xN-1/ '<>' /p/, /xN/]@
punctuateR  (Traversable t, Printer p)  p  t p  t p
punctuateR :: p -> t p -> t p
punctuateR p
p =
  (Bool, t p) -> t p
forall a b. (a, b) -> b
snd ((Bool, t p) -> t p) -> (t p -> (Bool, t p)) -> t p -> t p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> p -> (Bool, p)) -> Bool -> t p -> (Bool, t p)
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumR (\Bool
l p
a  if Bool
l then (Bool
False, p
a) else (Bool
False, p
a p -> p -> p
forall a. Semigroup a => a -> a -> a
<> p
p)) Bool
True
{-# INLINE punctuateR #-}

infixr 5 <->

-- | Printers that can produce multiple lines of text.
class Printer p  MultilinePrinter p where
  -- | Combine two lines. Must be associative, i.e.
  --   /x/ '<->' (/y/ '<->' /z/) = (/x/ '<->' /y/) '<->' /z/.
  (<->)  p  p  p

instance MultilinePrinter PrettyPrinter where
  PrettyPrinter
p₁ <-> :: PrettyPrinter -> PrettyPrinter -> PrettyPrinter
<-> PrettyPrinter
p₂ = Doc -> PrettyPrinter
PrettyPrinter 
            (Doc -> PrettyPrinter) -> Doc -> PrettyPrinter
forall a b. (a -> b) -> a -> b
$ Doc -> Doc -> Doc
(PP.$+$) (PrettyPrinter -> Doc
prettyPrinter PrettyPrinter
p₁) (PrettyPrinter -> Doc
prettyPrinter PrettyPrinter
p₂)
  {-# INLINE (<->) #-}

-- | Combine the items of a 'Foldable' data structure with '<->'.
lines  (MultilinePrinter p, Foldable f)  f p  p
lines :: f p -> p
lines = (p -> p -> p) -> f p -> p
forall (f :: * -> *) p.
(Foldable f, Printer p) =>
(p -> p -> p) -> f p -> p
fcat p -> p -> p
forall p. MultilinePrinter p => p -> p -> p
(<->)
{-# INLINE lines #-}

-- | Print the LF character (/'\n'/).
newLine  Printer p  p
newLine :: p
newLine = Char -> p
forall p. Printer p => Char -> p
char Char
'\n'
{-# INLINE newLine #-}

-- | Print CR (/'\r'/) followed by LF (/'\n'/).
crlf  Printer p  p
crlf :: p
crlf = Char -> p
forall p. Printer p => Char -> p
char Char
'\r' p -> p -> p
forall a. Semigroup a => a -> a -> a
<> Char -> p
forall p. Printer p => Char -> p
char Char
'\n'
{-# INLINE crlf #-}

-- | A multiline printer that combines lines with the provided function.
newtype LinePrinter p = LinePrinter { LinePrinter p -> (p -> p -> p) -> p
linePrinter  (p  p  p)  p }
                        deriving ( Typeable
#if __GLASGOW_HASKELL__ >= 706
                                 , (forall x. LinePrinter p -> Rep (LinePrinter p) x)
-> (forall x. Rep (LinePrinter p) x -> LinePrinter p)
-> Generic (LinePrinter p)
forall x. Rep (LinePrinter p) x -> LinePrinter p
forall x. LinePrinter p -> Rep (LinePrinter p) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall p x. Rep (LinePrinter p) x -> LinePrinter p
forall p x. LinePrinter p -> Rep (LinePrinter p) x
$cto :: forall p x. Rep (LinePrinter p) x -> LinePrinter p
$cfrom :: forall p x. LinePrinter p -> Rep (LinePrinter p) x
Generic
#endif
                                 )

instance IsString p  IsString (LinePrinter p) where
  fromString :: String -> LinePrinter p
fromString = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> (String -> (p -> p -> p) -> p) -> String -> LinePrinter p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p -> (p -> p -> p) -> p
forall a b. a -> b -> a
const (p -> (p -> p -> p) -> p)
-> (String -> p) -> String -> (p -> p -> p) -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> p
forall a. IsString a => String -> a
fromString
  {-# INLINE fromString #-}

instance Semigroup p  Semigroup (LinePrinter p) where
  LinePrinter p
x <> :: LinePrinter p -> LinePrinter p -> LinePrinter p
<> LinePrinter p
y = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> ((p -> p -> p) -> p) -> LinePrinter p
forall a b. (a -> b) -> a -> b
$ \p -> p -> p
l  LinePrinter p -> (p -> p -> p) -> p
forall p. LinePrinter p -> (p -> p -> p) -> p
linePrinter LinePrinter p
x p -> p -> p
l p -> p -> p
forall a. Semigroup a => a -> a -> a
S.<> LinePrinter p -> (p -> p -> p) -> p
forall p. LinePrinter p -> (p -> p -> p) -> p
linePrinter LinePrinter p
y p -> p -> p
l
  {-# INLINE (<>) #-}
  stimes :: b -> LinePrinter p -> LinePrinter p
stimes b
n LinePrinter p
x = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> ((p -> p -> p) -> p) -> LinePrinter p
forall a b. (a -> b) -> a -> b
$ b -> p -> p
forall a b. (Semigroup a, Integral b) => b -> a -> a
S.stimes b
n (p -> p) -> ((p -> p -> p) -> p) -> (p -> p -> p) -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LinePrinter p -> (p -> p -> p) -> p
forall p. LinePrinter p -> (p -> p -> p) -> p
linePrinter LinePrinter p
x
  {-# INLINE stimes #-}

instance Monoid p  Monoid (LinePrinter p) where
  mempty :: LinePrinter p
mempty = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> ((p -> p -> p) -> p) -> LinePrinter p
forall a b. (a -> b) -> a -> b
$ p -> (p -> p -> p) -> p
forall a b. a -> b -> a
const p
forall a. Monoid a => a
mempty
  {-# INLINE mempty #-}
  mappend :: LinePrinter p -> LinePrinter p -> LinePrinter p
mappend LinePrinter p
x LinePrinter p
y = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> ((p -> p -> p) -> p) -> LinePrinter p
forall a b. (a -> b) -> a -> b
$ \p -> p -> p
l  p -> p -> p
forall a. Monoid a => a -> a -> a
mappend (LinePrinter p -> (p -> p -> p) -> p
forall p. LinePrinter p -> (p -> p -> p) -> p
linePrinter LinePrinter p
x p -> p -> p
l) (LinePrinter p -> (p -> p -> p) -> p
forall p. LinePrinter p -> (p -> p -> p) -> p
linePrinter LinePrinter p
y p -> p -> p
l)
  {-# INLINE mappend #-}
  mconcat :: [LinePrinter p] -> LinePrinter p
mconcat [LinePrinter p]
xs = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> ((p -> p -> p) -> p) -> LinePrinter p
forall a b. (a -> b) -> a -> b
$ \p -> p -> p
l  [p] -> p
forall a. Monoid a => [a] -> a
mconcat ((LinePrinter p -> p) -> [LinePrinter p] -> [p]
forall a b. (a -> b) -> [a] -> [b]
map (\LinePrinter p
x  LinePrinter p -> (p -> p -> p) -> p
forall p. LinePrinter p -> (p -> p -> p) -> p
linePrinter LinePrinter p
x p -> p -> p
l) [LinePrinter p]
xs)
  {-# INLINE mconcat #-}

instance Printer p  Printer (LinePrinter p) where
  char :: Char -> LinePrinter p
char = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> (Char -> (p -> p -> p) -> p) -> Char -> LinePrinter p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p -> (p -> p -> p) -> p
forall a b. a -> b -> a
const (p -> (p -> p -> p) -> p)
-> (Char -> p) -> Char -> (p -> p -> p) -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> p
forall p. Printer p => Char -> p
char
  {-# INLINE char #-}
  char7 :: Char -> LinePrinter p
char7 = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> (Char -> (p -> p -> p) -> p) -> Char -> LinePrinter p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p -> (p -> p -> p) -> p
forall a b. a -> b -> a
const (p -> (p -> p -> p) -> p)
-> (Char -> p) -> Char -> (p -> p -> p) -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> p
forall p. Printer p => Char -> p
char7
  {-# INLINE char7 #-}
  string :: String -> LinePrinter p
string = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> (String -> (p -> p -> p) -> p) -> String -> LinePrinter p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p -> (p -> p -> p) -> p
forall a b. a -> b -> a
const (p -> (p -> p -> p) -> p)
-> (String -> p) -> String -> (p -> p -> p) -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> p
forall p. Printer p => String -> p
string
  {-# INLINE string #-}
  string7 :: String -> LinePrinter p
string7 = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> (String -> (p -> p -> p) -> p) -> String -> LinePrinter p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p -> (p -> p -> p) -> p
forall a b. a -> b -> a
const (p -> (p -> p -> p) -> p)
-> (String -> p) -> String -> (p -> p -> p) -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> p
forall p. Printer p => String -> p
string7
  {-# INLINE string7 #-}
  text :: Text -> LinePrinter p
text = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> (Text -> (p -> p -> p) -> p) -> Text -> LinePrinter p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p -> (p -> p -> p) -> p
forall a b. a -> b -> a
const (p -> (p -> p -> p) -> p)
-> (Text -> p) -> Text -> (p -> p -> p) -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> p
forall p. Printer p => Text -> p
text
  {-# INLINE text #-}
  lazyText :: Text -> LinePrinter p
lazyText = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> (Text -> (p -> p -> p) -> p) -> Text -> LinePrinter p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p -> (p -> p -> p) -> p
forall a b. a -> b -> a
const (p -> (p -> p -> p) -> p)
-> (Text -> p) -> Text -> (p -> p -> p) -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> p
forall p. Printer p => Text -> p
lazyText
  {-# INLINE lazyText #-}
  ascii :: ByteString -> LinePrinter p
ascii = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> (ByteString -> (p -> p -> p) -> p)
-> ByteString
-> LinePrinter p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p -> (p -> p -> p) -> p
forall a b. a -> b -> a
const (p -> (p -> p -> p) -> p)
-> (ByteString -> p) -> ByteString -> (p -> p -> p) -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> p
forall p. Printer p => ByteString -> p
ascii
  {-# INLINE ascii #-}
  lazyAscii :: ByteString -> LinePrinter p
lazyAscii = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> (ByteString -> (p -> p -> p) -> p)
-> ByteString
-> LinePrinter p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p -> (p -> p -> p) -> p
forall a b. a -> b -> a
const (p -> (p -> p -> p) -> p)
-> (ByteString -> p) -> ByteString -> (p -> p -> p) -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> p
forall p. Printer p => ByteString -> p
lazyAscii
  {-# INLINE lazyAscii #-}
  utf8 :: ByteString -> LinePrinter p
utf8 = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> (ByteString -> (p -> p -> p) -> p)
-> ByteString
-> LinePrinter p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p -> (p -> p -> p) -> p
forall a b. a -> b -> a
const (p -> (p -> p -> p) -> p)
-> (ByteString -> p) -> ByteString -> (p -> p -> p) -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> p
forall p. Printer p => ByteString -> p
utf8
  {-# INLINE utf8 #-}
  lazyUtf8 :: ByteString -> LinePrinter p
lazyUtf8 = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> (ByteString -> (p -> p -> p) -> p)
-> ByteString
-> LinePrinter p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p -> (p -> p -> p) -> p
forall a b. a -> b -> a
const (p -> (p -> p -> p) -> p)
-> (ByteString -> p) -> ByteString -> (p -> p -> p) -> p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> p
forall p. Printer p => ByteString -> p
lazyUtf8
  {-# INLINE lazyUtf8 #-}
  
instance Printer p  MultilinePrinter (LinePrinter p) where
  LinePrinter p
x <-> :: LinePrinter p -> LinePrinter p -> LinePrinter p
<-> LinePrinter p
y = ((p -> p -> p) -> p) -> LinePrinter p
forall p. ((p -> p -> p) -> p) -> LinePrinter p
LinePrinter (((p -> p -> p) -> p) -> LinePrinter p)
-> ((p -> p -> p) -> p) -> LinePrinter p
forall a b. (a -> b) -> a -> b
$ \p -> p -> p
l  p -> p -> p
l (LinePrinter p -> (p -> p -> p) -> p
forall p. LinePrinter p -> (p -> p -> p) -> p
linePrinter LinePrinter p
x p -> p -> p
l) (LinePrinter p -> (p -> p -> p) -> p
forall p. LinePrinter p -> (p -> p -> p) -> p
linePrinter LinePrinter p
y p -> p -> p
l)
  {-# INLINE (<->) #-}

-- | Separate lines with 'newLine'.
lfPrinter  Printer p  LinePrinter p  p
lfPrinter :: LinePrinter p -> p
lfPrinter LinePrinter p
p = LinePrinter p -> (p -> p -> p) -> p
forall p. LinePrinter p -> (p -> p -> p) -> p
linePrinter LinePrinter p
p (p -> p -> p -> p
forall p. Printer p => p -> p -> p -> p
separate p
forall p. Printer p => p
newLine)
{-# INLINE lfPrinter #-}

-- | Separate lines with 'crlf'.
crlfPrinter  Printer p  LinePrinter p  p
crlfPrinter :: LinePrinter p -> p
crlfPrinter LinePrinter p
p = LinePrinter p -> (p -> p -> p) -> p
forall p. LinePrinter p -> (p -> p -> p) -> p
linePrinter LinePrinter p
p (p -> p -> p -> p
forall p. Printer p => p -> p -> p -> p
separate p
forall p. Printer p => p
crlf)
{-# INLINE crlfPrinter #-}