| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Zabt
Description
Abstract binding trees with a nameless internal representation.
- data Term v f
- pattern Var :: forall f v. (Freshen v, Foldable f, Ord v, Functor f) => v -> Term v f
- pattern Lam :: forall f v. (Freshen v, Foldable f, Ord v, Functor f) => v -> Term v f -> Term v f
- pattern Pat :: forall f v. (Freshen v, Foldable f, Ord v, Functor f) => f (Term v f) -> Term v f
- subst :: (Foldable f, Functor f, Ord v) => Map v (Term v f) -> Term v f -> Term v f
- subst1 :: (Foldable f, Ord v, Functor f) => (v, Term v f) -> Term v f -> Term v f
- freeVars :: Term v f -> Set v
- data View v f x
- fold :: (Functor f, Foldable f, Ord v) => View v f (Term v f) -> Term v f
- unfold :: (Functor f, Foldable f, Ord v, Freshen v) => Term v f -> View v f (Term v f)
- class Eq v => Freshen v where
Documentation
An abstract Term v f is an abstract binding tree of the shape described
by the pattern functor f augmented with variables named by v. Equality is
alpha-equivalence. In particular, Term v f is (morally) equivalent to the
fixed-point of the pattern-algebra View respecting the binding
properties of VLam and VVar.
pattern Var :: forall f v. (Freshen v, Foldable f, Ord v, Functor f) => v -> Term v f Source #
Var v creates and matches a Term value corresponding to a free
variable.
pattern Lam :: forall f v. (Freshen v, Foldable f, Ord v, Functor f) => v -> Term v f -> Term v f Source #
Lam v t creates and matches a Term value where the free variable v
has been abstracted over, becoming bound.
pattern Pat :: forall f v. (Freshen v, Foldable f, Ord v, Functor f) => f (Term v f) -> Term v f Source #
Pat f creates and matches a Term value built from a layer of the
pattern functor f.
subst :: (Foldable f, Functor f, Ord v) => Map v (Term v f) -> Term v f -> Term v f Source #
Substitute some free variables.
subst1 :: (Foldable f, Ord v, Functor f) => (v, Term v f) -> Term v f -> Term v f Source #
Substitute just one free variable.
freeVars :: Term v f -> Set v Source #
Returns the free variables used within a given Term.
NOTE: We have to define a new function in order to not accidentally break
encapsulation. Just exporting free direction would allow uses to manipulate
the Term value and break invariants (!).
A concrete view of the top "layer" of a Term ABT. This top layer may be
an abstraction, a raw variable, or a branch of the pattern functor f.
Normally View is wrapping a Term value, the abstract "remainder" of the
tree.
fold :: (Functor f, Foldable f, Ord v) => View v f (Term v f) -> Term v f Source #
Construct a Term from one layer of a View.
unfold :: (Functor f, Foldable f, Ord v, Freshen v) => Term v f -> View v f (Term v f) Source #
Strip the top layer of a View off of a Term.
class Eq v => Freshen v where Source #
A type which can be freshened has an operation which attempts to find a
unique version of its input. The principal thing that must hold is that
`freshen n /= n`. It's not necessary that `freshen n` be totally fresh with
respect to a context---that's too much to ask of a value---but it is
necessary that freshen *eventually* produces a fresh value.
Minimal complete definition