text-show-instances-3.9.4: Additional instances for text-show
Copyright(C) 2014-2017 Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerRyan Scott
StabilityProvisional
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

TextShow.Instances

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

Instances details
TextShow Key Source # 
Instance details

Defined in TextShow.Data.Aeson

TextShow Value Source # 
Instance details

Defined in TextShow.Data.Aeson

TextShow IntSet Source #

Since: 2

Instance details

Defined in TextShow.Data.Containers

TextShow Permissions Source #

Since: 2

Instance details

Defined in TextShow.System.Directory

TextShow XdgDirectory Source #

Since: 3.6

Instance details

Defined in TextShow.System.Directory

TextShow ForeignSrcLang Source #

Since: 3.6

Instance details

Defined in TextShow.GHC.ForeignSrcLang.Type

TextShow Extension Source #

Since: 3.3

Instance details

Defined in TextShow.GHC.LanguageExtensions.Type

TextShow Completion Source #

Since: 2

Instance details

Defined in TextShow.System.Console.Haskeline

TextShow History Source #

Since: 2

Instance details

Defined in TextShow.System.Console.Haskeline

TextShow Prefs Source #

Since: 2

Instance details

Defined in TextShow.System.Console.Haskeline

TextShow Interrupt Source #

Since: 2

Instance details

Defined in TextShow.System.Console.Haskeline

TextShow BoxLabel Source #

Since: 2

Instance details

Defined in TextShow.Trace.Hpc

TextShow CondBox Source #

Since: 2

Instance details

Defined in TextShow.Trace.Hpc

TextShow Mix Source #

Since: 2

Instance details

Defined in TextShow.Trace.Hpc

TextShow Tix Source #

Since: 2

Instance details

Defined in TextShow.Trace.Hpc

TextShow TixModule Source #

Since: 2

Instance details

Defined in TextShow.Trace.Hpc

TextShow Hash Source #

Since: 2

Instance details

Defined in TextShow.Trace.Hpc

TextShow HpcPos Source #

Since: 2

Instance details

Defined in TextShow.Trace.Hpc

TextShow TimeLocale Source #

Since: 2

Instance details

Defined in TextShow.System.Locale

TextShow CalendarTime Source #

Since: 2

Instance details

Defined in TextShow.System.Time

TextShow ClockTime Source #

Since: 2

Instance details

Defined in TextShow.System.Time

TextShow Day Source #

Since: 2

Instance details

Defined in TextShow.System.Time

TextShow Month Source #

Since: 2

Instance details

Defined in TextShow.System.Time

TextShow TimeDiff Source #

Since: 2

Instance details

Defined in TextShow.System.Time

TextShow Mode Source #

Since: 2

Instance details

Defined in TextShow.Text.PrettyPrint

TextShow Style Source #

Since: 2

Instance details

Defined in TextShow.Text.PrettyPrint

TextShow TextDetails Source #

Since: 2

Instance details

Defined in TextShow.Text.PrettyPrint

TextShow PrettyLevel Source #

Since: 3

Instance details

Defined in TextShow.Text.PrettyPrint

TextShow Doc Source #

Since: 2

Instance details

Defined in TextShow.Text.PrettyPrint

TextShow PrettyLevel Source #

Since: 2

Instance details

Defined in TextShow.Text.PrettyPrint

TextShow StdGen Source #

Since: 2

Instance details

Defined in TextShow.System.Random

TextShow Scientific Source # 
Instance details

Defined in TextShow.Data.Scientific

TextShow Doc Source #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow AnnLookup Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow AnnTarget Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Bang Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Body Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Bytes Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Callconv Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Clause Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Con Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Dec Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow DecidedStrictness Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow DerivClause Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow DerivStrategy Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Exp Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow FamilyResultSig Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Fixity Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow FixityDirection Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Foreign Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow FunDep Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Guard Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Info Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow InjectivityAnn Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Inline Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Lit Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Loc Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Match Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow ModName Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Module Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow ModuleInfo Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Name Source #

Since: 2

Instance details

Defined in TextShow.Language.Haskell.TH

TextShow NameFlavour Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow NameSpace Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow OccName Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Overlap Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Pat Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow PatSynArgs Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow PatSynDir Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Phases Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow PkgName Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Pragma Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Range Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Role Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow RuleBndr Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow RuleMatch Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Safety Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow SourceStrictness Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow SourceUnpackedness Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Specificity Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Stmt Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow TyLit Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow TySynEqn Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow Type Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow TypeFamilyHead Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

TextShow SetupTermError Source #

Since: 2

Instance details

Defined in TextShow.System.Console.Terminfo

TextShow Color Source #

Since: 2

Instance details

Defined in TextShow.System.Console.Terminfo

TextShow ShortText Source #

Since: 3.8

Instance details

Defined in TextShow.Data.ShortText

TextShow Day Source #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow AbsoluteTime Source #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow DiffTime Source #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow NominalDiffTime Source #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow SystemTime Source #

Only available with time-1.8 or later.

Since: 3.6

Instance details

Defined in TextShow.Data.Time

TextShow UTCTime Source #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow UniversalTime Source #

Since: 3.6

Instance details

Defined in TextShow.Data.Time

TextShow TimeLocale Source #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow LocalTime Source #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow TimeOfDay Source #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow TimeZone Source #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow ZonedTime Source #

Since: 2

Instance details

Defined in TextShow.Data.Time

TextShow DL Source #

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

Since: 2

Instance details

Defined in TextShow.System.Posix

TextShow ProcessStatus Source #

Since: 2

Instance details

Defined in TextShow.System.Posix

TextShow GroupEntry Source #

Since: 2

Instance details

Defined in TextShow.System.Posix

TextShow UserEntry Source #

Since: 2

Instance details

Defined in TextShow.System.Posix

TextShow UUID Source # 
Instance details

Defined in TextShow.Data.UUID

TextShow Size Source #

Since: 2

Instance details

Defined in TextShow.Data.Vector

TextShow HotLink Source #

Since: 2

Instance details

Defined in TextShow.Text.XHtml

TextShow Html Source #

Since: 2

Instance details

Defined in TextShow.Text.XHtml

TextShow HtmlAttr Source #

Since: 2

Instance details

Defined in TextShow.Text.XHtml

TextShow HtmlTable Source #

Since: 2

Instance details

Defined in TextShow.Text.XHtml

TextShow a => TextShow (Decoder a) Source #

Since: 2

Instance details

Defined in TextShow.Data.Binary

TextShow vertex => TextShow (SCC vertex) Source #

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 v => TextShow (IntMap v) Source #

Since: 2

Instance details

Defined in TextShow.Data.Containers

TextShow a => TextShow (Seq a) Source #

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

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

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

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 a => TextShow (Tree a) Source #

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

Since: 3

Instance details

Defined in TextShow.Text.PrettyPrint

TextShow (Doc a) Source #

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

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 #

TextShow flag => TextShow (TyVarBndr flag) Source # 
Instance details

Defined in TextShow.Language.Haskell.TH

Methods

showbPrec :: Int -> TyVarBndr flag -> Builder #

showb :: TyVarBndr flag -> Builder #

showbList :: [TyVarBndr flag] -> Builder #

showtPrec :: Int -> TyVarBndr flag -> Text #

showt :: TyVarBndr flag -> Text #

showtList :: [TyVarBndr flag] -> Text #

showtlPrec :: Int -> TyVarBndr flag -> Text #

showtl :: TyVarBndr flag -> Text #

showtlList :: [TyVarBndr flag] -> 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) Source #

Since: 2

Instance details

Defined in TextShow.Data.UnorderedContainers

TextShow a => TextShow (Vector a) Source #

Since: 2

Instance details

Defined in TextShow.Data.Vector

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

Since: 2

Instance details

Defined in TextShow.Data.Vector

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

Since: 2

Instance details

Defined in TextShow.Data.Vector

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

Since: 2

Instance details

Defined in TextShow.Data.Vector

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

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 f, TextShow a) => TextShow (Lift f a) Source #

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 (MaybeT m a) Source #

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 #

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

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 (Fix p a) a) => TextShow (Fix p a) Source #

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 #

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

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 b => TextShow (Tagged s b) Source #

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, TextShow a) => TextShow (FromStringShow1 f a)

Not available if using transformers-0.4

This instance is somewhat strange, as its instance context mixes a Show1 constraint with a TextShow constraint. This is done for consistency with the Show instance for FromTextShow1, which mixes constraints in a similar way to satisfy superclass constraints. See the Haddocks on the Show instance for FromTextShow1 for more details.

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 (Backwards f a) Source #

Since: 2

Instance details

Defined in TextShow.Control.Applicative.Trans

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

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 #

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

Since: 2

Instance details

Defined in TextShow.Control.Monad.Trans

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

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

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 a => TextShow (Constant a b) Source #

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 #

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

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 (f a) => TextShow (Clown f a b) Source #

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 #

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

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 (g b) => TextShow (Joker g a b) Source #

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 a b) => TextShow (WrappedBifunctor p a b) Source #

Since: 2

Instance details

Defined in TextShow.Data.Bifunctor

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

Not available if using transformers-0.4

This instance is somewhat strange, as its instance context mixes a Show2 constraint with TextShow constraints. This is done for consistency with the Show instance for FromTextShow2, which mixes constraints in a similar way to satisfy superclass constraints. See the Haddocks on the Show instance for FromTextShow2 for more details.

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 (Product f g a b) Source #

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 a b), TextShow (g a b)) => TextShow (Sum f g a b) Source #

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 (p a b)) => TextShow (Tannen f p a b) Source #

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

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 (forall a. TextShow a => TextShow (f a)) => TextShow1 (f :: TYPE LiftedRep -> TYPE LiftedRep) 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

Instances details
TextShow1 Decoder Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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 f => TextShow1 (Lift f) Source #

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

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 #

TextShow k => TextShow1 (HashMap k) Source #

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

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 #

TextShow2 p => TextShow1 (Join p) Source #

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 #

TextShow1 (Tagged s) Source #

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

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 #

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

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 #

TextShow1 f => TextShow1 (IdentityT f) Source #

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 #

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

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

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 a => TextShow1 (Constant a :: TYPE LiftedRep -> Type) Source #

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 #

TextShow1 f => TextShow1 (Reverse f) Source #

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 (f a) => TextShow1 (Clown f a :: TYPE LiftedRep -> Type) Source #

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 #

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

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 #

TextShow1 g => TextShow1 (Joker g a) Source #

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 (WrappedBifunctor p a) Source #

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 #

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

Not available if using transformers-0.4

This instance is somewhat strange, as its instance context mixes a Show2 constraint with a TextShow constraint. This is done for consistency with the Show1 instance for FromTextShow2, which mixes constraints in a similar way to satisfy superclass constraints. See the Haddocks on the Show1 instance for FromTextShow2 for more details.

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 (Product f g a) Source #

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 #

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

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 #

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

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

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 (forall a. TextShow a => TextShow1 (f a)) => TextShow2 (f :: TYPE LiftedRep -> TYPE LiftedRep -> TYPE LiftedRep) 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

Instances details
TextShow2 Map Source #

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

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 :: TYPE LiftedRep -> Type -> Type) Source #

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 :: Type -> TYPE LiftedRep -> Type) Source #

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 #

TextShow1 f => TextShow2 (Clown f :: TYPE LiftedRep -> TYPE LiftedRep -> Type) Source #

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 #

TextShow2 p => TextShow2 (Flip p) Source #

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 g => TextShow2 (Joker g :: TYPE LiftedRep -> TYPE LiftedRep -> Type) Source #

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

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 #

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 f, TextShow2 g) => TextShow2 (Product f g) Source #

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 #

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

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 #

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

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

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 #