nominal-0.1.0.0: Binders and alpha-equivalence made easy

Safe HaskellNone
LanguageHaskell2010

Nominal.Nominal

Contents

Description

This module provides the Nominal type class. A type is Nominal if the group of finitely supported permutations of atoms acts on it. We can abstract over an atom in such a type.

We also provide some generic programming so that instances of Nominal can be automatically derived in most cases.

Synopsis

The Nominal class

class Nominal t where Source #

A type is nominal if the group of finitely supported permutations of atoms acts on it.

In most cases, instances of Nominal 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.

Methods

(•) :: NominalPermutation -> t -> t Source #

Apply a permutation of atoms to a term.

(•) :: (Generic t, GNominal (Rep t)) => NominalPermutation -> t -> t Source #

Apply a permutation of atoms to a term.

Instances

Nominal Bool Source # 
Nominal Char Source # 
Nominal Double Source # 
Nominal Float Source # 
Nominal Int Source # 
Nominal Integer Source # 
Nominal () Source # 

Methods

(•) :: NominalPermutation -> () -> () Source #

Nominal Atom Source # 
Nominal Literal Source # 
Nominal t => Nominal [t] Source # 

Methods

(•) :: NominalPermutation -> [t] -> [t] Source #

(Ord k, Nominal k) => Nominal (Set k) Source # 

Methods

(•) :: NominalPermutation -> Set k -> Set k Source #

Nominal (Basic t) Source # 
Nominal t => Nominal (BindAtom t) Source # 
Nominal (Defer t) Source # 
Nominal t => Nominal (NoBind t) Source # 
Nominal t => Nominal (BindAtomList t) Source # 
AtomKind a => Nominal (AtomOfKind a) Source # 
(Nominal t, Nominal s) => Nominal (t -> s) Source # 

Methods

(•) :: NominalPermutation -> (t -> s) -> t -> s Source #

(Nominal t, Nominal s) => Nominal (t, s) Source # 

Methods

(•) :: NominalPermutation -> (t, s) -> (t, s) Source #

(Ord k, Nominal k, Nominal v) => Nominal (Map k v) Source # 

Methods

(•) :: NominalPermutation -> Map k v -> Map k v Source #

(Bindable a, Nominal t) => Nominal (Bind a t) Source # 

Methods

(•) :: NominalPermutation -> Bind a t -> Bind a t Source #

(Nominal t, Nominal s, Nominal r) => Nominal (t, s, r) Source # 

Methods

(•) :: NominalPermutation -> (t, s, r) -> (t, s, r) Source #

(Nominal t, Nominal s, Nominal r, Nominal q) => Nominal (t, s, r, q) Source # 

Methods

(•) :: NominalPermutation -> (t, s, r, q) -> (t, s, r, q) Source #

(Nominal t, Nominal s, Nominal r, Nominal q, Nominal p) => Nominal (t, s, r, q, p) Source # 

Methods

(•) :: NominalPermutation -> (t, s, r, q, p) -> (t, s, r, q, p) Source #

(Nominal t, Nominal s, Nominal r, Nominal q, Nominal p, Nominal o) => Nominal (t, s, r, q, p, o) Source # 

Methods

(•) :: NominalPermutation -> (t, s, r, q, p, o) -> (t, s, r, q, p, o) Source #

(Nominal t, Nominal s, Nominal r, Nominal q, Nominal p, Nominal o, Nominal n) => Nominal (t, s, r, q, p, o, n) Source # 

Methods

(•) :: NominalPermutation -> (t, s, r, q, p, o, n) -> (t, s, r, q, p, o, n) Source #

Deferred permutation

data Defer t Source #

Defer t is the type t, but equipped with an explicit substitution. This is used to cache substitutions so that they can be optimized and applied all at once.

Constructors

Defer NominalPermutation t 

force :: Nominal t => Defer t -> t Source #

Apply a deferred permutation.

Atom abstraction

data BindAtom t Source #

BindAtom t is the type of atom abstractions, denoted [a]t in the nominal logic literature. Its elements are of the form (a.v) modulo alpha-equivalence. For full technical details on what this means, see Definition 4 of [Pitts 2002].

Implementation note: we currently use an HOAS encoding, as this turns out to be far more efficient (both in time and memory usage) than the alternatives. An important invariant of the HOAS encoding is that the underlying function must only be applied to fresh atoms.

Constructors

BindAtom NameGen (Atom -> Defer t) 

atom_abst :: Atom -> t -> BindAtom t Source #

Atom abstraction: atom_abst a t represents the equivalence class of pairs (a,t) modulo alpha-equivalence. We first define this for Atom and later generalize to other Atomic types.

atom_open :: Nominal t => BindAtom t -> (Atom -> t -> s) -> s Source #

Pattern matching for atom abstraction. In an ideal programming idiom, we would be able to define a function on atom abstractions like this:

f (x.s) = body.

Haskell doesn't let us provide this syntax, but the open function provides the equivalent syntax

f t = open t (\x s -> body).

To be referentially transparent and equivariant, the body is subject to the same restriction as with_fresh, namely, x must be fresh for the body (in symbols x # body).

atom_merge :: (Nominal t, Nominal s) => BindAtom t -> BindAtom s -> BindAtom (t, s) Source #

Sometimes, it is necessary to open two abstractions, using the same fresh name for both of them. An example of this is the typing rule for lambda abstraction in dependent type theory:

          Gamma, x:t  |-  e : s
     ------------------------------------
       Gamma |-  Lam (x.e) : Pi t (x.s)

In the bottom-up reading of this rule, we are given the terms Lam body and Pi t body', and we require a fresh name x and terms e, s such that body = (x.e) and body' = (x.s). Crucially, the same atom x should be used in both e and s, because we subsequently need to check that e has type s in some scope that is common to e and s.

The merge primitive permits us to deal with such situations. Its defining property is

merge (x.e) (x.s) = (x.(e,s)).

We can therefore solve the above problem:

open (merge body body') (\x (e,s) -> .....)

Moreover, the merge primitive can be used to define other merge-like functionality. For example, it is easy to define a function

merge_list :: (Atomic a, Nominal t) => [Bind a t] -> Bind a [t]

in terms of it.

Semantically, the merge operation implements the isomorphism of nominal sets [A]T x [A]S = [A](T x S).

If x and y are atoms with user-suggested concrete names and

(z.(t',s')) = merge (x.t) (y.s),

then z will be preferably given the concrete name of x, but the concrete name of y will be used if the name of x would cause a clash.

Basic types

newtype Basic t Source #

A basic or non-nominal type is a type whose elements cannot contain any atoms. Typical examples are base types, such as Integer or Bool, and other types constructed exclusively from them, such as [Integer] or Bool -> Bool. On such types, the nominal structure is trivial, i.e., π • x = x for all x.

For convenience, we define Basic as a wrapper around such types, which will automatically generate appropriate instances of Nominal, NominalSupport, NominalShow, and Bindable. You can use it, for example, like this:

type Term = Var Atom | Const (Basic Int) | App Term Term

Some common base types, including Bool, Char, Int, Integer, Double, and Float, are already instances of the relevant type classes, and do not need to be wrapped in Basic.

The use of Basic can sometimes have a performance advantage. For example, Basic String is a more efficient Nominal instance than String. Although they are semantically equivalent, the use of Basic prevents having to traverse the string to check each character for atoms that are clearly not there.

Constructors

Basic t 

Instances

Eq t => Eq (Basic t) Source # 

Methods

(==) :: Basic t -> Basic t -> Bool #

(/=) :: Basic t -> Basic t -> Bool #

Ord t => Ord (Basic t) Source # 

Methods

compare :: Basic t -> Basic t -> Ordering #

(<) :: Basic t -> Basic t -> Bool #

(<=) :: Basic t -> Basic t -> Bool #

(>) :: Basic t -> Basic t -> Bool #

(>=) :: Basic t -> Basic t -> Bool #

max :: Basic t -> Basic t -> Basic t #

min :: Basic t -> Basic t -> Basic t #

Show t => Show (Basic t) Source # 

Methods

showsPrec :: Int -> Basic t -> ShowS #

show :: Basic t -> String #

showList :: [Basic t] -> ShowS #

Nominal (Basic t) Source # 
NominalSupport (Basic t) Source # 

Methods

support :: Basic t -> Support Source #

Bindable (Basic t) Source # 
Show t => NominalShow (Basic t) Source # 

Nominal instances

Most of the time, instances of Nominal should be derived using deriving (Generic, Nominal), as in this example:

{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}

data Term = Var Atom | App Term Term | Abs (Bind Atom Term)
  deriving (Generic, Nominal)

In the case of non-nominal types (typically base types such as Double), a Nominal instance can be defined using basic_action:

instance Nominal MyType where
  (•) = basic_action

basic_action :: NominalPermutation -> t -> t Source #

A helper function for defining Nominal instances for non-nominal types.

Generic programming for Nominal

class GNominal f where Source #

A version of the Nominal class suitable for generic programming.

Minimal complete definition

gbullet

Methods

gbullet :: NominalPermutation -> f a -> f a Source #

Instances

GNominal (V1 *) Source # 

Methods

gbullet :: NominalPermutation -> V1 * a -> V1 * a Source #

GNominal (U1 *) Source # 

Methods

gbullet :: NominalPermutation -> U1 * a -> U1 * a Source #

Nominal a => GNominal (K1 * i a) Source # 

Methods

gbullet :: NominalPermutation -> K1 * i a a -> K1 * i a a Source #

(GNominal a, GNominal b) => GNominal ((:+:) * a b) Source # 

Methods

gbullet :: NominalPermutation -> (* :+: a) b a -> (* :+: a) b a Source #

(GNominal a, GNominal b) => GNominal ((:*:) * a b) Source # 

Methods

gbullet :: NominalPermutation -> (* :*: a) b a -> (* :*: a) b a Source #

GNominal a => GNominal (M1 * i c a) Source # 

Methods

gbullet :: NominalPermutation -> M1 * i c a a -> M1 * i c a a Source #