| Copyright | (C) 2014-2016 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
- showbParen :: Bool -> Builder -> Builder
- showbSpace :: Builder
- class TextShow1 f where
- 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
- newtype FromStringShow1 f a = FromStringShow1 {
- fromStringShow1 :: f a
- newtype FromTextShow1 f a = FromTextShow1 {
- fromTextShow1 :: f a
- newtype FromStringShow2 f a b = FromStringShow2 {
- fromStringShow2 :: f a b
- newtype FromTextShow2 f a b = FromTextShow2 {
- fromTextShow2 :: f a b
- showsPrecToShowbPrec :: (Int -> a -> ShowS) -> Int -> a -> Builder
- showsToShowb :: (a -> ShowS) -> a -> Builder
- showbPrecToShowsPrec :: (Int -> a -> Builder) -> Int -> a -> ShowS
- showbToShows :: (a -> Builder) -> a -> ShowS
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
Converts a value to a strict Text. If you hand-define this, it should
satisfy:
showb=showbPrec0
Since: 2
Converts a list of values to a Builder. By default, this is defined as
'showbList = , but it can be overridden to allow
for specialized displaying of lists (e.g., lists of showbListWith showbChars).
Since: 2
Arguments
| :: Int | The operator precedence of the enclosing context (a number
from |
| -> a | The value to be converted to a strict |
| -> Text |
Converts a value to a strict Text with the given precedence. This
can be overridden for efficiency, but it should satisfy:
showtPrecp =toStrict.showtlPrecp
Since: 3
Converts a value to a strict Text. This can be overridden for
efficiency, but it should satisfy:
showt=toStrict.showtl
Since: 3
Converts a list of values to a strict Text. This can be overridden for
efficiency, but it should satisfy:
showtList=toStrict.showtlList
Since: 3
Arguments
| :: Int | The operator precedence of the enclosing context (a number
from |
| -> a | The value to be converted to a lazy |
| -> Text |
Converts a value to a lazy Text with the given precedence. This
can be overridden for efficiency, but it should satisfy:
showtlPrecp =toLazyText.showbPrecp
Since: 3
Converts a value to a lazy Text. This can be overridden for
efficiency, but it should satisfy:
showtl=toLazyText.showb
Since: 3
Converts a list of values to a lazy Text. This can be overridden for
efficiency, but it should satisfy:
showtlList=toLazyText.showbList
Since: 3
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
Minimal complete definition
Methods
liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder Source
showbPrec function for an application of the type constructor
based on showbPrec and showbList functions for the argument type.
Since: 3
liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [f a] -> Builder Source
Instances
| TextShow1 FromTextShow Source | |
| TextShow1 FromStringShow Source | |
| TextShow1 f => TextShow1 (FromTextShow1 * f) Source | |
| (TextShow2 f, TextShow a) => TextShow1 (FromTextShow2 * * f a) Source |
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
Minimal complete definition
Methods
liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> f a b -> Builder Source
showbPrec function for an application of the type constructor
based on showbPrec and showbList functions for the argument types.
Since: 3
liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [f a b] -> Builder Source
Instances
| TextShow2 f => TextShow2 (FromTextShow2 * * f) Source |
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) =showsToShowbshowsPrecp x
Since: 2
Constructors
| FromStringShow | |
Fields
| |
Instances
| Functor FromStringShow Source | |
| Foldable FromStringShow Source | |
| Traversable FromStringShow Source | |
| Generic1 FromStringShow Source | |
| Show1 FromStringShow Source | |
| TextShow1 FromStringShow Source | |
| Eq a => Eq (FromStringShow a) Source | |
| Data a => Data (FromStringShow a) Source | |
| Ord a => Ord (FromStringShow a) Source | |
| Read a => Read (FromStringShow a) Source | |
| Show a => Show (FromStringShow a) Source | |
| Generic (FromStringShow a) Source | |
| Lift a0 => Lift (FromStringShow a) Source | |
| Show a => TextShow (FromStringShow a) Source | |
| type Rep1 FromStringShow Source | |
| type Rep (FromStringShow a) Source |
newtype FromTextShow a Source
The String Show instance for FromTextShow is based on its
TextShow instance. That is,
showsPrec p (FromTextShowx) =showbToShowsshowbPrecp x
Since: 2
Constructors
| FromTextShow | |
Fields
| |
Instances
| Functor FromTextShow Source | |
| Foldable FromTextShow Source | |
| Traversable FromTextShow Source | |
| Generic1 FromTextShow Source | |
| Show1 FromTextShow Source | |
| TextShow1 FromTextShow Source | |
| Eq a => Eq (FromTextShow a) Source | |
| Data a => Data (FromTextShow a) Source | |
| Ord a => Ord (FromTextShow a) Source | |
| Read a => Read (FromTextShow a) Source | |
| TextShow a => Show (FromTextShow a) Source | |
| Generic (FromTextShow a) Source | |
| Lift a0 => Lift (FromTextShow a) Source | |
| TextShow a => TextShow (FromTextShow a) Source | |
| type Rep1 FromTextShow Source | |
| type Rep (FromTextShow a) Source |
newtype FromStringShow1 f a Source
The TextShow1 instance for FromStringShow1 is based on its String
Show1 instance. That is,
liftShowbPrecsp sl p (FromStringShow1x) =showsPrecToShowbPrec(liftShowsPrec(showbPrecToShowsPrecsp) (showbToShowssl)) p x
Since: 3
Constructors
| FromStringShow1 | |
Fields
| |
Instances
| Functor f => Functor (FromStringShow1 * f) Source | |
| Foldable f => Foldable (FromStringShow1 * f) Source | |
| Traversable f => Traversable (FromStringShow1 * f) Source | |
| Generic1 (FromStringShow1 * f) Source | |
| Show1 f => Show1 (FromStringShow1 * f) Source | |
| Eq (f a) => Eq (FromStringShow1 k f a) Source | |
| (Data (f a), Typeable (* -> *) f, Typeable * a) => Data (FromStringShow1 * f a) Source | |
| Ord (f a) => Ord (FromStringShow1 k f a) Source | |
| Read (f a) => Read (FromStringShow1 k f a) Source | |
| (Show1 f, Show a) => Show (FromStringShow1 * f a) Source | |
| Generic (FromStringShow1 k f a) Source | |
| Lift (f a) => Lift (FromStringShow1 k f a) Source | |
| type Rep1 (FromStringShow1 k f) Source | |
| type Rep (FromStringShow1 k f a) Source |
newtype FromTextShow1 f a Source
The String Show1 instance for FromTextShow1 is based on its
TextShow1 instance. That is,
liftShowsPrecsp sl p (FromTextShow1x) =showbPrecToShowsPrec(liftShowbPrec(showsPrecToShowbPrecsp) (showsToShowbsl)) p x
Since: 3
Constructors
| FromTextShow1 | |
Fields
| |
Instances
| Functor f => Functor (FromTextShow1 * f) Source | |
| Foldable f => Foldable (FromTextShow1 * f) Source | |
| Traversable f => Traversable (FromTextShow1 * f) Source | |
| Generic1 (FromTextShow1 * f) Source | |
| TextShow1 f => Show1 (FromTextShow1 * f) Source | |
| TextShow1 f => TextShow1 (FromTextShow1 * f) Source | |
| Eq (f a) => Eq (FromTextShow1 k f a) Source | |
| (Data (f a), Typeable (* -> *) f, Typeable * a) => Data (FromTextShow1 * f a) Source | |
| Ord (f a) => Ord (FromTextShow1 k f a) Source | |
| Read (f a) => Read (FromTextShow1 k f a) Source | |
| Generic (FromTextShow1 k f a) Source | |
| Lift (f a) => Lift (FromTextShow1 k f a) Source | |
| (TextShow1 f, TextShow a) => TextShow (FromTextShow1 * f a) Source | |
| type Rep1 (FromTextShow1 k f) Source | |
| type Rep (FromTextShow1 k f a) Source |
newtype FromStringShow2 f a b Source
The TextShow2 instance for FromStringShow2 is based on its String
Show2 instance. That is,
liftShowbPrec2sp1 sl1 sp2 sl2 p (FromStringShow2x) =showsPrecToShowbPrec(liftShowsPrec2(showbPrecToShowsPrecsp1) (showbToShowssl1) (showbPrecToShowsPrecsp2) (showbToShowssl2)) p x
Since: 3
Constructors
| FromStringShow2 | |
Fields
| |
Instances
| Bifunctor f0 => Bifunctor (FromStringShow2 * * f) Source | |
| Bitraversable f0 => Bitraversable (FromStringShow2 * * f) Source | |
| Bifoldable f0 => Bifoldable (FromStringShow2 * * f) Source | |
| Functor (f a) => Functor (FromStringShow2 k * f a) Source | |
| Foldable (f a) => Foldable (FromStringShow2 k * f a) Source | |
| Traversable (f a) => Traversable (FromStringShow2 k * f a) Source | |
| Generic1 (FromStringShow2 k * f a) Source | |
| Eq (f a b) => Eq (FromStringShow2 k k f a b) Source | |
| (Data (f a b), Typeable (* -> * -> *) f, Typeable * a, Typeable * b) => Data (FromStringShow2 * * f a b) Source | |
| Ord (f a b) => Ord (FromStringShow2 k k f a b) Source | |
| Read (f a b) => Read (FromStringShow2 k k f a b) Source | |
| Generic (FromStringShow2 k k f a b) Source | |
| Lift (f a b) => Lift (FromStringShow2 k k f a b) Source | |
| type Rep1 (FromStringShow2 k k1 f a) Source | |
| type Rep (FromStringShow2 k k1 f a b) Source |
newtype FromTextShow2 f a b Source
The String Show2 instance for FromTextShow2 is based on its
TextShow2 instance. That is,
liftShowsPrec2 sp1 sl1 sp2 sl2 p (FromTextShow2x) =showbPrecToShowsPrec(liftShowbPrec2(showsPrecToShowbPrecsp1) (showsToShowbsl1) (showsPrecToShowbPrecsp2) (showsToShowbsl2)) p x
Since: 3
Constructors
| FromTextShow2 | |
Fields
| |
Instances
showsPrecToShowbPrec :: (Int -> a -> ShowS) -> Int -> a -> Builder Source
Convert a precedence-aware ShowS-based show function to a Builder-based one.
Since: 3
showsToShowb :: (a -> ShowS) -> a -> Builder Source
Convert a ShowS-based show function to a Builder-based one.
Since: 3
showbPrecToShowsPrec :: (Int -> a -> Builder) -> Int -> a -> ShowS Source
Convert a precedence-aware Builder-based show function to a ShowS-based one.
Since: 3
showbToShows :: (a -> Builder) -> a -> ShowS Source
Convert a Builder-based show function to a ShowS-based one.
Since: 3