ghc-internal-9.1001.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

GHC.Internal.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 Void Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Show

Show ByteOrder Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.ByteOrder

Show ClosureType Source # 
Instance details

Defined in GHC.Internal.ClosureTypes

Show BlockReason Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Show ThreadId Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Show ThreadStatus Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Show NestedAtomically Source #

@since base-4.0

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show NoMatchingContinuationPrompt Source #

@since base-4.18

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show NoMethodError Source #

@since base-4.0

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show NonTermination Source #

@since base-4.0

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show PatternMatchFail Source #

@since base-4.0

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show RecConError Source #

@since base-4.0

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show RecSelError Source #

@since base-4.0

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show RecUpdError Source #

@since base-4.0

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show TypeError Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Control.Exception.Base

Show Constr Source #

@since base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Show ConstrRep Source #

@since base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Show DataRep Source #

@since base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Show DataType Source #

@since base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Show Fixity Source #

@since base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Show Dynamic Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Dynamic

Show All Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show Any Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show SomeTypeRep Source #

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.Data.Typeable.Internal

Show Version Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Version

Show Event Source #

@since base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Show Lifetime Source #

@since base-4.8.1.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Show FdKey Source #

@since base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Manager

Show ErrorCall Source #

@since base-4.0.0.0

Instance details

Defined in GHC.Internal.Exception

Show ArithException Source #

@since base-4.0.0.0

Instance details

Defined in GHC.Internal.Exception.Type

Show SomeException Source #

Since: ghc-internal-3.0

Instance details

Defined in GHC.Internal.Exception.Type

Show Fingerprint Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Fingerprint.Type

Show CBool Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CClock Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CDouble Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CFloat Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CInt Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CIntMax Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CIntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CLLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CPtrdiff Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CSChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CSUSeconds Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CShort Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CSigAtomic Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CSize Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CTime Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CUChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CUInt Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CUIntMax Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CUIntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CULLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CULong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CUSeconds Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CUShort Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show CWchar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Show IntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Show WordPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Show Associativity Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Show DecidedStrictness Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Show Fixity Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Show SourceStrictness Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Show SourceUnpackedness Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Show MaskingState Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.IO

Show SeekMode Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Device

Show CodingFailureMode Source #

@since base-4.4.0.0

Instance details

Defined in GHC.Internal.IO.Encoding.Failure

Show CodingProgress Source #

@since base-4.4.0.0

Instance details

Defined in GHC.Internal.IO.Encoding.Types

Show TextEncoding Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.IO.Encoding.Types

Show AllocationLimitExceeded Source #

@since base-4.7.1.0

Instance details

Defined in GHC.Internal.IO.Exception

Show ArrayException Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show AssertionFailed Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show AsyncException Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show BlockedIndefinitelyOnMVar Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show BlockedIndefinitelyOnSTM Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show CompactionFailed Source #

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show Deadlock Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show ExitCode Source # 
Instance details

Defined in GHC.Internal.IO.Exception

Show FixIOException Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show IOErrorType Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show IOException Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show SomeAsyncException Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Show FD Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.FD

Show HandlePosn Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Handle

Show FileLockingNotSupported Source #

@since base-4.10.0.0

Instance details

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

Show BufferMode Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Show Handle Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Show HandleType Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Show Newline Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Show NewlineMode Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Show IOMode Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.IOMode

Show InfoProv Source # 
Instance details

Defined in GHC.Internal.InfoProv.Types

Show Int16 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Show Int32 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Show Int64 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Show Int8 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Show CCFlags Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show ConcFlags Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show DebugFlags Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show DoCostCentres Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show DoHeapProfile Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show DoTrace Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show GCFlags Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show GiveGCStats Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show HpcFlags Source #

@since base-4.22.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show IoManagerFlag Source # 
Instance details

Defined in GHC.Internal.RTS.Flags

Show MiscFlags Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show ParFlags Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show ProfFlags Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show RTSFlags Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show TickyFlags Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show TraceFlags Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.RTS.Flags

Show FractionalExponentBase Source # 
Instance details

Defined in GHC.Internal.Real

Show StackEntry Source # 
Instance details

Defined in GHC.Internal.Stack.CloneStack

Show CallStack Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Show

Show SrcLoc Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Show

Show StaticPtrInfo Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.StaticPtr

Show GCDetails Source #

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.Stats

Show RTSStats Source #

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.Stats

Show CBlkCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CBlkSize Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CCc Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CClockId Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CDev Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CFsBlkCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CFsFilCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CGid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CId Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CIno Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CKey Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CMode Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CNfds Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CNlink Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show COff Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CPid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CRLim Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CSocklen Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CSpeed Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CSsize Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CTcflag Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CTimer Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show CUid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show Fd Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Show Lexeme Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Text.Read.Lex

Show Number Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Text.Read.Lex

Show SomeChar Source # 
Instance details

Defined in GHC.Internal.TypeLits

Show SomeSymbol Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.TypeLits

Show SomeNat Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.TypeNats

Show GeneralCategory Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Unicode

Show Word16 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Show Word32 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Show Word64 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Show Word8 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Show KindRep Source # 
Instance details

Defined in GHC.Internal.Show

Show Module Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Show

Show Ordering Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Show TrName Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Show

Show TyCon Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Show TypeLitSort Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Show

Show Integer Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Show Natural Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Show

Show () Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Methods

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

show :: () -> String Source #

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

Show Bool Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Show Char Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Show Double Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

Show Float Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

Show Int Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Show Levity Source #

@since base-4.15.0.0

Instance details

Defined in GHC.Internal.Show

Show RuntimeRep Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Show

Show VecCount Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Show

Show VecElem Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Show

Show Word Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Show a => Show (NonEmpty a) Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Show

Show a => Show (And a) Source #

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

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

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

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

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

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Monoid

Show a => Show (Last a) Source #

@since base-2.01

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

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

@since base-2.01

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

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Show a => Show (Sum a) Source #

@since base-2.01

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

Defined in GHC.Internal.Exception.Type

Show e => Show (NoBacktrace e) Source # 
Instance details

Defined in GHC.Internal.Exception.Type

Show (ConstPtr a) Source # 
Instance details

Defined in GHC.Internal.Foreign.C.ConstPtr

Show (ForeignPtr a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.ForeignPtr

Show a => Show (ZipList a) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Functor.ZipList

Show p => Show (Par1 p) Source #

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

@since base-2.01

Instance details

Defined in GHC.Internal.Ptr

Show (Ptr a) Source #

@since base-2.01

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

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Show (SChar c) Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeLits

Show (SSymbol s) Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeLits

Show (SNat n) Source #

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

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Show a => Show (Solo a) Source #

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

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Methods

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

show :: [a] -> String Source #

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

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

@since base-2.01

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

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

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Show (TypeRep a) Source # 
Instance details

Defined in GHC.Internal.Data.Typeable.Internal

Show (U1 p) Source #

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

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

@since base-2.01

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

@since base-2.01

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

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

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

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Type.Coercion

Show (a :~: b) Source #

@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) Source # 
Instance details

Defined in GHC.Internal.Data.Type.Ord

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

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

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Show (URec Double p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Show (URec Float p) Source # 
Instance details

Defined in GHC.Internal.Generics

Show (URec Int p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Show (URec Word p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

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

@since base-2.01

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 (a :~~: b) Source #

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

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

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

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

@since base-2.01

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

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

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

@since base-2.01

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

@since base-2.01

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

@since base-2.01

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

@since base-2.01

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

@since base-2.01

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

@since base-2.01

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

@since base-2.01

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

@since base-2.01

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

@since base-2.01

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

@since base-2.01

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

@since base-2.01

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.