Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides the NominalShow
type class, which is an
extension of Show
with support for renaming of bound variables.
We also provide generic programming so that instances of
NominalShow
can be automatically derived in most cases.
This module exposes implementation details of the Nominal library, and should not normally be imported. Users of the library should only import the top-level module Nominal.
- class NominalSupport t => NominalShow t where
- nominal_show :: NominalShow t => t -> String
- nominal_showsPrec :: NominalShow t => Int -> t -> ShowS
- basic_showsPrecSup :: Show t => Support -> Int -> t -> ShowS
- data Separator
- class GNominalShow f where
Display of nominal values
class NominalSupport t => NominalShow t where Source #
NominalShow
is similar to Show
, but with support for renaming
of bound variables. With the exception of function types, most
Nominal
types are also instances of NominalShow
.
In most cases, instances of NominalShow
can be automatically
derived. See "Deriving generic instances" for
information on how to do so, and
"Defining custom instances" for how to write custom
instances.
showsPrecSup :: Support -> Int -> t -> ShowS Source #
A nominal version of showsPrec
. This function takes as its
first argument the support of t. This is then passed into the
subterms, making printing O(n) instead of O(n²).
It is recommended to define a NominalShow
instance, rather than
a Show
instance, for each nominal type, and then either
automatically derive the Show
instance, or define it using
nominal_showsPrec
. For example:
instance Show MyType where showsPrec = nominal_showsPrec
Please note: in defining showsPrecSup
, neither show
nor nominal_show
should be used for the recursive cases, or
else the benefit of fast printing will be lost.
nominal_showList :: Support -> [t] -> ShowS Source #
The method nominal_showList
is provided to allow the
programmer to give a specialized way of showing lists of values,
similarly to showList
. The principal use of this is in the
NominalShow
instance of the Char
type, so that strings are
shown in double quotes, rather than as character lists.
showsPrecSup :: (Generic t, GNominalShow (Rep t)) => Support -> Int -> t -> ShowS Source #
A nominal version of showsPrec
. This function takes as its
first argument the support of t. This is then passed into the
subterms, making printing O(n) instead of O(n²).
It is recommended to define a NominalShow
instance, rather than
a Show
instance, for each nominal type, and then either
automatically derive the Show
instance, or define it using
nominal_showsPrec
. For example:
instance Show MyType where showsPrec = nominal_showsPrec
Please note: in defining showsPrecSup
, neither show
nor nominal_show
should be used for the recursive cases, or
else the benefit of fast printing will be lost.
nominal_show :: NominalShow t => t -> String Source #
Like show
, but for nominal types. Normally all instances of
NominalShow
are also instances of Show
, so show
can usually
be used instead of nominal_show
.
nominal_showsPrec :: NominalShow t => Int -> t -> ShowS Source #
This function can be used in the definition of Show
instances for nominal types, like this:
instance Show MyType where showsPrec = nominal_showsPrec
NominalShow instances
Most of the time, instances of NominalShow
should be derived using
deriving (Generic, NominalSupport, NominalShow)
, as in this example:
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveAnyClass #-} data Term = Var Atom | App Term Term | Abs (Bind Atom Term) deriving (Generic, NominalSupport, NominalShow)
In the case of non-nominal types (typically base types such as
Double
), a NominalShow
instance can be defined using
basic_showsPrecSup
:
instance NominalShow MyType where showsPrecSup = basic_showsPrecSup
basic_showsPrecSup :: Show t => Support -> Int -> t -> ShowS Source #
A helper function for defining NominalShow
instances
for non-nominal types. This requires an existing Show
instance.
Generic programming for NominalShow
This type keeps track of which separator to use for the next tuple.
class GNominalShow f where Source #
A version of the NominalShow
class suitable for generic
programming. The implementation uses ideas from
Generics.Deriving.Show.
GNominalShow (V1 *) Source # | |
GNominalShow (U1 *) Source # | |
NominalShow a => GNominalShow (K1 * i a) Source # | |
(GNominalShow a, GNominalShow b) => GNominalShow ((:+:) * a b) Source # | |
(GNominalShow a, GNominalShow b) => GNominalShow ((:*:) * a b) Source # | |
GNominalShow a => GNominalShow (M1 * D c a) Source # | |
(GNominalShow a, Constructor Meta c) => GNominalShow (M1 * C c a) Source # | |
(GNominalShow a, Selector Meta c) => GNominalShow (M1 * S c a) Source # | |
Orphan instances
(Bindable a, NominalShow a, NominalShow t) => Show (Bind a t) Source # | |