text-show-3.2.1: Efficient conversion of values into Text

Copyright(C) 2014-2016 Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerRyan Scott
StabilityProvisional
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

TextShow

Contents

Description

Efficiently convert from values to Text via Builders.

Since: 2

Synopsis

The TextShow classes

TextShow

class TextShow a where Source

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

Minimal complete definition

showbPrec | showb

Methods

showbPrec Source

Arguments

:: Int

The operator precedence of the enclosing context (a number from 0 to 11). Function application has precedence 10.

-> a

The value to be converted to a Builder.

-> Builder 

Convert a value to a Builder with the given predence.

Since: 2

showb Source

Arguments

:: a

The value to be converted to a Builder.

-> Builder 

Converts a value to a strict Text. If you hand-define this, it should satisfy:

showb = showbPrec 0

Since: 2

showbList Source

Arguments

:: [a]

The list of values to be converted to a Builder.

-> Builder 

Converts a list of values to a Builder. By default, this is defined as 'showbList = showbListWith showb, but it can be overridden to allow for specialized displaying of lists (e.g., lists of Chars).

Since: 2

showtPrec Source

Arguments

:: Int

The operator precedence of the enclosing context (a number from 0 to 11). Function application has precedence 10.

-> a

The value to be converted to a strict Text.

-> Text 

Converts a value to a strict Text with the given precedence. This can be overridden for efficiency, but it should satisfy:

showtPrec p = toStrict . showtlPrec p

Since: 3

showt Source

Arguments

:: a

The value to be converted to a strict Text.

-> Text 

Converts a value to a strict Text. This can be overridden for efficiency, but it should satisfy:

showt = toStrict . showtl

Since: 3

showtList Source

Arguments

:: [a]

The list of values to be converted to a strict Text.

-> Text 

Converts a list of values to a strict Text. This can be overridden for efficiency, but it should satisfy:

showtList = toStrict . showtlList

Since: 3

showtlPrec Source

Arguments

:: Int

The operator precedence of the enclosing context (a number from 0 to 11). Function application has precedence 10.

-> a

The value to be converted to a lazy Text.

-> Text 

Converts a value to a lazy Text with the given precedence. This can be overridden for efficiency, but it should satisfy:

showtlPrec p = toLazyText . showbPrec p

Since: 3

showtl Source

Arguments

:: a

The value to be converted to a lazy Text.

-> Text 

Converts a value to a lazy Text. This can be overridden for efficiency, but it should satisfy:

showtl = toLazyText . showb

Since: 3

showtlList Source

Arguments

:: [a]

The list of values to be converted to a lazy Text.

-> Text 

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

Surrounds Builder output with parentheses if the Bool parameter is True.

Since: 2

showbSpace :: 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

liftShowbPrec

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

showbList function for an application of the type constructor based on showbPrec and showbList functions for the argument type. The default implementation using standard list syntax is correct for most types.

Since: 3

showbPrec1 :: (TextShow1 f, TextShow a) => Int -> f a -> Builder Source

Lift the standard showbPrec and showbList functions through the type constructor.

Since: 2

showbUnaryWith :: (Int -> a -> Builder) -> Builder -> Int -> a -> Builder Source

showbUnaryWith sp n p x produces the Builder 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

liftShowbPrec2

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

showbList function for an application of the type constructor based on showbPrec and showbList functions for the argument types. The default implementation using standard list syntax is correct for most types.

Since: 3

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

showbBinaryWith sp n p x y produces the Builder 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.

toText :: Builder -> Text Source

Convert a Builder to a strict Text.

Since: 2

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.

toString :: Builder -> String Source

Convert a Builder to a String (without surrounding it with double quotes, as show would).

Since: 2

Constructing Builders

singleton :: Char -> Builder

O(1). A Builder taking a single character, satisfying

fromText :: Text -> Builder

O(1). A Builder taking a Text, satisfying

fromLazyText :: Text -> Builder

O(1). A Builder taking a lazy Text, satisfying

fromString :: String -> Builder

O(1). A Builder taking a String, satisfying

Flushing the buffer state

flush :: Builder

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

lengthB :: Builder -> Int64 Source

Computes the length of a Builder.

Since: 2

unlinesB :: [Builder] -> Builder Source

Merges several Builders, separating them by newlines.

Since: 2

unwordsB :: [Builder] -> Builder Source

Merges several Builders, separating them by spaces.

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 FromStringShow1 f a Source

The TextShow1 instance for FromStringShow1 is based on its String Show1 instance. That is,

liftShowbPrec sp sl p (FromStringShow1 x) =
    showsPrecToShowbPrec (liftShowsPrec (showbPrecToShowsPrec sp)
                                            (showbToShows         sl))
                           p x

Since: 3

Constructors

FromStringShow1 

Fields

fromStringShow1 :: f a
 

newtype FromTextShow1 f a Source

The String Show1 instance for FromTextShow1 is based on its TextShow1 instance. That is,

liftShowsPrec sp sl p (FromTextShow1 x) =
    showbPrecToShowsPrec (liftShowbPrec (showsPrecToShowbPrec sp)
                                            (showsToShowb         sl))
                           p x

Since: 3

Constructors

FromTextShow1 

Fields

fromTextShow1 :: f a
 

newtype FromStringShow2 f a b Source

The TextShow2 instance for FromStringShow2 is based on its String Show2 instance. That is,

liftShowbPrec2 sp1 sl1 sp2 sl2 p (FromStringShow2 x) =
    showsPrecToShowbPrec (liftShowsPrec2 (showbPrecToShowsPrec sp1)
                                             (showbToShows         sl1)
                                             (showbPrecToShowsPrec sp2)
                                             (showbToShows         sl2))
                           p x

Since: 3

Constructors

FromStringShow2 

Fields

fromStringShow2 :: f a b
 

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 (FromTextShow2 x) =
    showbPrecToShowsPrec (liftShowbPrec2 (showsPrecToShowbPrec sp1)
                                             (showsToShowb         sl1)
                                             (showsPrecToShowbPrec sp2)
                                             (showsToShowb         sl2))
                           p x

Since: 3

Constructors

FromTextShow2 

Fields

fromTextShow2 :: f a b
 

Instances

Bifunctor f0 => Bifunctor (FromTextShow2 * * f) Source 
Bitraversable f0 => Bitraversable (FromTextShow2 * * f) Source 
Bifoldable f0 => Bifoldable (FromTextShow2 * * f) Source 
TextShow2 f => TextShow2 (FromTextShow2 * * f) Source 
Functor (f a) => Functor (FromTextShow2 k * f a) Source 
Foldable (f a) => Foldable (FromTextShow2 k * f a) Source 
Traversable (f a) => Traversable (FromTextShow2 k * f a) Source 
Generic1 (FromTextShow2 k * f a) Source 
(TextShow2 f, TextShow a) => TextShow1 (FromTextShow2 * * f a) Source 
Eq (f a b) => Eq (FromTextShow2 k k f a b) Source 
(Data (f a b), Typeable (* -> * -> *) f, Typeable * a, Typeable * b) => Data (FromTextShow2 * * f a b) Source 
Ord (f a b) => Ord (FromTextShow2 k k f a b) Source 
Read (f a b) => Read (FromTextShow2 k k f a b) Source 
Generic (FromTextShow2 k k f a b) Source 
Lift (f a b) => Lift (FromTextShow2 k k f a b) Source 
(TextShow2 f, TextShow a, TextShow b) => TextShow (FromTextShow2 * * f a b) Source 
type Rep1 (FromTextShow2 k k1 f a) Source 
type Rep (FromTextShow2 k k1 f a b) Source 

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