| Safe Haskell | None |
|---|
Text.Printer
Description
Monoids with a homomorphism from String to themselves.
- class (IsString 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
- newtype AsciiBuilder = AsciiBuilder {}
- buildAscii :: AsciiBuilder -> ByteString
- newtype Utf8Builder = Utf8Builder {}
- buildUtf8 :: Utf8Builder -> ByteString
- (<>) :: Monoid m => m -> m -> m
- 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
- unsignedBinary :: (Num α, Bits α, Printer p) => α -> p
- unsignedOctal :: (Num α, Bits α, Printer p) => α -> p
- unsignedUpHex :: (Num α, Bits α, Printer p) => α -> p
- unsignedLowHex :: (Num α, Bits α, Printer p) => α -> p
- unsignedDecimal :: (Integral α, Printer p) => α -> p
- binary' :: (Ord α, Num α, Bits α, Printer p) => p -> p -> p -> α -> p
- binary :: (Ord α, Num α, Bits α, Printer p) => α -> p
- octal' :: (Ord α, Num α, Bits α, Printer p) => p -> p -> p -> α -> p
- octal :: (Ord α, Num α, Bits α, Printer p) => α -> p
- lowHex' :: (Ord α, Num α, Bits α, Printer p) => p -> p -> p -> α -> p
- lowHex :: (Ord α, Num α, Bits α, Printer p) => α -> p
- upHex' :: (Ord α, Num α, Bits α, Printer p) => p -> p -> p -> α -> p
- upHex :: (Ord α, Num α, Bits α, Printer p) => α -> p
- decimal' :: (Integral α, Printer p) => p -> p -> p -> α -> p
- decimal :: (Integral α, Printer p) => α -> 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
- class Printable α where
- defaultPrintList :: (Printable α, Printer p) => [α] -> p
- toString :: Printable α => α -> String
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. 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
Methods
Print an ASCII character, can be faster than char.
Print a string.
Print an ASCII string, can be faster than string.
Print a Text.
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
Instances
Builders
newtype StringBuilder Source
A simple string builder as used by Show.
Constructors
| StringBuilder | |
Fields
| |
newtype AsciiBuilder Source
Use this builder when you are sure that only ASCII characters will get printed to it.
Constructors
| AsciiBuilder | |
Fields | |
Combinators
Arguments
| :: Printer p | |
| => p | The separator |
| -> p | |
| -> p | |
| -> p |
Concatenate two Printers with a separator between them.
hsep :: (Printer p, Foldable f) => f p -> pSource
Concatenate the items of a Foldable data structure
with spaces between them.
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]
Number printers
unsignedBinary :: (Num α, Bits α, Printer p) => α -> pSource
Print an unsigned number in the binary numeral system.
unsignedOctal :: (Num α, Bits α, Printer p) => α -> pSource
Print an unsigned number in the octal numeral system.
unsignedUpHex :: (Num α, Bits α, Printer p) => α -> pSource
Print an unsigned number in the hexadecimal numeral system using upper case digits.
unsignedLowHex :: (Num α, Bits α, Printer p) => α -> pSource
Print an unsigned number in the hexadecimal numeral system using lower case digits.
unsignedDecimal :: (Integral α, Printer p) => α -> pSource
Print an unsigned number in the decimal numeral system.
Arguments
| :: (Ord α, Num α, Bits α, Printer p) | |
| => p | Prefix for negative values |
| -> p | Prefix for the zero |
| -> p | Prefix for positive values |
| -> α | |
| -> p |
Print a number in the binary numeral system.
binary :: (Ord α, Num α, Bits α, Printer p) => α -> pSource
Print a number in the binary numeral system. Negative values are prefixed with "-0b", postive values are prefixed with "0b".
Arguments
| :: (Ord α, Num α, Bits α, Printer p) | |
| => p | Prefix for negative values |
| -> p | Prefix for the zero |
| -> p | Prefix for positive values |
| -> α | |
| -> p |
Print a number in the octal numeral system.
octal :: (Ord α, Num α, Bits α, Printer p) => α -> pSource
Print a number in the octal numeral system. Negative values are prefixed with "-0o", postive values are prefixed with "0o".
Arguments
| :: (Ord α, Num α, Bits α, Printer p) | |
| => p | Prefix for negative values |
| -> p | Prefix for the zero |
| -> p | Prefix for postive values |
| -> α | |
| -> p |
Print a number in the hexadecimal numeral system using lower case digits.
lowHex :: (Ord α, Num α, Bits α, Printer p) => α -> pSource
Print a number in the hexadecimal numeral system using lower case digits. Negative values are prefixed with "-0x", positive values are prefixed with "0x".
Arguments
| :: (Ord α, Num α, Bits α, Printer p) | |
| => p | Prefix for negative values |
| -> p | Prefix for the zero |
| -> p | Prefix for postive values |
| -> α | |
| -> p |
Print a number in the hexadecimal numeral system using upper case digits.
upHex :: (Ord α, Num α, Bits α, Printer p) => α -> pSource
Print a number in the hexadecimal numeral system using upper case digits. Negative values are prefixed with "-0x", positive values are prefixed with "0x".
Arguments
| :: (Integral α, Printer p) | |
| => p | Prefix for negative values |
| -> p | Prefix for the zero |
| -> p | Prefix for postive values |
| -> α | |
| -> p |
Print a number in the decimal numeral system.
decimal :: (Integral α, Printer p) => α -> pSource
Print a number in the decimal numeral system. Negative values are prefixed with "-".
Multiline printers
class Printer p => MultilinePrinter p whereSource
Printers that can produce multiple lines of text.
Methods
Instances
lines :: (MultilinePrinter p, Foldable f) => f p -> pSource
newtype LinePrinter p Source
A multiline printer that combines lines with the provided function.
Constructors
| LinePrinter | |
Fields
| |
Instances
| Typeable1 LinePrinter | |
| IsString p => IsString (LinePrinter p) | |
| Monoid p => Monoid (LinePrinter p) | |
| Printer p => MultilinePrinter (LinePrinter p) | |
| Printer p => Printer (LinePrinter p) |
lfPrinter :: Printer p => LinePrinter p -> pSource
Separate lines with newLine.
crlfPrinter :: Printer p => LinePrinter p -> pSource
Separate lines with crlf.
Default printers
The default printer for values of a type.
Instances
| Printable Char | |
| Printable Double | |
| Printable Float | |
| Printable Int | |
| Printable Int8 | |
| Printable Int16 | |
| Printable Int32 | |
| Printable Int64 | |
| Printable Integer | |
| Printable Word | |
| Printable Word8 | |
| Printable Word16 | |
| Printable Word32 | |
| Printable Word64 | |
| Printable () | |
| Printable Text | |
| Printable Text | |
| Printable α => Printable [α] | |
| (Printable α, Printable β) => Printable (α, β) | |
| (Printable α, Printable β, Printable γ) => Printable (α, β, γ) | |
| (Printable α, Printable β, Printable γ, Printable δ) => Printable (α, β, γ, δ) |
defaultPrintList :: (Printable α, Printer p) => [α] -> pSource
toString :: Printable α => α -> StringSource
Print a Printable value via StringBuilder, i.e.
.
toString = buildString . print