text-show-3.9.2: Efficient conversion of values into Text
Copyright(C) 2014-2017 Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerRyan Scott
StabilityProvisional
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

TextShow

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.Semigroup
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 GHC.Generics.

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 = showtPrec 0
showt = toStrict . showtl

The first equation is the default definition of showt.

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 = showtlPrec 0
showtl = toLazyText . showb

The first equation is the default definition of showtl.

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

Instances

Instances details
TextShow Bool Source #

Since: 2

Instance details

Defined in TextShow.Data.Bool

TextShow Char Source #

Since: 2

Instance details

Defined in TextShow.Data.Char

TextShow Double Source #

Since: 2

Instance details

Defined in TextShow.Data.Floating

TextShow Float Source #

Since: 2

Instance details

Defined in TextShow.Data.Floating

TextShow Int Source #

Since: 2

Instance details

Defined in TextShow.Data.Integral

TextShow Int8 Source #

Since: 2

Instance details

Defined in TextShow.Data.Integral

TextShow Int16 Source #

Since: 2

Instance details

Defined in TextShow.Data.Integral

TextShow Int32 Source #

Since: 2

Instance details

Defined in TextShow.Data.Integral

TextShow Int64 Source #

Since: 2

Instance details

Defined in TextShow.Data.Integral

TextShow Integer Source #

Since: 2

Instance details

Defined in TextShow.Data.Integral

TextShow Natural Source #

Since: 2

Instance details

Defined in TextShow.Numeric.Natural

TextShow Ordering Source #

Since: 2

Instance details

Defined in TextShow.Data.Ord

TextShow Word Source #

Since: 2

Instance details

Defined in TextShow.Data.Integral

TextShow Word8 Source #

Since: 2

Instance details

Defined in TextShow.Data.Integral

TextShow Word16 Source #

Since: 2

Instance details

Defined in TextShow.Data.Integral

TextShow Word32 Source #

Since: 2

Instance details

Defined in TextShow.Data.Integral

TextShow Word64 Source #

Since: 2

Instance details

Defined in TextShow.Data.Integral

TextShow CallStack Source #

Since: 3.0.1

Instance details

Defined in TextShow.GHC.Stack

TextShow SomeTypeRep Source #

Only available with base-4.10.0.0 or later.

Since: 3.6

Instance details

Defined in TextShow.Data.Typeable

TextShow () Source #

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

showbPrec :: Int -> () -> Builder Source #

showb :: () -> Builder Source #

showbList :: [()] -> Builder Source #

showtPrec :: Int -> () -> Text Source #

showt :: () -> Text Source #

showtList :: [()] -> Text Source #

showtlPrec :: Int -> () -> Text Source #

showtl :: () -> Text Source #

showtlList :: [()] -> Text Source #

TextShow TyCon Source #

Since: 2

Instance details

Defined in TextShow.Data.Typeable

TextShow Module Source #

Only available with base-4.9.0.0 or later.

Since: 3

Instance details

Defined in TextShow.Data.Typeable

TextShow TrName Source #

Only available with base-4.9.0.0 or later.

Since: 3

Instance details

Defined in TextShow.Data.Typeable

TextShow Handle Source #

Since: 2

Instance details

Defined in TextShow.System.IO

TextShow Unique Source # 
Instance details

Defined in TextShow.GHC.Event

Methods

showbPrec :: Int -> Unique -> Builder Source #

showb :: Unique -> Builder Source #

showbList :: [Unique] -> Builder Source #

showtPrec :: Int -> Unique -> Text Source #

showt :: Unique -> Text Source #

showtList :: [Unique] -> Text Source #

showtlPrec :: Int -> Unique -> Text Source #

showtl :: Unique -> Text Source #

showtlList :: [Unique] -> Text Source #

TextShow Void Source #

Since: 2

Instance details

Defined in TextShow.Data.Void

TextShow DataType Source #

Since: 2

Instance details

Defined in TextShow.Data.Data

TextShow Constr Source #

Since: 2

Instance details

Defined in TextShow.Data.Data

TextShow DataRep Source #

Since: 2

Instance details

Defined in TextShow.Data.Data

TextShow ConstrRep Source #

Since: 2

Instance details

Defined in TextShow.Data.Data

TextShow Fixity Source #

Since: 2

Instance details

Defined in TextShow.Data.Data

TextShow GiveGCStats Source #

Since: 2.1

Instance details

Defined in TextShow.GHC.RTS.Flags

TextShow GCFlags Source #

Since: 2

Instance details

Defined in TextShow.GHC.RTS.Flags

TextShow ConcFlags Source #

Since: 2

Instance details

Defined in TextShow.GHC.RTS.Flags

TextShow MiscFlags Source #

Since: 2

Instance details

Defined in TextShow.GHC.RTS.Flags

TextShow DebugFlags Source #

Since: 2

Instance details

Defined in TextShow.GHC.RTS.Flags

TextShow DoCostCentres Source #

Since: 2.1

Instance details

Defined in TextShow.GHC.RTS.Flags

TextShow CCFlags Source #

Since: 2

Instance details

Defined in TextShow.GHC.RTS.Flags

TextShow DoHeapProfile Source #

Since: 2.1

Instance details

Defined in TextShow.GHC.RTS.Flags

TextShow ProfFlags Source #

Since: 2

Instance details

Defined in TextShow.GHC.RTS.Flags

TextShow DoTrace Source #

Since: 2.1

Instance details

Defined in TextShow.GHC.RTS.Flags

TextShow TraceFlags Source #

Since: 2

Instance details

Defined in TextShow.GHC.RTS.Flags

TextShow TickyFlags Source #

Since: 2

Instance details

Defined in TextShow.GHC.RTS.Flags

TextShow ParFlags Source #

Only available with base-4.10.0.0 or later.

Since: 3.3

Instance details

Defined in TextShow.GHC.RTS.Flags

TextShow RTSFlags Source #

Since: 2

Instance details

Defined in TextShow.GHC.RTS.Flags

TextShow StaticPtrInfo Source #

Since: 2

Instance details

Defined in TextShow.GHC.StaticPtr

TextShow Version Source #

Since: 2

Instance details

Defined in TextShow.Data.Version

TextShow HandlePosn Source #

Since: 2

Instance details

Defined in TextShow.System.IO

TextShow FdKey Source #

Since: 2

Instance details

Defined in TextShow.GHC.Event

TextShow PatternMatchFail Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow RecSelError Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow RecConError Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow RecUpdError Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow NoMethodError Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow TypeError Source #

Only available with base-4.9.0.0 or later.

Since: 3

Instance details

Defined in TextShow.Control.Exception

TextShow NonTermination Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow NestedAtomically Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow ThreadId Source #

Since: 2

Instance details

Defined in TextShow.Control.Concurrent

TextShow BlockReason Source #

Since: 2

Instance details

Defined in TextShow.Control.Concurrent

TextShow ThreadStatus Source #

Since: 2

Instance details

Defined in TextShow.Control.Concurrent

TextShow Dynamic Source #

Since: 2

Instance details

Defined in TextShow.Data.Dynamic

TextShow Event Source #

Since: 2

Instance details

Defined in TextShow.GHC.Event

TextShow Lifetime Source #

Only available with base-4.8.1.0 or later.

Since: 2

Instance details

Defined in TextShow.GHC.Event

TextShow CDev Source #

Since: 2

Instance details

Defined in TextShow.System.Posix.Types

TextShow CIno Source #

Since: 2

Instance details

Defined in TextShow.System.Posix.Types

TextShow CMode Source #

Since: 2

Instance details

Defined in TextShow.System.Posix.Types

TextShow COff Source #

Since: 2

Instance details

Defined in TextShow.System.Posix.Types

TextShow CPid Source #

Since: 2

Instance details

Defined in TextShow.System.Posix.Types

TextShow CSsize Source #

Since: 2

Instance details

Defined in TextShow.System.Posix.Types

TextShow CGid Source #

Since: 2

Instance details

Defined in TextShow.System.Posix.Types

TextShow CNlink Source #

Since: 2

Instance details

Defined in TextShow.System.Posix.Types

TextShow CUid Source #

Since: 2

Instance details

Defined in TextShow.System.Posix.Types

TextShow CCc Source #

Since: 2

Instance details

Defined in TextShow.System.Posix.Types

TextShow CSpeed Source #

Since: 2

Instance details

Defined in TextShow.System.Posix.Types

TextShow CTcflag Source #

Since: 2

Instance details

Defined in TextShow.System.Posix.Types

TextShow CRLim Source #

Since: 2

Instance details

Defined in TextShow.System.Posix.Types

TextShow CBlkSize Source #

Only available with base-4.10.0.0 or later.

Since: 3.6

Instance details

Defined in TextShow.System.Posix.Types

TextShow CBlkCnt Source #

Only available with base-4.10.0.0 or later.

Since: 3.6

Instance details

Defined in TextShow.System.Posix.Types

TextShow CClockId Source #

Only available with base-4.10.0.0 or later.

Since: 3.6

Instance details

Defined in TextShow.System.Posix.Types

TextShow CFsBlkCnt Source #

Only available with base-4.10.0.0 or later.

Since: 3.6

Instance details

Defined in TextShow.System.Posix.Types

TextShow CFsFilCnt Source #

Only available with base-4.10.0.0 or later.

Since: 3.6

Instance details

Defined in TextShow.System.Posix.Types

TextShow CId Source #

Only available with base-4.10.0.0 or later.

Since: 3.6

Instance details

Defined in TextShow.System.Posix.Types

TextShow CKey Source #

Only available with base-4.10.0.0 or later.

Since: 3.6

Instance details

Defined in TextShow.System.Posix.Types

TextShow CTimer Source #

Only available with base-4.10.0.0 or later.

Since: 3.6

Instance details

Defined in TextShow.System.Posix.Types

TextShow Fd Source #

Since: 2

Instance details

Defined in TextShow.System.Posix.Types

TextShow CodingFailureMode Source #

Since: 2

Instance details

Defined in TextShow.System.IO

TextShow BlockedIndefinitelyOnMVar Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow BlockedIndefinitelyOnSTM Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow Deadlock Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow AllocationLimitExceeded Source #

Only available with base-4.8.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow CompactionFailed Source #

Only available with base-4.10.0.0 or later.

Since: 3.6

Instance details

Defined in TextShow.Control.Exception

TextShow AssertionFailed Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow SomeAsyncException Source #

Only available with base-4.7.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow AsyncException Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow ArrayException Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow FixIOException Source #

Only available with base-4.11.0.0 or later.

Since: 3.7.3

Instance details

Defined in TextShow.Control.Exception

TextShow ExitCode Source #

Since: 2

Instance details

Defined in TextShow.System.Exit

TextShow BufferMode Source #

Since: 2

Instance details

Defined in TextShow.System.IO

TextShow Newline Source #

Since: 2

Instance details

Defined in TextShow.System.IO

TextShow NewlineMode Source #

Since: 2

Instance details

Defined in TextShow.System.IO

TextShow SeekMode Source #

Since: 2

Instance details

Defined in TextShow.System.IO

TextShow TextEncoding Source #

Since: 2

Instance details

Defined in TextShow.System.IO

TextShow CodingProgress Source #

Since: 2

Instance details

Defined in TextShow.System.IO

TextShow MaskingState Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow IOException Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow ErrorCall Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow ArithException Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow All Source #

Since: 2

Instance details

Defined in TextShow.Data.Monoid

TextShow Any Source #

Since: 2

Instance details

Defined in TextShow.Data.Monoid

TextShow Fixity Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

TextShow Associativity Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

TextShow SourceUnpackedness Source #

Only available with base-4.9.0.0 or later.

Since: 3

Instance details

Defined in TextShow.GHC.Generics

TextShow SourceStrictness Source #

Only available with base-4.9.0.0 or later.

Since: 3

Instance details

Defined in TextShow.GHC.Generics

TextShow DecidedStrictness Source #

Only available with base-4.9.0.0 or later.

Since: 3

Instance details

Defined in TextShow.GHC.Generics

TextShow SomeSymbol Source #

Only available with base-4.7.0.0 or later.

Since: 2

Instance details

Defined in TextShow.GHC.TypeLits

TextShow SomeNat Source #

Only available with base-4.7.0.0 or later.

Since: 2

Instance details

Defined in TextShow.GHC.TypeLits

TextShow CChar Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CSChar Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CUChar Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CShort Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CUShort Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CInt Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CUInt Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CLong Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CULong Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CLLong Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CULLong Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CBool Source #

Only available with base-4.10.0.0 or later.

Since: 3.6

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CFloat Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CDouble Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CPtrdiff Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CSize Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CWchar Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CSigAtomic Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CClock Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CTime Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CUSeconds Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CSUSeconds Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CIntPtr Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CUIntPtr Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CIntMax Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow CUIntMax Source #

Since: 2

Instance details

Defined in TextShow.Foreign.C.Types

TextShow WordPtr Source #

Since: 2

Instance details

Defined in TextShow.Foreign.Ptr

TextShow IntPtr Source #

Since: 2

Instance details

Defined in TextShow.Foreign.Ptr

TextShow IOMode Source #

Since: 2

Instance details

Defined in TextShow.System.IO

TextShow Fingerprint Source #

Since: 2

Instance details

Defined in TextShow.GHC.Fingerprint

TextShow Lexeme Source #

Since: 2

Instance details

Defined in TextShow.Text.Read

TextShow Number Source #

Only available with base-4.6.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Text.Read

TextShow GeneralCategory Source #

Since: 2

Instance details

Defined in TextShow.Data.Char

TextShow SrcLoc Source #

Since: 3.0.1

Instance details

Defined in TextShow.GHC.Stack

TextShow SomeException Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow ShortByteString Source #

Since: 2

Instance details

Defined in TextShow.Data.ByteString

TextShow ByteString Source #

Since: 2

Instance details

Defined in TextShow.Data.ByteString

TextShow ByteString Source #

Since: 2

Instance details

Defined in TextShow.Data.ByteString

TextShow FPFormat Source #

Since: 2

Instance details

Defined in TextShow.Data.Floating

TextShow Builder Source #

Since: 2

Instance details

Defined in TextShow.Data.Text

TextShow Text Source #

Since: 2

Instance details

Defined in TextShow.Data.Text

TextShow Decoding Source #

Only available with text-1.0.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Data.Text

TextShow Size Source #

Only available with text-1.1.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Data.Text

TextShow Text Source #

Since: 2

Instance details

Defined in TextShow.Data.Text

TextShow UnicodeException Source #

Since: 2

Instance details

Defined in TextShow.Data.Text

TextShow GenTextMethods Source # 
Instance details

Defined in TextShow.TH

TextShow Options Source # 
Instance details

Defined in TextShow.TH

TextShow ConType Source # 
Instance details

Defined in TextShow.Generic

TextShow a => TextShow [a] Source #

Since: 2

Instance details

Defined in TextShow.Data.List

Methods

showbPrec :: Int -> [a] -> Builder Source #

showb :: [a] -> Builder Source #

showbList :: [[a]] -> Builder Source #

showtPrec :: Int -> [a] -> Text Source #

showt :: [a] -> Text Source #

showtList :: [[a]] -> Text Source #

showtlPrec :: Int -> [a] -> Text Source #

showtl :: [a] -> Text Source #

showtlList :: [[a]] -> Text Source #

TextShow a => TextShow (Maybe a) Source #

Since: 2

Instance details

Defined in TextShow.Data.Maybe

TextShow a => TextShow (Ratio a) Source #

Since: 2

Instance details

Defined in TextShow.Data.Ratio

TextShow (Ptr a) Source #

Since: 2

Instance details

Defined in TextShow.Foreign.Ptr

TextShow (FunPtr a) Source #

Since: 2

Instance details

Defined in TextShow.Foreign.Ptr

TextShow p => TextShow (Par1 p) Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

TextShow (ForeignPtr a) Source #

Since: 2

Instance details

Defined in TextShow.Foreign.Ptr

TextShow a => TextShow (Complex a) Source #

Since: 2

Instance details

Defined in TextShow.Data.Complex

TextShow a => TextShow (Min a) Source #

Since: 3

Instance details

Defined in TextShow.Data.Semigroup

TextShow a => TextShow (Max a) Source #

Since: 3

Instance details

Defined in TextShow.Data.Semigroup

TextShow a => TextShow (First a) Source #

Since: 3

Instance details

Defined in TextShow.Data.Semigroup

TextShow a => TextShow (Last a) Source #

Since: 3

Instance details

Defined in TextShow.Data.Semigroup

TextShow m => TextShow (WrappedMonoid m) Source #

Since: 3

Instance details

Defined in TextShow.Data.Semigroup

TextShow a => TextShow (ZipList a) Source #

Since: 2

Instance details

Defined in TextShow.Control.Applicative

TextShow a => TextShow (Identity a) Source #

Since: 3

Instance details

Defined in TextShow.Data.Functor.Identity

TextShow a => TextShow (First a) Source #

Since: 2

Instance details

Defined in TextShow.Data.Monoid

TextShow a => TextShow (Last a) Source #

Since: 2

Instance details

Defined in TextShow.Data.Monoid

TextShow a => TextShow (Dual a) Source #

Since: 2

Instance details

Defined in TextShow.Data.Monoid

TextShow a => TextShow (Sum a) Source #

Since: 2

Instance details

Defined in TextShow.Data.Monoid

TextShow a => TextShow (Product a) Source #

Since: 2

Instance details

Defined in TextShow.Data.Monoid

TextShow a => TextShow (Down a) Source #

This instance would be equivalent to a derived TextShow instance if the getDown field were removed.

Since: 2

Instance details

Defined in TextShow.Data.Ord

TextShow a => TextShow (NonEmpty a) Source #

Since: 3

Instance details

Defined in TextShow.Data.List.NonEmpty

TextShow a => TextShow (FromTextShow a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Show a => TextShow (FromStringShow a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

(Generic a, GTextShowB Zero (Rep a)) => TextShow (FromGeneric a) Source #

Since: 3.7.4

Instance details

Defined in TextShow.Generic

TextShow (a -> b) Source #

Since: 2

Instance details

Defined in TextShow.Functions

Methods

showbPrec :: Int -> (a -> b) -> Builder Source #

showb :: (a -> b) -> Builder Source #

showbList :: [a -> b] -> Builder Source #

showtPrec :: Int -> (a -> b) -> Text Source #

showt :: (a -> b) -> Text Source #

showtList :: [a -> b] -> Text Source #

showtlPrec :: Int -> (a -> b) -> Text Source #

showtl :: (a -> b) -> Text Source #

showtlList :: [a -> b] -> Text Source #

(TextShow a, TextShow b) => TextShow (Either a b) Source #

Since: 2

Instance details

Defined in TextShow.Data.Either

TextShow (U1 p) Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

TextShow (UChar p) Source #

Since: 2.1.2

Instance details

Defined in TextShow.GHC.Generics

TextShow (UDouble p) Source #

Since: 2.1.2

Instance details

Defined in TextShow.GHC.Generics

TextShow (UFloat p) Source #

Since: 2.1.2

Instance details

Defined in TextShow.GHC.Generics

TextShow (UInt p) Source #

Since: 2.1.2

Instance details

Defined in TextShow.GHC.Generics

TextShow (UWord p) Source #

Since: 2.1.2

Instance details

Defined in TextShow.GHC.Generics

TextShow (TypeRep a) Source #

Only available with base-4.10.0.0 or later.

Since: 3.6

Instance details

Defined in TextShow.Data.Typeable

(TextShow a, TextShow b) => TextShow (a, b) Source #

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

showbPrec :: Int -> (a, b) -> Builder Source #

showb :: (a, b) -> Builder Source #

showbList :: [(a, b)] -> Builder Source #

showtPrec :: Int -> (a, b) -> Text Source #

showt :: (a, b) -> Text Source #

showtList :: [(a, b)] -> Text Source #

showtlPrec :: Int -> (a, b) -> Text Source #

showtl :: (a, b) -> Text Source #

showtlList :: [(a, b)] -> Text Source #

TextShow (ST s a) Source #

Since: 2

Instance details

Defined in TextShow.Control.Monad.ST

Methods

showbPrec :: Int -> ST s a -> Builder Source #

showb :: ST s a -> Builder Source #

showbList :: [ST s a] -> Builder Source #

showtPrec :: Int -> ST s a -> Text Source #

showt :: ST s a -> Text Source #

showtList :: [ST s a] -> Text Source #

showtlPrec :: Int -> ST s a -> Text Source #

showtl :: ST s a -> Text Source #

showtlList :: [ST s a] -> Text Source #

(IArray UArray e, Ix i, TextShow i, TextShow e) => TextShow (UArray i e) Source #

Since: 2

Instance details

Defined in TextShow.Data.Array

(TextShow i, TextShow e, Ix i) => TextShow (Array i e) Source #

Since: 2

Instance details

Defined in TextShow.Data.Array

HasResolution a => TextShow (Fixed a) Source #

Since: 2

Instance details

Defined in TextShow.Data.Fixed

(TextShow a, TextShow b) => TextShow (Arg a b) Source #

Since: 3

Instance details

Defined in TextShow.Data.Semigroup

Methods

showbPrec :: Int -> Arg a b -> Builder Source #

showb :: Arg a b -> Builder Source #

showbList :: [Arg a b] -> Builder Source #

showtPrec :: Int -> Arg a b -> Text Source #

showt :: Arg a b -> Text Source #

showtList :: [Arg a b] -> Text Source #

showtlPrec :: Int -> Arg a b -> Text Source #

showtl :: Arg a b -> Text Source #

showtlList :: [Arg a b] -> Text Source #

TextShow (Proxy s) Source #

Since: 2

Instance details

Defined in TextShow.Data.Proxy

TextShow (f p) => TextShow (Rec1 f p) Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

Methods

showbPrec :: Int -> Rec1 f p -> Builder Source #

showb :: Rec1 f p -> Builder Source #

showbList :: [Rec1 f p] -> Builder Source #

showtPrec :: Int -> Rec1 f p -> Text Source #

showt :: Rec1 f p -> Text Source #

showtList :: [Rec1 f p] -> Text Source #

showtlPrec :: Int -> Rec1 f p -> Text Source #

showtl :: Rec1 f p -> Text Source #

showtlList :: [Rec1 f p] -> Text Source #

(TextShow a, TextShow b, TextShow c) => TextShow (a, b, c) Source #

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

showbPrec :: Int -> (a, b, c) -> Builder Source #

showb :: (a, b, c) -> Builder Source #

showbList :: [(a, b, c)] -> Builder Source #

showtPrec :: Int -> (a, b, c) -> Text Source #

showt :: (a, b, c) -> Text Source #

showtList :: [(a, b, c)] -> Text Source #

showtlPrec :: Int -> (a, b, c) -> Text Source #

showtl :: (a, b, c) -> Text Source #

showtlList :: [(a, b, c)] -> Text Source #

TextShow a => TextShow (Const a b) Source #

Since: 2

Instance details

Defined in TextShow.Control.Applicative

TextShow (f a) => TextShow (Ap f a) Source #

Only available with base-4.12.0.0 or later.

Since: 3.7.4

Instance details

Defined in TextShow.Data.Monoid

Methods

showbPrec :: Int -> Ap f a -> Builder Source #

showb :: Ap f a -> Builder Source #

showbList :: [Ap f a] -> Builder Source #

showtPrec :: Int -> Ap f a -> Text Source #

showt :: Ap f a -> Text Source #

showtList :: [Ap f a] -> Text Source #

showtlPrec :: Int -> Ap f a -> Text Source #

showtl :: Ap f a -> Text Source #

showtlList :: [Ap f a] -> Text Source #

TextShow (f a) => TextShow (Alt f a) Source #

Only available with base-4.8.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Data.Monoid

Methods

showbPrec :: Int -> Alt f a -> Builder Source #

showb :: Alt f a -> Builder Source #

showbList :: [Alt f a] -> Builder Source #

showtPrec :: Int -> Alt f a -> Text Source #

showt :: Alt f a -> Text Source #

showtList :: [Alt f a] -> Text Source #

showtlPrec :: Int -> Alt f a -> Text Source #

showtl :: Alt f a -> Text Source #

showtlList :: [Alt f a] -> Text Source #

TextShow (Coercion a b) Source #

Since: 2

Instance details

Defined in TextShow.Data.Type.Coercion

TextShow (a :~: b) Source #

Since: 2

Instance details

Defined in TextShow.Data.Type.Equality

Methods

showbPrec :: Int -> (a :~: b) -> Builder Source #

showb :: (a :~: b) -> Builder Source #

showbList :: [a :~: b] -> Builder Source #

showtPrec :: Int -> (a :~: b) -> Text Source #

showt :: (a :~: b) -> Text Source #

showtList :: [a :~: b] -> Text Source #

showtlPrec :: Int -> (a :~: b) -> Text Source #

showtl :: (a :~: b) -> Text Source #

showtlList :: [a :~: b] -> Text Source #

(TextShow1 f, TextShow a) => TextShow (FromTextShow1 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

(Show1 f, Show a) => TextShow (FromStringShow1 f a) Source #

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

TextShow c => TextShow (K1 i c p) Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

Methods

showbPrec :: Int -> K1 i c p -> Builder Source #

showb :: K1 i c p -> Builder Source #

showbList :: [K1 i c p] -> Builder Source #

showtPrec :: Int -> K1 i c p -> Text Source #

showt :: K1 i c p -> Text Source #

showtList :: [K1 i c p] -> Text Source #

showtlPrec :: Int -> K1 i c p -> Text Source #

showtl :: K1 i c p -> Text Source #

showtlList :: [K1 i c p] -> Text Source #

(TextShow (f p), TextShow (g p)) => TextShow ((f :+: g) p) Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

Methods

showbPrec :: Int -> (f :+: g) p -> Builder Source #

showb :: (f :+: g) p -> Builder Source #

showbList :: [(f :+: g) p] -> Builder Source #

showtPrec :: Int -> (f :+: g) p -> Text Source #

showt :: (f :+: g) p -> Text Source #

showtList :: [(f :+: g) p] -> Text Source #

showtlPrec :: Int -> (f :+: g) p -> Text Source #

showtl :: (f :+: g) p -> Text Source #

showtlList :: [(f :+: g) p] -> Text Source #

(TextShow (f p), TextShow (g p)) => TextShow ((f :*: g) p) Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

Methods

showbPrec :: Int -> (f :*: g) p -> Builder Source #

showb :: (f :*: g) p -> Builder Source #

showbList :: [(f :*: g) p] -> Builder Source #

showtPrec :: Int -> (f :*: g) p -> Text Source #

showt :: (f :*: g) p -> Text Source #

showtList :: [(f :*: g) p] -> Text Source #

showtlPrec :: Int -> (f :*: g) p -> Text Source #

showtl :: (f :*: g) p -> Text Source #

showtlList :: [(f :*: g) p] -> Text Source #

(TextShow a, TextShow b, TextShow c, TextShow d) => TextShow (a, b, c, d) Source #

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

showbPrec :: Int -> (a, b, c, d) -> Builder Source #

showb :: (a, b, c, d) -> Builder Source #

showbList :: [(a, b, c, d)] -> Builder Source #

showtPrec :: Int -> (a, b, c, d) -> Text Source #

showt :: (a, b, c, d) -> Text Source #

showtList :: [(a, b, c, d)] -> Text Source #

showtlPrec :: Int -> (a, b, c, d) -> Text Source #

showtl :: (a, b, c, d) -> Text Source #

showtlList :: [(a, b, c, d)] -> Text Source #

(TextShow1 f, TextShow1 g, TextShow a) => TextShow (Product f g a) Source #

Since: 3

Instance details

Defined in TextShow.Data.Functor.Product

Methods

showbPrec :: Int -> Product f g a -> Builder Source #

showb :: Product f g a -> Builder Source #

showbList :: [Product f g a] -> Builder Source #

showtPrec :: Int -> Product f g a -> Text Source #

showt :: Product f g a -> Text Source #

showtList :: [Product f g a] -> Text Source #

showtlPrec :: Int -> Product f g a -> Text Source #

showtl :: Product f g a -> Text Source #

showtlList :: [Product f g a] -> Text Source #

(TextShow1 f, TextShow1 g, TextShow a) => TextShow (Sum f g a) Source #

Since: 3

Instance details

Defined in TextShow.Data.Functor.Sum

Methods

showbPrec :: Int -> Sum f g a -> Builder Source #

showb :: Sum f g a -> Builder Source #

showbList :: [Sum f g a] -> Builder Source #

showtPrec :: Int -> Sum f g a -> Text Source #

showt :: Sum f g a -> Text Source #

showtList :: [Sum f g a] -> Text Source #

showtlPrec :: Int -> Sum f g a -> Text Source #

showtl :: Sum f g a -> Text Source #

showtlList :: [Sum f g a] -> Text Source #

TextShow (a :~~: b) Source #

Since: 3.6

Instance details

Defined in TextShow.Data.Type.Equality

Methods

showbPrec :: Int -> (a :~~: b) -> Builder Source #

showb :: (a :~~: b) -> Builder Source #

showbList :: [a :~~: b] -> Builder Source #

showtPrec :: Int -> (a :~~: b) -> Text Source #

showt :: (a :~~: b) -> Text Source #

showtList :: [a :~~: b] -> Text Source #

showtlPrec :: Int -> (a :~~: b) -> Text Source #

showtl :: (a :~~: b) -> Text Source #

showtlList :: [a :~~: b] -> Text Source #

TextShow (f p) => TextShow (M1 i c f p) Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

Methods

showbPrec :: Int -> M1 i c f p -> Builder Source #

showb :: M1 i c f p -> Builder Source #

showbList :: [M1 i c f p] -> Builder Source #

showtPrec :: Int -> M1 i c f p -> Text Source #

showt :: M1 i c f p -> Text Source #

showtList :: [M1 i c f p] -> Text Source #

showtlPrec :: Int -> M1 i c f p -> Text Source #

showtl :: M1 i c f p -> Text Source #

showtlList :: [M1 i c f p] -> Text Source #

TextShow (f (g p)) => TextShow ((f :.: g) p) Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

Methods

showbPrec :: Int -> (f :.: g) p -> Builder Source #

showb :: (f :.: g) p -> Builder Source #

showbList :: [(f :.: g) p] -> Builder Source #

showtPrec :: Int -> (f :.: g) p -> Text Source #

showt :: (f :.: g) p -> Text Source #

showtList :: [(f :.: g) p] -> Text Source #

showtlPrec :: Int -> (f :.: g) p -> Text Source #

showtl :: (f :.: g) p -> Text Source #

showtlList :: [(f :.: g) p] -> Text Source #

(TextShow a, TextShow b, TextShow c, TextShow d, TextShow e) => TextShow (a, b, c, d, e) Source #

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

showbPrec :: Int -> (a, b, c, d, e) -> Builder Source #

showb :: (a, b, c, d, e) -> Builder Source #

showbList :: [(a, b, c, d, e)] -> Builder Source #

showtPrec :: Int -> (a, b, c, d, e) -> Text Source #

showt :: (a, b, c, d, e) -> Text Source #

showtList :: [(a, b, c, d, e)] -> Text Source #

showtlPrec :: Int -> (a, b, c, d, e) -> Text Source #

showtl :: (a, b, c, d, e) -> Text Source #

showtlList :: [(a, b, c, d, e)] -> Text Source #

(TextShow1 f, TextShow1 g, TextShow a) => TextShow (Compose f g a) Source #

Since: 3

Instance details

Defined in TextShow.Data.Functor.Compose

Methods

showbPrec :: Int -> Compose f g a -> Builder Source #

showb :: Compose f g a -> Builder Source #

showbList :: [Compose f g a] -> Builder Source #

showtPrec :: Int -> Compose f g a -> Text Source #

showt :: Compose f g a -> Text Source #

showtList :: [Compose f g a] -> Text Source #

showtlPrec :: Int -> Compose f g a -> Text Source #

showtl :: Compose f g a -> Text Source #

showtlList :: [Compose f g a] -> Text Source #

(TextShow2 f, TextShow a, TextShow b) => TextShow (FromTextShow2 f a b) Source # 
Instance details

Defined in TextShow.FromStringTextShow

(Show2 f, Show a, Show b) => TextShow (FromStringShow2 f a b) Source #

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

(TextShow a, TextShow b, TextShow c, TextShow d, TextShow e, TextShow f) => TextShow (a, b, c, d, e, f) Source #

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

showbPrec :: Int -> (a, b, c, d, e, f) -> Builder Source #

showb :: (a, b, c, d, e, f) -> Builder Source #

showbList :: [(a, b, c, d, e, f)] -> Builder Source #

showtPrec :: Int -> (a, b, c, d, e, f) -> Text Source #

showt :: (a, b, c, d, e, f) -> Text Source #

showtList :: [(a, b, c, d, e, f)] -> Text Source #

showtlPrec :: Int -> (a, b, c, d, e, f) -> Text Source #

showtl :: (a, b, c, d, e, f) -> Text Source #

showtlList :: [(a, b, c, d, e, f)] -> Text Source #

(TextShow a, TextShow b, TextShow c, TextShow d, TextShow e, TextShow f, TextShow g) => TextShow (a, b, c, d, e, f, g) Source #

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

showbPrec :: Int -> (a, b, c, d, e, f, g) -> Builder Source #

showb :: (a, b, c, d, e, f, g) -> Builder Source #

showbList :: [(a, b, c, d, e, f, g)] -> Builder Source #

showtPrec :: Int -> (a, b, c, d, e, f, g) -> Text Source #

showt :: (a, b, c, d, e, f, g) -> Text Source #

showtList :: [(a, b, c, d, e, f, g)] -> Text Source #

showtlPrec :: Int -> (a, b, c, d, e, f, g) -> Text Source #

showtl :: (a, b, c, d, e, f, g) -> Text Source #

showtlList :: [(a, b, c, d, e, f, g)] -> Text Source #

(TextShow a, TextShow b, TextShow c, TextShow d, TextShow e, TextShow f, TextShow g, TextShow h) => TextShow (a, b, c, d, e, f, g, h) Source #

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

showbPrec :: Int -> (a, b, c, d, e, f, g, h) -> Builder Source #

showb :: (a, b, c, d, e, f, g, h) -> Builder Source #

showbList :: [(a, b, c, d, e, f, g, h)] -> Builder Source #

showtPrec :: Int -> (a, b, c, d, e, f, g, h) -> Text Source #

showt :: (a, b, c, d, e, f, g, h) -> Text Source #

showtList :: [(a, b, c, d, e, f, g, h)] -> Text Source #

showtlPrec :: Int -> (a, b, c, d, e, f, g, h) -> Text Source #

showtl :: (a, b, c, d, e, f, g, h) -> Text Source #

showtlList :: [(a, b, c, d, e, f, g, h)] -> Text Source #

(TextShow a, TextShow b, TextShow c, TextShow d, TextShow e, TextShow f, TextShow g, TextShow h, TextShow i) => TextShow (a, b, c, d, e, f, g, h, i) Source #

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

showbPrec :: Int -> (a, b, c, d, e, f, g, h, i) -> Builder Source #

showb :: (a, b, c, d, e, f, g, h, i) -> Builder Source #

showbList :: [(a, b, c, d, e, f, g, h, i)] -> Builder Source #

showtPrec :: Int -> (a, b, c, d, e, f, g, h, i) -> Text Source #

showt :: (a, b, c, d, e, f, g, h, i) -> Text Source #

showtList :: [(a, b, c, d, e, f, g, h, i)] -> Text Source #

showtlPrec :: Int -> (a, b, c, d, e, f, g, h, i) -> Text Source #

showtl :: (a, b, c, d, e, f, g, h, i) -> Text Source #

showtlList :: [(a, b, c, d, e, f, g, h, i)] -> Text Source #

(TextShow a, TextShow b, TextShow c, TextShow d, TextShow e, TextShow f, TextShow g, TextShow h, TextShow i, TextShow j) => TextShow (a, b, c, d, e, f, g, h, i, j) Source #

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

showbPrec :: Int -> (a, b, c, d, e, f, g, h, i, j) -> Builder Source #

showb :: (a, b, c, d, e, f, g, h, i, j) -> Builder Source #

showbList :: [(a, b, c, d, e, f, g, h, i, j)] -> Builder Source #

showtPrec :: Int -> (a, b, c, d, e, f, g, h, i, j) -> Text Source #

showt :: (a, b, c, d, e, f, g, h, i, j) -> Text Source #

showtList :: [(a, b, c, d, e, f, g, h, i, j)] -> Text Source #

showtlPrec :: Int -> (a, b, c, d, e, f, g, h, i, j) -> Text Source #

showtl :: (a, b, c, d, e, f, g, h, i, j) -> Text Source #

showtlList :: [(a, b, c, d, e, f, g, h, i, j)] -> Text Source #

(TextShow a, TextShow b, TextShow c, TextShow d, TextShow e, TextShow f, TextShow g, TextShow h, TextShow i, TextShow j, TextShow k) => TextShow (a, b, c, d, e, f, g, h, i, j, k) Source #

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

showbPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k) -> Builder Source #

showb :: (a, b, c, d, e, f, g, h, i, j, k) -> Builder Source #

showbList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Builder Source #

showtPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k) -> Text Source #

showt :: (a, b, c, d, e, f, g, h, i, j, k) ->