base-4.9.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 :: Int -> a -> ShowS Source #

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 Source # 
Show Char Source # 
Show Int Source # 
Show Int8 Source # 
Show Int16 Source # 
Show Int32 Source # 
Show Int64 Source # 
Show Integer Source # 
Show Ordering Source # 
Show Word Source # 
Show Word8 Source # 
Show Word16 Source # 
Show Word32 Source # 
Show Word64 Source # 
Show CallStack Source # 
Show TypeRep Source # 
Show () Source # 

Methods

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

show :: () -> String Source #

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

Show TyCon Source # 
Show Module Source # 
Show TrName Source # 
Show SrcLoc Source # 
Show SomeException Source # 
Show GeneralCategory Source # 
Show Number Source # 
Show Lexeme Source # 
Show IOMode Source # 
Show SomeSymbol Source # 
Show SomeNat Source # 
Show Fingerprint Source # 
Show ArithException Source # 
Show ErrorCall Source # 
Show Dynamic Source # 
Show IOException Source # 
Show MaskingState Source # 
Show DecidedStrictness Source # 
Show SourceStrictness Source # 
Show SourceUnpackedness Source # 
Show Associativity Source # 
Show Fixity Source # 
Show Any Source # 
Show All Source # 
Show SeekMode Source # 
Show CUIntMax Source # 
Show CIntMax Source # 
Show CUIntPtr Source # 
Show CIntPtr Source # 
Show CSUSeconds Source # 
Show CUSeconds Source # 
Show CTime Source # 
Show CClock Source # 
Show CSigAtomic Source # 
Show CWchar Source # 
Show CSize Source # 
Show CPtrdiff Source # 
Show CDouble Source # 
Show CFloat Source # 
Show CULLong Source # 
Show CLLong Source # 
Show CULong Source # 
Show CLong Source # 
Show CUInt Source # 
Show CInt Source # 
Show CUShort Source # 
Show CShort Source # 
Show CUChar Source # 
Show CSChar Source # 
Show CChar Source # 
Show IntPtr Source # 
Show WordPtr Source # 
Show CodingProgress Source # 
Show TextEncoding Source # 
Show NewlineMode Source # 
Show Newline Source # 
Show BufferMode Source # 
Show Handle Source # 
Show IOErrorType Source # 
Show ExitCode Source # 
Show ArrayException Source # 
Show AsyncException Source # 
Show SomeAsyncException Source # 
Show AssertionFailed Source # 
Show AllocationLimitExceeded Source # 
Show Deadlock Source # 
Show BlockedIndefinitelyOnSTM Source # 
Show BlockedIndefinitelyOnMVar Source # 
Show CodingFailureMode Source # 
Show ThreadStatus Source # 
Show BlockReason Source # 
Show ThreadId Source # 
Show Fd Source # 
Show CRLim Source # 
Show CTcflag Source # 
Show CSpeed Source # 
Show CCc Source # 
Show CUid Source # 
Show CNlink Source # 
Show CGid Source # 
Show CSsize Source # 
Show CPid Source # 
Show COff Source # 
Show CMode Source # 
Show CIno Source # 
Show CDev Source # 
Show Lifetime Source # 
Show Event Source # 
Show NestedAtomically Source # 
Show NonTermination Source # 
Show TypeError Source # 
Show NoMethodError Source # 
Show RecUpdError Source # 
Show RecConError Source # 
Show RecSelError Source # 
Show PatternMatchFail Source # 
Show FdKey Source # 
Show HandlePosn Source # 
Show GCStats Source # 
Show Version Source # 
Show Fixity Source # 
Show ConstrRep Source # 
Show DataRep Source # 
Show Constr Source # 
Show DataType Source # 
Show Void Source # 
Show Natural Source # 
Show StaticPtrInfo Source # 
Show RTSFlags Source # 
Show TickyFlags Source # 
Show TraceFlags Source # 
Show DoTrace Source # 
Show ProfFlags Source # 
Show DoHeapProfile Source # 
Show CCFlags Source # 
Show DoCostCentres Source # 
Show DebugFlags Source # 
Show MiscFlags Source # 
Show ConcFlags Source # 
Show GCFlags Source # 
Show GiveGCStats Source # 
Show a => Show [a] Source # 

Methods

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

show :: [a] -> String Source #

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

Show a => Show (Maybe a) Source # 
Show a => Show (Ratio a) Source # 
Show (Ptr a) Source # 

Methods

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

show :: Ptr a -> String Source #

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

Show (FunPtr a) Source # 
Show (V1 p) Source # 

Methods

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

show :: V1 p -> String Source #

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

Show (U1 p) Source # 

Methods

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

show :: U1 p -> String Source #

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

Show p => Show (Par1 p) Source # 

Methods

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

show :: Par1 p -> String Source #

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

Show a => Show (Down a) Source # 

Methods

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

show :: Down a -> String Source #

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

Show a => Show (Last a) Source # 

Methods

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

show :: Last a -> String Source #

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

Show a => Show (First a) Source # 
Show a => Show (Product a) Source # 
Show a => Show (Sum a) Source # 

Methods

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

show :: Sum a -> String Source #

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

Show a => Show (Dual a) Source # 

Methods

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

show :: Dual a -> String Source #

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

Show (ForeignPtr a) Source # 
Show a => Show (ZipList a) Source # 
Show a => Show (Complex a) Source # 
HasResolution a => Show (Fixed a) Source # 
Show a => Show (NonEmpty a) Source # 
Show a => Show (Option a) Source # 
Show m => Show (WrappedMonoid m) Source # 
Show a => Show (Last a) Source # 

Methods

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

show :: Last a -> String Source #

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

Show a => Show (First a) Source # 
Show a => Show (Max a) Source # 

Methods

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

show :: Max a -> String Source #

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

Show a => Show (Min a) Source # 

Methods

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

show :: Min a -> String Source #

showList :: [Min 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

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

Methods

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

show :: Either a b -> String Source #

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

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

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 # 
Show (URec Double p) Source # 
Show (URec Float p) Source # 
Show (URec Int p) Source # 
Show (URec Word p) Source # 
(Show a, Show b) => Show (a, b) Source # 

Methods

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

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

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

Show (ST s a) Source # 

Methods

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

show :: ST s a -> String Source #

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

Show (Proxy k s) Source # 

Methods

showsPrec :: Int -> Proxy k s -> ShowS Source #

show :: Proxy k s -> String Source #

showList :: [Proxy k s] -> ShowS Source #

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

Methods

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

show :: Arg a b -> String Source #

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

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

Methods

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

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

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

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

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 # 

Methods

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

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

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

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

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 (a, b, c) Source # 

Methods

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

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

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

Show ((:~:) k a b) Source # 

Methods

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

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

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

Show (Coercion k a b) Source # 

Methods

showsPrec :: Int -> Coercion k a b -> ShowS Source #

show :: Coercion k a b -> String Source #

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

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

Methods

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

show :: Alt k f a -> String Source #

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

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

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

Methods

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

show :: Const k a b -> String Source #

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

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

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 (a, b, c, d) Source # 

Methods

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

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

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

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

Methods

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

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

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

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

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, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) Source # 

Methods

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

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

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

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

Methods

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

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

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

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

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 # 

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 # 

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 # 

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 # 

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 # 

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 # 

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 # 

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 # 

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 # 

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.