base-4.11.0.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
Show Bool # 
Instance details
Show Char #

Since: 2.1

Instance details
Show Int #

Since: 2.1

Instance details
Show Int8 #

Since: 2.1

Instance details
Show Int16 #

Since: 2.1

Instance details
Show Int32 #

Since: 2.1

Instance details
Show Int64 #

Since: 2.1

Instance details
Show Integer #

Since: 2.1

Instance details
Show Natural #

Since: 4.8.0.0

Instance details
Show Ordering # 
Instance details
Show Word #

Since: 2.1

Instance details
Show Word8 #

Since: 2.1

Instance details
Show Word16 #

Since: 2.1

Instance details
Show Word32 #

Since: 2.1

Instance details
Show Word64 #

Since: 2.1

Instance details
Show RuntimeRep # 
Instance details
Show VecCount # 
Instance details
Show VecElem # 
Instance details
Show CallStack #

Since: 4.9.0.0

Instance details
Show SomeTypeRep #

Since: 4.10.0.0

Instance details
Show () # 
Instance details

Methods

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

show :: () -> String Source #

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

Show TyCon #

Since: 2.1

Instance details
Show Module #

Since: 4.9.0.0

Instance details
Show TrName #

Since: 4.9.0.0

Instance details
Show KindRep # 
Instance details
Show TypeLitSort # 
Instance details
Show SrcLoc # 
Instance details
Show SomeException #

Since: 3.0

Instance details
Show GeneralCategory # 
Instance details
Show Number # 
Instance details
Show Lexeme # 
Instance details
Show Fingerprint #

Since: 4.7.0.0

Instance details
Show IOMode # 
Instance details
Show IntPtr # 
Instance details
Show WordPtr # 
Instance details
Show CUIntMax # 
Instance details
Show CIntMax # 
Instance details
Show CUIntPtr # 
Instance details
Show CIntPtr # 
Instance details
Show CSUSeconds # 
Instance details
Show CUSeconds # 
Instance details
Show CTime # 
Instance details
Show CClock # 
Instance details
Show CSigAtomic # 
Instance details
Show CWchar # 
Instance details
Show CSize # 
Instance details
Show CPtrdiff # 
Instance details
Show CDouble # 
Instance details
Show CFloat # 
Instance details
Show CBool # 
Instance details
Show CULLong # 
Instance details
Show CLLong # 
Instance details
Show CULong # 
Instance details
Show CLong # 
Instance details
Show CUInt # 
Instance details
Show CInt # 
Instance details
Show CUShort # 
Instance details
Show CShort # 
Instance details
Show CUChar # 
Instance details
Show CSChar # 
Instance details
Show CChar # 
Instance details
Show SomeNat #

Since: 4.7.0.0

Instance details
Show SomeSymbol #

Since: 4.7.0.0

Instance details
Show DecidedStrictness # 
Instance details
Show SourceStrictness # 
Instance details
Show SourceUnpackedness # 
Instance details
Show Associativity # 
Instance details
Show Fixity # 
Instance details
Show Any # 
Instance details
Show All # 
Instance details
Show ArithException #

Since: 4.0.0.0

Instance details
Show ErrorCall #

Since: 4.0.0.0

Instance details
Show IOException #

Since: 4.1.0.0

Instance details
Show MaskingState # 
Instance details
Show CodingProgress # 
Instance details
Show TextEncoding #

Since: 4.3.0.0

Instance details
Show SeekMode # 
Instance details
Show NewlineMode # 
Instance details
Show Newline # 
Instance details
Show BufferMode # 
Instance details
Show Handle #

Since: 4.1.0.0

Instance details
Show IOErrorType #

Since: 4.1.0.0

Instance details
Show ExitCode # 
Instance details
Show FixIOException # 
Instance details
Show ArrayException #

Since: 4.1.0.0

Instance details
Show AsyncException #

Since: 4.1.0.0

Instance details
Show SomeAsyncException #

Since: 4.7.0.0

Instance details
Show AssertionFailed #

Since: 4.1.0.0

Instance details
Show CompactionFailed #

Since: 4.10.0.0

Instance details
Show AllocationLimitExceeded #

Since: 4.7.1.0

Instance details
Show Deadlock #

Since: 4.1.0.0

Instance details
Show BlockedIndefinitelyOnSTM #

Since: 4.1.0.0

Instance details
Show BlockedIndefinitelyOnMVar #

Since: 4.1.0.0

Instance details
Show CodingFailureMode # 
Instance details
Show Fd # 
Instance details
Show CTimer # 
Instance details
Show CKey # 
Instance details
Show CId # 
Instance details
Show CFsFilCnt # 
Instance details
Show CFsBlkCnt # 
Instance details
Show CClockId # 
Instance details
Show CBlkCnt # 
Instance details
Show CBlkSize # 
Instance details
Show CRLim # 
Instance details
Show CTcflag # 
Instance details
Show CSpeed # 
Instance details
Show CCc # 
Instance details
Show CUid # 
Instance details
Show CNlink # 
Instance details
Show CGid # 
Instance details
Show CSsize # 
Instance details
Show CPid # 
Instance details
Show COff # 
Instance details
Show CMode # 
Instance details
Show CIno # 
Instance details
Show CDev # 
Instance details
Show Lifetime # 
Instance details
Show Event #

Since: 4.3.1.0

Instance details
Show Dynamic #

Since: 2.1

Instance details
Show ThreadStatus # 
Instance details
Show BlockReason # 
Instance details
Show ThreadId #

Since: 4.2.0.0

Instance details
Show NestedAtomically #

Since: 4.0

Instance details
Show NonTermination #

Since: 4.0

Instance details
Show TypeError #

Since: 4.9.0.0

Instance details
Show NoMethodError #

Since: 4.0

Instance details
Show RecUpdError #

Since: 4.0

Instance details
Show RecConError #

Since: 4.0

Instance details
Show RecSelError #

Since: 4.0

Instance details
Show PatternMatchFail #

Since: 4.0

Instance details
Show FdKey # 
Instance details
Show FileLockingNotSupported # 
Instance details
Show HandlePosn #

Since: 4.1.0.0

Instance details
Show Version # 
Instance details
Show ByteOrder # 
Instance details
Show GCDetails # 
Instance details
Show RTSStats # 
Instance details
Show RTSFlags # 
Instance details
Show ParFlags # 
Instance details
Show TickyFlags # 
Instance details
Show TraceFlags # 
Instance details
Show DoTrace # 
Instance details
Show ProfFlags # 
Instance details
Show DoHeapProfile # 
Instance details
Show CCFlags # 
Instance details
Show DoCostCentres # 
Instance details
Show DebugFlags # 
Instance details
Show MiscFlags # 
Instance details
Show ConcFlags # 
Instance details
Show GCFlags # 
Instance details
Show GiveGCStats # 
Instance details
Show Fixity # 
Instance details
Show ConstrRep # 
Instance details
Show DataRep # 
Instance details
Show Constr #

Since: 4.0.0.0

Instance details
Show DataType # 
Instance details
Show StaticPtrInfo # 
Instance details
Show Void #

Since: 4.8.0.0

Instance details
Show a => Show [a] #

Since: 2.1

Instance details

Methods

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

show :: [a] -> String Source #

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

Show a => Show (Maybe a) # 
Instance details
Show a => Show (Ratio a) #

Since: 2.0.1

Instance details
Show (Ptr a) #

Since: 2.1

Instance details

Methods

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

show :: Ptr a -> String Source #

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

Show (FunPtr a) #

Since: 2.1

Instance details
Show p => Show (Par1 p) # 
Instance details

Methods

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

show :: Par1 p -> String Source #

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

Show a => Show (NonEmpty a) # 
Instance details
Show a => Show (Down a) #

Since: 4.7.0.0

Instance details

Methods

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

show :: Down a -> String Source #

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

Show a => Show (Product a) # 
Instance details
Show a => Show (Sum a) # 
Instance details

Methods

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

show :: Sum a -> String Source #

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

Show a => Show (Dual a) # 
Instance details

Methods

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

show :: Dual a -> String Source #

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

Show a => Show (Last a) # 
Instance details

Methods

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

show :: Last a -> String Source #

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

Show a => Show (First a) # 
Instance details
Show (ForeignPtr a) #

Since: 2.1

Instance details
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: 4.8.0.0

Instance details
Show a => Show (ZipList a) # 
Instance details
Show a => Show (Option a) # 
Instance details
Show m => Show (WrappedMonoid m) # 
Instance details
Show a => Show (Last a) # 
Instance details

Methods

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

show :: Last a -> String Source #

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

Show a => Show (First a) # 
Instance details
Show a => Show (Max a) # 
Instance details

Methods

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

show :: Max a -> String Source #

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

Show a => Show (Min a) # 
Instance details

Methods

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

show :: Min a -> String Source #

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

HasResolution a => Show (Fixed a) #

Since: 2.1

Instance details
Show a => Show (Complex a) # 
Instance details
(Show a, Show b) => Show (Either a b) # 
Instance details

Methods

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

show :: Either a b -> String Source #

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

Show (V1 p) #

Since: 4.9.0.0

Instance details

Methods

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

show :: V1 p -> String Source #

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

Show (U1 p) #

Since: 4.9.0.0

Instance details

Methods

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

show :: U1 p -> String Source #

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

Show (TypeRep a) # 
Instance details
(Show a, Show b) => Show (a, b) #

Since: 2.1

Instance details

Methods

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

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

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

Show (ST s a) #

Since: 2.1

Instance details

Methods

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

show :: ST s a -> String Source #

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

Show (Proxy s) #

Since: 4.7.0.0

Instance details
(Show a, Show b) => Show (Arg a b) # 
Instance details

Methods

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

show :: Arg a b -> String Source #

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

Show (f p) => Show (Rec1 f p) # 
Instance details

Methods

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

show :: Rec1 f p -> String Source #

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

Show (URec Word p) # 
Instance details
Show (URec Int p) # 
Instance details
Show (URec Float p) # 
Instance details
Show (URec Double p) # 
Instance details
Show (URec Char p) # 
Instance details
(Show a, Show b, Show c) => Show (a, b, c) #

Since: 2.1

Instance details

Methods

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

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

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

Show (a :~: b) # 
Instance details

Methods

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

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

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

Show (Coercion a b) # 
Instance details
Show (f a) => Show (Alt f a) # 
Instance details

Methods

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

show :: Alt f a -> String Source #

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

Show a => Show (Const a b) #

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

Since: 4.8.0.0

Instance details

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

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

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

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

Since: 2.1

Instance details

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

Since: 4.10.0.0

Instance details

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

Since: 4.9.0.0

Instance details

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

Since: 4.9.0.0

Instance details

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

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

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

Since: 2.1

Instance details

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

Since: 4.9.0.0

Instance details

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

Since: 2.1

Instance details

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: 2.1

Instance details

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: 2.1

Instance details

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: 2.1

Instance details

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: 2.1

Instance details

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: 2.1

Instance details

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: 2.1

Instance details

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: 2.1

Instance details

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: 2.1

Instance details

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: 2.1

Instance details

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.