Safe Haskell | None |
---|---|
Language | Haskell2010 |
Monoids with a homomorphism from String
to themselves.
Synopsis
- class (IsString p, Semigroup p, Monoid p) => Printer p where
- char :: Char -> p
- char7 :: Char -> p
- string :: String -> p
- string7 :: String -> p
- text :: Text -> p
- lazyText :: Text -> p
- ascii :: ByteString -> p
- lazyAscii :: ByteString -> p
- utf8 :: ByteString -> p
- lazyUtf8 :: ByteString -> p
- newtype StringBuilder = StringBuilder {
- stringBuilder :: String -> String
- buildString :: StringBuilder -> String
- buildText :: Builder -> Text
- buildLazyText :: Builder -> Text
- newtype AsciiBuilder = AsciiBuilder {}
- buildAscii :: AsciiBuilder -> ByteString
- buildLazyAscii :: AsciiBuilder -> ByteString
- newtype Utf8Builder = Utf8Builder {}
- buildUtf8 :: Utf8Builder -> ByteString
- buildLazyUtf8 :: Utf8Builder -> ByteString
- newtype PrettyPrinter = PrettyPrinter {
- prettyPrinter :: Doc
- renderPretty :: PrettyPrinter -> String
- (<>) :: Semigroup a => a -> a -> a
- hcat :: (Printer p, Foldable f) => f p -> p
- fcat :: (Foldable f, Printer p) => (p -> p -> p) -> f p -> p
- separate :: Printer p => p -> p -> p -> p
- (<+>) :: Printer p => p -> p -> p
- hsep :: (Printer p, Foldable f) => f p -> p
- fsep :: (Foldable f, Printer p) => p -> f p -> p
- list :: (Foldable f, Printer p) => f p -> p
- parens :: Printer p => p -> p
- brackets :: Printer p => p -> p
- braces :: Printer p => p -> p
- angles :: Printer p => p -> p
- squotes :: Printer p => p -> p
- dquotes :: Printer p => p -> p
- punctuateL :: (Traversable t, Printer p) => p -> t p -> t p
- punctuateR :: (Traversable t, Printer p) => p -> t p -> t p
- class Printer p => MultilinePrinter p where
- (<->) :: p -> p -> p
- lines :: (MultilinePrinter p, Foldable f) => f p -> p
- newLine :: Printer p => p
- crlf :: Printer p => p
- newtype LinePrinter p = LinePrinter {
- linePrinter :: (p -> p -> p) -> p
- lfPrinter :: Printer p => LinePrinter p -> p
- crlfPrinter :: Printer p => LinePrinter p -> p
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.
and
string
mempty
= mempty
.
Other operations must be monoid homomorphisms that are eqiuvalent (but
possibly faster) to the composition of mappend
(string
x) (string
y) = string
(mappend
x y)string
and the corresponding
embedding, e.g.
.text
= string
. unpack
Nothing
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
.
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
Builders
newtype StringBuilder Source #
A simple string builder as used by Show
.
Instances
buildString :: StringBuilder -> String Source #
buildLazyText :: Builder -> Text Source #
newtype AsciiBuilder Source #
Use this builder when you are sure that only ASCII characters will get printed to it.
Instances
buildAscii :: AsciiBuilder -> ByteString Source #
newtype Utf8Builder Source #
UTF-8 lazy ByteString
builder.
Instances
buildUtf8 :: Utf8Builder -> ByteString Source #
newtype PrettyPrinter Source #
Instances
renderPretty :: PrettyPrinter -> String Source #
An alias for render
. prettyPrinter
Combinators
:: Printer p | |
=> p | The separator |
-> p | |
-> p | |
-> p |
Concatenate two Printer
s with a separator between them.
(<+>) :: Printer p => p -> p -> p infixr 6 Source #
Concatenate two Printer
s 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.
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.
Instances
MultilinePrinter PrettyPrinter Source # | |
Defined in Text.Printer (<->) :: PrettyPrinter -> PrettyPrinter -> PrettyPrinter Source # | |
Printer p => MultilinePrinter (LinePrinter p) Source # | |
Defined in Text.Printer (<->) :: LinePrinter p -> LinePrinter p -> LinePrinter p Source # |
lines :: (MultilinePrinter p, Foldable f) => f p -> p Source #
newtype LinePrinter p Source #
A multiline printer that combines lines with the provided function.
LinePrinter | |
|
Instances
crlfPrinter :: Printer p => LinePrinter p -> p Source #
Separate lines with crlf
.