base-4.14.1.0: Basic libraries
Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Text.Show

Description

Converting values to readable strings: the Show class and associated functions.

Synopsis

Documentation

type ShowS = String -> String Source #

The shows functions return a function that prepends the output String to an existing String. This allows constant-time concatenation of results using function composition.

class Show a where Source #

Conversion of values to readable Strings.

Derived instances of Show have the following properties, which are compatible with derived instances of Read:

  • The result of show is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used.
  • If the constructor is defined to be an infix operator, then showsPrec will produce infix applications of the constructor.
  • the representation will be enclosed in parentheses if the precedence of the top-level constructor in x is less than d (associativity is ignored). Thus, if d is 0 then the result is never surrounded in parentheses; if d is 11 it is always surrounded in parentheses, unless it is an atomic expression.
  • If the constructor is defined using record syntax, then show will produce the record-syntax form, with the fields given in the same order as the original declaration.

For example, given the declarations

infixr 5 :^:
data Tree a =  Leaf a  |  Tree a :^: Tree a

the derived instance of Show is equivalent to

instance (Show a) => Show (Tree a) where

       showsPrec d (Leaf m) = showParen (d > app_prec) $
            showString "Leaf " . showsPrec (app_prec+1) m
         where app_prec = 10

       showsPrec d (u :^: v) = showParen (d > up_prec) $
            showsPrec (up_prec+1) u .
            showString " :^: "      .
            showsPrec (up_prec+1) v
         where up_prec = 5

Note that right-associativity of :^: is ignored. For example,

  • show (Leaf 1 :^: Leaf 2 :^: Leaf 3) produces the string "Leaf 1 :^: (Leaf 2 :^: Leaf 3)".

Minimal complete definition

showsPrec | show

Methods

showsPrec Source #

Arguments

:: Int

the operator precedence of the enclosing context (a number from 0 to 11). Function application has precedence 10.

-> a

the value to be converted to a String

-> ShowS 

Convert a value to a readable String.

showsPrec should satisfy the law

showsPrec d x r ++ s  ==  showsPrec d x (r ++ s)

Derived instances of Read and Show satisfy the following:

That is, readsPrec parses the string produced by showsPrec, and delivers the value that showsPrec started with.

show :: a -> String Source #

A specialised variant of showsPrec, using precedence context zero, and returning an ordinary String.

showList :: [a] -> ShowS Source #

The method showList is provided to allow the programmer to give a specialised way of showing lists of values. For example, this is used by the predefined Show instance of the Char type, where values of type String should be shown in double quotes, rather than between square brackets.

Instances

Instances details
Show Bool Source #

Since: 2.1

Instance details

Defined in GHC.Show

Show Char Source #

Since: 2.1

Instance details

Defined in GHC.Show

Show Double Source #

Since: 2.1

Instance details

Defined in GHC.Float

Show Float Source #

Since: 2.1

Instance details

Defined in GHC.Float

Show Int Source #

Since: 2.1

Instance details

Defined in GHC.Show

Show Int8 Source #

Since: 2.1

Instance details

Defined in GHC.Int

Show Int16 Source #

Since: 2.1

Instance details

Defined in GHC.Int

Show Int32 Source #

Since: 2.1

Instance details

Defined in GHC.Int

Show Int64 Source #

Since: 2.1

Instance details

Defined in GHC.Int

Show Integer Source #

Since: 2.1

Instance details

Defined in GHC.Show

Show Natural Source #

Since: 4.8.0.0

Instance details

Defined in GHC.Show

Show Ordering Source #

Since: 2.1

Instance details

Defined in GHC.Show

Show Word Source #

Since: 2.1

Instance details

Defined in GHC.Show

Show Word8 Source #

Since: 2.1

Instance details

Defined in GHC.Word

Show Word16 Source #

Since: 2.1

Instance details

Defined in GHC.Word

Show Word32 Source #

Since: 2.1

Instance details

Defined in GHC.Word

Show Word64 Source #

Since: 2.1

Instance details

Defined in GHC.Word

Show RuntimeRep Source #

Since: 4.11.0.0

Instance details

Defined in GHC.Show

Show VecCount Source #

Since: 4.11.0.0

Instance details

Defined in GHC.Show

Show VecElem Source #

Since: 4.11.0.0

Instance details

Defined in GHC.Show

Show CallStack Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Show

Show SomeTypeRep Source #

Since: 4.10.0.0

Instance details

Defined in Data.Typeable.Internal

Show () Source #

Since: 2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> () -> ShowS Source #

show :: () -> String Source #

showList :: [()] -> ShowS Source #

Show TyCon Source #

Since: 2.1

Instance details

Defined in GHC.Show

Show Module Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Show

Show TrName Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Show

Show KindRep Source # 
Instance details

Defined in GHC.Show

Show TypeLitSort Source #

Since: 4.11.0.0

Instance details

Defined in GHC.Show

Show SomeException Source #

Since: 3.0

Instance details

Defined in GHC.Exception.Type

Show SrcLoc Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Show

Show GeneralCategory Source #

Since: 2.1

Instance details

Defined in GHC.Unicode

Show Number Source #

Since: 4.6.0.0

Instance details

Defined in Text.Read.Lex

Show Lexeme Source #

Since: 2.1

Instance details

Defined in Text.Read.Lex

Show Fingerprint Source #

Since: 4.7.0.0

Instance details

Defined in GHC.Fingerprint.Type

Show IOMode Source #

Since: 4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Show IntPtr Source # 
Instance details

Defined in Foreign.Ptr

Show WordPtr Source # 
Instance details

Defined in Foreign.Ptr

Show CUIntMax Source # 
Instance details

Defined in Foreign.C.Types

Show CIntMax Source # 
Instance details

Defined in Foreign.C.Types

Show CUIntPtr Source # 
Instance details

Defined in Foreign.C.Types

Show CIntPtr Source # 
Instance details

Defined in Foreign.C.Types

Show CSUSeconds Source # 
Instance details

Defined in Foreign.C.Types

Show CUSeconds Source # 
Instance details

Defined in Foreign.C.Types

Show CTime Source # 
Instance details

Defined in Foreign.C.Types

Show CClock Source # 
Instance details

Defined in Foreign.C.Types

Show CSigAtomic Source # 
Instance details

Defined in Foreign.C.Types

Show CWchar Source # 
Instance details

Defined in Foreign.C.Types

Show CSize Source # 
Instance details

Defined in Foreign.C.Types

Show CPtrdiff Source # 
Instance details

Defined in Foreign.C.Types

Show CDouble Source # 
Instance details

Defined in Foreign.C.Types

Show CFloat Source # 
Instance details

Defined in Foreign.C.Types

Show CBool Source # 
Instance details

Defined in Foreign.C.Types

Show CULLong Source # 
Instance details

Defined in Foreign.C.Types

Show CLLong Source # 
Instance details

Defined in Foreign.C.Types

Show CULong Source # 
Instance details

Defined in Foreign.C.Types

Show CLong Source # 
Instance details

Defined in Foreign.C.Types

Show CUInt Source # 
Instance details

Defined in Foreign.C.Types

Show CInt Source # 
Instance details

Defined in Foreign.C.Types

Show CUShort Source # 
Instance details

Defined in Foreign.C.Types

Show CShort Source # 
Instance details

Defined in Foreign.C.Types

Show CUChar Source # 
Instance details

Defined in Foreign.C.Types

Show CSChar Source # 
Instance details

Defined in Foreign.C.Types

Show CChar Source # 
Instance details

Defined in Foreign.C.Types

Show SomeNat Source #

Since: 4.7.0.0

Instance details

Defined in GHC.TypeNats

Show SomeSymbol Source #

Since: 4.7.0.0

Instance details

Defined in GHC.TypeLits

Show DecidedStrictness Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Show SourceStrictness Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Show SourceUnpackedness Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Show Associativity Source #

Since: 4.6.0.0

Instance details

Defined in GHC.Generics

Show Fixity Source #

Since: 4.6.0.0

Instance details

Defined in GHC.Generics

Show Any Source #

Since: 2.1

Instance details

Defined in Data.Semigroup.Internal

Show All Source #

Since: 2.1

Instance details

Defined in Data.Semigroup.Internal

Show ArithException Source #

Since: 4.0.0.0

Instance details

Defined in GHC.Exception.Type

Show ErrorCall Source #

Since: 4.0.0.0

Instance details

Defined in GHC.Exception

Show FileLockingNotSupported Source #

Since: 4.10.0.0

Instance details

Defined in GHC.IO.Handle.Lock.Common

Show IOException Source #

Since: 4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show MaskingState Source #

Since: 4.3.0.0

Instance details

Defined in GHC.IO

Show CodingProgress Source #

Since: 4.4.0.0

Instance details

Defined in GHC.IO.Encoding.Types

Show TextEncoding Source #

Since: 4.3.0.0

Instance details

Defined in GHC.IO.Encoding.Types

Show SeekMode Source #

Since: 4.2.0.0

Instance details

Defined in GHC.IO.Device

Show NewlineMode Source #

Since: 4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show Newline Source #

Since: 4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show BufferMode Source #

Since: 4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show HandleType Source #

Since: 4.1.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show Handle Source #

Since: 4.1.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show IOErrorType Source #

Since: 4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show ExitCode Source # 
Instance details

Defined in GHC.IO.Exception

Show FixIOException Source #

Since: 4.11.0.0

Instance details

Defined in GHC.IO.Exception

Show ArrayException Source #

Since: 4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show AsyncException Source #

Since: 4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show SomeAsyncException Source #

Since: 4.7.0.0

Instance details

Defined in GHC.IO.Exception

Show AssertionFailed Source #

Since: 4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show CompactionFailed Source #

Since: 4.10.0.0

Instance details

Defined in GHC.IO.Exception

Show AllocationLimitExceeded Source #

Since: 4.7.1.0

Instance details

Defined in GHC.IO.Exception

Show Deadlock Source #

Since: 4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show BlockedIndefinitelyOnSTM Source #

Since: 4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show BlockedIndefinitelyOnMVar Source #

Since: 4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show CodingFailureMode Source #

Since: 4.4.0.0

Instance details

Defined in GHC.IO.Encoding.Failure

Show Fd Source # 
Instance details

Defined in System.Posix.Types

Show CNfds Source # 
Instance details

Defined in System.Posix.Types

Show CSocklen Source # 
Instance details

Defined in System.Posix.Types

Show CTimer Source # 
Instance details

Defined in System.Posix.Types

Show CKey Source # 
Instance details

Defined in System.Posix.Types

Show CId Source # 
Instance details

Defined in System.Posix.Types

Show CFsFilCnt Source # 
Instance details

Defined in System.Posix.Types

Show CFsBlkCnt Source # 
Instance details

Defined in System.Posix.Types

Show CClockId Source # 
Instance details

Defined in System.Posix.Types

Show CBlkCnt Source # 
Instance details

Defined in System.Posix.Types

Show CBlkSize Source # 
Instance details

Defined in System.Posix.Types

Show CRLim Source # 
Instance details

Defined in System.Posix.Types

Show CTcflag Source # 
Instance details

Defined in System.Posix.Types

Show CSpeed Source # 
Instance details

Defined in System.Posix.Types

Show CCc Source # 
Instance details

Defined in System.Posix.Types

Show CUid Source # 
Instance details

Defined in System.Posix.Types

Show CNlink Source # 
Instance details

Defined in System.Posix.Types

Show CGid Source # 
Instance details

Defined in System.Posix.Types

Show CSsize Source # 
Instance details

Defined in System.Posix.Types

Show CPid Source # 
Instance details

Defined in System.Posix.Types

Show COff Source # 
Instance details

Defined in System.Posix.Types

Show CMode Source # 
Instance details

Defined in System.Posix.Types

Show CIno Source # 
Instance details

Defined in System.Posix.Types

Show CDev Source # 
Instance details

Defined in System.Posix.Types

Show Lifetime Source #

Since: 4.8.1.0

Instance details

Defined in GHC.Event.Internal

Show Event Source #

Since: 4.4.0.0

Instance details

Defined in GHC.Event.Internal

Show Dynamic Source #

Since: 2.1

Instance details

Defined in Data.Dynamic

Show ThreadStatus Source #

Since: 4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Show BlockReason Source #

Since: 4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Show ThreadId Source #

Since: 4.2.0.0

Instance details

Defined in GHC.Conc.Sync

Show NestedAtomically Source #

Since: 4.0

Instance details

Defined in Control.Exception.Base

Show NonTermination Source #

Since: 4.0

Instance details

Defined in Control.Exception.Base

Show TypeError Source #

Since: 4.9.0.0

Instance details

Defined in Control.Exception.Base

Show NoMethodError Source #

Since: 4.0

Instance details

Defined in Control.Exception.Base

Show RecUpdError Source #

Since: 4.0

Instance details

Defined in Control.Exception.Base

Show RecConError Source #

Since: 4.0

Instance details

Defined in Control.Exception.Base

Show RecSelError Source #

Since: 4.0

Instance details

Defined in Control.Exception.Base

Show PatternMatchFail Source #

Since: 4.0

Instance details

Defined in Control.Exception.Base

Show FdKey Source #

Since: 4.4.0.0

Instance details

Defined in GHC.Event.Manager

Show FD Source #

Since: 4.1.0.0

Instance details

Defined in GHC.IO.FD

Show HandlePosn Source #

Since: 4.1.0.0

Instance details

Defined in GHC.IO.Handle

Show Version Source #

Since: 2.1

Instance details

Defined in Data.Version

Show StaticPtrInfo Source #

Since: 4.8.0.0

Instance details

Defined in GHC.StaticPtr

Show ByteOrder Source #

Since: 4.11.0.0

Instance details

Defined in GHC.ByteOrder

Show GCDetails Source #

Since: 4.10.0.0

Instance details

Defined in GHC.Stats

Show RTSStats Source #

Since: 4.10.0.0

Instance details

Defined in GHC.Stats

Show RTSFlags Source #

Since: 4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show ParFlags Source #

Since: 4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show TickyFlags Source #

Since: 4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show TraceFlags Source #

Since: 4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show DoTrace Source #

Since: 4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show ProfFlags Source #

Since: 4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show DoHeapProfile Source #

Since: 4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show CCFlags Source #

Since: 4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show DoCostCentres Source #

Since: 4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show DebugFlags Source #

Since: 4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show MiscFlags Source #

Since: 4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show ConcFlags Source #

Since: 4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show GCFlags Source #

Since: 4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show GiveGCStats Source #

Since: 4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show Timeout Source #

Since: 4.0

Instance details

Defined in System.Timeout

Show Fixity Source #

Since: 4.0.0.0

Instance details

Defined in Data.Data

Show ConstrRep Source #

Since: 4.0.0.0

Instance details

Defined in Data.Data

Show DataRep Source #

Since: 4.0.0.0

Instance details

Defined in Data.Data

Show Constr Source #

Since: 4.0.0.0

Instance details

Defined in Data.Data

Show DataType Source #

Since: 4.0.0.0

Instance details

Defined in Data.Data

Show Void Source #

Since: 4.8.0.0

Instance details

Defined in Data.Void

Show a => Show [a] Source #

Since: 2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> [a] -> ShowS Source #

show :: [a] -> String Source #

showList :: [[a]] -> ShowS Source #

Show a => Show (Maybe a) Source #

Since: 2.1

Instance details

Defined in GHC.Show

Show a => Show (Ratio a) Source #

Since: 2.0.1

Instance details

Defined in GHC.Real

Show (Ptr a) Source #

Since: 2.1

Instance details

Defined in GHC.Ptr

Methods

showsPrec :: Int -> Ptr a -> ShowS Source #

show :: Ptr a -> String Source #

showList :: [Ptr a] -> ShowS Source #

Show (FunPtr a) Source #

Since: 2.1

Instance details

Defined in GHC.Ptr

Show p => Show (Par1 p) Source #

Since: 4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> Par1 p -> ShowS Source #

show :: Par1 p -> String Source #

showList :: [Par1 p] -> ShowS Source #

Show a => Show (NonEmpty a) Source #

Since: 4.11.0.0

Instance details

Defined in GHC.Show

Show a => Show (Down a) Source #

This instance would be equivalent to the derived instances of the Down newtype if the getDown field were removed

Since: 4.7.0.0

Instance details

Defined in Data.Ord

Methods

showsPrec :: Int -> Down a -> ShowS Source #

show :: Down a -> String Source #

showList :: [Down a] -> ShowS Source #

Show a => Show (Product a) Source #

Since: 2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show (Sum a) Source #

Since: 2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Sum a -> ShowS Source #

show :: Sum a -> String Source #

showList :: [Sum a] -> ShowS Source #

Show a => Show (Dual a) Source #

Since: 2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Dual a -> ShowS Source #

show :: Dual a -> String Source #

showList :: [Dual a] -> ShowS Source #

Show a => Show (Last a) Source #

Since: 2.1

Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> Last a -> ShowS Source #

show :: Last a -> String Source #

showList :: [Last a] -> ShowS Source #

Show a => Show (First a) Source #

Since: 2.1

Instance details

Defined in Data.Monoid

Show (ForeignPtr a) Source #

Since: 2.1

Instance details

Defined in GHC.ForeignPtr

Show a => Show (Identity a) Source #

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Since: 4.8.0.0

Instance details

Defined in Data.Functor.Identity

Show a => Show (ZipList a) Source #

Since: 4.7.0.0

Instance details

Defined in Control.Applicative

Show a => Show (Option a) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Semigroup

Show m => Show (WrappedMonoid m) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Semigroup

Show a => Show (Last a) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Last a -> ShowS Source #

show :: Last a -> String Source #

showList :: [Last a] -> ShowS Source #

Show a => Show (First a) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Semigroup

Show a => Show (Max a) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Max a -> ShowS Source #

show :: Max a -> String Source #

showList :: [Max a] -> ShowS Source #

Show a => Show (Min a) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Min a -> ShowS Source #

show :: Min a -> String Source #

showList :: [Min a] -> ShowS Source #

Show a => Show (Complex a) Source #

Since: 2.1

Instance details

Defined in Data.Complex

Show (a -> b) Source #

Since: 2.1

Instance details

Defined in Text.Show.Functions

Methods

showsPrec :: Int -> (a -> b) -> ShowS Source #

show :: (a -> b) -> String Source #

showList :: [a -> b] -> ShowS Source #

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

Since: 3.0

Instance details

Defined in Data.Either

Methods

showsPrec :: Int -> Either a b -> ShowS Source #

show :: Either a b -> String Source #

showList :: [Either a b] -> ShowS Source #

Show (V1 p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> V1 p -> ShowS Source #

show :: V1 p -> String Source #

showList :: [V1 p] -> ShowS Source #

Show (U1 p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> U1 p -> ShowS Source #

show :: U1 p -> String Source #

showList :: [U1 p] -> ShowS Source #

Show (TypeRep a) Source # 
Instance details

Defined in Data.Typeable.Internal

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

Since: 2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b) -> ShowS Source #

show :: (a, b) -> String Source #

showList :: [(a, b)] -> ShowS Source #

Show (ST s a) Source #

Since: 2.1

Instance details

Defined in GHC.ST

Methods

showsPrec :: Int -> ST s a -> ShowS Source #

show :: ST s a -> String Source #

showList :: [ST s a] -> ShowS Source #

(Ix a, Show a, Show b) => Show (Array a b) Source #

Since: 2.1

Instance details

Defined in GHC.Arr

Methods

showsPrec :: Int -> Array a b -> ShowS Source #

show :: Array a b -> String Source #

showList :: [Array a b] -> ShowS Source #

Show (Proxy s) Source #

Since: 4.7.0.0

Instance details

Defined in Data.Proxy

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

Since: 4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Arg a b -> ShowS Source #

show :: Arg a b -> String Source #

showList :: [Arg a b] -> ShowS Source #

HasResolution a => Show (Fixed a) Source #

Since: 2.1

Instance details

Defined in Data.Fixed

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

Since: 4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> Rec1 f p -> ShowS Source #

show :: Rec1 f p -> String Source #

showList :: [Rec1 f p] -> ShowS Source #

Show (URec Word p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Show (URec Int p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Show (URec Float p) Source # 
Instance details

Defined in GHC.Generics

Show (URec Double p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

Show (URec Char p) Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Generics

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

Since: 2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c) -> ShowS Source #

show :: (a, b, c) -> String Source #

showList :: [(a, b, c)] -> ShowS Source #

Show (a :~: b) Source #

Since: 4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

showsPrec :: Int -> (a :~: b) -> ShowS Source #

show :: (a :~: b) -> String Source #

showList :: [a :~: b] -> ShowS Source #

Show (Coercion a b) Source #

Since: 4.7.0.0

Instance details

Defined in Data.Type.Coercion

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

Since: 4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Alt f a -> ShowS Source #

show :: Alt f a -> String Source #

showList :: [Alt f a] -> ShowS Source #

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

Since: 4.12.0.0

Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> Ap f a -> ShowS Source #

show :: Ap f a -> String Source #

showList :: [Ap f a] -> ShowS Source #

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

This instance would be equivalent to the derived instances of the Const newtype if the getConst field were removed

Since: 4.8.0.0

Instance details

Defined in Data.Functor.Const

Methods

showsPrec :: Int -> Const a b -> ShowS Source #

show :: Const a b -> String Source #

showList :: [Const a b] -> ShowS Source #

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

Since: 4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> K1 i c p -> ShowS Source #

show :: K1 i c p -> String Source #

showList :: [K1 i c p] -> ShowS Source #

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

Since: 4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> (f :+: g) p -> ShowS Source #

show :: (f :+: g) p -> String Source #

showList :: [(f :+: g) p] -> ShowS Source #

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

Since: 4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> (f :*: g) p -> ShowS Source #

show :: (f :*: g) p -> String Source #

showList :: [(f :*: g) p] -> ShowS Source #

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

Since: 2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d) -> ShowS Source #

show :: (a, b, c, d) -> String Source #

showList :: [(a, b, c, d)] -> ShowS Source #

Show (a :~~: b) Source #

Since: 4.10.0.0

Instance details

Defined in Data.Type.Equality

Methods

showsPrec :: Int -> (a :~~: b) -> ShowS Source #

show :: (a :~~: b) -> String Source #

showList :: [a :~~: b] -> ShowS Source #

(Show1 f, Show1 g, Show a) => Show (Sum f g a) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

showsPrec :: Int -> Sum f g a -> ShowS Source #

show :: Sum f g a -> String Source #

showList :: [Sum f g a] -> ShowS Source #

(Show1 f, Show1 g, Show a) => Show (Product f g a) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

showsPrec :: Int -> Product f g a -> ShowS Source #

show :: Product f g a -> String Source #

showList :: [Product f g a] -> ShowS Source #

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

Since: 4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> M1 i c f p -> ShowS Source #

show :: M1 i c f p -> String Source #

showList :: [M1 i c f p] -> ShowS Source #

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

Since: 4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> (f :.: g) p -> ShowS Source #

show :: (f :.: g) p -> String Source #

showList :: [(f :.: g) p] -> ShowS Source #

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

Since: 2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e) -> ShowS Source #

show :: (a, b, c, d, e) -> String Source #

showList :: [(a, b, c, d, e)] -> ShowS Source #

(Show1 f, Show1 g, Show a) => Show (Compose f g a) Source #

Since: 4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

showsPrec :: Int -> Compose f g a -> ShowS Source #

show :: Compose f g a -> String Source #

showList :: [Compose f g a] -> ShowS Source #

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

Since: 2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f) -> ShowS Source #

show :: (a, b, c, d, e, f) -> String Source #

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

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

Since: 2.1

Instance details

Defined in GHC.Show

Methods

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

show :: (a, b, c, d, e, f, g) -> String Source #

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

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

Since: 2.1

Instance details

Defined in GHC.Show

Methods

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

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

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

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

Since: 2.1

Instance details

Defined in GHC.Show

Methods

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

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

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

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

Since: 2.1

Instance details

Defined in GHC.Show

Methods

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

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

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

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

Since: 2.1

Instance details

Defined in GHC.Show

Methods

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

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

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

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

Since: 2.1

Instance details

Defined in GHC.Show

Methods

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

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

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

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

Since: 2.1

Instance details

Defined in GHC.Show

Methods

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

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

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

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

Since: 2.1

Instance details

Defined in GHC.Show

Methods

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

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

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

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

Since: 2.1

Instance details

Defined in GHC.Show

Methods

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

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

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

shows :: Show a => a -> ShowS Source #

equivalent to showsPrec with a precedence of 0.

showChar :: Char -> ShowS Source #

utility function converting a Char to a show function that simply prepends the character unchanged.

showString :: String -> ShowS Source #

utility function converting a String to a show function that simply prepends the string unchanged.

showParen :: Bool -> ShowS -> ShowS Source #

utility function that surrounds the inner show function with parentheses when the Bool parameter is True.

showListWith :: (a -> ShowS) -> [a] -> ShowS Source #

Show a list (using square brackets and commas), given a function for showing elements.