Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
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
- module Text.Show
- 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
module Text.Show
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 showInfixl
.
showInfixl :: String -> Int -> PrecShowS -> PrecShowS -> PrecShowS Source #
Show an applied infix operator which is left associative (infixl
).
Use with care.
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.
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.
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.
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 '='
.
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
.