nominal-0.3.0.0: Binders and alpha-equivalence made easy

Safe HaskellNone
LanguageHaskell2010

Nominal.NominalShow

Contents

Description

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.

Synopsis

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.

Minimal complete definition

Nothing

Methods

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.

Instances
NominalShow Bool Source # 
Instance details

Defined in Nominal.NominalShow

NominalShow Char Source # 
Instance details

Defined in Nominal.NominalShow

NominalShow Double Source # 
Instance details

Defined in Nominal.NominalShow

NominalShow Float Source # 
Instance details

Defined in Nominal.NominalShow

NominalShow Int Source # 
Instance details

Defined in Nominal.NominalShow

NominalShow Integer Source # 
Instance details

Defined in Nominal.NominalShow

NominalShow Ordering Source # 
Instance details

Defined in Nominal.NominalShow

NominalShow () Source # 
Instance details

Defined in Nominal.NominalShow

NominalShow Atom Source # 
Instance details

Defined in Nominal.NominalShow

NominalShow Literal Source # 
Instance details

Defined in Nominal.NominalShow

NominalShow t => NominalShow [t] Source # 
Instance details

Defined in Nominal.NominalShow

Methods

showsPrecSup :: Support -> Int -> [t] -> ShowS Source #

nominal_showList :: Support -> [[t]] -> ShowS Source #

NominalShow a => NominalShow (Maybe a) Source # 
Instance details

Defined in Nominal.NominalShow

(Ord k, NominalShow k) => NominalShow (Set k) Source # 
Instance details

Defined in Nominal.NominalShow

Show t => NominalShow (Basic t) Source # 
Instance details

Defined in Nominal.NominalShow

NominalShow t => NominalShow (Defer t) Source # 
Instance details

Defined in Nominal.NominalShow

AtomKind a => NominalShow (AtomOfKind a) Source # 
Instance details

Defined in Nominal.Atomic

(NominalShow a, NominalShow b) => NominalShow (Either a b) Source # 
Instance details

Defined in Nominal.NominalShow

(NominalShow t, NominalShow s) => NominalShow (t, s) Source # 
Instance details

Defined in Nominal.NominalShow

Methods

showsPrecSup :: Support -> Int -> (t, s) -> ShowS Source #

nominal_showList :: Support -> [(t, s)] -> ShowS Source #

(Ord k, NominalShow k, NominalShow v) => NominalShow (Map k v) Source # 
Instance details

Defined in Nominal.NominalShow

(Bindable a, NominalShow a, NominalShow t) => NominalShow (Bind a t) Source # 
Instance details

Defined in Nominal.Bindable

(NominalShow t, NominalShow s, NominalShow r) => NominalShow (t, s, r) Source # 
Instance details

Defined in Nominal.NominalShow

Methods

showsPrecSup :: Support -> Int -> (t, s, r) -> ShowS Source #

nominal_showList :: Support -> [(t, s, r)] -> ShowS Source #

(NominalShow t, NominalShow s, NominalShow r, NominalShow q) => NominalShow (t, s, r, q) Source # 
Instance details

Defined in Nominal.NominalShow

Methods

showsPrecSup :: Support -> Int -> (t, s, r, q) -> ShowS Source #

nominal_showList :: Support -> [(t, s, r, q)] -> ShowS Source #

(NominalShow t, NominalShow s, NominalShow r, NominalShow q, NominalShow p) => NominalShow (t, s, r, q, p) Source # 
Instance details

Defined in Nominal.NominalShow

Methods

showsPrecSup :: Support -> Int -> (t, s, r, q, p) -> ShowS Source #

nominal_showList :: Support -> [(t, s, r, q, p)] -> ShowS Source #

(NominalShow t, NominalShow s, NominalShow r, NominalShow q, NominalShow p, NominalShow o) => NominalShow (t, s, r, q, p, o) Source # 
Instance details

Defined in Nominal.NominalShow

Methods

showsPrecSup :: Support -> Int -> (t, s, r, q, p, o) -> ShowS Source #

nominal_showList :: Support -> [(t, s, r, q, p, o)] -> ShowS Source #

(NominalShow t, NominalShow s, NominalShow r, NominalShow q, NominalShow p, NominalShow o, NominalShow n) => NominalShow (t, s, r, q, p, o, n) Source # 
Instance details

Defined in Nominal.NominalShow

Methods

showsPrecSup :: Support -> Int -> (t, s, r, q, p, o, n) -> ShowS Source #

nominal_showList :: Support -> [(t, s, r, q, p, o, n)] -> ShowS Source #

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

data Separator Source #

This type keeps track of which separator to use for the next tuple.

Constructors

Rec 
Tup 
Inf String 
Pre 

class GNominalShow f where Source #

A version of the NominalShow class suitable for generic programming. The implementation uses ideas from Generics.Deriving.Show.

Minimal complete definition

gshowsPrecSup

Methods

gshowsPrecSup :: Separator -> Support -> Int -> f a -> ShowS Source #

isNullary :: f a -> Bool Source #

Instances
GNominalShow (V1 :: Type -> Type) Source # 
Instance details

Defined in Nominal.NominalShow

GNominalShow (U1 :: Type -> Type) Source # 
Instance details

Defined in Nominal.NominalShow

NominalShow a => GNominalShow (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Nominal.NominalShow

Methods

gshowsPrecSup :: Separator -> Support -> Int -> K1 i a a0 -> ShowS Source #

isNullary :: K1 i a a0 -> Bool Source #

(GNominalShow a, GNominalShow b) => GNominalShow (a :+: b) Source # 
Instance details

Defined in Nominal.NominalShow

Methods

gshowsPrecSup :: Separator -> Support -> Int -> (a :+: b) a0 -> ShowS Source #

isNullary :: (a :+: b) a0 -> Bool Source #

(GNominalShow a, GNominalShow b) => GNominalShow (a :*: b) Source # 
Instance details

Defined in Nominal.NominalShow

Methods

gshowsPrecSup :: Separator -> Support -> Int -> (a :*: b) a0 -> ShowS Source #

isNullary :: (a :*: b) a0 -> Bool Source #

GNominalShow a => GNominalShow (M1 D c a) Source # 
Instance details

Defined in Nominal.NominalShow

Methods

gshowsPrecSup :: Separator -> Support -> Int -> M1 D c a a0 -> ShowS Source #

isNullary :: M1 D c a a0 -> Bool Source #

(GNominalShow a, Constructor c) => GNominalShow (M1 C c a) Source # 
Instance details

Defined in Nominal.NominalShow

Methods

gshowsPrecSup :: Separator -> Support -> Int -> M1 C c a a0 -> ShowS Source #

isNullary :: M1 C c a a0 -> Bool Source #

(GNominalShow a, Selector c) => GNominalShow (M1 S c a) Source # 
Instance details

Defined in Nominal.NominalShow

Methods

gshowsPrecSup :: Separator -> Support -> Int -> M1 S c a a0 -> ShowS Source #

isNullary :: M1 S c a a0 -> Bool Source #