text-show-instances-3.7: Additional instances for text-show

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

TextShow.Instances

Contents

Description

Additional TextShow, TextShow1, and TextShow2 instances not provided by text-show.

Since: 2

Synopsis

Class re-exports

class TextShow a where #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 Exp #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Match #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Clause #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Pat #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Type #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Dec #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Name #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow FunDep #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow InjectivityAnn #

Only available with template-haskell-2.11.0.0 or later.

Since: 3

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Overlap #

Only available with template-haskell-2.11.0.0 or later.

Since: 3

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow DerivStrategy #

Only available with template-haskell-2.12.0.0 or later.

Since: 3.6

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow IntSet #

Since: 2

Instance details

Defined in TextShow.Data.Containers

TextShow XdgDirectory #

Only available with directory-1.2.3.0 or later.

Since: 3.6

Instance details

Defined in TextShow.System.Directory

TextShow Permissions #

Since: 2

Instance details

Defined in TextShow.System.Directory

TextShow Extension #

Since: 3.3

Instance details

Defined in TextShow.GHC.LanguageExtensions.Type

TextShow ForeignSrcLang #

Since: 3.6

Instance details

Defined in TextShow.GHC.ForeignSrcLang.Type

TextShow Interrupt #

Since: 2

Instance details

Defined in TextShow.System.Console.Haskeline

TextShow History #

Since: 2

Instance details

Defined in TextShow.System.Console.Haskeline

TextShow Prefs #

Since: 2

Instance details

Defined in TextShow.System.Console.Haskeline

TextShow Completion #

Since: 2

Instance details

Defined in TextShow.System.Console.Haskeline

TextShow Mix #

Since: 2

Instance details

Defined in TextShow.Trace.Hpc

TextShow BoxLabel #

Since: 2

Instance details

Defined in TextShow.Trace.Hpc

TextShow CondBox #

Since: 2

Instance details

Defined in TextShow.Trace.Hpc

TextShow Tix #

Since: 2

Instance details

Defined in TextShow.Trace.Hpc

TextShow TixModule #

Since: 2

Instance details

Defined in TextShow.Trace.Hpc

TextShow HpcPos #

Since: 2

Instance details

Defined in TextShow.Trace.Hpc

TextShow Hash #

Since: 2

Instance details

Defined in TextShow.Trace.Hpc

TextShow TimeLocale #

Since: 2

Instance details

Defined in TextShow.System.Locale

TextShow Month #

Since: 2

Instance details

Defined in TextShow.System.Time

TextShow Day #

Since: 2

Instance details

Defined in TextShow.System.Time

TextShow ClockTime #

Since: 2

Instance details

Defined in TextShow.System.Time

TextShow CalendarTime #

Since: 2

Instance details

Defined in TextShow.System.Time

TextShow TimeDiff #

Since: 2

Instance details

Defined in TextShow.System.Time

TextShow PrettyLevel #

Only available with pretty-1.1.2.0 or later.

Since: 2

Instance details

Defined in TextShow.Text.PrettyPrint

TextShow Doc #

Since: 2

Instance details

Defined in TextShow.Text.PrettyPrint

TextShow PrettyLevel #

Only available with pretty-1.1.3 or later.

Since: 3

Instance details

Defined in TextShow.Text.PrettyPrint

TextShow TextDetails #

Since: 2

Instance details

Defined in TextShow.Text.PrettyPrint

TextShow Style #

Since: 2

Instance details

Defined in TextShow.Text.PrettyPrint

TextShow Mode #

Since: 2

Instance details

Defined in TextShow.Text.PrettyPrint

TextShow StdGen #

Since: 2

Instance details

Defined in TextShow.System.Random

TextShow Doc #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow ModName #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow PkgName #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Module #

Only available with template-haskell-2.9.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow OccName #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow NameFlavour #

Since: 3.3

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow NameSpace #

Since: 3.3

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Loc #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Info #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow ModuleInfo #

Only available with template-haskell-2.9.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Fixity #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow FixityDirection #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Lit #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Body #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Guard #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Stmt #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Range #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow DerivClause #

Only available with template-haskell-2.12.0.0 or later.

Since: 3.6

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow TypeFamilyHead #

Only available with template-haskell-2.11.0.0 or later.

Since: 3

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow TySynEqn #

Only available with template-haskell-2.9.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Foreign #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Callconv #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Safety #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Pragma #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Inline #

Only available with template-haskell-2.8.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow RuleMatch #

Only available with template-haskell-2.8.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Phases #

Only available with template-haskell-2.8.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow RuleBndr #

Only available with template-haskell-2.8.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow AnnTarget #

Only available with template-haskell-2.9.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow SourceUnpackedness #

Only available with template-haskell-2.11.0.0 or later.

Since: 3

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow SourceStrictness #

Only available with template-haskell-2.11.0.0 or later.

Since: 3

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow DecidedStrictness #

Only available with template-haskell-2.11.0.0 or later.

Since: 3

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Con #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Bang #

Only available with template-haskell-2.11.0.0 or later.

Since: 3

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow PatSynDir #

Only available with template-haskell-2.12.0.0 or later.

Since: 3.3

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow PatSynArgs #

Only available with template-haskell-2.12.0.0 or later.

Since: 3.3

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow TyVarBndr #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow FamilyResultSig #

Only available with template-haskell-2.11.0.0 or later.

Since: 3

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow TyLit #

Only available with template-haskell-2.8.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Role #

Only available with template-haskell-2.9.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow AnnLookup #

Only available with template-haskell-2.9.0.0 or later.

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Color #

Since: 2

Instance details

Defined in TextShow.System.Console.Terminfo

TextShow SetupTermError #

Since: 2

Instance details

Defined in TextShow.System.Console.Terminfo

TextShow ZonedTime #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow TimeLocale #

Only available with time-1.5 or later.

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow LocalTime #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow TimeOfDay #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow TimeZone #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow UniversalTime #

Since: 3.6

Instance details

Defined in TextShow.Data.Time

TextShow UTCTime #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow SystemTime #

Only available with time-1.8 or later.

Since: 3.6

Instance details

Defined in TextShow.Data.Time

TextShow NominalDiffTime #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow AbsoluteTime #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow DiffTime #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow Day #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow GroupEntry #

Since: 2

Instance details

Defined in TextShow.System.Posix

TextShow UserEntry #

Since: 2

Instance details

Defined in TextShow.System.Posix

TextShow ProcessStatus #

Since: 2

Instance details

Defined in TextShow.System.Posix

TextShow RTLDFlags #

Since: 2

Instance details

Defined in TextShow.System.Posix

TextShow DL #

Since: 2

Instance details

Defined in TextShow.System.Posix

Methods

showbPrec :: Int -> DL -> Builder #

showb :: DL -> Builder #

showbList :: [DL] -> Builder #

showtPrec :: Int -> DL -> Text #

showt :: DL -> Text #

showtList :: [DL] -> Text #

showtlPrec :: Int -> DL -> Text #

showtl :: DL -> Text #

showtlList :: [DL] -> Text #

TextShow Size #

Since: 2

Instance details

Defined in TextShow.Data.Vector

TextShow HtmlTable #

Since: 2

Instance details

Defined in TextShow.Text.XHtml

TextShow HotLink #

Since: 2

Instance details

Defined in TextShow.Text.XHtml

TextShow HtmlAttr #

Since: 2

Instance details

Defined in TextShow.Text.XHtml

TextShow Html #

Since: 2

Instance details

Defined in TextShow.Text.XHtml

TextShow a => TextShow (Decoder a) #

Since: 2

Instance details

Defined in TextShow.Data.Binary

TextShow v => TextShow (IntMap v) #

Since: 2

Instance details

Defined in TextShow.Data.Containers

TextShow vertex => TextShow (SCC vertex) #

Since: 3.6

Instance details

Defined in TextShow.Data.Containers

Methods

showbPrec :: Int -> SCC vertex -> Builder #

showb :: SCC vertex -> Builder #

showbList :: [SCC vertex] -> Builder #

showtPrec :: Int -> SCC vertex -> Text #

showt :: SCC vertex -> Text #

showtList :: [SCC vertex] -> Text #

showtlPrec :: Int -> SCC vertex -> Text #

showtl :: SCC vertex -> Text #

showtlList :: [SCC vertex] -> Text #

TextShow a => TextShow (Tree a) #

Since: 2

Instance details

Defined in TextShow.Data.Containers

Methods

showbPrec :: Int -> Tree a -> Builder #

showb :: Tree a -> Builder #

showbList :: [Tree a] -> Builder #

showtPrec :: Int -> Tree a -> Text #

showt :: Tree a -> Text #

showtList :: [Tree a] -> Text #

showtlPrec :: Int -> Tree a -> Text #

showtl :: Tree a -> Text #

showtlList :: [Tree a] -> Text #

TextShow a => TextShow (Seq a) #

Since: 2

Instance details

Defined in TextShow.Data.Containers

Methods

showbPrec :: Int -> Seq a -> Builder #

showb :: Seq a -> Builder #

showbList :: [Seq a] -> Builder #

showtPrec :: Int -> Seq a -> Text #

showt :: Seq a -> Text #

showtList :: [Seq a] -> Text #

showtlPrec :: Int -> Seq a -> Text #

showtl :: Seq a -> Text #

showtlList :: [Seq a] -> Text #

TextShow a => TextShow (ViewL a) #

Since: 2

Instance details

Defined in TextShow.Data.Containers

Methods

showbPrec :: Int -> ViewL a -> Builder #

showb :: ViewL a -> Builder #

showbList :: [ViewL a] -> Builder #

showtPrec :: Int -> ViewL a -> Text #

showt :: ViewL a -> Text #

showtList :: [ViewL a] -> Text #

showtlPrec :: Int -> ViewL a -> Text #

showtl :: ViewL a -> Text #

showtlList :: [ViewL a] -> Text #

TextShow a => TextShow (ViewR a) #

Since: 2

Instance details

Defined in TextShow.Data.Containers

Methods

showbPrec :: Int -> ViewR a -> Builder #

showb :: ViewR a -> Builder #

showbList :: [ViewR a] -> Builder #

showtPrec :: Int -> ViewR a -> Text #

showt :: ViewR a -> Text #

showtList :: [ViewR a] -> Text #

showtlPrec :: Int -> ViewR a -> Text #

showtl :: ViewR a -> Text #

showtlList :: [ViewR a] -> Text #

TextShow a => TextShow (Set a) #

Since: 2

Instance details

Defined in TextShow.Data.Containers

Methods

showbPrec :: Int -> Set a -> Builder #

showb :: Set a -> Builder #

showbList :: [Set a] -> Builder #

showtPrec :: Int -> Set a -> Text #

showt :: Set a -> Text #

showtList :: [Set a] -> Text #

showtlPrec :: Int -> Set a -> Text #

showtl :: Set a -> Text #

showtlList :: [Set a] -> Text #

TextShow (Doc a) #

Only available with pretty-1.1.3 or later.

Since: 3

Instance details

Defined in TextShow.Text.PrettyPrint

Methods

showbPrec :: Int -> Doc a -> Builder #

showb :: Doc a -> Builder #

showbList :: [Doc a] -> Builder #

showtPrec :: Int -> Doc a -> Text #

showt :: Doc a -> Text #

showtList :: [Doc a] -> Text #

showtlPrec :: Int -> Doc a -> Text #

showtl :: Doc a -> Text #

showtlList :: [Doc a] -> Text #

TextShow a => TextShow (AnnotDetails a) #

Only available with pretty-1.1.3 or later.

Since: 3

Instance details

Defined in TextShow.Text.PrettyPrint

TextShow a => TextShow (Span a) #

Only available with pretty-1.1.3 or later.

Since: 3

Instance details

Defined in TextShow.Text.PrettyPrint

Methods

showbPrec :: Int -> Span a -> Builder #

showb :: Span a -> Builder #

showbList :: [Span a] -> Builder #

showtPrec :: Int -> Span a -> Text #

showt :: Span a -> Text #

showtList :: [Span a] -> Text #

showtlPrec :: Int -> Span a -> Text #

showtl :: Span a -> Text #

showtlList :: [Span a] -> Text #

Show a => TextShow (FromStringShow a) 
Instance details

Defined in TextShow.FromStringTextShow

TextShow a => TextShow (FromTextShow a) 
Instance details

Defined in TextShow.FromStringTextShow

TextShow a => TextShow (HashSet a) #

Since: 2

Instance details

Defined in TextShow.Data.UnorderedContainers

(TextShow a, Unbox a) => TextShow (Vector a) #

Since: 2

Instance details

Defined in TextShow.Data.Vector

(TextShow a, Storable a) => TextShow (Vector a) #

Since: 2

Instance details

Defined in TextShow.Data.Vector

(TextShow a, Prim a) => TextShow (Vector a) #

Since: 2

Instance details

Defined in TextShow.Data.Vector

TextShow a => TextShow (Vector a) #

Since: 2

Instance details

Defined in TextShow.Data.Vector

(TextShow k, TextShow v) => TextShow (Map k v) #

Since: 2

Instance details

Defined in TextShow.Data.Containers

Methods

showbPrec :: Int -> Map k v -> Builder #

showb :: Map k v -> Builder #

showbList :: [Map k v] -> Builder #

showtPrec :: Int -> Map k v -> Text #

showt :: Map k v -> Text #

showtList :: [Map k v] -> Text #

showtlPrec :: Int -> Map k v -> Text #

showtl :: Map k v -> Text #

showtlList :: [Map k v] -> Text #

(TextShow1 m, TextShow a) => TextShow (MaybeT m a) #

Since: 2

Instance details

Defined in TextShow.Control.Monad.Trans

Methods

showbPrec :: Int -> MaybeT m a -> Builder #

showb :: MaybeT m a -> Builder #

showbList :: [MaybeT m a] -> Builder #

showtPrec :: Int -> MaybeT m a -> Text #

showt :: MaybeT m a -> Text #

showtList :: [MaybeT m a] -> Text #

showtlPrec :: Int -> MaybeT m a -> Text #

showtl :: MaybeT m a -> Text #

showtlList :: [MaybeT m a] -> Text #

(TextShow1 f, TextShow a) => TextShow (Lift f a) #

Since: 2

Instance details

Defined in TextShow.Control.Applicative.Trans

Methods

showbPrec :: Int -> Lift f a -> Builder #

showb :: Lift f a -> Builder #

showbList :: [Lift f a] -> Builder #

showtPrec :: Int -> Lift f a -> Text #

showt :: Lift f a -> Text #

showtList :: [Lift f a] -> Text #

showtlPrec :: Int -> Lift f a -> Text #

showtl :: Lift f a -> Text #

showtlList :: [Lift f a] -> Text #

(TextShow1 m, TextShow a) => TextShow (ListT m a) #

Since: 2

Instance details

Defined in TextShow.Control.Monad.Trans

Methods

showbPrec :: Int -> ListT m a -> Builder #

showb :: ListT m a -> Builder #

showbList :: [ListT m a] -> Builder #

showtPrec :: Int -> ListT m a -> Text #

showt :: ListT m a -> Text #

showtList :: [ListT m a] -> Text #

showtlPrec :: Int -> ListT m a -> Text #

showtl :: ListT m a -> Text #

showtlList :: [ListT m a] -> Text #

(TextShow k, TextShow v) => TextShow (HashMap k v) #

Since: 2

Instance details

Defined in TextShow.Data.UnorderedContainers

Methods

showbPrec :: Int -> HashMap k v -> Builder #

showb :: HashMap k v -> Builder #

showbList :: [HashMap k v] -> Builder #

showtPrec :: Int -> HashMap k v -> Text #

showt :: HashMap k v -> Text #

showtList :: [HashMap k v] -> Text #

showtlPrec :: Int -> HashMap k v -> Text #

showtl :: HashMap k v -> Text #

showtlList :: [HashMap k v] -> Text #

TextShow (p a a) => TextShow (Join p a) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

showbPrec :: Int -> Join p a -> Builder #

showb :: Join p a -> Builder #

showbList :: [Join p a] -> Builder #

showtPrec :: Int -> Join p a -> Text #

showt :: Join p a -> Text #

showtList :: [Join p a] -> Text #

showtlPrec :: Int -> Join p a -> Text #

showtl :: Join p a -> Text #

showtlList :: [Join p a] -> Text #

TextShow (p (Fix p a) a) => TextShow (Fix p a) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

showbPrec :: Int -> Fix p a -> Builder #

showb :: Fix p a -> Builder #

showbList :: [Fix p a] -> Builder #

showtPrec :: Int -> Fix p a -> Text #

showt :: Fix p a -> Text #

showtList :: [Fix p a] -> Text #

showtlPrec :: Int -> Fix p a -> Text #

showtl :: Fix p a -> Text #

showtlList :: [Fix p a] -> Text #

(TextShow1 f, TextShow a) => TextShow (IdentityT f a) #

Since: 2

Instance details

Defined in TextShow.Control.Monad.Trans

TextShow b => TextShow (Tagged s b) #

Since: 2

Instance details

Defined in TextShow.Data.Tagged

Methods

showbPrec :: Int -> Tagged s b -> Builder #

showb :: Tagged s b -> Builder #

showbList :: [Tagged s b] -> Builder #

showtPrec :: Int -> Tagged s b -> Text #

showt :: Tagged s b -> Text #

showtList :: [Tagged s b] -> Text #

showtlPrec :: Int -> Tagged s b -> Text #

showtl :: Tagged s b -> Text #

showtlList :: [Tagged s b] -> Text #

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

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

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

Defined in TextShow.FromStringTextShow

(TextShow1 f, TextShow a) => TextShow (Reverse f a) #

Since: 2

Instance details

Defined in TextShow.Data.Functor.Trans

Methods

showbPrec :: Int -> Reverse f a -> Builder #

showb :: Reverse f a -> Builder #

showbList :: [Reverse f a] -> Builder #

showtPrec :: Int -> Reverse f a -> Text #

showt :: Reverse f a -> Text #

showtList :: [Reverse f a] -> Text #

showtlPrec :: Int -> Reverse f a -> Text #

showtl :: Reverse f a -> Text #

showtlList :: [Reverse f a] -> Text #

TextShow a => TextShow (Constant a b) #

Since: 2

Instance details

Defined in TextShow.Data.Functor.Trans

Methods

showbPrec :: Int -> Constant a b -> Builder #

showb :: Constant a b -> Builder #

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

showtPrec :: Int -> Constant a b -> Text #

showt :: Constant a b -> Text #

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

showtlPrec :: Int -> Constant a b -> Text #

showtl :: Constant a b -> Text #

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

(TextShow w, TextShow1 m, TextShow a) => TextShow (WriterT w m a) #

Since: 2

Instance details

Defined in TextShow.Control.Monad.Trans

Methods

showbPrec :: Int -> WriterT w m a -> Builder #

showb :: WriterT w m a -> Builder #

showbList :: [WriterT w m a] -> Builder #

showtPrec :: Int -> WriterT w m a -> Text #

showt :: WriterT w m a -> Text #

showtList :: [WriterT w m a] -> Text #

showtlPrec :: Int -> WriterT w m a -> Text #

showtl :: WriterT w m a -> Text #

showtlList :: [WriterT w m a] -> Text #

(TextShow w, TextShow1 m, TextShow a) => TextShow (WriterT w m a) #

Since: 2

Instance details

Defined in TextShow.Control.Monad.Trans

Methods

showbPrec :: Int -> WriterT w m a -> Builder #

showb :: WriterT w m a -> Builder #

showbList :: [WriterT w m a] -> Builder #

showtPrec :: Int -> WriterT w m a -> Text #

showt :: WriterT w m a -> Text #

showtList :: [WriterT w m a] -> Text #

showtlPrec :: Int -> WriterT w m a -> Text #

showtl :: WriterT w m a -> Text #

showtlList :: [WriterT w m a] -> Text #

(TextShow e, TextShow1 m, TextShow a) => TextShow (ExceptT e m a) #

Since: 2

Instance details

Defined in TextShow.Control.Monad.Trans

Methods

showbPrec :: Int -> ExceptT e m a -> Builder #

showb :: ExceptT e m a -> Builder #

showbList :: [ExceptT e m a] -> Builder #

showtPrec :: Int -> ExceptT e m a -> Text #

showt :: ExceptT e m a -> Text #

showtList :: [ExceptT e m a] -> Text #

showtlPrec :: Int -> ExceptT e m a -> Text #

showtl :: ExceptT e m a -> Text #

showtlList :: [ExceptT e m a] -> Text #

(TextShow e, TextShow1 m, TextShow a) => TextShow (ErrorT e m a) #

Since: 2

Instance details

Defined in TextShow.Control.Monad.Trans

Methods

showbPrec :: Int -> ErrorT e m a -> Builder #

showb :: ErrorT e m a -> Builder #

showbList :: [ErrorT e m a] -> Builder #

showtPrec :: Int -> ErrorT e m a -> Text #

showt :: ErrorT e m a -> Text #

showtList :: [ErrorT e m a] -> Text #

showtlPrec :: Int -> ErrorT e m a -> Text #

showtl :: ErrorT e m a -> Text #

showtlList :: [ErrorT e m a] -> Text #

(TextShow1 f, TextShow a) => TextShow (Backwards f a) #

Since: 2

Instance details

Defined in TextShow.Control.Applicative.Trans

TextShow (p a b) => TextShow (WrappedBifunctor p a b) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

TextShow (g b) => TextShow (Joker g a b) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

showbPrec :: Int -> Joker g a b -> Builder #

showb :: Joker g a b -> Builder #

showbList :: [Joker g a b] -> Builder #

showtPrec :: Int -> Joker g a b -> Text #

showt :: Joker g a b -> Text #

showtList :: [Joker g a b] -> Text #

showtlPrec :: Int -> Joker g a b -> Text #

showtl :: Joker g a b -> Text #

showtlList :: [Joker g a b] -> Text #

TextShow (p b a) => TextShow (Flip p a b) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

showbPrec :: Int -> Flip p a b -> Builder #

showb :: Flip p a b -> Builder #

showbList :: [Flip p a b] -> Builder #

showtPrec :: Int -> Flip p a b -> Text #

showt :: Flip p a b -> Text #

showtList :: [Flip p a b] -> Text #

showtlPrec :: Int -> Flip p a b -> Text #

showtl :: Flip p a b -> Text #

showtlList :: [Flip p a b] -> Text #

TextShow (f a) => TextShow (Clown f a b) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

showbPrec :: Int -> Clown f a b -> Builder #

showb :: Clown f a b -> Builder #

showbList :: [Clown f a b] -> Builder #

showtPrec :: Int -> Clown f a b -> Text #

showt :: Clown f a b -> Text #

showtList :: [Clown f a b] -> Text #

showtlPrec :: Int -> Clown f a b -> Text #

showtl :: Clown f a b -> Text #

showtlList :: [Clown f a b] -> Text #

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

Not available if using transformers-0.4

Instance details

Defined in TextShow.FromStringTextShow

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

Defined in TextShow.FromStringTextShow

(TextShow (f a b), TextShow (g a b)) => TextShow (Sum f g a b) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

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

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

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

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

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

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

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

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

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

(TextShow (f a b), TextShow (g a b)) => TextShow (Product f g a b) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

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

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

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

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

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

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

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

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

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

TextShow (f (p a b)) => TextShow (Tannen f p a b) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

showbPrec :: Int -> Tannen f p a b -> Builder #

showb :: Tannen f p a b -> Builder #

showbList :: [Tannen f p a b] -> Builder #

showtPrec :: Int -> Tannen f p a b -> Text #

showt :: Tannen f p a b -> Text #

showtList :: [Tannen f p a b] -> Text #

showtlPrec :: Int -> Tannen f p a b -> Text #

showtl :: Tannen f p a b -> Text #

showtlList :: [Tannen f p a b] -> Text #

TextShow (p (f a) (g b)) => TextShow (Biff p f g a b) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

showbPrec :: Int -> Biff p f g a b -> Builder #

showb :: Biff p f g a b -> Builder #

showbList :: [Biff p f g a b] -> Builder #

showtPrec :: Int -> Biff p f g a b -> Text #

showt :: Biff p f g a b -> Text #

showtList :: [Biff p f g a b] -> Text #

showtlPrec :: Int -> Biff p f g a b -> Text #

showtl :: Biff p f g a b -> Text #

showtlList :: [Biff p f g a b] -> Text #

class TextShow1 (f :: * -> *) where #

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 #

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 #

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 Decoder #

Since: 2

Instance details

Defined in TextShow.Data.Binary

Methods

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

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

TextShow1 IntMap #

Since: 2

Instance details

Defined in TextShow.Data.Containers

Methods

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

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

TextShow1 SCC #

Since: 3.6

Instance details

Defined in TextShow.Data.Containers

Methods

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

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

TextShow1 Tree #

Since: 2

Instance details

Defined in TextShow.Data.Containers

Methods

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

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

TextShow1 Seq #

Since: 2

Instance details

Defined in TextShow.Data.Containers

Methods

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

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

TextShow1 ViewL #

Since: 2

Instance details

Defined in TextShow.Data.Containers

Methods

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

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

TextShow1 ViewR #

Since: 2

Instance details

Defined in TextShow.Data.Containers

Methods

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

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

TextShow1 Set #

Since: 2

Instance details

Defined in TextShow.Data.Containers

Methods

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

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

TextShow1 Doc #

Only available with pretty-1.1.3 or later.

Since: 3

Instance details

Defined in TextShow.Text.PrettyPrint

Methods

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

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

TextShow1 AnnotDetails #

Only available with pretty-1.1.3 or later.

Since: 3

Instance details

Defined in TextShow.Text.PrettyPrint

Methods

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

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

TextShow1 Span #

Only available with pretty-1.1.3 or later.

Since: 3

Instance details

Defined in TextShow.Text.PrettyPrint

Methods

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

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

TextShow1 FromStringShow 
Instance details

Defined in TextShow.FromStringTextShow

Methods

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

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

TextShow1 FromTextShow 
Instance details

Defined in TextShow.FromStringTextShow

Methods

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

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

TextShow1 HashSet #

Since: 2

Instance details

Defined in TextShow.Data.UnorderedContainers

Methods

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

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

TextShow1 Vector #

Since: 2

Instance details

Defined in TextShow.Data.Vector

Methods

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

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

TextShow k => TextShow1 (Map k) #

Since: 2

Instance details

Defined in TextShow.Data.Containers

Methods

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

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

TextShow1 m => TextShow1 (MaybeT m) #

Since: 2

Instance details

Defined in TextShow.Control.Monad.Trans

Methods

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

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

TextShow1 f => TextShow1 (Lift f) #

Since: 2

Instance details

Defined in TextShow.Control.Applicative.Trans

Methods

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

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

TextShow1 m => TextShow1 (ListT m) #

Since: 2

Instance details

Defined in TextShow.Control.Monad.Trans

Methods

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

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

TextShow k => TextShow1 (HashMap k) #

Since: 2

Instance details

Defined in TextShow.Data.UnorderedContainers

Methods

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

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

TextShow2 p => TextShow1 (Join p) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

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

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

TextShow2 p => TextShow1 (Fix p) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

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

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

TextShow1 f => TextShow1 (IdentityT f) #

Since: 2

Instance details

Defined in TextShow.Control.Monad.Trans

Methods

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

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

TextShow1 (Tagged s) #

Since: 2

Instance details

Defined in TextShow.Data.Tagged

Methods

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

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

Show1 f => TextShow1 (FromStringShow1 f)

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 #

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

TextShow1 f => TextShow1 (FromTextShow1 f) 
Instance details

Defined in TextShow.FromStringTextShow

Methods

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

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

TextShow1 f => TextShow1 (Reverse f) #

Since: 2

Instance details

Defined in TextShow.Data.Functor.Trans

Methods

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

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

TextShow a => TextShow1 (Constant a :: * -> *) #

Since: 2

Instance details

Defined in TextShow.Data.Functor.Trans

Methods

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

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

(TextShow w, TextShow1 m) => TextShow1 (WriterT w m) #

Since: 2

Instance details

Defined in TextShow.Control.Monad.Trans

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> WriterT w m a -> Builder #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [WriterT w m a] -> Builder #

(TextShow w, TextShow1 m) => TextShow1 (WriterT w m) #

Since: 2

Instance details

Defined in TextShow.Control.Monad.Trans

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> WriterT w m a -> Builder #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [WriterT w m a] -> Builder #

(TextShow e, TextShow1 m) => TextShow1 (ExceptT e m) #

Since: 2

Instance details

Defined in TextShow.Control.Monad.Trans

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> ExceptT e m a -> Builder #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [ExceptT e m a] -> Builder #

(TextShow e, TextShow1 m) => TextShow1 (ErrorT e m) #

Since: 2

Instance details

Defined in TextShow.Control.Monad.Trans

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> ErrorT e m a -> Builder #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [ErrorT e m a] -> Builder #

TextShow1 f => TextShow1 (Backwards f) #

Since: 2

Instance details

Defined in TextShow.Control.Applicative.Trans

Methods

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

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

(TextShow2 p, TextShow a) => TextShow1 (WrappedBifunctor p a) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

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

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

TextShow1 g => TextShow1 (Joker g a) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

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

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

(TextShow2 p, TextShow a) => TextShow1 (Flip p a) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

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

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

TextShow (f a) => TextShow1 (Clown f a :: * -> *) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

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

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

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

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 #

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

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

Defined in TextShow.FromStringTextShow

Methods

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

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

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

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

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

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

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

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

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

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

(TextShow1 f, TextShow2 p, TextShow a) => TextShow1 (Tannen f p a) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> Tannen f p a a0 -> Builder #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [Tannen f p a a0] -> Builder #

(TextShow2 p, TextShow1 f, TextShow1 g, TextShow a) => TextShow1 (Biff p f g a) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> Biff p f g a a0 -> Builder #

liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [Biff p f g a a0] -> Builder #

class TextShow2 (f :: * -> * -> *) where #

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 #

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 #

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 Map #

Since: 2

Instance details

Defined in TextShow.Data.Containers

Methods

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

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

TextShow2 HashMap #

Since: 2

Instance details

Defined in TextShow.Data.UnorderedContainers

Methods

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

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

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

Since: 2

Instance details

Defined in TextShow.Data.Tagged

Methods

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

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

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

Since: 2

Instance details

Defined in TextShow.Data.Functor.Trans

Methods

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

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

TextShow2 p => TextShow2 (WrappedBifunctor p) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

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

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

TextShow1 g => TextShow2 (Joker g :: * -> * -> *) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

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

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

TextShow2 p => TextShow2 (Flip p) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

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

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

TextShow1 f => TextShow2 (Clown f :: * -> * -> *) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

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

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

Show2 f => TextShow2 (FromStringShow2 f)

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 #

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

TextShow2 f => TextShow2 (FromTextShow2 f) 
Instance details

Defined in TextShow.FromStringTextShow

Methods

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

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

(TextShow2 p, TextShow2 q) => TextShow2 (Sum p q) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> Sum p q a b -> Builder #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [Sum p q a b] -> Builder #

(TextShow2 f, TextShow2 g) => TextShow2 (Product f g) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

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

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

(TextShow1 f, TextShow2 p) => TextShow2 (Tannen f p) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

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

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

(TextShow2 p, TextShow1 f, TextShow1 g) => TextShow2 (Biff p f g) #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> Biff p f g a b -> Builder #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [Biff p f g a b] -> Builder #