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

Copyright(C) 2014 Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerRyan Scott
StabilityExperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell98

Text.Show.Text

Contents

Description

Efficiently convert from values to Text via Builders.

Synopsis

The Show class

class Show a where Source

Conversion of values to Text. Because there are both strict and lazy Text variants, the Show 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 Show instances. As an example:

import Text.Show.Text

data Example = Example Int Int
instance Show Example where
    showb (Example i1 i2) = showb i1 <> singleton ' ' <> showb i2

If you do not want to create Show instances manually, you can alternatively use the Text.Show.Text.TH module to automatically generate default Show instances using Template Haskell.

Minimal complete definition

showbPrec | showb

Methods

showbPrec :: Int -> a -> Builder Source

Constructs a Text via an efficient Builder. The precedence is used to determine where to put parentheses in a shown expression involving operators.

Builders can be efficiently combined, so the showb functions are available for showing multiple values before producing an output Text.

showb :: a -> Builder Source

Constructs a Text via an efficient Builder. Builders can be efficiently combined, so this is available building a Text from multiple values.

showbList :: [a] -> Builder Source

Allows for specialized display of lists. This is used, for example, when showing lists of Chars.

Instances

Show Bool 
Show Char 
Show Double 
Show Float 
Show Int 
Show Int8 
Show Int16 
Show Int32 
Show Int64 
Show Integer 
Show Ordering 
Show Word 
Show Word8 
Show Word16 
Show Word32 
Show Word64 
Show () 
Show Handle 
Show GCStats 
Show DataType 
Show Constr 
Show DataRep 
Show ConstrRep 
Show Fixity 
Show Version 
Show HandlePosn 
Show FdKey 
Show Event 
Show IOMode 
Show PatternMatchFail 
Show RecSelError 
Show RecConError 
Show RecUpdError 
Show NoMethodError 
Show NonTermination 
Show NestedAtomically 
Show ThreadId 
Show BlockReason 
Show ThreadStatus 
Show CodingFailureMode 
Show CDev 
Show CIno 
Show CMode 
Show COff 
Show CPid 
Show CSsize 
Show CGid 
Show CNlink 
Show CUid 
Show CCc 
Show CSpeed 
Show CTcflag 
Show CRLim 
Show Fd 
Show BlockedIndefinitelyOnMVar 
Show BlockedIndefinitelyOnSTM 
Show Deadlock 
Show AssertionFailed 
Show SomeAsyncException 
Show AsyncException 
Show ArrayException 
Show ExitCode 
Show BufferMode 
Show Newline 
Show NewlineMode 
Show SeekMode 
Show TextEncoding 
Show CodingProgress 
Show WordPtr 
Show IntPtr 
Show GeneralCategory 
Show CChar 
Show CSChar 
Show CUChar 
Show CShort 
Show CUShort 
Show CInt 
Show CUInt 
Show CLong 
Show CULong 
Show CLLong 
Show CULLong 
Show CFloat 
Show CDouble 
Show CPtrdiff 
Show CSize 
Show CWchar 
Show CSigAtomic 
Show CClock 
Show CTime 
Show CUSeconds 
Show CSUSeconds 
Show CIntPtr 
Show CUIntPtr 
Show CIntMax 
Show CUIntMax 
Show Dynamic 
Show MaskingState 
Show IOException 
Show ErrorCall 
Show ArithException 
Show All 
Show Any 
Show Arity 
Show Fixity 
Show Associativity 
Show TypeRep 
Show TyCon 
Show Fingerprint 
Show Lexeme 
Show Number 
Show SomeException 
Show ByteString 
Show ShortByteString 
Show ByteString 
Show IntSet 
Show Builder 
Show Text 
Show Text 
Show AbsoluteTime 
Show LocalTime 
Show ZonedTime 
Show TimeOfDay 
Show TimeZone 
Show UTCTime 
Show NominalDiffTime 
Show Day 
Show DiffTime 
Show a => Show [a] 
(Show a, Integral a) => Show (Ratio a) 
Show (Ptr a) 
Show (FunPtr a) 
Show (U1 p) 
Show p0 => Show (Par1 p) 
Show (ForeignPtr a) 
HasResolution a => Show (Fixed a) 
(RealFloat a, Show a) => Show (Complex a) 
Show a0 => Show (ZipList a) 
Show a0 => Show (Dual a) 
Show a0 => Show (Sum a) 
Show a0 => Show (Product a) 
Show a0 => Show (First a) 
Show a0 => Show (Last a) 
Show a0 => Show (Down a) 
Show a0 => Show (Maybe a) 
Show v => Show (IntMap v) 
Show a => Show (Set a) 
Show a0 => Show (Tree a) 
Show a => Show (Seq a) 
Show (a -> b) 
(Show a0, Show b0) => Show (Either a b) 
Show (f p) => Show (Rec1 f p) 
(Show a, Show b) => Show (a, b) 
Show (ST s a) 
(Show i, Show e, Ix i) => Show (Array i e) 
Show (Proxy * s) 
(Show k, Show v) => Show (Map k v) 
Show c => Show (K1 i c p) 
(Show (f p), Show (g p)) => Show ((:+:) f g p) 
(Show (f p), Show (g p)) => Show ((:*:) f g p) 
Show (f (g p)) => Show ((:.:) f g p) 
(Show a, Show b, Show c) => Show (a, b, c) 
Show (Coercion * a b) 
Show ((:~:) * a b) 
Show (f p) => Show (M1 i c f p) 
(Show a, Show b, Show c, Show d) => Show (a, b, c, d) 
(Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) 
(Show a, Show b, Show c, Show d, Show e, Show f) => Show (a, b, c, d, e, f) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (a, b, c, d, e, f, g) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h) => Show (a, b, c, d, e, f, g, h) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i) => Show (a, b, c, d, e, f, g, h, i) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j) => Show (a, b, c, d, e, f, g, h, i, j) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k) => Show (a, b, c, d, e, f, g, h, i, j, k) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l) => Show (a, b, c, d, e, f, g, h, i, j, k, l) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

show :: Show a => a -> Text Source

Constructs a strict Text from a single value.

showLazy :: Show a => a -> Text Source

Constructs a lazy Text from a single value.

showPrec :: Show a => Int -> a -> Text Source

Constructs a strict Text from a single value with the given precedence.

showPrecLazy :: Show a => Int -> a -> Text Source

Constructs a lazy Text from a single value with the given precedence.

showList :: Show a => [a] -> Text Source

Construct a strict Text from a list of values.

showListLazy :: Show a => [a] -> Text Source

Construct a lazy Text from a list of values.

showbParen :: Bool -> Builder -> Builder Source

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

Builders

toString :: Builder -> String Source

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

toText :: Builder -> Text Source

Convert a Builder to a strict Text.

lengthB :: Builder -> Int64 Source

Computes the length of a Builder.

replicateB :: Int64 -> Builder -> Builder Source

replicateB n b yields a Builder containing b repeated n times.

unlinesB :: [Builder] -> Builder Source

Merges several Builders, separating them by newlines.

unwordsB :: [Builder] -> Builder Source

Merges several Builders, separating them by spaces.

Printing values

print :: Show a => a -> IO () Source

Writes a value's strict Text representation to the standard output, followed by a newline.

printLazy :: Show a => a -> IO () Source

Writes a value's lazy Text representation to the standard output, followed by a newline.

hPrint :: Show a => Handle -> a -> IO () Source

Writes a value's strict Text representation to a file handle, followed by a newline.

hPrintLazy :: Show a => Handle -> a -> IO () Source

Writes a value's lazy Text representation to a file handle, followed by a newline.