Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Text.Show.Combinators
Description
Combinators to write Show
instances.
The following type illustrates the common use cases.
data MyType a = C a a -- a regular constructor | a :+: a -- an infix constructor | R { f1 :: a, f2 :: a } -- a record infixl 4 :+: instanceShow
a =>Show
(MyType a) whereshowsPrec
=flip
precShows where precShows (C a b) =showCon
"C"@|
a@|
b precShows (c :+: d) =showInfix'
":+:" 4 c d precShows (R {f1 = e, f2 = f}) =showRecord
"R" ("f1".=.
e&|
"f2".=.
f)
Synopsis
- class Show a where
- type ShowS = String -> String
- showString :: String -> ShowS
- showParen :: Bool -> ShowS -> ShowS
- showChar :: Char -> ShowS
- shows :: Show a => a -> ShowS
- showListWith :: (a -> ShowS) -> [a] -> ShowS
- type PrecShowS = Int -> ShowS
- showCon :: String -> PrecShowS
- showApp :: PrecShowS -> PrecShowS -> PrecShowS
- (@|) :: Show a => PrecShowS -> a -> PrecShowS
- showInfix :: String -> Int -> PrecShowS -> PrecShowS -> PrecShowS
- showInfix' :: (Show a, Show b) => String -> Int -> a -> b -> PrecShowS
- showInfixl :: String -> Int -> PrecShowS -> PrecShowS -> PrecShowS
- showInfixl' :: (Show a, Show b) => String -> Int -> a -> b -> PrecShowS
- showInfixr :: String -> Int -> PrecShowS -> PrecShowS -> PrecShowS
- showInfixr' :: (Show a, Show b) => String -> Int -> a -> b -> PrecShowS
- type ShowFields = ShowS
- showRecord :: String -> ShowFields -> PrecShowS
- showField :: String -> PrecShowS -> ShowFields
- (.=.) :: Show a => String -> a -> ShowFields
- noFields :: ShowFields
- appendFields :: ShowFields -> ShowFields -> ShowFields
- (&|) :: ShowFields -> ShowFields -> ShowFields
Documentation
Instances
Show NestedAtomically | |
Show NoMatchingContinuationPrompt | |
Show NoMethodError | |
Show NonTermination | |
Show PatternMatchFail | |
Show RecConError | |
Show RecSelError | |
Show RecUpdError | |
Show TypeError | |
Show ByteArray | |
Show Constr | |
Show ConstrRep | |
Show DataRep | |
Show DataType | |
Show Fixity | |
Show Dynamic | |
Show Version | |
Show CBool | |
Show CChar | |
Show CClock | |
Show CDouble | |
Show CFloat | |
Show CInt | |
Show CIntMax | |
Show CIntPtr | |
Show CLLong | |
Show CLong | |
Show CPtrdiff | |
Show CSChar | |
Show CSUSeconds | |
Show CShort | |
Show CSigAtomic | |
Show CSize | |
Show CTime | |
Show CUChar | |
Show CUInt | |
Show CUIntMax | |
Show CUIntPtr | |
Show CULLong | |
Show CULong | |
Show CUSeconds | |
Show CUShort | |
Show CWchar | |
Show IntPtr | |
Show WordPtr | |
Show Void | |
Show ByteOrder | |
Show BlockReason | |
Show ThreadId | |
Show ThreadStatus | |
Show ErrorCall | |
Show ArithException | |
Show SomeException | |
Show Fingerprint | |
Show Associativity | |
Show DecidedStrictness | |
Show Fixity | |
Show SourceStrictness | |
Show SourceUnpackedness | |
Show MaskingState | |
Show SeekMode | |
Show CodingFailureMode | |
Show CodingProgress | |
Show TextEncoding | |
Show AllocationLimitExceeded | |
Show ArrayException | |
Show AssertionFailed | |
Show AsyncException | |
Show BlockedIndefinitelyOnMVar | |
Show BlockedIndefinitelyOnSTM | |
Show CompactionFailed | |
Show Deadlock | |
Show ExitCode | |
Show FixIOException | |
Show IOErrorType | |
Show IOException | |
Show SomeAsyncException | |
Show FD | |
Show HandlePosn | |
Show BufferMode | |
Show Handle | |
Show HandleType | |
Show Newline | |
Show NewlineMode | |
Show IOMode | |
Show IOPortException | |
Show InfoProv | |
Show Int16 | |
Show Int32 | |
Show Int64 | |
Show Int8 | |
Show CCFlags | |
Show ConcFlags | |
Show DebugFlags | |
Show DoCostCentres | |
Show DoHeapProfile | |
Show DoTrace | |
Show GCFlags | |
Show GiveGCStats | |
Show IoSubSystem | |
Show MiscFlags | |
Show ParFlags | |
Show ProfFlags | |
Show RTSFlags | |
Show TickyFlags | |
Show TraceFlags | |
Show FractionalExponentBase | |
Show StackEntry | |
Show CallStack | |
Show SrcLoc | |
Show StaticPtrInfo | |
Show GCDetails | |
Show RTSStats | |
Show SomeChar | |
Show SomeSymbol | |
Show SomeNat | |
Show GeneralCategory | |
Show Word16 | |
Show Word32 | |
Show Word64 | |
Show Word8 | |
Show CBlkCnt | |
Show CBlkSize | |
Show CCc | |
Show CClockId | |
Show CDev | |
Show CFsBlkCnt | |
Show CFsFilCnt | |
Show CGid | |
Show CId | |
Show CIno | |
Show CKey | |
Show CMode | |
Show CNfds | |
Show CNlink | |
Show COff | |
Show CPid | |
Show CRLim | |
Show CSocklen | |
Show CSpeed | |
Show CSsize | |
Show CTcflag | |
Show CTimer | |
Show CUid | |
Show Fd | |
Show Timeout | |
Show Lexeme | |
Show Number | |
Show KindRep | |
Show Module | |
Show Ordering | |
Show TrName | |
Show TyCon | |
Show TypeLitSort | |
Show Integer | |
Show Natural | |
Show () | |
Show Bool | |
Show Char | |
Show Int | |
Show Levity | |
Show RuntimeRep | |
Show VecCount | |
Show VecElem | |
Show Word | |
Show a => Show (ZipList a) | |
Show a => Show (And a) | |
Show a => Show (Iff a) | |
Show a => Show (Ior a) | |
Show a => Show (Xor a) | |
Show a => Show (Complex a) | |
Show a => Show (Identity a) | |
Show a => Show (First a) | |
Show a => Show (Last a) | |
Show a => Show (Down a) | |
Show a => Show (First a) | |
Show a => Show (Last a) | |
Show a => Show (Max a) | |
Show a => Show (Min a) | |
Show m => Show (WrappedMonoid m) | |
Show (ConstPtr a) | |
Show a => Show (NonEmpty a) | |
Show (ForeignPtr a) | |
Show p => Show (Par1 p) | |
Show (FunPtr a) | |
Show (Ptr a) | |
Show a => Show (Ratio a) | |
Show (SChar c) | |
Show (SSymbol s) | |
Show (SNat n) | |
Show a => Show (Maybe a) | |
Show a => Show (Solo a) | |
Show a => Show [a] | |
(Show a, Show b) => Show (Either a b) | |
HasResolution a => Show (Fixed a) | |
Show (Proxy s) | |
(Show a, Show b) => Show (Arg a b) | |
(Ix a, Show a, Show b) => Show (Array a b) | |
Show (U1 p) | |
Show (V1 p) | |
Show (ST s a) | |
(Show a, Show b) => Show (a, b) | |
Show a => Show (Const a b) | |
Show (f a) => Show (Ap f a) | |
Show (Coercion a b) | |
Show (a :~: b) | |
Show (OrderingI a b) | |
Show (f p) => Show (Rec1 f p) | |
Show (URec Char p) | |
Show (URec Double p) | |
Show (URec Float p) | |
Show (URec Int p) | |
Show (URec Word p) | |
(Show a, Show b, Show c) => Show (a, b, c) | |
(Show (f a), Show (g a)) => Show (Product f g a) | |
(Show (f a), Show (g a)) => Show (Sum f g a) | |
Show (a :~~: b) | |
(Show (f p), Show (g p)) => Show ((f :*: g) p) | |
(Show (f p), Show (g p)) => Show ((f :+: g) p) | |
Show c => Show (K1 i c p) | |
(Show a, Show b, Show c, Show d) => Show (a, b, c, d) | |
Show (f (g a)) => Show (Compose f g a) | |
Show (f (g p)) => Show ((f :.: g) p) | |
Show (f p) => Show (M1 i c f p) | |
(Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) | |
(Show a, Show b, Show c, Show d, Show e, Show f) => Show (a, b, c, d, e, f) | |
(Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (a, b, c, d, e, f, g) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
showString :: String -> ShowS #
showListWith :: (a -> ShowS) -> [a] -> ShowS #
type PrecShowS = Int -> ShowS Source #
Type of strings representing expressions, parameterized by the surrounding precedence level.
This is the return type of
.flip
showsPrec
Simple constructors and applications
showCon :: String -> PrecShowS Source #
Show a constructor.
Possible constructor names are:
- regular constructors (e.g.,
"Left"
); - parenthesized infix constructors (e.g.,
"(:)"
); - smart constructors, for abstract types (e.g.,
"Map.fromList"
).
Example with smart constructor
Infix constructors
showInfix :: String -> Int -> PrecShowS -> PrecShowS -> PrecShowS Source #
Show an applied infix operator with a given precedence.
Combinators for associative operators
Use with care, see warning under showInfixl
.
showInfixl :: String -> Int -> PrecShowS -> PrecShowS -> PrecShowS Source #
Show an applied infix operator which is left associative (infixl
).
Use with care.
Warning
This combinator assumes that, if there is another infix operator to the
left, it is either left associative with the same precedence, or it has a
different precedence.
An expression containing two operators at the same level with different
associativities is ambiguous and will not be shown correctly with
showInfixl
and showInfixr
.
By default, prefer showInfix
and showInfix'
.
showInfixl' :: (Show a, Show b) => String -> Int -> a -> b -> PrecShowS Source #
Show an applied infix operator which is left associative (infixl
).
Use with care, see showInfixl
.
This is a shorthand for showInfixl
when the arguments types are instances
of Show
.
By default, prefer showInfix
and showInfix'
.
showInfixr :: String -> Int -> PrecShowS -> PrecShowS -> PrecShowS Source #
Show an applied infix operator which is right associative (infixr
).
Use with care.
Warning
This combinator assumes that, if there is another infix operator to the
right, it is either right associative with the same precedence, or it has a
different precedence.
An expression containing two operators at the same level with different
associativities is ambiguous and will not be shown correctly with
showInfixl
and showInfixr
.
By default, prefer showInfix
and showInfix'
.
Example usage
showList :: Show a => [a] -> PrecShowS showList [] = showCon "[]" showList (x : xs) = showInfixr ":" 5 (flip showsPrec x) (showList xs) -- Example output: -- > 0 : 1 : 2 : 3 : []
showInfixr' :: (Show a, Show b) => String -> Int -> a -> b -> PrecShowS Source #
Show an applied infix operator which is right associative (infixr
).
Use with care, see showInfixr
.
This is a shorthand for showInfixr
when the arguments types are instances
of Show
.
By default, prefer showInfix
and showInfix'
.
Records
type ShowFields = ShowS Source #
Strings representing a set of record fields separated by commas.
They can be constructed using (.=.
) and (@|
), or using showField
and
appendFields
.
showRecord :: String -> ShowFields -> PrecShowS Source #
Show a record. The first argument is the constructor name. The second represents the set of record fields.
showField :: String -> PrecShowS -> ShowFields Source #
Show a single record field: a field name and a value separated by '='
.
(.=.) :: Show a => String -> a -> ShowFields infixr 8 Source #
noFields :: ShowFields Source #
Empty set of record fields.
appendFields :: ShowFields -> ShowFields -> ShowFields infixr 1 Source #
Separate two nonempty sets of record fields by a comma.
(&|) :: ShowFields -> ShowFields -> ShowFields infixr 1 Source #
An infix synonym of appendFields
.