text-show-3.7.5: 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

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.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
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 StaticPtrInfo Source #

Since: 2

Instance details

Defined in TextShow.GHC.StaticPtr

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 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 SomeException Source #

Since: 2

Instance details

Defined in TextShow.Control.Exception

TextShow SrcLoc Source #

Since: 3.0.1

Instance details

Defined in TextShow.GHC.Stack

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 I16 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

HasResolution a => TextShow (Fixed a) Source #

Since: 2

Instance details

Defined in TextShow.Data.Fixed

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 (Option a) 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 #

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

(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 (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) -> Text Source #

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

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

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

showtlList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> 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 l) => TextShow (a, b, c, d, e, f, g, h, i, j, k, l) Source #

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

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

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

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

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

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

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

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

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

showtlList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> 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 l, TextShow m) => TextShow (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

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

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

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

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

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

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

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

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

showtlList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> 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 l, TextShow m, TextShow n) => TextShow (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

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

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

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

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

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

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

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

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

showtlList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> 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 l, TextShow m, TextShow n, TextShow o) => TextShow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

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

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

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

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

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

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

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

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

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

showbParen :: Bool -> Builder -> Builder Source #

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

Since: 2

showtParen :: Bool -> Text -> Text Source #

Surrounds strict Text output with parentheses if the Bool parameter is True.

Since: 3.4

showtlParen :: Bool -> Text -> Text Source #

Surrounds lazy Text output with parentheses if the Bool parameter is True.

Since: 3.4

showbCommaSpace :: Builder Source #

Construct a Builder containing a comma followed by a space.

Since: 3.6

showtCommaSpace :: Text Source #

Construct a strict Text containing a comma followed by a space.

Since: 3.6

showtlCommaSpace :: Text Source #

Construct a lazy Text containing a comma followed by a space.

Since: 3.6

showbSpace :: Builder Source #

Construct a Builder containing a single space character.

Since: 2

showtSpace :: Text Source #

Construct a strict Text containing a single space character.

Since: 3.4

showtlSpace :: Text Source #

Construct a lazy Text containing a single space character.

Since: 3.4

TextShow1

class TextShow1 f where Source #

Lifting of the TextShow class to unary type constructors.

Since: 2

Minimal complete definition

liftShowbPrec

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder Source #

showbPrec function for an application of the type constructor based on showbPrec and showbList functions for the argument type.

Since: 3

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [f a] -> Builder Source #

showbList function for an application of the type constructor based on showbPrec and showbList functions for the argument type. The default implementation using standard list syntax is correct for most types.

Since: 3

Instances
TextShow1 [] Source #

Since: 2

Instance details

Defined in TextShow.Data.List

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> [a] -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [[a]] -> Builder Source #

TextShow1 Maybe Source #

Since: 2

Instance details

Defined in TextShow.Data.Maybe

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Maybe a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Maybe a] -> Builder Source #

TextShow1 Ratio Source #

Since: 2

Instance details

Defined in TextShow.Data.Ratio

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Ratio a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Ratio a] -> Builder Source #

TextShow1 Ptr Source #

Since: 2

Instance details

Defined in TextShow.Foreign.Ptr

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Ptr a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Ptr a] -> Builder Source #

TextShow1 FunPtr Source #

Since: 2

Instance details

Defined in TextShow.Foreign.Ptr

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FunPtr a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FunPtr a] -> Builder Source #

TextShow1 Par1 Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Par1 a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Par1 a] -> Builder Source #

TextShow1 ForeignPtr Source #

Since: 2

Instance details

Defined in TextShow.Foreign.Ptr

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> ForeignPtr a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [ForeignPtr a] -> Builder Source #

TextShow1 Complex Source #

Since: 2

Instance details

Defined in TextShow.Data.Complex

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Complex a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Complex a] -> Builder Source #

TextShow1 Min Source #

Since: 3

Instance details

Defined in TextShow.Data.Semigroup

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Min a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Min a] -> Builder Source #

TextShow1 Max Source #

Since: 3

Instance details

Defined in TextShow.Data.Semigroup

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Max a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Max a] -> Builder Source #

TextShow1 First Source #

Since: 3

Instance details

Defined in TextShow.Data.Semigroup

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> First a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [First a] -> Builder Source #

TextShow1 Last Source #

Since: 3

Instance details

Defined in TextShow.Data.Semigroup

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Last a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Last a] -> Builder Source #

TextShow1 WrappedMonoid Source #

Since: 3

Instance details

Defined in TextShow.Data.Semigroup

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> WrappedMonoid a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [WrappedMonoid a] -> Builder Source #

TextShow1 Option Source #

Since: 3

Instance details

Defined in TextShow.Data.Semigroup

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Option a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Option a] -> Builder Source #

TextShow1 ZipList Source #

Since: 2

Instance details

Defined in TextShow.Control.Applicative

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> ZipList a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [ZipList a] -> Builder Source #

TextShow1 Identity Source #

Since: 3

Instance details

Defined in TextShow.Data.Functor.Identity

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Identity a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Identity a] -> Builder Source #

TextShow1 First Source #

Since: 2

Instance details

Defined in TextShow.Data.Monoid

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> First a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [First a] -> Builder Source #

TextShow1 Last Source #

Since: 2

Instance details

Defined in TextShow.Data.Monoid

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Last a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Last a] -> Builder Source #

TextShow1 Dual Source #

Since: 2

Instance details

Defined in TextShow.Data.Monoid

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Dual a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Dual a] -> Builder Source #

TextShow1 Sum Source #

Since: 2

Instance details

Defined in TextShow.Data.Monoid

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Sum a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Sum a] -> Builder Source #

TextShow1 Product Source #

Since: 2

Instance details

Defined in TextShow.Data.Monoid

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Product a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Product a] -> Builder Source #

TextShow1 Down Source #

Since: 2

Instance details

Defined in TextShow.Data.Ord

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Down a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Down a] -> Builder Source #

TextShow1 NonEmpty Source #

Since: 3

Instance details

Defined in TextShow.Data.List.NonEmpty

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> NonEmpty a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [NonEmpty a] -> Builder Source #

TextShow1 FromTextShow Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromTextShow a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromTextShow a] -> Builder Source #

TextShow1 FromStringShow Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromStringShow a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromStringShow a] -> Builder Source #

TextShow a => TextShow1 (Either a) Source #

Since: 2

Instance details

Defined in TextShow.Data.Either

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> Either a a0 -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [Either a a0] -> Builder Source #

TextShow1 (U1 :: * -> *) Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> U1 a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [U1 a] -> Builder Source #

TextShow1 (TypeRep :: * -> *) Source #

Only available with base-4.10.0.0 or later.

Since: 3.6

Instance details

Defined in TextShow.Data.Typeable

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> TypeRep a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [TypeRep a] -> Builder Source #

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> (a, a0) -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [(a, a0)] -> Builder Source #

TextShow1 (ST s) Source #

Since: 2

Instance details

Defined in TextShow.Control.Monad.ST

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> ST s a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [ST s a] -> Builder Source #

TextShow a => TextShow1 (Arg a) Source #

Since: 3

Instance details

Defined in TextShow.Data.Semigroup

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> Arg a a0 -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [Arg a a0] -> Builder Source #

TextShow1 (Proxy :: * -> *) Source #

Since: 2

Instance details

Defined in TextShow.Data.Proxy

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Proxy a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Proxy a] -> Builder Source #

TextShow1 f => TextShow1 (Rec1 f) Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Rec1 f a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Rec1 f a] -> Builder Source #

TextShow1 (URec Char :: * -> *) Source #

Since: 2.1.2

Instance details

Defined in TextShow.GHC.Generics

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> URec Char a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [URec Char a] -> Builder Source #

TextShow1 (URec Double :: * -> *) Source #

Since: 2.1.2

Instance details

Defined in TextShow.GHC.Generics

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> URec Double a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [URec Double a] -> Builder Source #

TextShow1 (URec Float :: * -> *) Source #

Since: 2.1.2

Instance details

Defined in TextShow.GHC.Generics

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> URec Float a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [URec Float a] -> Builder Source #

TextShow1 (URec Int :: * -> *) Source #

Since: 2.1.2

Instance details

Defined in TextShow.GHC.Generics

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> URec Int a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [URec Int a] -> Builder Source #

TextShow1 (URec Word :: * -> *) Source #

Since: 2.1.2

Instance details

Defined in TextShow.GHC.Generics

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> URec Word a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [URec Word a] -> Builder Source #

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> (a, b, a0) -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [(a, b, a0)] -> Builder Source #

TextShow a => TextShow1 (Const a :: * -> *) Source #

Since: 2

Instance details

Defined in TextShow.Control.Applicative

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> Const a a0 -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [Const a a0] -> Builder Source #

TextShow1 f => TextShow1 (Alt f) Source #

Only available with base-4.8.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Data.Monoid

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Alt f a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Alt f a] -> Builder Source #

TextShow1 (Coercion a) Source #

Since: 2

Instance details

Defined in TextShow.Data.Type.Coercion

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> Coercion a a0 -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [Coercion a a0] -> Builder Source #

TextShow1 ((:~:) a) Source #

Since: 2

Instance details

Defined in TextShow.Data.Type.Equality

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> (a :~: a0) -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [a :~: a0] -> Builder Source #

TextShow1 f => TextShow1 (FromTextShow1 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromTextShow1 f a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromTextShow1 f a] -> Builder Source #

Show1 f => TextShow1 (FromStringShow1 f) Source #

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromStringShow1 f a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromStringShow1 f a] -> Builder Source #

(Generic1 f, GTextShowB One (Rep1 f)) => TextShow1 (FromGeneric1 f) Source #

Since: 3.7.4

Instance details

Defined in TextShow.Generic

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromGeneric1 f a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromGeneric1 f a] -> Builder Source #

TextShow1 ((->) a :: * -> *) Source #

Since: 2

Instance details

Defined in TextShow.Functions

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> (a -> a0) -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [a -> a0] -> Builder Source #

TextShow c => TextShow1 (K1 i c :: * -> *) Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> K1 i c a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [K1 i c a] -> Builder Source #

(TextShow1 f, TextShow1 g) => TextShow1 (f :+: g) Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> (f :+: g) a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [(f :+: g) a] -> Builder Source #

(TextShow1 f, TextShow1 g) => TextShow1 (f :*: g) Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> (f :*: g) a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [(f :*: g) a] -> Builder Source #

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> (a, b, c, a0) -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [(a, b, c, a0)] -> Builder Source #

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

Since: 3

Instance details

Defined in TextShow.Data.Functor.Product

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Product f g a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Product f g a] -> Builder Source #

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

Since: 3

Instance details

Defined in TextShow.Data.Functor.Sum

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Sum f g a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Sum f g a] -> Builder Source #

TextShow1 ((:~~:) a :: * -> *) Source #

Since: 3.6

Instance details

Defined in TextShow.Data.Type.Equality

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> (a :~~: a0) -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [a :~~: a0] -> Builder Source #

TextShow1 f => TextShow1 (M1 i c f) Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> M1 i c f a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [M1 i c f a] -> Builder Source #

(TextShow1 f, TextShow1 g) => TextShow1 (f :.: g) Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> (f :.: g) a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [(f :.: g) a] -> Builder Source #

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> (a, b, c, d, a0) -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [(a, b, c, d, a0)] -> Builder Source #

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

Since: 3

Instance details

Defined in TextShow.Data.Functor.Compose

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> Compose f g a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [Compose f g a] -> Builder Source #

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

Defined in TextShow.FromStringTextShow

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> FromTextShow2 f a a0 -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [FromTextShow2 f a a0] -> Builder Source #

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

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> FromStringShow2 f a a0 -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [FromStringShow2 f a a0] -> Builder Source #

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

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

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

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

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

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

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

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

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

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

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

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

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

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

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

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

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

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

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

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

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

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

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

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

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, a0) -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, a0)] -> Builder Source #

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, a0) -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, a0)] -> Builder Source #

showbPrec1 :: (TextShow1 f, TextShow a) => Int -> f a -> Builder Source #

Lift the standard showbPrec and showbList functions 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

liftShowtPrec :: TextShow1 f => (Int -> a -> Text) -> ([a] -> Text) -> Int -> f a -> Text Source #

showtPrec function for an application of the type constructor based on showtPrec and showtList functions for the argument type.

The current implementation is based on liftShowbPrec internally.

Since: 3.4

liftShowtlPrec :: TextShow1 f => (Int -> a -> Text) -> ([a] -> Text) -> Int -> f a -> Text Source #

showtlPrec function for an application of the type constructor based on showtlPrec and showtlList functions for the argument type.

The current implementation is based on liftShowbPrec internally.

Since: 3.4

TextShow2

class TextShow2 f where Source #

Lifting of the TextShow class to binary type constructors.

Since: 2

Minimal complete definition

liftShowbPrec2

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> f a b -> Builder Source #

showbPrec function for an application of the type constructor based on showbPrec and showbList functions for the argument types.

Since: 3

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [f a b] -> Builder Source #

showbList function for an application of the type constructor based on showbPrec and showbList functions for the argument types. The default implementation using standard list syntax is correct for most types.

Since: 3

Instances
TextShow2 Either Source #

Since: 2

Instance details

Defined in TextShow.Data.Either

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> Either a b -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [Either a b] -> Builder Source #

TextShow2 (,) Source #

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

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

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

TextShow2 ST Source #

Since: 2

Instance details

Defined in TextShow.Control.Monad.ST

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> ST a b -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [ST a b] -> Builder Source #

TextShow2 Arg Source #

Since: 3

Instance details

Defined in TextShow.Data.Semigroup

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> Arg a b -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [Arg a b] -> Builder Source #

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> (a, a0, b) -> Builder Source #

liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [(a, a0, b)] -> Builder Source #

TextShow2 (Const :: * -> * -> *) Source #

Since: 2

Instance details

Defined in TextShow.Control.Applicative

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> Const a b -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [Const a b] -> Builder Source #

TextShow2 (Coercion :: * -> * -> *) Source #

Since: 2

Instance details

Defined in TextShow.Data.Type.Coercion

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> Coercion a b -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [Coercion a b] -> Builder Source #

TextShow2 ((:~:) :: * -> * -> *) Source #

Since: 2

Instance details

Defined in TextShow.Data.Type.Equality

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> (a :~: b) -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [a :~: b] -> Builder Source #

TextShow2 ((->) :: * -> * -> *) Source #

Since: 2

Instance details

Defined in TextShow.Functions

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> (a -> b) -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [a -> b] -> Builder Source #

TextShow2 (K1 i :: * -> * -> *) Source #

Since: 2

Instance details

Defined in TextShow.GHC.Generics

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> K1 i a b -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [K1 i a b] -> Builder Source #

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, a0, b0) -> Builder Source #

liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, a0, b0)] -> Builder Source #

TextShow2 ((:~~:) :: * -> * -> *) Source #

Since: 3.6

Instance details

Defined in TextShow.Data.Type.Equality

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> (a :~~: b) -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [a :~~: b] -> Builder Source #

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, a0, b0) -> Builder Source #

liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, a0, b0)] -> Builder Source #

TextShow2 f => TextShow2 (FromTextShow2 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> FromTextShow2 f a b -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [FromTextShow2 f a b] -> Builder Source #

Show2 f => TextShow2 (FromStringShow2 f) Source #

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> FromStringShow2 f a b -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [FromStringShow2 f a b] -> Builder Source #

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, a0, b0) -> Builder Source #

liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, a0, b0)] -> Builder Source #

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, e, a0, b0) -> Builder Source #

liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, e, a0, b0)] -> Builder Source #

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, e, f, a0, b0) -> Builder Source #

liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, e, f, a0, b0)] -> Builder Source #

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, e, f, g, a0, b0) -> Builder Source #

liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, e, f, g, a0, b0)] -> Builder Source #

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, e, f, g, h, a0, b0) -> Builder Source #

liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, e, f, g, h, a0, b0)] -> Builder Source #

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

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

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

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

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

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

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

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

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

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, e, f, g, h, i, j, k, l, a0, b0) -> Builder Source #

liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, e, f, g, h, i, j, k, l, a0, b0)] -> Builder Source #

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

Since: 2

Instance details

Defined in TextShow.Data.Tuple

Methods

liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, a0, b0) -> Builder Source #

liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, a0, b0)] -> Builder Source #

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

liftShowtPrec2 :: TextShow2 f => (Int -> a -> Text) -> ([a] -> Text) -> (Int -> b -> Text) -> ([b] -> Text) -> Int -> f a b -> Text Source #

showtPrec function for an application of the type constructor based on showtPrec and showtList functions for the argument type.

The current implementation is based on liftShowbPrec2 internally.

Since: 3.4

liftShowtlPrec2 :: TextShow2 f => (Int -> a -> Text) -> ([a] -> Text) -> (Int -> b -> Text) -> ([b] -> Text) -> Int -> f a b -> Text Source #

showtlPrec function for an application of the type constructor based on showtlPrec and showtlList functions for the argument type.

The current implementation is based on liftShowbPrec2 internally.

Since: 3.4

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.

Instances
Eq Builder 
Instance details

Defined in Data.Text.Internal.Builder

Methods

(==) :: Builder -> Builder -> Bool #

(/=) :: Builder -> Builder -> Bool #

Ord Builder 
Instance details

Defined in Data.Text.Internal.Builder

Show Builder 
Instance details

Defined in Data.Text.Internal.Builder

IsString Builder 
Instance details

Defined in Data.Text.Internal.Builder

Methods

fromString :: String -> Builder #

Semigroup Builder 
Instance details

Defined in Data.Text.Internal.Builder

Monoid Builder 
Instance details

Defined in Data.Text.Internal.Builder

TextShow Builder Source #

Since: 2

Instance details

Defined in TextShow.Data.Text

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

Conversions

Conversion between TextShow and string Show

newtype FromStringShow a Source #

An adapter newtype, suitable for DerivingVia. The TextShow instance for FromStringShow is based on its String Show instance. That is,

showbPrec p (FromStringShow x) = showsToShowb showsPrec p x

Since: 2

Constructors

FromStringShow 

Fields

Instances
Functor FromStringShow Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

fmap :: (a -> b) -> FromStringShow a -> FromStringShow b #

(<$) :: a -> FromStringShow b -> FromStringShow a #

Foldable FromStringShow Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

fold :: Monoid m => FromStringShow m -> m #

foldMap :: Monoid m => (a -> m) -> FromStringShow a -> m #

foldr :: (a -> b -> b) -> b -> FromStringShow a -> b #

foldr' :: (a -> b -> b) -> b -> FromStringShow a -> b #

foldl :: (b -> a -> b) -> b -> FromStringShow a -> b #

foldl' :: (b -> a -> b) -> b -> FromStringShow a -> b #

foldr1 :: (a -> a -> a) -> FromStringShow a -> a #

foldl1 :: (a -> a -> a) -> FromStringShow a -> a #

toList :: FromStringShow a -> [a] #

null :: FromStringShow a -> Bool #

length :: FromStringShow a -> Int #

elem :: Eq a => a -> FromStringShow a -> Bool #

maximum :: Ord a => FromStringShow a -> a #

minimum :: Ord a => FromStringShow a -> a #

sum :: Num a => FromStringShow a -> a #

product :: Num a => FromStringShow a -> a #

Traversable FromStringShow Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

traverse :: Applicative f => (a -> f b) -> FromStringShow a -> f (FromStringShow b) #

sequenceA :: Applicative f => FromStringShow (f a) -> f (FromStringShow a) #

mapM :: Monad m => (a -> m b) -> FromStringShow a -> m (FromStringShow b) #

sequence :: Monad m => FromStringShow (m a) -> m (FromStringShow a) #

Show1 FromStringShow Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> FromStringShow a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [FromStringShow a] -> ShowS #

TextShow1 FromStringShow Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromStringShow a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromStringShow a] -> Builder Source #

Eq a => Eq (FromStringShow a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Data a => Data (FromStringShow a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FromStringShow a -> c (FromStringShow a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromStringShow a) #

toConstr :: FromStringShow a -> Constr #

dataTypeOf :: FromStringShow a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FromStringShow a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FromStringShow a)) #

gmapT :: (forall b. Data b => b -> b) -> FromStringShow a -> FromStringShow a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromStringShow a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromStringShow a -> r #

gmapQ :: (forall d. Data d => d -> u) -> FromStringShow a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FromStringShow a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromStringShow a -> m (FromStringShow a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromStringShow a -> m (FromStringShow a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromStringShow a -> m (FromStringShow a) #

Ord a => Ord (FromStringShow a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Read a => Read (FromStringShow a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

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

Defined in TextShow.FromStringTextShow

Generic (FromStringShow a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Associated Types

type Rep (FromStringShow a) :: * -> * #

Lift a => Lift (FromStringShow a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

lift :: FromStringShow a -> Q Exp #

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

Defined in TextShow.FromStringTextShow

Generic1 FromStringShow Source # 
Instance details

Defined in TextShow.FromStringTextShow

Associated Types

type Rep1 FromStringShow :: k -> * #

type Rep (FromStringShow a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

type Rep (FromStringShow a) = D1 (MetaData "FromStringShow" "TextShow.FromStringTextShow" "text-show-3.7.5-Gp7gM9Y3nCY2xeUEqySIHL" True) (C1 (MetaCons "FromStringShow" PrefixI True) (S1 (MetaSel (Just "fromStringShow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 FromStringShow Source # 
Instance details

Defined in TextShow.FromStringTextShow

type Rep1 FromStringShow = D1 (MetaData "FromStringShow" "TextShow.FromStringTextShow" "text-show-3.7.5-Gp7gM9Y3nCY2xeUEqySIHL" True) (C1 (MetaCons "FromStringShow" PrefixI True) (S1 (MetaSel (Just "fromStringShow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

newtype FromTextShow a Source #

An adapter newtype, suitable for DerivingVia. 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

Instances
Functor FromTextShow Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

fmap :: (a -> b) -> FromTextShow a -> FromTextShow b #

(<$) :: a -> FromTextShow b -> FromTextShow a #

Foldable FromTextShow Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

fold :: Monoid m => FromTextShow m -> m #

foldMap :: Monoid m => (a -> m) -> FromTextShow a -> m #

foldr :: (a -> b -> b) -> b -> FromTextShow a -> b #

foldr' :: (a -> b -> b) -> b -> FromTextShow a -> b #

foldl :: (b -> a -> b) -> b -> FromTextShow a -> b #

foldl' :: (b -> a -> b) -> b -> FromTextShow a -> b #

foldr1 :: (a -> a -> a) -> FromTextShow a -> a #

foldl1 :: (a -> a -> a) -> FromTextShow a -> a #

toList :: FromTextShow a -> [a] #

null :: FromTextShow a -> Bool #

length :: FromTextShow a -> Int #

elem :: Eq a => a -> FromTextShow a -> Bool #

maximum :: Ord a => FromTextShow a -> a #

minimum :: Ord a => FromTextShow a -> a #

sum :: Num a => FromTextShow a -> a #

product :: Num a => FromTextShow a -> a #

Traversable FromTextShow Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

traverse :: Applicative f => (a -> f b) -> FromTextShow a -> f (FromTextShow b) #

sequenceA :: Applicative f => FromTextShow (f a) -> f (FromTextShow a) #

mapM :: Monad m => (a -> m b) -> FromTextShow a -> m (FromTextShow b) #

sequence :: Monad m => FromTextShow (m a) -> m (FromTextShow a) #

Show1 FromTextShow Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> FromTextShow a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [FromTextShow a] -> ShowS #

TextShow1 FromTextShow Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromTextShow a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromTextShow a] -> Builder Source #

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

Defined in TextShow.FromStringTextShow

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

Defined in TextShow.FromStringTextShow

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FromTextShow a -> c (FromTextShow a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromTextShow a) #

toConstr :: FromTextShow a -> Constr #

dataTypeOf :: FromTextShow a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FromTextShow a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FromTextShow a)) #

gmapT :: (forall b. Data b => b -> b) -> FromTextShow a -> FromTextShow a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromTextShow a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromTextShow a -> r #

gmapQ :: (forall d. Data d => d -> u) -> FromTextShow a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FromTextShow a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromTextShow a -> m (FromTextShow a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromTextShow a -> m (FromTextShow a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromTextShow a -> m (FromTextShow a) #

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

Defined in TextShow.FromStringTextShow

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

Defined in TextShow.FromStringTextShow

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

Defined in TextShow.FromStringTextShow

Generic (FromTextShow a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Associated Types

type Rep (FromTextShow a) :: * -> * #

Methods

from :: FromTextShow a -> Rep (FromTextShow a) x #

to :: Rep (FromTextShow a) x -> FromTextShow a #

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

Defined in TextShow.FromStringTextShow

Methods

lift :: FromTextShow a -> Q Exp #

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

Defined in TextShow.FromStringTextShow

Generic1 FromTextShow Source # 
Instance details

Defined in TextShow.FromStringTextShow

Associated Types

type Rep1 FromTextShow :: k -> * #

type Rep (FromTextShow a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

type Rep (FromTextShow a) = D1 (MetaData "FromTextShow" "TextShow.FromStringTextShow" "text-show-3.7.5-Gp7gM9Y3nCY2xeUEqySIHL" True) (C1 (MetaCons "FromTextShow" PrefixI True) (S1 (MetaSel (Just "fromTextShow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 FromTextShow Source # 
Instance details

Defined in TextShow.FromStringTextShow

type Rep1 FromTextShow = D1 (MetaData "FromTextShow" "TextShow.FromStringTextShow" "text-show-3.7.5-Gp7gM9Y3nCY2xeUEqySIHL" True) (C1 (MetaCons "FromTextShow" PrefixI True) (S1 (MetaSel (Just "fromTextShow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

newtype FromStringShow1 f a Source #

An adapter newtype, suitable for DerivingVia. The TextShow1 instance for FromStringShow1 is based on its String Show1 instance. That is,

liftShowbPrec sp sl p (FromStringShow1 x) =
    showsPrecToShowbPrec (liftShowsPrec (showbPrecToShowsPrec sp)
                                            (showbToShows         sl))
                           p x

Since: 3

Constructors

FromStringShow1 

Fields

Instances
Generic1 (FromStringShow1 f :: k -> *) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Associated Types

type Rep1 (FromStringShow1 f) :: k -> * #

Functor f => Functor (FromStringShow1 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

fmap :: (a -> b) -> FromStringShow1 f a -> FromStringShow1 f b #

(<$) :: a -> FromStringShow1 f b -> FromStringShow1 f a #

Foldable f => Foldable (FromStringShow1 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

fold :: Monoid m => FromStringShow1 f m -> m #

foldMap :: Monoid m => (a -> m) -> FromStringShow1 f a -> m #

foldr :: (a -> b -> b) -> b -> FromStringShow1 f a -> b #

foldr' :: (a -> b -> b) -> b -> FromStringShow1 f a -> b #

foldl :: (b -> a -> b) -> b -> FromStringShow1 f a -> b #

foldl' :: (b -> a -> b) -> b -> FromStringShow1 f a -> b #

foldr1 :: (a -> a -> a) -> FromStringShow1 f a -> a #

foldl1 :: (a -> a -> a) -> FromStringShow1 f a -> a #

toList :: FromStringShow1 f a -> [a] #

null :: FromStringShow1 f a -> Bool #

length :: FromStringShow1 f a -> Int #

elem :: Eq a => a -> FromStringShow1 f a -> Bool #

maximum :: Ord a => FromStringShow1 f a -> a #

minimum :: Ord a => FromStringShow1 f a -> a #

sum :: Num a => FromStringShow1 f a -> a #

product :: Num a => FromStringShow1 f a -> a #

Traversable f => Traversable (FromStringShow1 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

traverse :: Applicative f0 => (a -> f0 b) -> FromStringShow1 f a -> f0 (FromStringShow1 f b) #

sequenceA :: Applicative f0 => FromStringShow1 f (f0 a) -> f0 (FromStringShow1 f a) #

mapM :: Monad m => (a -> m b) -> FromStringShow1 f a -> m (FromStringShow1 f b) #

sequence :: Monad m => FromStringShow1 f (m a) -> m (FromStringShow1 f a) #

Show1 f => Show1 (FromStringShow1 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> FromStringShow1 f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [FromStringShow1 f a] -> ShowS #

Show1 f => TextShow1 (FromStringShow1 f) Source #

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromStringShow1 f a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromStringShow1 f a] -> Builder Source #

Eq (f a) => Eq (FromStringShow1 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

(Typeable a, Typeable f, Typeable k, Data (f a)) => Data (FromStringShow1 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FromStringShow1 f a -> c (FromStringShow1 f a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromStringShow1 f a) #

toConstr :: FromStringShow1 f a -> Constr #

dataTypeOf :: FromStringShow1 f a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FromStringShow1 f a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FromStringShow1 f a)) #

gmapT :: (forall b. Data b => b -> b) -> FromStringShow1 f a -> FromStringShow1 f a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromStringShow1 f a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromStringShow1 f a -> r #

gmapQ :: (forall d. Data d => d -> u) -> FromStringShow1 f a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FromStringShow1 f a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromStringShow1 f a -> m (FromStringShow1 f a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromStringShow1 f a -> m (FromStringShow1 f a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromStringShow1 f a -> m (FromStringShow1 f a) #

Ord (f a) => Ord (FromStringShow1 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Read (f a) => Read (FromStringShow1 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

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

Defined in TextShow.FromStringTextShow

Generic (FromStringShow1 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Associated Types

type Rep (FromStringShow1 f a) :: * -> * #

Methods

from :: FromStringShow1 f a -> Rep (FromStringShow1 f a) x #

to :: Rep (FromStringShow1 f a) x -> FromStringShow1 f a #

Lift (f a) => Lift (FromStringShow1 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

lift :: FromStringShow1 f a -> Q Exp #

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

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

type Rep1 (FromStringShow1 f :: k -> *) Source # 
Instance details

Defined in TextShow.FromStringTextShow

type Rep1 (FromStringShow1 f :: k -> *) = D1 (MetaData "FromStringShow1" "TextShow.FromStringTextShow" "text-show-3.7.5-Gp7gM9Y3nCY2xeUEqySIHL" True) (C1 (MetaCons "FromStringShow1" PrefixI True) (S1 (MetaSel (Just "fromStringShow1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 f)))
type Rep (FromStringShow1 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

type Rep (FromStringShow1 f a) = D1 (MetaData "FromStringShow1" "TextShow.FromStringTextShow" "text-show-3.7.5-Gp7gM9Y3nCY2xeUEqySIHL" True) (C1 (MetaCons "FromStringShow1" PrefixI True) (S1 (MetaSel (Just "fromStringShow1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a))))

newtype FromTextShow1 f a Source #

An adapter newtype, suitable for DerivingVia. The String Show1 instance for FromTextShow1 is based on its TextShow1 instance. That is,

liftShowsPrec sp sl p (FromTextShow1 x) =
    showbPrecToShowsPrec (liftShowbPrec (showsPrecToShowbPrec sp)
                                            (showsToShowb         sl))
                           p x

Since: 3

Constructors

FromTextShow1 

Fields

Instances
Generic1 (FromTextShow1 f :: k -> *) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Associated Types

type Rep1 (FromTextShow1 f) :: k -> * #

Methods

from1 :: FromTextShow1 f a -> Rep1 (FromTextShow1 f) a #

to1 :: Rep1 (FromTextShow1 f) a -> FromTextShow1 f a #

Functor f => Functor (FromTextShow1 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

fmap :: (a -> b) -> FromTextShow1 f a -> FromTextShow1 f b #

(<$) :: a -> FromTextShow1 f b -> FromTextShow1 f a #

Foldable f => Foldable (FromTextShow1 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

fold :: Monoid m => FromTextShow1 f m -> m #

foldMap :: Monoid m => (a -> m) -> FromTextShow1 f a -> m #

foldr :: (a -> b -> b) -> b -> FromTextShow1 f a -> b #

foldr' :: (a -> b -> b) -> b -> FromTextShow1 f a -> b #

foldl :: (b -> a -> b) -> b -> FromTextShow1 f a -> b #

foldl' :: (b -> a -> b) -> b -> FromTextShow1 f a -> b #

foldr1 :: (a -> a -> a) -> FromTextShow1 f a -> a #

foldl1 :: (a -> a -> a) -> FromTextShow1 f a -> a #

toList :: FromTextShow1 f a -> [a] #

null :: FromTextShow1 f a -> Bool #

length :: FromTextShow1 f a -> Int #

elem :: Eq a => a -> FromTextShow1 f a -> Bool #

maximum :: Ord a => FromTextShow1 f a -> a #

minimum :: Ord a => FromTextShow1 f a -> a #

sum :: Num a => FromTextShow1 f a -> a #

product :: Num a => FromTextShow1 f a -> a #

Traversable f => Traversable (FromTextShow1 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

traverse :: Applicative f0 => (a -> f0 b) -> FromTextShow1 f a -> f0 (FromTextShow1 f b) #

sequenceA :: Applicative f0 => FromTextShow1 f (f0 a) -> f0 (FromTextShow1 f a) #

mapM :: Monad m => (a -> m b) -> FromTextShow1 f a -> m (FromTextShow1 f b) #

sequence :: Monad m => FromTextShow1 f (m a) -> m (FromTextShow1 f a) #

TextShow1 f => Show1 (FromTextShow1 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> FromTextShow1 f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [FromTextShow1 f a] -> ShowS #

TextShow1 f => TextShow1 (FromTextShow1 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromTextShow1 f a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromTextShow1 f a] -> Builder Source #

Eq (f a) => Eq (FromTextShow1 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

(==) :: FromTextShow1 f a -> FromTextShow1 f a -> Bool #

(/=) :: FromTextShow1 f a -> FromTextShow1 f a -> Bool #

(Typeable a, Typeable f, Typeable k, Data (f a)) => Data (FromTextShow1 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FromTextShow1 f a -> c (FromTextShow1 f a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromTextShow1 f a) #

toConstr :: FromTextShow1 f a -> Constr #

dataTypeOf :: FromTextShow1 f a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FromTextShow1 f a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FromTextShow1 f a)) #

gmapT :: (forall b. Data b => b -> b) -> FromTextShow1 f a -> FromTextShow1 f a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromTextShow1 f a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromTextShow1 f a -> r #

gmapQ :: (forall d. Data d => d -> u) -> FromTextShow1 f a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FromTextShow1 f a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromTextShow1 f a -> m (FromTextShow1 f a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromTextShow1 f a -> m (FromTextShow1 f a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromTextShow1 f a -> m (FromTextShow1 f a) #

Ord (f a) => Ord (FromTextShow1 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Read (f a) => Read (FromTextShow1 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

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

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

Generic (FromTextShow1 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Associated Types

type Rep (FromTextShow1 f a) :: * -> * #

Methods

from :: FromTextShow1 f a -> Rep (FromTextShow1 f a) x #

to :: Rep (FromTextShow1 f a) x -> FromTextShow1 f a #

Lift (f a) => Lift (FromTextShow1 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

lift :: FromTextShow1 f a -> Q Exp #

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

Defined in TextShow.FromStringTextShow

type Rep1 (FromTextShow1 f :: k -> *) Source # 
Instance details

Defined in TextShow.FromStringTextShow

type Rep1 (FromTextShow1 f :: k -> *) = D1 (MetaData "FromTextShow1" "TextShow.FromStringTextShow" "text-show-3.7.5-Gp7gM9Y3nCY2xeUEqySIHL" True) (C1 (MetaCons "FromTextShow1" PrefixI True) (S1 (MetaSel (Just "fromTextShow1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 f)))
type Rep (FromTextShow1 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

type Rep (FromTextShow1 f a) = D1 (MetaData "FromTextShow1" "TextShow.FromStringTextShow" "text-show-3.7.5-Gp7gM9Y3nCY2xeUEqySIHL" True) (C1 (MetaCons "FromTextShow1" PrefixI True) (S1 (MetaSel (Just "fromTextShow1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a))))

newtype FromStringShow2 f a b Source #

An adapter newtype, suitable for DerivingVia. The TextShow2 instance for FromStringShow2 is based on its String Show2 instance. That is,

liftShowbPrec2 sp1 sl1 sp2 sl2 p (FromStringShow2 x) =
    showsPrecToShowbPrec (liftShowsPrec2 (showbPrecToShowsPrec sp1)
                                             (showbToShows         sl1)
                                             (showbPrecToShowsPrec sp2)
                                             (showbToShows         sl2))
                           p x

Since: 3

Constructors

FromStringShow2 

Fields

Instances
Generic1 (FromStringShow2 f a :: k1 -> *) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Associated Types

type Rep1 (FromStringShow2 f a) :: k -> * #

Methods

from1 :: FromStringShow2 f a a0 -> Rep1 (FromStringShow2 f a) a0 #

to1 :: Rep1 (FromStringShow2 f a) a0 -> FromStringShow2 f a a0 #

Bitraversable f => Bitraversable (FromStringShow2 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> FromStringShow2 f a b -> f0 (FromStringShow2 f c d) #

Bifoldable f => Bifoldable (FromStringShow2 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

bifold :: Monoid m => FromStringShow2 f m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> FromStringShow2 f a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> FromStringShow2 f a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> FromStringShow2 f a b -> c #

Bifunctor f => Bifunctor (FromStringShow2 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

bimap :: (a -> b) -> (c -> d) -> FromStringShow2 f a c -> FromStringShow2 f b d #

first :: (a -> b) -> FromStringShow2 f a c -> FromStringShow2 f b c #

second :: (b -> c) -> FromStringShow2 f a b -> FromStringShow2 f a c #

Show2 f => Show2 (FromStringShow2 f) Source #

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> FromStringShow2 f a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [FromStringShow2 f a b] -> ShowS #

Show2 f => TextShow2 (FromStringShow2 f) Source #

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> FromStringShow2 f a b -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [FromStringShow2 f a b] -> Builder Source #

Functor (f a) => Functor (FromStringShow2 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

fmap :: (a0 -> b) -> FromStringShow2 f a a0 -> FromStringShow2 f a b #

(<$) :: a0 -> FromStringShow2 f a b -> FromStringShow2 f a a0 #

Foldable (f a) => Foldable (FromStringShow2 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

fold :: Monoid m => FromStringShow2 f a m -> m #

foldMap :: Monoid m => (a0 -> m) -> FromStringShow2 f a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> FromStringShow2 f a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> FromStringShow2 f a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> FromStringShow2 f a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> FromStringShow2 f a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> FromStringShow2 f a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> FromStringShow2 f a a0 -> a0 #

toList :: FromStringShow2 f a a0 -> [a0] #

null :: FromStringShow2 f a a0 -> Bool #

length :: FromStringShow2 f a a0 -> Int #

elem :: Eq a0 => a0 -> FromStringShow2 f a a0 -> Bool #

maximum :: Ord a0 => FromStringShow2 f a a0 -> a0 #

minimum :: Ord a0 => FromStringShow2 f a a0 -> a0 #

sum :: Num a0 => FromStringShow2 f a a0 -> a0 #

product :: Num a0 => FromStringShow2 f a a0 -> a0 #

Traversable (f a) => Traversable (FromStringShow2 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

traverse :: Applicative f0 => (a0 -> f0 b) -> FromStringShow2 f a a0 -> f0 (FromStringShow2 f a b) #

sequenceA :: Applicative f0 => FromStringShow2 f a (f0 a0) -> f0 (FromStringShow2 f a a0) #

mapM :: Monad m => (a0 -> m b) -> FromStringShow2 f a a0 -> m (FromStringShow2 f a b) #

sequence :: Monad m => FromStringShow2 f a (m a0) -> m (FromStringShow2 f a a0) #

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

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> FromStringShow2 f a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [FromStringShow2 f a a0] -> ShowS #

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

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> FromStringShow2 f a a0 -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [FromStringShow2 f a a0] -> Builder Source #

Eq (f a b) => Eq (FromStringShow2 f a b) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

(==) :: FromStringShow2 f a b -> FromStringShow2 f a b -> Bool #

(/=) :: FromStringShow2 f a b -> FromStringShow2 f a b -> Bool #

(Typeable a, Typeable b, Typeable f, Typeable k1, Typeable k2, Data (f a b)) => Data (FromStringShow2 f a b) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> FromStringShow2 f a b -> c (FromStringShow2 f a b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromStringShow2 f a b) #

toConstr :: FromStringShow2 f a b -> Constr #

dataTypeOf :: FromStringShow2 f a b -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FromStringShow2 f a b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FromStringShow2 f a b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> FromStringShow2 f a b -> FromStringShow2 f a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromStringShow2 f a b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromStringShow2 f a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> FromStringShow2 f a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FromStringShow2 f a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromStringShow2 f a b -> m (FromStringShow2 f a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromStringShow2 f a b -> m (FromStringShow2 f a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromStringShow2 f a b -> m (FromStringShow2 f a b) #

Ord (f a b) => Ord (FromStringShow2 f a b) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Read (f a b) => Read (FromStringShow2 f a b) Source # 
Instance details

Defined in TextShow.FromStringTextShow

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

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

Generic (FromStringShow2 f a b) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Associated Types

type Rep (FromStringShow2 f a b) :: * -> * #

Methods

from :: FromStringShow2 f a b -> Rep (FromStringShow2 f a b) x #

to :: Rep (FromStringShow2 f a b) x -> FromStringShow2 f a b #

Lift (f a b) => Lift (FromStringShow2 f a b) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

lift :: FromStringShow2 f a b -> Q Exp #

(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

type Rep1 (FromStringShow2 f a :: k1 -> *) Source # 
Instance details

Defined in TextShow.FromStringTextShow

type Rep1 (FromStringShow2 f a :: k1 -> *) = D1 (MetaData "FromStringShow2" "TextShow.FromStringTextShow" "text-show-3.7.5-Gp7gM9Y3nCY2xeUEqySIHL" True) (C1 (MetaCons "FromStringShow2" PrefixI True) (S1 (MetaSel (Just "fromStringShow2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 (f a))))
type Rep (FromStringShow2 f a b) Source # 
Instance details

Defined in TextShow.FromStringTextShow

type Rep (FromStringShow2 f a b) = D1 (MetaData "FromStringShow2" "TextShow.FromStringTextShow" "text-show-3.7.5-Gp7gM9Y3nCY2xeUEqySIHL" True) (C1 (MetaCons "FromStringShow2" PrefixI True) (S1 (MetaSel (Just "fromStringShow2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a b))))

newtype FromTextShow2 f a b Source #

An adapter newtype, suitable for DerivingVia. The String Show2 instance for FromTextShow2 is based on its TextShow2 instance. That is,

liftShowsPrec2 sp1 sl1 sp2 sl2 p (FromTextShow2 x) =
    showbPrecToShowsPrec (liftShowbPrec2 (showsPrecToShowbPrec sp1)
                                             (showsToShowb         sl1)
                                             (showsPrecToShowbPrec sp2)
                                             (showsToShowb         sl2))
                           p x

Since: 3

Constructors

FromTextShow2 

Fields

Instances
Generic1 (FromTextShow2 f a :: k1 -> *) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Associated Types

type Rep1 (FromTextShow2 f a) :: k -> * #

Methods

from1 :: FromTextShow2 f a a0 -> Rep1 (FromTextShow2 f a) a0 #

to1 :: Rep1 (FromTextShow2 f a) a0 -> FromTextShow2 f a a0 #

Bitraversable f => Bitraversable (FromTextShow2 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> FromTextShow2 f a b -> f0 (FromTextShow2 f c d) #

Bifoldable f => Bifoldable (FromTextShow2 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

bifold :: Monoid m => FromTextShow2 f m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> FromTextShow2 f a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> FromTextShow2 f a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> FromTextShow2 f a b -> c #

Bifunctor f => Bifunctor (FromTextShow2 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

bimap :: (a -> b) -> (c -> d) -> FromTextShow2 f a c -> FromTextShow2 f b d #

first :: (a -> b) -> FromTextShow2 f a c -> FromTextShow2 f b c #

second :: (b -> c) -> FromTextShow2 f a b -> FromTextShow2 f a c #

TextShow2 f => Show2 (FromTextShow2 f) Source #

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> FromTextShow2 f a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [FromTextShow2 f a b] -> ShowS #

TextShow2 f => TextShow2 (FromTextShow2 f) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> FromTextShow2 f a b -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [FromTextShow2 f a b] -> Builder Source #

Functor (f a) => Functor (FromTextShow2 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

fmap :: (a0 -> b) -> FromTextShow2 f a a0 -> FromTextShow2 f a b #

(<$) :: a0 -> FromTextShow2 f a b -> FromTextShow2 f a a0 #

Foldable (f a) => Foldable (FromTextShow2 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

fold :: Monoid m => FromTextShow2 f a m -> m #

foldMap :: Monoid m => (a0 -> m) -> FromTextShow2 f a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> FromTextShow2 f a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> FromTextShow2 f a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> FromTextShow2 f a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> FromTextShow2 f a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> FromTextShow2 f a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> FromTextShow2 f a a0 -> a0 #

toList :: FromTextShow2 f a a0 -> [a0] #

null :: FromTextShow2 f a a0 -> Bool #

length :: FromTextShow2 f a a0 -> Int #

elem :: Eq a0 => a0 -> FromTextShow2 f a a0 -> Bool #

maximum :: Ord a0 => FromTextShow2 f a a0 -> a0 #

minimum :: Ord a0 => FromTextShow2 f a a0 -> a0 #

sum :: Num a0 => FromTextShow2 f a a0 -> a0 #

product :: Num a0 => FromTextShow2 f a a0 -> a0 #

Traversable (f a) => Traversable (FromTextShow2 f a) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

traverse :: Applicative f0 => (a0 -> f0 b) -> FromTextShow2 f a a0 -> f0 (FromTextShow2 f a b) #

sequenceA :: Applicative f0 => FromTextShow2 f a (f0 a0) -> f0 (FromTextShow2 f a a0) #

mapM :: Monad m => (a0 -> m b) -> FromTextShow2 f a a0 -> m (FromTextShow2 f a b) #

sequence :: Monad m => FromTextShow2 f a (m a0) -> m (FromTextShow2 f a a0) #

(TextShow2 f, TextShow a) => Show1 (FromTextShow2 f a) Source #

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> FromTextShow2 f a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [FromTextShow2 f a a0] -> ShowS #

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

Defined in TextShow.FromStringTextShow

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> FromTextShow2 f a a0 -> Builder Source #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [FromTextShow2 f a a0] -> Builder Source #

Eq (f a b) => Eq (FromTextShow2 f a b) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

(==) :: FromTextShow2 f a b -> FromTextShow2 f a b -> Bool #

(/=) :: FromTextShow2 f a b -> FromTextShow2 f a b -> Bool #

(Typeable a, Typeable b, Typeable f, Typeable k1, Typeable k2, Data (f a b)) => Data (FromTextShow2 f a b) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> FromTextShow2 f a b -> c (FromTextShow2 f a b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromTextShow2 f a b) #

toConstr :: FromTextShow2 f a b -> Constr #

dataTypeOf :: FromTextShow2 f a b -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FromTextShow2 f a b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FromTextShow2 f a b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> FromTextShow2 f a b -> FromTextShow2 f a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromTextShow2 f a b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromTextShow2 f a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> FromTextShow2 f a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FromTextShow2 f a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromTextShow2 f a b -> m (FromTextShow2 f a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromTextShow2 f a b -> m (FromTextShow2 f a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromTextShow2 f a b -> m (FromTextShow2 f a b) #

Ord (f a b) => Ord (FromTextShow2 f a b) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

compare :: FromTextShow2 f a b -> FromTextShow2 f a b -> Ordering #

(<) :: FromTextShow2 f a b -> FromTextShow2 f a b -> Bool #

(<=) :: FromTextShow2 f a b -> FromTextShow2 f a b -> Bool #

(>) :: FromTextShow2 f a b -> FromTextShow2 f a b -> Bool #

(>=) :: FromTextShow2 f a b -> FromTextShow2 f a b -> Bool #

max :: FromTextShow2 f a b -> FromTextShow2 f a b -> FromTextShow2 f a b #

min :: FromTextShow2 f a b -> FromTextShow2 f a b -> FromTextShow2 f a b #

Read (f a b) => Read (FromTextShow2 f a b) Source # 
Instance details

Defined in TextShow.FromStringTextShow

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

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

Methods

showsPrec :: Int -> FromTextShow2 f a b -> ShowS #

show :: FromTextShow2 f a b -> String #

showList :: [FromTextShow2 f a b] -> ShowS #

Generic (FromTextShow2 f a b) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Associated Types

type Rep (FromTextShow2 f a b) :: * -> * #

Methods

from :: FromTextShow2 f a b -> Rep (FromTextShow2 f a b) x #

to :: Rep (FromTextShow2 f a b) x -> FromTextShow2 f a b #

Lift (f a b) => Lift (FromTextShow2 f a b) Source # 
Instance details

Defined in TextShow.FromStringTextShow

Methods

lift :: FromTextShow2 f a b -> Q Exp #

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

Defined in TextShow.FromStringTextShow

type Rep1 (FromTextShow2 f a :: k1 -> *) Source # 
Instance details

Defined in TextShow.FromStringTextShow

type Rep1 (FromTextShow2 f a :: k1 -> *) = D1 (MetaData "FromTextShow2" "TextShow.FromStringTextShow" "text-show-3.7.5-Gp7gM9Y3nCY2xeUEqySIHL" True) (C1 (MetaCons "FromTextShow2" PrefixI True) (S1 (MetaSel (Just "fromTextShow2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 (f a))))
type Rep (FromTextShow2 f a b) Source # 
Instance details

Defined in TextShow.FromStringTextShow

type Rep (FromTextShow2 f a b) = D1 (MetaData "FromTextShow2" "TextShow.FromStringTextShow" "text-show-3.7.5-Gp7gM9Y3nCY2xeUEqySIHL" True) (C1 (MetaCons "FromTextShow2" PrefixI True) (S1 (MetaSel (Just "fromTextShow2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a b))))

showsPrecToShowbPrec :: (Int -> a -> ShowS) -> Int -> a -> Builder Source #

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

Since: 3

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

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

Since: 3

showbPrecToShowsPrec :: (Int -> a -> Builder) -> Int -> a -> ShowS Source #

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

Since: 3

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

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

Since: 3

Conversions between Builder, strict Text, and lazy Text

showtPrecToShowbPrec :: (Int -> a -> Text) -> Int -> a -> Builder Source #

Convert a precedence-aware, strict Text-based show function to a Builder-based one.

Since: 3.4

showtlPrecToShowbPrec :: (Int -> a -> Text) -> Int -> a -> Builder Source #

Convert a precedence-aware, lazy Text-based show function to a Builder-based one.

Since: 3.4

showtToShowb :: (a -> Text) -> a -> Builder Source #

Convert a strict Text-based show function to a Builder-based one.

Since: 3.4

showtlToShowb :: (a -> Text) -> a -> Builder Source #

Convert a lazy Text-based show function to a Builder-based one.

Since: 3.4

showbPrecToShowtPrec :: (Int -> a -> Builder) -> Int -> a -> Text Source #

Convert a precedence-aware Builder-based show function to a strict Text-based one.

Since: 3.4

showbPrecToShowtlPrec :: (Int -> a -> Builder) -> Int -> a -> Text Source #

Convert a precedence-aware Builder-based show function to a lazy Text-based one.

Since: 3.4

showbToShowt :: (a -> Builder) -> a -> Text Source #

Convert a Builder-based show function to a strict Text-based one.

Since: 3

showbToShowtl :: (a -> Builder) -> a -> Text Source #

Convert a Builder-based show function to a lazy Text-based one.

Since: 3