| Copyright | (C) 2014-2015 Ryan Scott |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Ryan Scott |
| Stability | Provisional |
| Portability | GHC |
| Safe Haskell | None |
| Language | Haskell2010 |
Text.Show.Text
Contents
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
- class Show1 f where
- showbPrecWith :: (Int -> a -> Builder) -> Int -> f a -> Builder
- showbPrec1 :: (Show1 f, Show a) => Int -> f a -> Builder
- showbUnaryWith :: (Int -> a -> Builder) -> Builder -> Int -> a -> Builder
- class Show2 f where
- showbPrec2 :: (Show2 f, Show a, Show b) => Int -> f a b -> Builder
- showbBinaryWith :: (Int -> a -> Builder) -> (Int -> b -> Builder) -> Builder -> Int -> a -> b -> 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-related classes
Show
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
Show1
Lifting of the Show class to unary type constructors.
Since: 1
Methods
showbPrecWith :: (Int -> a -> Builder) -> Int -> f a -> Builder Source
Lifts a showbPrec function through the type constructor.
Since: 1
Instances
| Show1 [] | |
| Show1 Ratio | |
| Show1 Ptr | |
| Show1 FunPtr | |
| Show1 U1 | |
| Show1 Par1 | |
| Show1 ForeignPtr | |
| Show1 Complex | |
| Show1 ZipList | |
| Show1 Dual | |
| Show1 Sum | |
| Show1 Product | |
| Show1 First | |
| Show1 Last | |
| Show1 Down | |
| Show1 Maybe | |
| Show1 Identity | |
| Show1 FromTextShow | |
| Show1 ((->) a) | |
| Show a0 => Show1 (Either a) | |
| Show1 f0 => Show1 (Rec1 f) | |
| Show a0 => Show1 ((,) a) | |
| Show1 (ST s) | |
| Show a => Show1 (Const a) | |
| Show1 (Proxy *) | |
| Show c => Show1 (K1 i c) | |
| (Show1 f0, Show1 g0) => Show1 ((:+:) f g) | |
| (Show1 f0, Show1 g0) => Show1 ((:*:) f g) | |
| (Show1 f0, Show1 g0) => Show1 ((:.:) f g) | |
| (Show a0, Show b0) => Show1 ((,,) a b) | |
| Show1 (Coercion * a) | |
| Show1 ((:~:) * a) | |
| Typeable ((* -> *) -> Constraint) Show1 | |
| Show1 f => Show1 (M1 i c f) | |
| (Show a0, Show b0, Show c0) => Show1 ((,,,) a b c) | |
| (Show a0, Show b0, Show c0, Show d0) => Show1 ((,,,,) a b c d) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0) => Show1 ((,,,,,) a b c d e) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0) => Show1 ((,,,,,,) a b c d e f) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0, Show g0) => Show1 ((,,,,,,,) a b c d e f g) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0, Show g0, Show h0) => Show1 ((,,,,,,,,) a b c d e f g h) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0, Show g0, Show h0, Show i0) => Show1 ((,,,,,,,,,) a b c d e f g h i) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0, Show g0, Show h0, Show i0, Show j0) => Show1 ((,,,,,,,,,,) a b c d e f g h i j) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0, Show g0, Show h0, Show i0, Show j0, Show k0) => Show1 ((,,,,,,,,,,,) a b c d e f g h i j k) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0, Show g0, Show h0, Show i0, Show j0, Show k0, Show l0) => Show1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0, Show g0, Show h0, Show i0, Show j0, Show k0, Show l0, Show m0) => Show1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0, Show g0, Show h0, Show i0, Show j0, Show k0, Show l0, Show m0, Show n0) => Show1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) |
showbPrec1 :: (Show1 f, Show a) => Int -> f a -> Builder Source
Lift the standard showbPrec function through the type constructor.
Since: 1
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: 1
Show2
Lifting of the Show class to binary type constructors.
Since: 1
Methods
showbPrecWith2 :: (Int -> a -> Builder) -> (Int -> b -> Builder) -> Int -> f a b -> Builder Source
Lifts showbPrec functions through the type constructor.
Since: 1
Instances
| Show2 (->) | |
| Show2 Either | |
| Show2 (,) | |
| Show2 ST | |
| Show2 Const | |
| Show2 (K1 i) | |
| Show a0 => Show2 ((,,) a) | |
| Show2 (Coercion *) | |
| Show2 ((:~:) *) | |
| (Show a0, Show b0) => Show2 ((,,,) a b) | |
| Typeable ((* -> * -> *) -> Constraint) Show2 | |
| (Show a0, Show b0, Show c0) => Show2 ((,,,,) a b c) | |
| (Show a0, Show b0, Show c0, Show d0) => Show2 ((,,,,,) a b c d) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0) => Show2 ((,,,,,,) a b c d e) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0) => Show2 ((,,,,,,,) a b c d e f) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0, Show g0) => Show2 ((,,,,,,,,) a b c d e f g) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0, Show g0, Show h0) => Show2 ((,,,,,,,,,) a b c d e f g h) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0, Show g0, Show h0, Show i0) => Show2 ((,,,,,,,,,,) a b c d e f g h i) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0, Show g0, Show h0, Show i0, Show j0) => Show2 ((,,,,,,,,,,,) a b c d e f g h i j) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0, Show g0, Show h0, Show i0, Show j0, Show k0) => Show2 ((,,,,,,,,,,,,) a b c d e f g h i j k) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0, Show g0, Show h0, Show i0, Show j0, Show k0, Show l0) => Show2 ((,,,,,,,,,,,,,) a b c d e f g h i j k l) | |
| (Show a0, Show b0, Show c0, Show d0, Show e0, Show f0, Show g0, Show h0, Show i0, Show j0, Show k0, Show l0, Show m0) => Show2 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m) |
showbPrec2 :: (Show2 f, Show a, Show b) => Int -> f a b -> Builder Source
Lift two showbPrec functions through the type constructor.
Since: 1
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: 1
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
| Functor FromStringShow | |
| Foldable FromStringShow | |
| Traversable FromStringShow | |
| Generic1 FromStringShow | |
| Eq a => Eq (FromStringShow a) | |
| Data a => Data (FromStringShow a) | |
| Ord a => Ord (FromStringShow a) | |
| Read a => Read (FromStringShow a) | |
| Show a => Show (FromStringShow a) | |
| Generic (FromStringShow a) | |
| Show a => Show (FromStringShow a) | |
| Typeable (* -> *) FromStringShow | |
| Typeable (k -> FromStringShow k) (FromStringShow k) | |
| type Rep1 FromStringShow | |
| type Rep (FromStringShow a) |
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
| Functor FromTextShow | |
| Foldable FromTextShow | |
| Traversable FromTextShow | |
| Generic1 FromTextShow | |
| Show1 FromTextShow | |
| Eq a => Eq (FromTextShow a) | |
| Data a => Data (FromTextShow a) | |
| Ord a => Ord (FromTextShow a) | |
| Read a => Read (FromTextShow a) | |
| Show a => Show (FromTextShow a) | |
| Generic (FromTextShow a) | |
| Show a => Show (FromTextShow a) | |
| Typeable (* -> *) FromTextShow | |
| Typeable (k -> FromTextShow k) (FromTextShow k) | |
| type Rep1 FromTextShow | |
| type Rep (FromTextShow a) |