nom-0.1.0.1: Name-binding & alpha-equivalence

Copyright(c) Murdoch J. Gabbay 2020
LicenseGPL-3
Maintainermurdoch.gabbay@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Language.Nominal.NameSet

Contents

Description

Typeclasses and operations having to do with sets of names/atoms, namely:

Synopsis

Support and apartness

class (Typeable s, Swappable a) => KSupport s a where Source #

A typeclass for elements for which a supporting set of atoms can be computed in an efficient, structural, type-directed manner.

So: lists, sets, and name-abstractions yes, and function-types no. See instances for full details.

Note: This gives KSupport a strictly more specific and structure-directed meaning than the motivating mathematical notion of support, which does work e.g. on function-types.

Minimal complete definition

Nothing

Methods

ksupp :: proxy s -> a -> Set (KAtom s) Source #

ksupp :: (Generic a, GSupport s (Rep a)) => proxy s -> a -> Set (KAtom s) Source #

Instances
Typeable s => KSupport s Int Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

ksupp :: proxy s -> Int -> Set (KAtom s) Source #

Typeable s => KSupport s Char Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

ksupp :: proxy s -> Char -> Set (KAtom s) Source #

Typeable s => KSupport s Bool Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

ksupp :: proxy s -> Bool -> Set (KAtom s) Source #

Typeable s => KSupport s () Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

ksupp :: proxy s -> () -> Set (KAtom s) Source #

(Ord a, KSupport s a) => KSupport s (Set a) Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

ksupp :: proxy s -> Set a -> Set (KAtom s) Source #

KSupport s a => KSupport s (NonEmpty a) Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

ksupp :: proxy s -> NonEmpty a -> Set (KAtom s) Source #

KSupport s a => KSupport s [a] Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

ksupp :: proxy s -> [a] -> Set (KAtom s) Source #

KSupport s a => KSupport s (Maybe a) Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

ksupp :: proxy s -> Maybe a -> Set (KAtom s) Source #

(Typeable s, Typeable t) => KSupport s (KAtom t) Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

ksupp :: proxy s -> KAtom t -> Set (KAtom s) Source #

Typeable s => KSupport s (Nameless a) Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

ksupp :: proxy s -> Nameless a -> Set (KAtom s) Source #

(Binder ctxbody ctx body s, KSupport s ctx, KSupport s body) => KSupport s (BinderSupp ctxbody) Source # 
Instance details

Defined in Language.Nominal.Binder

Methods

ksupp :: proxy s -> BinderSupp ctxbody -> Set (KAtom s) Source #

Typeable s => KSupport s (KRen s) Source #

Support of a renaming is the set of nontrivially mapped atoms

>>> (supp (idRen :: Ren)) == S.empty
True
>>> (supp (nothingRen :: Ren)) == S.empty
True
Instance details

Defined in Language.Nominal.Unify

Methods

ksupp :: proxy s -> KRen s -> Set (KAtom s) Source #

Support r => KSupport Tom (Input r) Source # 
Instance details

Defined in Language.Nominal.Examples.IdealisedEUTxO

Methods

ksupp :: proxy Tom -> Input r -> Set (KAtom Tom) Source #

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

Defined in Language.Nominal.NameSet

Methods

ksupp :: proxy s -> Either a b -> Set (KAtom s) Source #

(KSupport s a, KSupport s b) => KSupport s (a, b) Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

ksupp :: proxy s -> (a, b) -> Set (KAtom s) Source #

(Typeable s, Typeable u, KSupport s t) => KSupport s (KName u t) Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

ksupp :: proxy s -> KName u t -> Set (KAtom s) Source #

(KSupport t a, Typeable s) => KSupport t (KNom s a) Source # 
Instance details

Defined in Language.Nominal.Nom

Methods

ksupp :: proxy t -> KNom s a -> Set (KAtom t) Source #

(KSupport s a, KSupport s t) => KSupport s (KAbs (KName s t) a) Source #

Support of a :@> x is the support of x minus a

Instance details

Defined in Language.Nominal.Abs

Methods

ksupp :: proxy s -> KAbs (KName s t) a -> Set (KAtom s) Source #

KSupport Tom (ValFin r d) Source # 
Instance details

Defined in Language.Nominal.Examples.IdealisedEUTxO

Methods

ksupp :: proxy Tom -> ValFin r d -> Set (KAtom Tom) Source #

KSupport Tom (Val r d) Source # 
Instance details

Defined in Language.Nominal.Examples.IdealisedEUTxO

Methods

ksupp :: proxy Tom -> Val r d -> Set (KAtom Tom) Source #

KSupport Tom (ValTriv r d) Source # 
Instance details

Defined in Language.Nominal.Examples.IdealisedEUTxO

Methods

ksupp :: proxy Tom -> ValTriv r d -> Set (KAtom Tom) Source #

(Support d, Support v) => KSupport Tom (Output d v) Source # 
Instance details

Defined in Language.Nominal.Examples.IdealisedEUTxO

Methods

ksupp :: proxy Tom -> Output d v -> Set (KAtom Tom) Source #

(KSupport s a, KSupport s b, KSupport s c) => KSupport s (a, b, c) Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

ksupp :: proxy s -> (a, b, c) -> Set (KAtom s) Source #

(Typeable s, Swappable a, Swappable b) => KSupport s (KEvFinMap s a b) Source #

We insist a and b be k-swappable so that the mathematical notion of support (which is based on nominal sets) makes sense.

Operationally, we don't care: if see something of type KEvFinMap s a b, we return Set.empty.

Instance details

Defined in Language.Nominal.Equivar

Methods

ksupp :: proxy s -> KEvFinMap s a b -> Set (KAtom s) Source #

(Typeable s, Swappable a, Swappable b) => KSupport s (KEvFun s a b) Source # 
Instance details

Defined in Language.Nominal.Equivar

Methods

ksupp :: proxy s -> KEvFun s a b -> Set (KAtom s) Source #

(Support r, Support d, Support v) => KSupport Tom (Blockchain r d v) Source # 
Instance details

Defined in Language.Nominal.Examples.IdealisedEUTxO

Methods

ksupp :: proxy Tom -> Blockchain r d v -> Set (KAtom Tom) Source #

(Support r, Support d, Support v) => KSupport Tom (Chunk r d v) Source # 
Instance details

Defined in Language.Nominal.Examples.IdealisedEUTxO

Methods

ksupp :: proxy Tom -> Chunk r d v -> Set (KAtom Tom) Source #

(Support d, Support r, Support v) => KSupport Tom (Context r d v) Source # 
Instance details

Defined in Language.Nominal.Examples.IdealisedEUTxO

Methods

ksupp :: proxy Tom -> Context r d v -> Set (KAtom Tom) Source #

(Support d, Support r, Support v) => KSupport Tom (Transaction r d v) Source # 
Instance details

Defined in Language.Nominal.Examples.IdealisedEUTxO

Methods

ksupp :: proxy Tom -> Transaction r d v -> Set (KAtom Tom) Source #

(KSupport s a, KSupport s b, KSupport s c, KSupport s d) => KSupport s (a, b, c, d) Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

ksupp :: proxy s -> (a, b, c, d) -> Set (KAtom s) Source #

(KSupport s a, KSupport s b, KSupport s c, KSupport s d, KSupport s e) => KSupport s (a, b, c, d, e) Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

ksupp :: proxy s -> (a, b, c, d, e) -> Set (KAtom s) Source #

type Support a = KSupport Tom a Source #

A Tom instance of KSupport.

supp :: Support a => a -> Set Atom Source #

A Tom instance of ksupp.

kapart :: (KSupport s a, KSupport s b) => proxy s -> a -> b -> Bool Source #

a and b are kapart when they are supported by disjoint sets of s-atoms.

We use proxy instead of Proxy below, so the user can supply any type that mentions s.

apart :: (Support a, Support b) => a -> b -> Bool Source #

a and b are apart when they are supported by disjoint sets of atoms.

Identifying list elements by name or atom

atomPoint :: (Foldable f, KSupport s a) => KAtom s -> f a -> NonEmpty a Source #

Bring the first element of a list-like structure that an atom points to (by being mentioned in the support), and put it at the head of the nonempty list. Raises error if no such element exists.

namePoint :: (Foldable f, KSupport s a) => KName s t -> f a -> NonEmpty a Source #

atomPoint, for names. A name is just a labelled atom, and namePoint just discards the label and calls atomPoint.

Restriction

class (Typeable s, Swappable a) => KRestrict s a where Source #

Class for types that support a remove these atoms from my support, please operation. Should satisfy e.g.:

restrict atms $ restrict atms x == restrict atms x
atms `apart` x ==> restrict atms x == x

The canonical instance of KRestrict is Nom. The Swappable constraint is not necessary for the code to run, but in practice wherever we use KRestrict we expect the type to have a swapping action.

Note for experts: We may want KRestrict without KSupport, for example to work with Nom (Atom -> Atom).

Note for experts: Restriction is familiar in general terms (e.g. pi-calculus restriction). In a nominal context, the original paper is nominal rewriting with name-generation (author's pdf), and this has a for-us highly pertinent emphasis on unification and rewriting.

Methods

restrict :: [KAtom s] -> a -> a Source #

Instances
Typeable s => KRestrict s Char Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

restrict :: [KAtom s] -> Char -> Char Source #

Typeable s => KRestrict s () Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

restrict :: [KAtom s] -> () -> () Source #

Typeable s => KRestrict s Int Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

restrict :: [KAtom s] -> Int -> Int Source #

Typeable s => KRestrict s Bool Source # 
Instance details

Defined in Language.Nominal.NameSet

Methods

restrict :: [KAtom s] -> Bool -> Bool Source #

(Ord a, KSupport s a) => KRestrict s (Set a) Source #

Eliminate elements for which any of the atms are in the support

Instance details

Defined in Language.Nominal.NameSet

Methods

restrict :: [KAtom s] -> Set a -> Set a Source #

KSupport s a => KRestrict s [a] Source #

On lists, Restrict traverses the list and eliminate elements for which any of the atms are in the support.

A alternative is to assume restriction on the underlying elements and restrict pointwise. The elimination choice seems more useful in practice.

Instance details

Defined in Language.Nominal.NameSet

Methods

restrict :: [KAtom s] -> [a] -> [a] Source #

KRestrict s a => KRestrict s (Maybe a) Source #

Restriction is monadic on Maybe

Instance details

Defined in Language.Nominal.NameSet

Methods

restrict :: [KAtom s] -> Maybe a -> Maybe a Source #

Typeable s => KRestrict s (Nameless a) Source #

Restriction is trivial on elements of nameless types

Instance details

Defined in Language.Nominal.NameSet

Methods

restrict :: [KAtom s] -> Nameless a -> Nameless a Source #

Typeable s => KRestrict s (KRen s) Source #

There are two reasonable notions of restriction; filter, or default to Nothing. We choose the option that discards minimal information, i.e. the filter.

Instance details

Defined in Language.Nominal.Unify

Methods

restrict :: [KAtom s] -> KRen s -> KRen s Source #

(Typeable s, Swappable a, KRestrict t a) => KRestrict t (KNom s a) Source # 
Instance details

Defined in Language.Nominal.Nom

Methods

restrict :: [KAtom t] -> KNom s a -> KNom s a Source #

(Typeable s, Swappable a) => KRestrict s (KNom s a) Source #

KRestrict atms in a, inside KNom monad.

Instance details

Defined in Language.Nominal.Nom

Methods

restrict :: [KAtom s] -> KNom s a -> KNom s a Source #

KRestrict Tom (ValFin r d) Source # 
Instance details

Defined in Language.Nominal.Examples.IdealisedEUTxO

Methods

restrict :: [KAtom Tom] -> ValFin r d -> ValFin r d Source #

KRestrict Tom (Val r d) Source # 
Instance details

Defined in Language.Nominal.Examples.IdealisedEUTxO

Methods

restrict :: [KAtom Tom] -> Val r d -> Val r d Source #

(Swappable r, Swappable d, Swappable v) => KRestrict Tom (Chunk r d v) Source #

Restrict atoms in a Chunk.

Instance details

Defined in Language.Nominal.Examples.IdealisedEUTxO

Methods

restrict :: [KAtom Tom] -> Chunk r d v -> Chunk r d v Source #

type Restrict = KRestrict Tom Source #

Instance of KRestrict on a Tom.

restrictN :: KRestrict s a => [KName s t] -> a -> a Source #

Form of restriction that takes names instead of atoms. Just discards name labels and calls restrict.

Tests

Property-based tests are in Language.Nominal.Properties.NameSetSpec.