| Copyright | (C) 2014-2015 Ryan Scott |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Ryan Scott |
| Stability | Provisional |
| Portability | GHC |
| Safe Haskell | None |
| Language | Haskell2010 |
TextShow
Contents
Description
Efficiently convert from values to Text via Builders.
Since: 2
- class TextShow a where
- showt :: TextShow a => a -> Text
- showtl :: TextShow a => a -> Text
- showtPrec :: TextShow a => Int -> a -> Text
- showtlPrec :: TextShow a => Int -> a -> Text
- showtList :: TextShow a => [a] -> Text
- showtlList :: TextShow a => [a] -> Text
- showbParen :: Bool -> Builder -> Builder
- showbSpace :: Builder
- class TextShow1 f where
- showbPrecWith :: (Int -> a -> Builder) -> Int -> f a -> Builder
- showbPrec1 :: (TextShow1 f, TextShow a) => Int -> f a -> Builder
- showbUnaryWith :: (Int -> a -> Builder) -> Builder -> Int -> a -> Builder
- class TextShow2 f where
- showbPrec2 :: (TextShow2 f, TextShow a, TextShow b) => Int -> f a b -> Builder
- showbBinaryWith :: (Int -> a -> Builder) -> (Int -> b -> Builder) -> Builder -> Int -> a -> b -> Builder
- data Builder :: *
- toText :: Builder -> Text
- toLazyText :: Builder -> Text
- toLazyTextWith :: Int -> Builder -> Text
- toString :: Builder -> String
- singleton :: Char -> Builder
- fromText :: Text -> Builder
- fromLazyText :: Text -> Builder
- fromString :: String -> Builder
- flush :: Builder
- lengthB :: Builder -> Int64
- unlinesB :: [Builder] -> Builder
- unwordsB :: [Builder] -> Builder
- printT :: TextShow a => a -> IO ()
- printTL :: TextShow a => a -> IO ()
- hPrintT :: TextShow a => Handle -> a -> IO ()
- hPrintTL :: TextShow a => Handle -> a -> IO ()
- newtype FromStringShow a = FromStringShow {
- fromStringShow :: a
- newtype FromTextShow a = FromTextShow {
- fromTextShow :: a
The TextShow classes
TextShow
Conversion of values to Text. Because there are both strict and lazy Text
variants, the TextShow class deliberately avoids using Text in its functions.
Instead, showbPrec, showb, and showbList all return Builder, an
efficient intermediate form that can be converted to either kind of Text.
Builder is a Monoid, so it is useful to use the mappend (or <>) function
to combine Builders when creating TextShow instances. As an example:
import Data.Monoid
import TextShow
data Example = Example Int Int
instance TextShow Example where
showb (Example i1 i2) = showb i1 <> showbSpace <> showb i2
If you do not want to create TextShow instances manually, you can alternatively
use the TextShow.TH module to automatically generate default TextShow
instances using Template Haskell, or the TextShow.Generic module to
quickly define TextShow instances using genericShowbPrec.
Since: 2
Methods
Arguments
| :: Int | The operator precedence of the enclosing context (a number
from |
| -> a | The value to be converted to a |
| -> Builder |
Convert a value to a Builder with the given predence.
Since: 2
A specialized variant of showbPrec using precedence context zero.
Since: 2
showbList :: [a] -> Builder Source
Allows for specialized display of lists. This is used, for example, when
showing lists of Chars.
Since: 2
Instances
showtPrec :: TextShow a => Int -> a -> Text Source
Constructs a strict Text from a single value with the given precedence.
Since: 2
showtlPrec :: TextShow a => Int -> a -> Text Source
Constructs a lazy Text from a single value with the given precedence.
Since: 2
showtlList :: TextShow a => [a] -> Text Source
Construct a lazy Text from a list of values.
Since: 2
showbParen :: Bool -> Builder -> Builder Source
Construct a Builder containing a single space character.
Since: 2
TextShow1
class TextShow1 f where Source
Lifting of the TextShow class to unary type constructors.
Since: 2
Methods
showbPrecWith :: (Int -> a -> Builder) -> Int -> f a -> Builder Source
Lifts a showbPrec function through the type constructor.
Since: 2
Instances
showbPrec1 :: (TextShow1 f, TextShow a) => Int -> f a -> Builder Source
Lift the standard showbPrec function through the type constructor.
Since: 2
showbUnaryWith :: (Int -> a -> Builder) -> Builder -> Int -> a -> Builder Source
produces the showbUnaryWith sp n p xBuilder representation of a unary data
constructor with name n and argument x, in precedence context p, using the
function sp to show occurrences of the type argument.
Since: 2
TextShow2
class TextShow2 f where Source
Lifting of the TextShow class to binary type constructors.
Since: 2
Methods
showbPrecWith2 :: (Int -> a -> Builder) -> (Int -> b -> Builder) -> Int -> f a b -> Builder Source
Lifts showbPrec functions through the type constructor.
Since: 2
Instances
showbPrec2 :: (TextShow2 f, TextShow a, TextShow b) => Int -> f a b -> Builder Source
Lift two showbPrec functions through the type constructor.
Since: 2
showbBinaryWith :: (Int -> a -> Builder) -> (Int -> b -> Builder) -> Builder -> Int -> a -> b -> Builder Source
produces the showbBinaryWith sp n p x yBuilder representation of a binary
data constructor with name n and arguments x and y, in precedence context
p, using the functions sp1 and sp2 to show occurrences of the type arguments.
Since: 2
Builders
The Builder type
data Builder :: *
A Builder is an efficient way to build lazy Text values.
There are several functions for constructing builders, but only one
to inspect them: to extract any data, you have to turn them into
lazy Text values using toLazyText.
Internally, a builder constructs a lazy Text by filling arrays
piece by piece. As each buffer is filled, it is 'popped' off, to
become a new chunk of the resulting lazy Text. All this is
hidden from the user of the Builder.
toLazyText :: Builder -> Text
O(n). Extract a lazy Text from a Builder with a default
buffer size. The construction work takes place if and when the
relevant part of the lazy Text is demanded.
toLazyTextWith :: Int -> Builder -> Text
O(n). Extract a lazy Text from a Builder, using the given
size for the initial buffer. The construction work takes place if
and when the relevant part of the lazy Text is demanded.
If the initial buffer is too small to hold all data, subsequent buffers will be the default buffer size.
Constructing Builders
O(1). A Builder taking a single character, satisfying
toLazyText(singletonc) =singletonc
O(1). A Builder taking a Text, satisfying
toLazyText(fromTextt) =fromChunks[t]
fromLazyText :: Text -> Builder
O(1). A Builder taking a lazy Text, satisfying
toLazyText(fromLazyTextt) = t
fromString :: String -> Builder
O(1). A Builder taking a String, satisfying
toLazyText(fromStrings) =fromChunks[S.pack s]
Flushing the buffer state
O(1). Pop the strict Text we have constructed so far, if any,
yielding a new chunk in the result lazy Text.
Builder utility functions
unlinesB :: [Builder] -> Builder Source
Merges several Builders, separating them by newlines.
Since: 2
Printing values
printT :: TextShow a => a -> IO () Source
Writes a value's strict Text representation to the standard output, followed
by a newline.
Since: 2
printTL :: TextShow a => a -> IO () Source
Writes a value's lazy Text representation to the standard output, followed
by a newline.
Since: 2
hPrintT :: TextShow a => Handle -> a -> IO () Source
Writes a value's strict Text representation to a file handle, followed
by a newline.
Since: 2
hPrintTL :: TextShow a => Handle -> a -> IO () Source
Writes a value's lazy Text representation to a file handle, followed
by a newline.
Since: 2
Conversion between TextShow and string Show
newtype FromStringShow a Source
The TextShow instance for FromStringShow is based on its String
Show instance. That is,
showbPrec p (FromStringShowx) =fromString(showsPrec p x "")
Since: 2
Constructors
| FromStringShow | |
Fields
| |
Instances
| Functor FromStringShow | |
| Foldable FromStringShow | |
| Traversable FromStringShow | |
| Generic1 FromStringShow | |
| Eq a => Eq (FromStringShow a) | |
| Data a => Data (FromStringShow a) | |
| Ord a => Ord (FromStringShow a) | |
| Read a => Read (FromStringShow a) | |
| Show a => Show (FromStringShow a) | |
| Generic (FromStringShow a) | |
| Show a => TextShow (FromStringShow a) | |
| Typeable (* -> *) FromStringShow | |
| Typeable (k -> FromStringShow k) (FromStringShow k) | |
| type Rep1 FromStringShow | |
| type Rep (FromStringShow a) |
newtype FromTextShow a Source
The String Show instance for FromTextShow is based on its
TextShow instance. That is,
showsPrec p (FromTextShowx) =showString(toString(showbPrec p x))
Since: 2
Constructors
| FromTextShow | |
Fields
| |
Instances
| Functor FromTextShow | |
| Foldable FromTextShow | |
| Traversable FromTextShow | |
| Generic1 FromTextShow | |
| TextShow1 FromTextShow | |
| Eq a => Eq (FromTextShow a) | |
| Data a => Data (FromTextShow a) | |
| Ord a => Ord (FromTextShow a) | |
| Read a => Read (FromTextShow a) | |
| TextShow a => Show (FromTextShow a) | |
| Generic (FromTextShow a) | |
| TextShow a => TextShow (FromTextShow a) | |
| Typeable (* -> *) FromTextShow | |
| Typeable (k -> FromTextShow k) (FromTextShow k) | |
| type Rep1 FromTextShow | |
| type Rep (FromTextShow a) |