| Portability | non-portable (GHC Extensions) | 
|---|---|
| Stability | experimental | 
| Maintainer | Patrick Bahr <paba@diku.dk> | 
| Safe Haskell | None | 
Data.Comp.Multi.Variables
Description
This module defines an abstract notion of (bound) variables in compositional data types, and scoped substitution. Capture-avoidance is not taken into account. All definitions are generalised versions of those in Data.Comp.Variables.
- class HasVars f v where
- type GSubst v a = Map v (A a)
- type CxtSubst h a f v = GSubst v (Cxt h f a)
- type Subst f v = CxtSubst NoHole (K ()) f v
- varsToHoles :: forall f v. (HTraversable f, HasVars f v, Ord v) => Term f :-> Context f (K v)
- containsVar :: (Ord v, HasVars f v, HTraversable f, HFunctor f) => v -> Cxt h f a :=> Bool
- variables :: (Ord v, HasVars f v, HTraversable f, HFunctor f) => Cxt h f a :=> Set v
- variableList :: (HasVars f v, HTraversable f, HFunctor f, Ord v) => Cxt h f a :=> [v]
- variables' :: (Ord v, HasVars f v, HFoldable f, HFunctor f) => Const f :=> Set v
- appSubst :: (Ord v, SubstVars v t a) => GSubst v t -> a :-> a
- compSubst :: (Ord v, HasVars f v, HTraversable f) => CxtSubst h a f v -> CxtSubst h a f v -> CxtSubst h a f v
Documentation
This multiparameter class defines functors with variables. An instance
  HasVar f v denotes that values over f might contain and bind variables of
  type v. 
Methods
isVar :: f a :=> Maybe vSource
Indicates whether the f constructor is a variable. The
 default implementation returns Nothing.
bindsVars :: KOrd a => f a :=> Map (E a) (Set v)Source
Indicates the set of variables bound by the f constructor
 for each argument of the constructor. For example for a
 non-recursive let binding:
 
 data Let i e = Let Var (e i) (e i)
 instance HasVars Let Var where
   bindsVars (Let v x y) = Map.fromList [(y, (Set.singleton v))]
 
 If, instead, the let binding is recursive, the methods has to
 be implemented like this:
 
   bindsVars (Let v x y) = Map.fromList [(x, (Set.singleton v)),
                                         (y, (Set.singleton v))]
 
 This indicates that the scope of the bound variable also
 extends to the right-hand side of the variable binding.
The default implementation returns the empty map.
varsToHoles :: forall f v. (HTraversable f, HasVars f v, Ord v) => Term f :-> Context f (K v)Source
containsVar :: (Ord v, HasVars f v, HTraversable f, HFunctor f) => v -> Cxt h f a :=> BoolSource
This function checks whether a variable is contained in a context.
variables :: (Ord v, HasVars f v, HTraversable f, HFunctor f) => Cxt h f a :=> Set vSource
This function computes the set of variables occurring in a context.
variableList :: (HasVars f v, HTraversable f, HFunctor f, Ord v) => Cxt h f a :=> [v]Source
This function computes the list of variables occurring in a context.