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

Since: 2.1

Instance details
Show Double Source #

Since: 2.1

Instance details
Show Float Source #

Since: 2.1

Instance details
Show Int Source #

Since: 2.1

Instance details
Show Int8 Source #

Since: 2.1

Instance details
Show Int16 Source #

Since: 2.1

Instance details
Show Int32 Source #

Since: 2.1

Instance details
Show Int64 Source #

Since: 2.1

Instance details
Show Integer Source #

Since: 2.1

Instance details
Show Natural Source #

Since: 4.8.0.0

Instance details
Show Ordering Source # 
Instance details
Show Word Source #

Since: 2.1

Instance details
Show Word8 Source #

Since: 2.1

Instance details
Show Word16 Source #

Since: 2.1

Instance details
Show Word32 Source #

Since: 2.1

Instance details
Show Word64 Source #

Since: 2.1

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

Since: 4.9.0.0

Instance details
Show SomeTypeRep Source #

Since: 4.10.0.0

Instance details
Show () Source # 
Instance details

Methods

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

show :: () -> String Source #

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

Show TyCon Source #

Since: 2.1

Instance details
Show Module Source #

Since: 4.9.0.0

Instance details
Show TrName Source #

Since: 4.9.0.0

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

Since: 3.0

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

Since: 4.7.0.0

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

Since: 4.7.0.0

Instance details
Show SomeSymbol Source #

Since: 4.7.0.0

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

Since: 4.0.0.0

Instance details
Show ErrorCall Source #

Since: 4.0.0.0

Instance details
Show IOException Source #

Since: 4.1.0.0

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

Since: 4.3.0.0

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

Since: 4.1.0.0

Instance details
Show IOErrorType Source #

Since: 4.1.0.0

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

Since: 4.1.0.0

Instance details
Show AsyncException Source #

Since: 4.1.0.0

Instance details
Show SomeAsyncException Source #

Since: 4.7.0.0

Instance details
Show AssertionFailed Source #

Since: 4.1.0.0

Instance details
Show CompactionFailed Source #

Since: 4.10.0.0

Instance details
Show AllocationLimitExceeded Source #

Since: 4.7.1.0

Instance details
Show Deadlock Source #

Since: 4.1.0.0

Instance details
Show BlockedIndefinitelyOnSTM Source #

Since: 4.1.0.0

Instance details
Show BlockedIndefinitelyOnMVar Source #

Since: 4.1.0.0

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

Since: 4.3.1.0

Instance details
Show Dynamic Source #

Since: 2.1

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

Since: 4.2.0.0

Instance details
Show NestedAtomically Source #

Since: 4.0

Instance details
Show NonTermination Source #

Since: 4.0

Instance details
Show TypeError Source #

Since: 4.9.0.0

Instance details
Show NoMethodError Source #

Since: 4.0

Instance details
Show RecUpdError Source #

Since: 4.0

Instance details
Show RecConError Source #

Since: 4.0

Instance details
Show RecSelError Source #

Since: 4.0

Instance details
Show PatternMatchFail Source #

Since: 4.0

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

Since: 4.1.0.0

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

Since: 4.0.0.0

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

Since: 4.8.0.0

Instance details
Show a => Show [a] Source #

Since: 2.1

Instance details

Methods

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

show :: [a] -> String Source #

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

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

Since: 2.0.1

Instance details
Show (Ptr a) Source #

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

Since: 2.1

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

Methods

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

show :: Par1 p -> String Source #

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

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

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) Source # 
Instance details
Show a => Show (Sum a) Source # 
Instance details

Methods

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

show :: Sum a -> String Source #

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

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

Methods

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

show :: Dual a -> String Source #

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

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

Methods

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

show :: Last a -> String Source #

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

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

Since: 2.1

Instance details
Show a => Show (Identity a) Source #

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

Since: 4.8.0.0

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

Methods

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

show :: Last a -> String Source #

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

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

Methods

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

show :: Max a -> String Source #

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

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

Methods

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

show :: Min a -> String Source #

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

HasResolution a => Show (Fixed a) Source #

Since: 2.1

Instance details
Show a => Show (Complex a) Source # 
Instance details
Show (a -> b) Source #

Since: 2.1

Instance details

Methods

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

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

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

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

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

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) Source # 
Instance details
(Show a, Show b) => Show (a, b) Source #

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

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

Since: 4.7.0.0

Instance details
(Show a, Show b) => Show (Arg a b) Source # 
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) Source # 
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) Source # 
Instance details
Show (URec Int p) Source # 
Instance details
Show (URec Float p) Source # 
Instance details
Show (URec Double p) Source # 
Instance details
Show (URec Char p) Source # 
Instance details
(Show a, Show b, Show c) => Show (a, b, c) Source #

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

Methods

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

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

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

Show (Coercion a b) Source # 
Instance details
Show (f a) => Show (Alt f a) Source # 
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) Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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.