base-4.20.0.1: Core data structures and operations
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 ByteArray Source #

Since: base-4.17.0.0

Instance details

Defined in Data.Array.Byte

Show Timeout Source #

Since: base-4.0

Instance details

Defined in System.Timeout

Show Void

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Show

Show ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.Internal.ByteOrder

Show ClosureType 
Instance details

Defined in GHC.Internal.ClosureTypes

Show BlockReason

Since: base-4.3.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Show ThreadId

Since: base-4.2.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Show ThreadStatus

Since: base-4.3.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Show NestedAtomically

Since: base-4.0

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show NoMatchingContinuationPrompt

Since: base-4.18

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show NoMethodError

Since: base-4.0

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show NonTermination

Since: base-4.0

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show PatternMatchFail

Since: base-4.0

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show RecConError

Since: base-4.0

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show RecSelError

Since: base-4.0

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show RecUpdError

Since: base-4.0

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show TypeError

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show Constr

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Show ConstrRep

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Show DataRep

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Show DataType

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Show Fixity

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Show Dynamic

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Dynamic

Show All

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show Any

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show SomeTypeRep

Since: base-4.10.0.0

Instance details

Defined in GHC.Internal.Data.Typeable.Internal

Show Version

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Version

Show ControlMessage

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Control

Methods

showsPrec :: Int -> ControlMessage -> ShowS Source #

show :: ControlMessage -> String Source #

showList :: [ControlMessage] -> ShowS Source #

Show Event

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Show EventLifetime

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Methods

showsPrec :: Int -> EventLifetime -> ShowS Source #

show :: EventLifetime -> String Source #

showList :: [EventLifetime] -> ShowS Source #

Show Lifetime

Since: base-4.8.1.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Show Timeout

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Methods

showsPrec :: Int -> Timeout -> ShowS Source #

show :: Timeout -> String Source #

showList :: [Timeout] -> ShowS Source #

Show FdKey

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Manager

Show State

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Manager

Methods

showsPrec :: Int -> State -> ShowS Source #

show :: State -> String Source #

showList :: [State] -> ShowS Source #

Show State

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Event.TimerManager

Methods

showsPrec :: Int -> State -> ShowS Source #

show :: State -> String Source #

showList :: [State] -> ShowS Source #

Show Unique

Since: base-4.3.1.0

Instance details

Defined in GHC.Internal.Event.Unique

Methods

showsPrec :: Int -> Unique -> ShowS Source #

show :: Unique -> String Source #

showList :: [Unique] -> ShowS Source #

Show ErrorCall

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Exception

Show ArithException

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Exception.Type

Show SomeException

Since: ghc-internal-3.0

Instance details

Defined in GHC.Internal.Exception.Type

Show Fingerprint

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Fingerprint.Type

Show CBool 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CChar 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CClock 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CDouble 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CFloat 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CInt 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CIntMax 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CIntPtr 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CLLong 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CLong 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CPtrdiff 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CSChar 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CSUSeconds 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CShort 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CSigAtomic 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CSize 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CTime 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CUChar 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CUInt 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CUIntMax 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CUIntPtr 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CULLong 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CULong 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CUSeconds 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CUShort 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CWchar 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Show WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Show Associativity

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Show DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Show Fixity

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Show SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Show SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Show MaskingState

Since: base-4.3.0.0

Instance details

Defined in GHC.Internal.IO

Show SeekMode

Since: base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Device

Show CodingFailureMode

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.IO.Encoding.Failure

Show CodingProgress

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.IO.Encoding.Types

Show TextEncoding

Since: base-4.3.0.0

Instance details

Defined in GHC.Internal.IO.Encoding.Types

Show AllocationLimitExceeded

Since: base-4.7.1.0

Instance details

Defined in GHC.Internal.IO.Exception

Show ArrayException

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show AssertionFailed

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show AsyncException

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show BlockedIndefinitelyOnMVar

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show BlockedIndefinitelyOnSTM

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show CompactionFailed

Since: base-4.10.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show Deadlock

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show ExitCode 
Instance details

Defined in GHC.Internal.IO.Exception

Show FixIOException

Since: base-4.11.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show IOErrorType

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show IOException

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show SomeAsyncException

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show FD

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.FD

Show HandlePosn

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Handle

Show FileLockingNotSupported

Since: base-4.10.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Lock.Common

Show BufferMode

Since: base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Show Handle

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Show HandleType

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Show Newline

Since: base-4.3.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Show NewlineMode

Since: base-4.3.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Show IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.IOMode

Show IOPortException 
Instance details

Defined in GHC.Internal.IOPort

Methods

showsPrec :: Int -> IOPortException -> ShowS Source #

show :: IOPortException -> String Source #

showList :: [IOPortException] -> ShowS Source #

Show InfoProv 
Instance details

Defined in GHC.Internal.InfoProv.Types

Show Int16

Since: base-2.1

Instance details

Defined in GHC.Internal.Int

Show Int32

Since: base-2.1

Instance details

Defined in GHC.Internal.Int

Show Int64

Since: base-2.1

Instance details

Defined in GHC.Internal.Int

Show Int8

Since: base-2.1

Instance details

Defined in GHC.Internal.Int

Show CCFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show ConcFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show DebugFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show DoCostCentres

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show DoHeapProfile

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show DoTrace

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show GCFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show GiveGCStats

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show HpcFlags

Since: base-4.20.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show IoSubSystem 
Instance details

Defined in GHC.Internal.RTS.Flags

Show MiscFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show ParFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show ProfFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show RTSFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show TickyFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show TraceFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show FractionalExponentBase 
Instance details

Defined in GHC.Internal.Real

Show StackEntry 
Instance details

Defined in GHC.Internal.Stack.CloneStack

Show CallStack

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Show

Show SrcLoc

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Show

Show StaticPtrInfo

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.StaticPtr

Show GCDetails

Since: base-4.10.0.0

Instance details

Defined in GHC.Internal.Stats

Show RTSStats

Since: base-4.10.0.0

Instance details

Defined in GHC.Internal.Stats

Show CBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CBlkSize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CCc 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CClockId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CDev 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CFsBlkCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CFsFilCnt 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CGid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CId 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CIno 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CKey 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CMode 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CNfds 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CNlink 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show COff 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CPid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CRLim 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CSocklen 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CSpeed 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CSsize 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CTcflag 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CTimer 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CUid 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show Fd 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show Lexeme

Since: base-2.1

Instance details

Defined in GHC.Internal.Text.Read.Lex

Show Number

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Text.Read.Lex

Show SomeChar 
Instance details

Defined in GHC.Internal.TypeLits

Show SomeSymbol

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.TypeLits

Show SomeNat

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.TypeNats

Show GeneralCategory

Since: base-2.1

Instance details

Defined in GHC.Internal.Unicode

Show Word16

Since: base-2.1

Instance details

Defined in GHC.Internal.Word

Show Word32

Since: base-2.1

Instance details

Defined in GHC.Internal.Word

Show Word64

Since: base-2.1

Instance details

Defined in GHC.Internal.Word

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Internal.Word

Show KindRep 
Instance details

Defined in GHC.Internal.Show

Show Module

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Show

Show Ordering

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Show TrName

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Show

Show TyCon

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Show TypeLitSort

Since: base-4.11.0.0

Instance details

Defined in GHC.Internal.Show

Show Integer

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Show Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Show

Show ()

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Methods

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

show :: () -> String Source #

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

Show Bool

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Show Char

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Show Int

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Show Levity

Since: base-4.15.0.0

Instance details

Defined in GHC.Internal.Show

Show RuntimeRep

Since: base-4.11.0.0

Instance details

Defined in GHC.Internal.Show

Show VecCount

Since: base-4.11.0.0

Instance details

Defined in GHC.Internal.Show

Show VecElem

Since: base-4.11.0.0

Instance details

Defined in GHC.Internal.Show

Show Word

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Show a => Show (Complex a) Source #

Since: base-2.1

Instance details

Defined in Data.Complex

Show a => Show (First a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show a => Show (Last a) Source #

Since: base-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 (Max a) Source #

Since: base-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: base-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 m => Show (WrappedMonoid m) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show a => Show (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Internal.Show

Show a => Show (And a)

Since: base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

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

show :: And a -> String Source #

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

Show a => Show (Iff a)

Since: base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

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

show :: Iff a -> String Source #

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

Show a => Show (Ior a)

Since: base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

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

show :: Ior a -> String Source #

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

Show a => Show (Xor a)

Since: base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

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

show :: Xor a -> String Source #

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

Show a => Show (Identity a)

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

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Show a => Show (First a)

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Monoid

Show a => Show (Last a)

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

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

show :: Last a -> String Source #

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

Show a => Show (Down a)

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

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Methods

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

show :: Down a -> String Source #

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

Show a => Show (Dual a)

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

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

show :: Dual a -> String Source #

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

Show a => Show (Product a)

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show a => Show (Sum a)

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

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

show :: Sum a -> String Source #

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

Show a => Show (ExceptionWithContext a) 
Instance details

Defined in GHC.Internal.Exception.Type

Show e => Show (NoBacktrace e) 
Instance details

Defined in GHC.Internal.Exception.Type

Show (ConstPtr a) 
Instance details

Defined in GHC.Internal.Foreign.C.ConstPtr

Show (ForeignPtr a)

Since: base-2.1

Instance details

Defined in GHC.Internal.ForeignPtr

Show a => Show (ZipList a)

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Functor.ZipList

Show p => Show (Par1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

show :: Par1 p -> String Source #

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

Show (FunPtr a)

Since: base-2.1

Instance details

Defined in GHC.Internal.Ptr

Show (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Internal.Ptr

Methods

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

show :: Ptr a -> String Source #

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

Show a => Show (Ratio a)

Since: base-2.0.1

Instance details

Defined in GHC.Internal.Real

Show (SChar c)

Since: base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeLits

Show (SSymbol s)

Since: base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeLits

Show (SNat n)

Since: base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeNats

Methods

showsPrec :: Int -> SNat n -> ShowS Source #

show :: SNat n -> String Source #

showList :: [SNat n] -> ShowS Source #

Show a => Show (Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Show a => Show (Solo a)

Since: base-4.15

Instance details

Defined in GHC.Internal.Show

Methods

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

show :: Solo a -> String Source #

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

Show a => Show [a]

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Methods

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

show :: [a] -> String Source #

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

HasResolution a => Show (Fixed a) Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

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

Since: base-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 #

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

Since: base-2.1

Instance details

Defined in GHC.Internal.Arr

Methods

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

show :: Array a b -> String Source #

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

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

Since: base-3.0

Instance details

Defined in GHC.Internal.Data.Either

Methods

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

show :: Either a b -> String Source #

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

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Show (TypeRep a) 
Instance details

Defined in GHC.Internal.Data.Typeable.Internal

Show (U1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

show :: U1 p -> String Source #

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

Show (V1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

show :: V1 p -> String Source #

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

Show (ST s a)

Since: base-2.1

Instance details

Defined in GHC.Internal.ST

Methods

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

show :: ST s a -> String Source #

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

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

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Methods

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

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

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

Show (a -> b) Source #

Since: base-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 (Const a b)

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

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

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

show :: Const a b -> String Source #

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

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

Since: base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

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

show :: Ap f a -> String Source #

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

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

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

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

show :: Alt f a -> String Source #

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

Show (Coercion a b)

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Type.Coercion

Show (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Type.Equality

Methods

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

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

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

Show (OrderingI a b) 
Instance details

Defined in GHC.Internal.Data.Type.Ord

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

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

show :: Rec1 f p -> String Source #

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

Show (URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Show (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Show (URec Float p) 
Instance details

Defined in GHC.Internal.Generics

Show (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Show (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

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

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Methods

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

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

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

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

Since: base-4.18.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 a), Show (g a)) => Show (Sum f g a) Source #

Since: base-4.18.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 #

Show (a :~~: b)

Since: base-4.10.0.0

Instance details

Defined in GHC.Internal.Data.Type.Equality

Methods

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

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

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

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

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.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)

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

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

Show c => Show (K1 i c p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.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 a, Show b, Show c, Show d) => Show (a, b, c, d)

Since: base-2.1

Instance details

Defined in GHC.Internal.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 (f (g a)) => Show (Compose f g a) Source #

Since: base-4.18.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 (f (g p)) => Show ((f :.: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.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 (M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.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 a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e)

Since: base-2.1

Instance details

Defined in GHC.Internal.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 #

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

Since: base-2.1

Instance details

Defined in GHC.Internal.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)

Since: base-2.1

Instance details

Defined in GHC.Internal.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)

Since: base-2.1

Instance details

Defined in GHC.Internal.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)

Since: base-2.1

Instance details

Defined in GHC.Internal.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)

Since: base-2.1

Instance details

Defined in GHC.Internal.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)

Since: base-2.1

Instance details

Defined in GHC.Internal.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)

Since: base-2.1

Instance details

Defined in GHC.Internal.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)

Since: base-2.1

Instance details

Defined in GHC.Internal.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)

Since: base-2.1

Instance details

Defined in GHC.Internal.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)

Since: base-2.1

Instance details

Defined in GHC.Internal.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.