| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Text.Show.Combinators
Description
Combinators for Show
The combinators below can be used 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 :+:
instance Show a => Show (MyType a) where
showsPrec = 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)
- 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
- 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
showInfix :: String -> Int -> PrecShowS -> PrecShowS -> PrecShowS Source #
Show an applied infix operator with a given precedence.
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.