| Copyright | (C) 2014-2015 Ryan Scott | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Ryan Scott | 
| Stability | Experimental | 
| Portability | GHC | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Text.Show.Text
Description
Efficiently convert from values to Text via Builders.
Since: 0.1
- class Show a where
- show :: Show a => a -> Text
- showLazy :: Show a => a -> Text
- showPrec :: Show a => Int -> a -> Text
- showPrecLazy :: Show a => Int -> a -> Text
- showList :: Show a => [a] -> Text
- showListLazy :: Show a => [a] -> Text
- showbParen :: Bool -> Builder -> Builder
- showbSpace :: Builder
- showbUnary :: Show a => Builder -> Int -> a -> Builder
- class Show1 f where- showbPrec1 :: Show a => Int -> f a -> Builder
 
- showbUnary1 :: (Show1 f, Show a) => Builder -> Int -> f a -> Builder
- showbBinary1 :: (Show1 f, Show1 g, Show a) => Builder -> Int -> f a -> g a -> Builder
- module Data.Text.Lazy.Builder
- toString :: Builder -> String
- toText :: Builder -> Text
- lengthB :: Builder -> Int64
- unlinesB :: [Builder] -> Builder
- unwordsB :: [Builder] -> Builder
- print :: Show a => a -> IO ()
- printLazy :: Show a => a -> IO ()
- hPrint :: Show a => Handle -> a -> IO ()
- hPrintLazy :: Show a => Handle -> a -> IO ()
- newtype FromStringShow a = FromStringShow {- fromStringShow :: a
 
- newtype FromTextShow a = FromTextShow {- fromTextShow :: a
 
The Show class
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 <> showbSpace <> 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, or the Text.Show.Text.Generic module to
 quickly define Show instances using genericShowbPrec.
Since: 0.1
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: 0.1
A specialized variant of showbPrec using precedence context zero.
Since: 0.1
showbList :: [a] -> Builder Source
Allows for specialized display of lists. This is used, for example, when
 showing lists of Chars.
Since: 0.1
Instances
showPrec :: Show a => Int -> a -> Text Source
Constructs a strict Text from a single value with the given precedence.
Since: 0.3
showPrecLazy :: Show a => Int -> a -> Text Source
Constructs a lazy Text from a single value with the given precedence.
Since: 0.3
showListLazy :: Show a => [a] -> Text Source
Construct a lazy Text from a list of values.
Since: 0.3.1
showbParen :: Bool -> Builder -> Builder Source
Construct a Builder containing a single space character.
Since: 0.5
showbUnary :: Show a => Builder -> Int -> a -> Builder Source
showbUnary n p xBuilder representation of a unary data
 constructor with name n and argument x, in precedence context p.
Since: 0.5
Lifting of the Show class to unary type constructors.
Since: 0.5
Methods
showbPrec1 :: Show a => Int -> f a -> Builder Source
Builder conversion for values of a type that has a unary type constructor.
Since: 0.5
Instances
showbUnary1 :: (Show1 f, Show a) => Builder -> Int -> f a -> Builder Source
showbUnary1 n p xBuilder representation of a unary data
 constructor with name n and argument x, in precedence context p.
Since: 0.5
showbBinary1 :: (Show1 f, Show1 g, Show a) => Builder -> Int -> f a -> g a -> Builder Source
showbBinary1 n p x yBuilder representation of a binary
 data constructor with name n and arguments x and y, in precedence
 context p.
Since: 0.5
Builders
module Data.Text.Lazy.Builder
unlinesB :: [Builder] -> Builder Source
Merges several Builders, separating them by newlines.
Since: 0.1
unwordsB :: [Builder] -> Builder Source
Merges several Builders, separating them by spaces.
Since: 0.1
Printing values
print :: Show a => a -> IO () Source
Writes a value's strict Text representation to the standard output, followed
   by a newline.
Since: 0.1
printLazy :: Show a => a -> IO () Source
Writes a value's lazy Text representation to the standard output, followed
   by a newline.
Since: 0.3
hPrint :: Show a => Handle -> a -> IO () Source
Writes a value's strict Text representation to a file handle, followed
   by a newline.
Since: 0.3
hPrintLazy :: Show a => Handle -> a -> IO () Source
Writes a value's lazy Text representation to a file handle, followed
   by a newline.
Since: 0.3
Conversion between String and Text Show
newtype FromStringShow a Source
The Text Show instance for FromStringShow is based on its String
 Show instance. That is,
showbPrec p (FromStringShowx) =fromString(showsPrec p x "")
Since: 0.5
Constructors
| FromStringShow | |
| Fields 
 | |
Instances
newtype FromTextShow a Source
The String Show instance for FromTextShow is based on its Text
 Show instance. That is,
showsPrec p (FromTextShowx) str =toString(showbPrec p x) ++ str
Since: 0.6
Constructors
| FromTextShow | |
| Fields 
 | |
Instances