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

Copyright(C) 2014-2015 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 String.

-> Builder 

Convert a value to a Builder with the given predence.

Since: 2

showb :: a -> Builder Source

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

TextShow Bool 
TextShow Char 
TextShow Double 
TextShow Float 
TextShow Int 
TextShow Int8 
TextShow Int16 
TextShow Int32 
TextShow Int64 
TextShow Integer 
TextShow Ordering 
TextShow Word 
TextShow Word8 
TextShow Word16 
TextShow Word32 
TextShow Word64 
TextShow () 
TextShow Handle 
TextShow Unique 
TextShow GCStats 
TextShow DataType 
TextShow Constr 
TextShow DataRep 
TextShow ConstrRep 
TextShow Fixity 
TextShow Version 
TextShow SomeNat 
TextShow SomeSymbol 
TextShow TypeRep 
TextShow TyCon 
TextShow HandlePosn 
TextShow FdKey 
TextShow Event 
TextShow IOMode 
TextShow PatternMatchFail 
TextShow RecSelError 
TextShow RecConError 
TextShow RecUpdError 
TextShow NoMethodError 
TextShow NonTermination 
TextShow NestedAtomically 
TextShow ThreadId 
TextShow BlockReason 
TextShow ThreadStatus 
TextShow CodingFailureMode 
TextShow CDev 
TextShow CIno 
TextShow CMode 
TextShow COff 
TextShow CPid 
TextShow CSsize 
TextShow CGid 
TextShow CNlink 
TextShow CUid 
TextShow CCc 
TextShow CSpeed 
TextShow CTcflag 
TextShow CRLim 
TextShow Fd 
TextShow BlockedIndefinitelyOnMVar 
TextShow BlockedIndefinitelyOnSTM 
TextShow Deadlock 
TextShow AssertionFailed 
TextShow SomeAsyncException 
TextShow AsyncException 
TextShow ArrayException 
TextShow ExitCode 
TextShow BufferMode 
TextShow Newline 
TextShow NewlineMode 
TextShow SeekMode 
TextShow TextEncoding 
TextShow CodingProgress 
TextShow WordPtr 
TextShow IntPtr 
TextShow GeneralCategory 
TextShow CChar 
TextShow CSChar 
TextShow CUChar 
TextShow CShort 
TextShow CUShort 
TextShow CInt 
TextShow CUInt 
TextShow CLong 
TextShow CULong 
TextShow CLLong 
TextShow CULLong 
TextShow CFloat 
TextShow CDouble 
TextShow CPtrdiff 
TextShow CSize 
TextShow CWchar 
TextShow CSigAtomic 
TextShow CClock 
TextShow CTime 
TextShow CUSeconds 
TextShow CSUSeconds 
TextShow CIntPtr 
TextShow CUIntPtr 
TextShow CIntMax 
TextShow CUIntMax 
TextShow Dynamic 
TextShow MaskingState 
TextShow IOException 
TextShow ErrorCall 
TextShow ArithException 
TextShow All 
TextShow Any 
TextShow Arity 
TextShow Fixity 
TextShow Associativity 
TextShow TypeRep 
TextShow TyCon 
TextShow Fingerprint 
TextShow Lexeme 
TextShow Number 
TextShow SomeException 
TextShow ByteString 
TextShow ByteString 
TextShow ShortByteString 
TextShow Natural 
TextShow FPFormat 
TextShow Builder 
TextShow Text 
TextShow I16 
TextShow Decoding 
TextShow Size 
TextShow Text 
TextShow UnicodeException 
TextShow Void 
TextShow ConType 
TextShow a => TextShow [a] 
TextShow a => TextShow (Ratio a) 
TextShow (Ptr a) 
TextShow (FunPtr a) 
TextShow (U1 p) 
TextShow p0 => TextShow (Par1 p) 
TextShow (ForeignPtr a) 
HasResolution a => TextShow (Fixed a) 
TextShow a => TextShow (Complex a) 
TextShow a0 => TextShow (ZipList a) 
TextShow a0 => TextShow (Dual a) 
TextShow a0 => TextShow (Sum a) 
TextShow a0 => TextShow (Product a) 
TextShow a0 => TextShow (First a) 
TextShow a0 => TextShow (Last a) 
TextShow a0 => TextShow (Down a) 
TextShow a0 => TextShow (Maybe a) 
TextShow a => TextShow (Identity a) 
TextShow a => TextShow (FromTextShow a) 
Show a => TextShow (FromStringShow a) 
TextShow (a -> b) 
(TextShow a0, TextShow b0) => TextShow (Either a b) 
TextShow (f p) => TextShow (Rec1 f p) 
(TextShow a0, TextShow b0) => TextShow (a, b) 
TextShow (ST s a) 
(IArray UArray e, Ix i, TextShow i, TextShow e) => TextShow (UArray i e) 
(TextShow i, TextShow e, Ix i) => TextShow (Array i e) 
TextShow a => TextShow (Const a b) 
TextShow (Proxy k s) 
Typeable (* -> Constraint) TextShow 
TextShow c => TextShow (K1 i c p) 
(TextShow (f p), TextShow (g p)) => TextShow ((:+:) f g p) 
(TextShow (f p), TextShow (g p)) => TextShow ((:*:) f g p) 
TextShow (f (g p)) => TextShow ((:.:) f g p) 
(TextShow a0, TextShow b0, TextShow c0) => TextShow (a, b, c) 
TextShow (Coercion k a b) 
TextShow ((:~:) k a b) 
TextShow (f p) => TextShow (M1 i c f p) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0) => TextShow (a, b, c, d) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0) => TextShow (a, b, c, d, e) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0) => TextShow (a, b, c, d, e, f) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0) => TextShow (a, b, c, d, e, f, g) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0) => TextShow (a, b, c, d, e, f, g, h) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0) => TextShow (a, b, c, d, e, f, g, h, i) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0, TextShow j0) => TextShow (a, b, c, d, e, f, g, h, i, j) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0, TextShow j0, TextShow k0) => TextShow (a, b, c, d, e, f, g, h, i, j, k) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0, TextShow j0, TextShow k0, TextShow l0) => TextShow (a, b, c, d, e, f, g, h, i, j, k, l) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0, TextShow j0, TextShow k0, TextShow l0, TextShow m0) => TextShow (a, b, c, d, e, f, g, h, i, j, k, l, m) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0, TextShow j0, TextShow k0, TextShow l0, TextShow m0, TextShow n0) => TextShow (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0, TextShow j0, TextShow k0, TextShow l0, TextShow m0, TextShow n0, TextShow o0) => TextShow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

showt :: TextShow a => a -> Text Source

Constructs a strict Text from a single value.

Since: 2

showtl :: TextShow a => a -> Text Source

Constructs a lazy Text from a single value.

Since: 2

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

showtList :: TextShow a => [a] -> Text Source

Construct a strict Text from a list of values.

Since: 2

showtlList :: TextShow a => [a] -> Text Source

Construct a lazy Text from a list of values.

Since: 2

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

Methods

showbPrecWith :: (Int -> a -> Builder) -> Int -> f a -> Builder Source

Lifts a showbPrec function through the type constructor.

Since: 2

Instances

TextShow1 [] 
TextShow1 Ratio 
TextShow1 Ptr 
TextShow1 FunPtr 
TextShow1 U1 
TextShow1 Par1 
TextShow1 ForeignPtr 
TextShow1 Complex 
TextShow1 ZipList 
TextShow1 Dual 
TextShow1 Sum 
TextShow1 Product 
TextShow1 First 
TextShow1 Last 
TextShow1 Down 
TextShow1 Maybe 
TextShow1 Identity 
TextShow1 FromTextShow 
TextShow1 FromStringShow 
TextShow1 ((->) a) 
TextShow a0 => TextShow1 (Either a) 
TextShow1 f0 => TextShow1 (Rec1 f) 
TextShow a0 => TextShow1 ((,) a) 
TextShow1 (ST s) 
TextShow a => TextShow1 (Const a) 
TextShow1 (Proxy *) 
TextShow c => TextShow1 (K1 i c) 
(TextShow1 f0, TextShow1 g0) => TextShow1 ((:+:) f g) 
(TextShow1 f0, TextShow1 g0) => TextShow1 ((:*:) f g) 
(TextShow1 f0, TextShow1 g0) => TextShow1 ((:.:) f g) 
(TextShow a0, TextShow b0) => TextShow1 ((,,) a b) 
TextShow1 (Coercion * a) 
TextShow1 ((:~:) * a) 
Typeable ((* -> *) -> Constraint) TextShow1 
TextShow1 f => TextShow1 (M1 i c f) 
(TextShow a0, TextShow b0, TextShow c0) => TextShow1 ((,,,) a b c) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0) => TextShow1 ((,,,,) a b c d) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0) => TextShow1 ((,,,,,) a b c d e) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0) => TextShow1 ((,,,,,,) a b c d e f) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0) => TextShow1 ((,,,,,,,) a b c d e f g) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0) => TextShow1 ((,,,,,,,,) a b c d e f g h) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0) => TextShow1 ((,,,,,,,,,) a b c d e f g h i) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0, TextShow j0) => TextShow1 ((,,,,,,,,,,) a b c d e f g h i j) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0, TextShow j0, TextShow k0) => TextShow1 ((,,,,,,,,,,,) a b c d e f g h i j k) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0, TextShow j0, TextShow k0, TextShow l0) => TextShow1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0, TextShow j0, TextShow k0, TextShow l0, TextShow m0) => TextShow1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0, TextShow j0, TextShow k0, TextShow l0, TextShow m0, TextShow n0) => TextShow1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) 

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

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

Methods

showbPrecWith2 :: (Int -> a -> Builder) -> (Int -> b -> Builder) -> Int -> f a b -> Builder Source

Lifts showbPrec functions through the type constructor.

Since: 2

Instances

TextShow2 (->) 
TextShow2 Either 
TextShow2 (,) 
TextShow2 ST 
TextShow2 Const 
TextShow2 (K1 i) 
TextShow a0 => TextShow2 ((,,) a) 
TextShow2 (Coercion *) 
TextShow2 ((:~:) *) 
(TextShow a0, TextShow b0) => TextShow2 ((,,,) a b) 
Typeable ((* -> * -> *) -> Constraint) TextShow2 
(TextShow a0, TextShow b0, TextShow c0) => TextShow2 ((,,,,) a b c) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0) => TextShow2 ((,,,,,) a b c d) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0) => TextShow2 ((,,,,,,) a b c d e) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0) => TextShow2 ((,,,,,,,) a b c d e f) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0) => TextShow2 ((,,,,,,,,) a b c d e f g) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0) => TextShow2 ((,,,,,,,,,) a b c d e f g h) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0) => TextShow2 ((,,,,,,,,,,) a b c d e f g h i) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0, TextShow j0) => TextShow2 ((,,,,,,,,,,,) a b c d e f g h i j) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0, TextShow j0, TextShow k0) => TextShow2 ((,,,,,,,,,,,,) a b c d e f g h i j k) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0, TextShow j0, TextShow k0, TextShow l0) => TextShow2 ((,,,,,,,,,,,,,) a b c d e f g h i j k l) 
(TextShow a0, TextShow b0, TextShow c0, TextShow d0, TextShow e0, TextShow f0, TextShow g0, TextShow h0, TextShow i0, TextShow j0, TextShow k0, TextShow l0, TextShow m0) => TextShow2 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m) 

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 FromTextShow a Source

The String Show instance for FromTextShow is based on its TextShow instance. That is,

showsPrec p (FromTextShow x) = showbToShows showbPrec p x

Since: 2

Constructors

FromTextShow 

Fields

fromTextShow :: a
 

showsToShowb :: (Int -> a -> ShowS) -> Int -> a -> Builder Source

Convert a ShowS-based show function to a Builder-based one.

Since: 2.1

showbToShows :: (Int -> a -> Builder) -> Int -> a -> ShowS Source

Convert a Builder-based show function to a ShowS-based one.

Since: 2.1