show-combinators-0.1.0.0: Combinators to write Show instances

Safe HaskellSafe
LanguageHaskell2010

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)

Synopsis

Documentation

module Text.Show

type PrecShowS = Int -> ShowS Source #

Type of strings representing expressions, parameterized by the surrounding precedence level.

This is the return type of flip showsPrec.

showCon :: String -> PrecShowS Source #

Show a constructor.

showApp :: PrecShowS -> PrecShowS -> PrecShowS infixl 2 Source #

Show a function application.

(@|) :: Show a => PrecShowS -> a -> PrecShowS infixl 2 Source #

Show a function application.

This is an infix shorthand for showApp when the argument type is an instance of Show.

showF @| x = showApp showF (flip showsPrec x)

showInfix :: String -> Int -> PrecShowS -> PrecShowS -> PrecShowS Source #

Show an applied infix operator with a given precedence.

showInfix' :: (Show a, Show b) => String -> Int -> a -> b -> PrecShowS Source #

Show an applied infix operator with a given precedence.

This is a shorthand for showInfix when the arguments types are instances of Show.

showInfix' op prec x y =
  showInfix op prec (flip showsPrec x) (flip showsPrec y)

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 #

Show a single record field: a field name and a value separated by '='.

This is an infix shorthand for showField when the value type is an instance of Show.

field .=. x = showField field (flip showsPrec x)

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.