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

Copyright(C) 2014-2016 Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerRyan Scott
StabilityProvisional
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

TextShow.GHC.Generics

Contents

Description

Monomorphic TextShow functions for generics-related data types.

Since: 2

Synopsis

Documentation

showbU1 :: U1 p -> Builder Source #

Convert a U1 value to a Builder.

Since: 2

liftShowbPar1Prec :: (Int -> p -> Builder) -> Int -> Par1 p -> Builder Source #

Convert a Par1 value to a Builder with the given show function and precedence.

Since: 3

showbRec1Prec :: TextShow (f p) => Int -> Rec1 f p -> Builder Source #

Convert a Rec1 value to a Builder with the given precedence.

Since: 2

liftShowbRec1Prec :: TextShow1 f => (Int -> p -> Builder) -> ([p] -> Builder) -> Int -> Rec1 f p -> Builder Source #

Convert a Rec1 value to a Builder with the given show function and precedence.

Since: 3

liftShowbK1Prec :: (Int -> c -> Builder) -> Int -> K1 i c p -> Builder Source #

Convert a K1 value to a Builder with the given show function and precedence.

Since: 3

showbM1Prec :: TextShow (f p) => Int -> M1 i c f p -> Builder Source #

Convert an M1 value to a Builder with the given precedence.

Since: 2

liftShowbM1Prec :: TextShow1 f => (Int -> p -> Builder) -> ([p] -> Builder) -> Int -> M1 i c f p -> Builder Source #

Convert an M1 value to a Builder with the given show function and precedence.

Since: 3

showbSumTypePrec :: (TextShow (f p), TextShow (g p)) => Int -> (f :+: g) p -> Builder Source #

Convert a '(:+:)' value to a Builder with the given precedence.

Since: 2

liftShowbSumTypePrec :: (TextShow1 f, TextShow1 g) => (Int -> p -> Builder) -> ([p] -> Builder) -> Int -> (f :+: g) p -> Builder Source #

Convert a '(:+:)' value to a Builder with the given show function and precedence.

Since: 3

showbProductTypePrec :: (TextShow (f p), TextShow (g p)) => Int -> (f :*: g) p -> Builder Source #

Convert a '(:*:)' value to a Builder with the given precedence.

Since: 2

liftShowbProductTypePrec :: (TextShow1 f, TextShow1 g) => (Int -> p -> Builder) -> ([p] -> Builder) -> Int -> (f :*: g) p -> Builder Source #

Convert a '(:*:)' value to a Builder with the given show function and precedence.

Since: 3

showbCompFunctorsPrec :: TextShow (f (g p)) => Int -> (f :.: g) p -> Builder Source #

Convert a '(:.:)' value to a Builder with the given precedence.

Since: 2

liftShowbCompFunctorsPrec :: (TextShow1 f, TextShow1 g) => (Int -> p -> Builder) -> ([p] -> Builder) -> Int -> (f :.: g) p -> Builder Source #

Convert a '(:.:)' value to a Builder with the given show function and precedence.

Since: 3

showbFixityPrec :: Int -> Fixity -> Builder Source #

Convert a Fixity value to a Builder with the given precedence.

Since: 2

showbSourceUnpackedness :: SourceUnpackedness -> Builder Source #

Convert a SourceUnpackedness value to a Builder. This function is only available with base-4.9.0.0 or later.

Since: 3

showbSourceStrictness :: SourceStrictness -> Builder Source #

Convert a SourceStrictness value to a Builder. This function is only available with base-4.9.0.0 or later.

Since: 3

showbDecidedStrictness :: DecidedStrictness -> Builder Source #

Convert a DecidedStrictness value to a Builder. This function is only available with base-4.9.0.0 or later.

Since: 3

showbUCharPrec :: Int -> UChar p -> Builder Source #

Convert a UChar to a Builder with the given precedence.

Since: 2.1.2

showbUDoublePrec :: Int -> UDouble p -> Builder Source #

Convert a UDouble to a Builder with the given precedence.

Since: 2.1.2

showbUFloatPrec :: Int -> UFloat p -> Builder Source #

Convert a UFloat to a Builder with the given precedence.

Since: 2.1.2

showbUIntPrec :: Int -> UInt p -> Builder Source #

Convert a UInt to a Builder with the given precedence.

Since: 2.1.2

showbUWordPrec :: Int -> UWord p -> Builder Source #

Convert a UWord to a Builder with the given precedence.

Since: 2.1.2

Orphan instances

TextShow1 U1 Source # 

Methods

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

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

TextShow1 Par1 Source # 

Methods

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

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

TextShow Fixity Source # 
TextShow Associativity Source # 
TextShow SourceUnpackedness Source # 
TextShow SourceStrictness Source # 
TextShow DecidedStrictness Source # 
TextShow2 (K1 i) Source # 

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 #

TextShow1 f0 => TextShow1 (Rec1 f0) Source # 

Methods

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

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

TextShow1 (URec Char) Source # 

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 # 

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 # 

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 # 

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 # 

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 (U1 p) Source # 
TextShow p0 => TextShow (Par1 p0) Source # 
TextShow (UChar p) Source # 
TextShow (UDouble p) Source # 
TextShow (UFloat p) Source # 
TextShow (UInt p) Source # 
TextShow (UWord p) Source # 
TextShow c => TextShow1 (K1 i c) Source # 

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 f0, TextShow1 g0) => TextShow1 ((:+:) f0 g0) Source # 

Methods

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

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

(TextShow1 f0, TextShow1 g0) => TextShow1 ((:*:) f0 g0) Source # 

Methods

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

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

(TextShow1 f0, TextShow1 g0) => TextShow1 ((:.:) f0 g0) Source # 

Methods

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

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

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

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 #

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

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 #

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

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 # 

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 # 

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 (g p)) => TextShow ((:.:) f g p) Source # 

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 (M1 i c f p) Source # 

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 #