text-printer-0.5: Abstract interface for text builders/printers.

Safe HaskellNone
LanguageHaskell2010

Text.Printer

Contents

Description

Monoids with a homomorphism from String to themselves.

Synopsis

The class

class (IsString p, Semigroup p, Monoid p) => Printer p where Source #

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 . unpack.

Methods

char :: Char -> p Source #

Print a character. char c must be equivalent to string [c], but hopefully is faster.

char7 :: Char -> p Source #

Print an ASCII character, can be faster than char.

string :: String -> p Source #

Print a string.

string7 :: String -> p Source #

Print an ASCII string, can be faster than string.

text :: Text -> p Source #

Print a Text.

lazyText :: Text -> p Source #

Print a lazy Text.

ascii :: ByteString -> p Source #

Print an ASCII ByteString.

lazyAscii :: ByteString -> p Source #

Print a lazy ASCII ByteString.

utf8 :: ByteString -> p Source #

Print a UTF-8 ByteString.

lazyUtf8 :: ByteString -> p Source #

Print a lazy UTF-8 ByteString

Instances

Printer String Source # 
Printer Builder Source # 
Printer PrettyPrinter Source # 
Printer Utf8Builder Source # 
Printer AsciiBuilder Source # 
Printer StringBuilder Source # 
Printer p => Printer (LinePrinter p) Source # 

Builders

newtype StringBuilder Source #

A simple string builder as used by Show.

Constructors

StringBuilder 

newtype AsciiBuilder Source #

Use this builder when you are sure that only ASCII characters will get printed to it.

Constructors

AsciiBuilder 

newtype PrettyPrinter Source #

Constructors

PrettyPrinter 

Fields

Instances

IsString PrettyPrinter Source # 
Generic PrettyPrinter Source # 

Associated Types

type Rep PrettyPrinter :: * -> * #

Semigroup PrettyPrinter Source # 
Monoid PrettyPrinter Source # 
MultilinePrinter PrettyPrinter Source # 
Printer PrettyPrinter Source # 
type Rep PrettyPrinter Source # 
type Rep PrettyPrinter = D1 (MetaData "PrettyPrinter" "Text.Printer" "text-printer-0.5-6BKOWR0cejT2opc7OlwZvB" True) (C1 (MetaCons "PrettyPrinter" PrefixI True) (S1 (MetaSel (Just Symbol "prettyPrinter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Doc)))

Combinators

(<>) :: Monoid m => m -> m -> m infixr 6 #

An infix synonym for mappend.

Since: 4.5.0.0

hcat :: (Printer p, Foldable f) => f p -> p Source #

mconcat for Foldable data structures.

fcat :: (Foldable f, Printer p) => (p -> p -> p) -> f p -> p Source #

Combine the items of a Foldable data structure using the provided function. If the data structure is empty, mempty is returned.

separate Source #

Arguments

:: Printer p 
=> p

The separator

-> p 
-> p 
-> p 

Concatenate two Printers with a separator between them.

(<+>) :: Printer p => p -> p -> p infixr 6 Source #

Concatenate two Printers with a space between them.

hsep :: (Printer p, Foldable f) => f p -> p Source #

Concatenate the items of a Foldable data structure with spaces between them.

fsep :: (Foldable f, Printer p) => p -> f p -> p Source #

A shorthand for fcat . separate.

list :: (Foldable f, Printer p) => f p -> p Source #

Concatenate the items of a Foldable data structure with commas between them.

  list = fsep (char7 ',')

parens :: Printer p => p -> p Source #

Enclose a Printer with parentheses.

brackets :: Printer p => p -> p Source #

Enclose a Printer with square brackets.

braces :: Printer p => p -> p Source #

Enclose a Printer with curly braces.

angles :: Printer p => p -> p Source #

Enclose a Printer with angle brackets.

squotes :: Printer p => p -> p Source #

Enclose a Printer with single quotes.

dquotes :: Printer p => p -> p Source #

Enclose a Printer with double quotes.

punctuateL :: (Traversable t, Printer p) => p -> t p -> t p Source #

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]

punctuateR :: (Traversable t, Printer p) => p -> t p -> t p Source #

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]

Multiline printers

class Printer p => MultilinePrinter p where Source #

Printers that can produce multiple lines of text.

Minimal complete definition

(<->)

Methods

(<->) :: p -> p -> p infixr 5 Source #

Combine two lines. Must be associative, i.e. x <-> (y <-> z) = (x <-> y) <-> z.

lines :: (MultilinePrinter p, Foldable f) => f p -> p Source #

Combine the items of a Foldable data structure with <->.

newLine :: Printer p => p Source #

Print the LF character ('\n').

crlf :: Printer p => p Source #

Print CR ('\r') followed by LF ('\n').

newtype LinePrinter p Source #

A multiline printer that combines lines with the provided function.

Constructors

LinePrinter 

Fields

Instances

IsString p => IsString (LinePrinter p) Source # 
Generic (LinePrinter p) Source # 

Associated Types

type Rep (LinePrinter p) :: * -> * #

Methods

from :: LinePrinter p -> Rep (LinePrinter p) x #

to :: Rep (LinePrinter p) x -> LinePrinter p #

Semigroup p => Semigroup (LinePrinter p) Source # 
Monoid p => Monoid (LinePrinter p) Source # 
Printer p => MultilinePrinter (LinePrinter p) Source # 
Printer p => Printer (LinePrinter p) Source # 
type Rep (LinePrinter p) Source # 
type Rep (LinePrinter p) = D1 (MetaData "LinePrinter" "Text.Printer" "text-printer-0.5-6BKOWR0cejT2opc7OlwZvB" True) (C1 (MetaCons "LinePrinter" PrefixI True) (S1 (MetaSel (Just Symbol "linePrinter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((p -> p -> p) -> p))))

lfPrinter :: Printer p => LinePrinter p -> p Source #

Separate lines with newLine.

crlfPrinter :: Printer p => LinePrinter p -> p Source #

Separate lines with crlf.