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

Safe HaskellNone

Text.Printer

Contents

Description

Monoids with a homomorphism from String to themselves.

Synopsis

The class

class (IsString p, Monoid p) => Printer p whereSource

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 -> pSource

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

char7 :: Char -> pSource

Print an ASCII character, can be faster than char.

string :: String -> pSource

Print a string.

string7 :: String -> pSource

Print an ASCII string, can be faster than string.

text :: Text -> pSource

Print a Text.

lazyText :: Text -> pSource

Print a lazy Text.

ascii :: ByteString -> pSource

Print an ASCII ByteString.

lazyAscii :: ByteString -> pSource

Print a lazy ASCII ByteString.

utf8 :: ByteString -> pSource

Print a UTF-8 ByteString.

lazyUtf8 :: ByteString -> pSource

Print a lazy UTF-8 ByteString

Builders

newtype AsciiBuilder Source

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

Constructors

AsciiBuilder 

Combinators

(<>) :: Monoid m => m -> m -> m

An infix synonym for mappend.

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

mconcat for Foldable data structures.

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

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

separateSource

Arguments

:: Printer p 
=> p

The separator

-> p 
-> p 
-> p 

Concatenate two Printers with a separator between them.

(<+>) :: Printer p => p -> p -> pSource

Concatenate two Printers with a space between them.

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

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

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

A shorthand for fcat . separate.

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

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

   list = fsep (char7 ',')

parens :: Printer p => p -> pSource

Enclose a Printer with parentheses.

brackets :: Printer p => p -> pSource

Enclose a Printer with square brackets.

braces :: Printer p => p -> pSource

Enclose a Printer with curly braces.

angles :: Printer p => p -> pSource

Enclose a Printer with angle brackets.

squotes :: Printer p => p -> pSource

Enclose a Printer with single quotes.

dquotes :: Printer p => p -> pSource

Enclose a Printer with double quotes.

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

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 pSource

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 whereSource

Printers that can produce multiple lines of text.

Methods

(<->) :: p -> p -> pSource

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

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

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

newLine :: Printer p => pSource

Print the LF character ('\n').

crlf :: Printer p => pSource

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

newtype LinePrinter p Source

A multiline printer that combines lines with the provided function.

Constructors

LinePrinter 

Fields

linePrinter :: (p -> p -> p) -> p
 

lfPrinter :: Printer p => LinePrinter p -> pSource

Separate lines with newLine.

crlfPrinter :: Printer p => LinePrinter p -> pSource

Separate lines with crlf.