Safe Haskell | None |
---|---|
Language | Haskell2010 |
Abstract binding trees with a nameless internal representation.
- data Term v f a
- type Flat v f = Term v f G
- pattern Var :: forall f v a. (Visits f, Freshen v, Ord v) => (~#) Arity Arity a G => v -> Term v f a
- pattern Abs :: forall f v a. (Visits f, Freshen v, Ord v) => forall a1. (~#) Arity Arity a (B a1) => v -> Term v f a1 -> Term v f a
- pattern Pat :: forall f v a. (Visits f, Freshen v, Ord v) => (~#) Arity Arity a G => f (Term v f) -> Term v f a
- data Arity
- type B a = B a
- type G = G
- type A0 = G
- type A1 = B G
- type A2 = B A1
- type A3 = B A2
- type family DownTo (c :: * -> Constraint) (x :: Arity -> *) (a :: Arity) :: Constraint where ...
- class Visits t where
- subst :: forall v f a. (Visits f, Ord v) => (v -> Maybe (Flat v f)) -> Term v f a -> Term v f a
- substMap :: forall v f a. (Visits f, Ord v) => Map v (Flat v f) -> Term v f a -> Term v f a
- subst1 :: forall v f a. (Visits f, Ord v) => (v, Flat v f) -> Term v f a -> Term v f a
- freeVars :: Term v f a -> Set v
- class Eq v => Freshen v where
- data View v f x a where
- fold :: (Visits f, Ord v) => View v f (Term v f) a -> Term v f a
- unfold :: (Visits f, Ord v, Freshen v) => Term v f a -> View v f (Term v f) a
Abstract binding tree terms
Abstract binding trees take the form
, or, more commonly, Term
v f a
. These
types are abstract—you will never construct or analyze them directly.Flat
v f
An abstract
is an abstract binding tree of the shape described
by the pattern functor Term
v ff
augmented with variables named by v
. Equality is
alpha-equivalence. In particular,
is (morally) equivalent to the
fixed-point of the pattern-algebra Term
v fView
respecting the binding
properties of 'Zabt.View.VAbs and VVar
.
(Eq v, Eq (f (Term v f)), Eq (Term v f a)) => Eq (Term v f (B a)) Source # | |
(Eq v, Eq (f (Term v f))) => Eq (Term v f G) Source # | |
(Ord v, Ord (f (Term v f)), Ord (Term v f a)) => Ord (Term v f (B a)) Source # | |
(Ord v, Ord (f (Term v f))) => Ord (Term v f G) Source # | |
(Show v, Show (Nameless v f (Term v f) a)) => Show (Term v f a) Source # | |
Constructing terms with View
patterns
To construct or analyze a Term
, the Var
, Abs
, and Pat
pattern synonyms are useful.
These synonyms let you essentially treat Term
as if it weren't abstract and both construct
new terms and case
analyze them.
pattern Var :: forall f v a. (Visits f, Freshen v, Ord v) => (~#) Arity Arity a G => v -> Term v f a Source #
pattern Abs :: forall f v a. (Visits f, Freshen v, Ord v) => forall a1. (~#) Arity Arity a (B a1) => v -> Term v f a1 -> Term v f a Source #
pattern Pat :: forall f v a. (Visits f, Freshen v, Ord v) => (~#) Arity Arity a G => f (Term v f) -> Term v f a Source #
Basic arities
When defining a pattern functor for Term
s you have to declare the arities of each
recursive use.
type family DownTo (c :: * -> Constraint) (x :: Arity -> *) (a :: Arity) :: Constraint where ... Source #
The DownTo
type family makes it easier to declare type constraints over
families of arities.
A type f :: Arity -> *
instantiating
essentially is
Visits
fTraversable
, but we define a new typeclass to handle the difference in
types.
Working with free variables
Abstract binding trees take the form
, or, more commonly, Term
v f a
. These
types are abstract---you will never construct or analyze them directly.Flat
v f
subst :: forall v f a. (Visits f, Ord v) => (v -> Maybe (Flat v f)) -> Term v f a -> Term v f a Source #
Substitute some free variables.
substMap :: forall v f a. (Visits f, Ord v) => Map v (Flat v f) -> Term v f a -> Term v f a Source #
Substitute some free variables from a finite map.
subst1 :: forall v f a. (Visits f, Ord v) => (v, Flat v f) -> Term v f a -> Term v f a Source #
Substitute just one free variable.
freeVars :: Term v f a -> 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 (!).
Freshen class
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.
Variable identifier types must be instances of Freshen.
View
in detail
data View v f x a where Source #
(Eq (x a), Eq (f x)) => Eq (View v f x (B a)) Source # | Alpha-equivalence |
(Eq v, Eq (f x)) => Eq (View v f x G) Source # | Alpha-equivalence |
(Ord v, Ord (x a), Ord (f x)) => Ord (View v f x (B a)) Source # | |
(Ord v, Ord (f x)) => Ord (View v f x G) Source # | |
(Show v, Show (x a), Show (f x)) => Show (View v f x (B a)) Source # | |
(Show v, Show (x G), Show (f x)) => Show (View v f x G) Source # | |