| Copyright | (c) Murdoch J. Gabbay 2020 |
|---|---|
| License | GPL-3 |
| Maintainer | murdoch.gabbay@gmail.com |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
Language.Nominal.Nom
Contents
Description
Nominal-flavoured implementation of data in a context of local names
Synopsis
- newtype KNom s a = Nom {}
- type Nom = KNom Tom
- res :: (Typeable s, Swappable a) => [KAtom s] -> a -> KNom s a
- kres :: (Typeable s, Swappable a) => proxy s -> [KAtom s] -> a -> KNom s a
- resN :: (Typeable s, Swappable a) => [KName s t] -> a -> KNom s a
- reRes :: (Typeable s, Swappable a) => KNom s a -> KNom s a
- unNom :: KRestrict s a => KNom s a -> a
- nomToIO :: KNom s a -> IO a
- freshKAtom :: KNom s (KAtom s)
- freshAtom :: Nom Atom
- freshKAtoms :: Traversable m => m t -> KNom s (m (KAtom s))
- freshAtoms :: Traversable m => m t -> Nom (m Atom)
- freshKName :: t -> KNom s (KName s t)
- freshName :: t -> Nom (Name t)
- freshKNames :: Traversable m => m t -> KNom s (m (KName s t))
- freshNames :: Traversable m => m t -> Nom (m (Name t))
- freshKNameIO :: t -> IO (KName s t)
- freshNameIO :: t -> IO (Name t)
- freshKNamesIO :: Traversable m => m t -> IO (m (KName s t))
- freshNamesIO :: Traversable m => m t -> IO (m (Name t))
- transposeNomF :: (Functor f, Typeable s, Swappable a) => KNom s (f a) -> f (KNom s a)
- module Language.Nominal.SMonad
The Nom monad
Broadly speaking there are three kinds of functions involving KNom:
KNom-specific functions that may involve creating fresh atoms, but do not involve swappings.- More general functions involving the
Bindertypeclass (defined usingKNom, and of whichKNomis the canonical instance). These functions tend to imposeSwappableandTypeableconstraints on their type parameters. KNom-specific functions in which, for various reasons (elegance, avoiding code duplication, necessity) we make use of both classes of functions above.
This file deals with the first class above. The second and third are in Language.Nominal.Binder.
Remark: KNom is more basic than Binder, though it's the canonical instance. This creates a design tension: is a function on KNom best viewed as a function directly on Nom, or as an instance of a more general function involving Binder?
Data in local -binding context.KAtom s
Constructors
| Nom | |
Instances
| (Typeable s, Swappable a, KRestrict t a) => KRestrict t (KNom s a) Source # | |
| (Typeable s, Swappable a) => KRestrict s (KNom s a) Source # | |
| (KSupport t a, Typeable s) => KSupport t (KNom s a) Source # | |
| (Typeable s, KUnifyPerm s a) => KUnifyPerm s (KNom s a) Source # | Unify |
| Monad (KNom s) Source # | |
| Functor (KNom s) Source # | |
| Applicative (KNom s) Source # | |
| (Swappable a, HasOutputPositions a) => HasOutputPositions (Nom a) Source # | |
Defined in Language.Nominal.Examples.IdealisedEUTxO Methods outputPositions :: Nom a -> [Position] Source # | |
| SMonad [KAtom s] (KNom s) Source # | |
| Eq a => Eq (KNom s a) Source # | Fresh names are generated when name contexts are opened for equality test |
| Show a => Show (KNom s a) Source # | Show a nom by unpacking it |
| Generic (KNom s a) Source # | |
| (Typeable s, Swappable a, Arbitrary a) => Arbitrary (KNom s a) Source # | |
| (Typeable s, Swappable a) => Swappable (KNom s a) Source # | Swap goes under name-binders. swp n1 n2 (ns @> x) = (swp n1 n2 ns) @> (swp n1 n2 x) |
| (Typeable s, Swappable a) => Binder (KNom s a) [KAtom s] a s Source # | Acts on a |
| (Typeable s, Swappable a, KRestrict s a) => BinderConc (KNom s a) [KAtom s] a s () Source # | Suppose we have a nominal abstraction cnoc () = unNom |
| (Typeable s, Swappable a) => BinderConc (KNom s a) [KAtom s] a s [KAtom s] Source # | Concrete a nominal abstraction at a particular list of atoms. Dangerous for two reasons:
|
| (Typeable s, Swappable a) => BinderConc (KNom s a) [KAtom s] a s (Proxy s) Source # | Suppose we have a nominal abstraction cnoc (Proxy :: Proxy s) = exit |
| Alternative f => Alternative (KNom s :. f) Source # | Alternatives are composed in a capture-avoiding manner |
| type Rep (KNom s a) Source # | |
Defined in Language.Nominal.Nom | |
Creating a KNom
KNomkres :: (Typeable s, Swappable a) => proxy s -> [KAtom s] -> a -> KNom s a Source #
Constructor for (proxy version). KNom s
Destroying a KNom
KNomunNom :: KRestrict s a => KNom s a -> a Source #
Use this to safely exit a monad.
It works by binding the KNomKNom-bound s-atoms using a's native instance of KRestrict. See Language.Nominal.Examples.Tutorial for examples.
unNom = resAppC id
Note: The less versions of unNom are the exit and exitWith instances of KNom as an instance of SMonad. See also @@.
nomToIO :: KNom s a -> IO a Source #
Another way to safely exit KNom: convert it to an IO action (the IO may generate fresh names)
Creating fresh ids in a KNom
KNomfreshKAtom :: KNom s (KAtom s) Source #
Create a fresh atom-in-nominal-context
freshKAtoms :: Traversable m => m t -> KNom s (m (KAtom s)) Source #
Fresh of atoms (e.g. Traversable mm is list or stream)
freshAtoms :: Traversable m => m t -> Nom (m Atom) Source #
Fresh of atoms (e.g. Traversable mm is list or stream).
| Tom instance.
freshKName :: t -> KNom s (KName s t) Source #
Create a fresh name-in-a-nominal-context with label t
freshKNames :: Traversable m => m t -> KNom s (m (KName s t)) Source #
Create fresh names-in-a-nominal-context
freshNames :: Traversable m => m t -> Nom (m (Name t)) Source #
Canonical version of freshKNames for names.Tom
freshKNameIO :: t -> IO (KName s t) Source #
Create a fresh name-in-a-nominal-context with label t
freshNameIO :: t -> IO (Name t) Source #
Canonical version of freshKName for name.Tom
freshKNamesIO :: Traversable m => m t -> IO (m (KName s t)) Source #
Create fresh names-in-a-nominal-context
freshNamesIO :: Traversable m => m t -> IO (m (Name t)) Source #
Canonical version of freshKNames for names.Tom
KNom and other functors
There are three functions that will commute KNom with some other f:
Taken together, these functions are making a point that KNom is compatible with your favourite container type. Because KNom commutes, there is no need to wonder whether (for example) a graph-with-binding should be a graph with binding on the vertices, or on the edges, or on the graph overall, or any combination. All of these are valid design decisions and one may be more convenient than the other, but we know we can isomorphically commute to a single top-level KNom binding.
In that sense, KNom captures a general theory of binding.
This also mathematically justifies why the Binder typeclass is so useful.
transposeNomF :: (Functor f, Typeable s, Swappable a) => KNom s (f a) -> f (KNom s a) Source #
KNom commutes down through functors.
transposeNomF is a version of transposeMF where bindings are have added capture-avoidance (for inverse, see transposeFM).
Tests
Property-based tests are in Language.Nominal.Properties.NomSpec.
module Language.Nominal.SMonad