unbound-generics-0.2: Support for programming with names and binders using GHC Generics

Copyright(c) 2014, Aleksey Kliger
LicenseBSD3 (See LICENSE)
MaintainerAleksey Kliger
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Unbound.Generics.LocallyNameless.Operations

Contents

Description

Operations on terms and patterns that contain names.

Synopsis

Equivalence, free variables, freshness

aeq :: Alpha a => a -> a -> Bool Source

aeq t1 t2 returns True iff t1 and t2 are alpha-equivalent terms.

acompare :: Alpha a => a -> a -> Ordering Source

An alpha-respecting total order on terms involving binders.

fvAny :: (Alpha a, Contravariant f, Applicative f) => (AnyName -> f AnyName) -> a -> f a Source

fvAny returns a fold over any names in a term a.

  fvAny :: Alpha a => Fold a AnyName

fv :: forall a f b. (Alpha a, Typeable b, Contravariant f, Applicative f) => (Name b -> f (Name b)) -> a -> f a Source

fv returns the free b variables of term a.

 fv :: (Alpha a, Typeable b) => Fold a (Name b)

freshen :: (Alpha p, Fresh m) => p -> m (p, Perm AnyName) Source

Freshen a pattern by replacing all old binding Names with new fresh Names, returning a new pattern and a Perm Name specifying how Names were replaced.

lfreshen :: (Alpha p, LFresh m) => p -> (p -> Perm AnyName -> m b) -> m b Source

"Locally" freshen a pattern, replacing all binding names with new names that are not already "in scope". The second argument is a continuation, which takes the renamed term and a permutation that specifies how the pattern has been renamed. The resulting computation will be run with the in-scope set extended by the names just generated.

swaps :: Alpha t => Perm AnyName -> t -> t Source

Apply the given permutation of variable names to the given term.

Binding, unbinding

data Bind p t Source

A term of type Bind p t is a term that binds the free variable occurrences of the variables in pattern p in the term t. In the overall term, those variables are now bound. See also bind and unbind and lunbind

Instances

(Subst c b, Subst c a, Alpha a, Alpha b) => Subst c (Bind a b) 
(Show p, Show t) => Show (Bind p t) 
Generic (Bind p t) 
(NFData p, NFData t) => NFData (Bind p t) 
(Alpha p, Alpha t) => Alpha (Bind p t) 
type Rep (Bind p t) 

bind :: (Alpha p, Alpha t) => p -> t -> Bind p t Source

bind p t closes over the variables of pattern p in the term t

unbind :: (Alpha p, Alpha t, Fresh m) => Bind p t -> m (p, t) Source

unbind b lets you descend beneath a binder b :: Bind p t by returning the pair of the pattern p and the term t where the variables in the pattern have been made globally fresh with respect to the freshness monad m.

lunbind :: (LFresh m, Alpha p, Alpha t) => Bind p t -> ((p, t) -> m c) -> m c Source

lunbind opens a binding in an LFresh monad, ensuring that the names chosen for the binders are locally fresh. The components of the binding are passed to a continuation, and the resulting monadic action is run in a context extended to avoid choosing new names which are the same as the ones chosen for this binding.

For more information, see the documentation for the LFresh type class.

unbind2 :: (Fresh m, Alpha p1, Alpha p2, Alpha t1, Alpha t2) => Bind p1 t1 -> Bind p2 t2 -> m (Maybe (p1, t1, p2, t2)) Source

Simultaneously unbind two patterns in two terms, returning Nothing if the two patterns don't bind the same number of variables.

lunbind2 :: (LFresh m, Alpha p1, Alpha p2, Alpha t1, Alpha t2) => Bind p1 t1 -> Bind p2 t2 -> (Maybe (p1, t1, p2, t2) -> m c) -> m c Source

Simultaneously lunbind two patterns in two terms in the LFresh monad, passing Just (p1, t1, p2, t2) to the continuation such that the patterns are permuted such that they introduce the same free names, or Nothing if the number of variables differs.

unbind2Plus :: (MonadPlus m, Fresh m, Alpha p1, Alpha p2, Alpha t1, Alpha t2) => Bind p1 t1 -> Bind p2 t2 -> m (p1, t1, p2, t2) Source

Simultaneously unbind two patterns in two terms, returning mzero if the patterns don't bind the same number of variables.

Rebinding, embedding

data Rebind p1 p2 Source

Rebind p1 p2 is a pattern that binds the names of p1 and p2, and additionally brings the names of p1 into scope over p2.

This may be used, for example, to faithfully represent Scheme's let* binding form, defined by:

 (let* () body) ≙ body
 (let* ([v1, e1] binds ...) body) ≙ (let ([v1, e1]) (let* (binds ...) body))

using the following AST:

type Var = Name Expr
data Lets = EmptyLs
          | ConsLs (Rebind (Var, Embed Expr) Lets)
data Expr = ...
          | LetStar (Bind Lets Expr)
          | ...

Instances

(Subst c p1, Subst c p2) => Subst c (Rebind p1 p2) 
(Eq p1, Eq p2) => Eq (Rebind p1 p2) 
(Show p1, Show p2) => Show (Rebind p1 p2) 
Generic (Rebind p1 p2) 
(NFData p1, NFData p2) => NFData (Rebind p1 p2) 
(Alpha p1, Alpha p2) => Alpha (Rebind p1 p2) 
type Rep (Rebind p1 p2) 

rebind :: (Alpha p1, Alpha p2) => p1 -> p2 -> Rebind p1 p2 Source

rebind p1 p2 is a smart constructor for Rebind. It captures the variables of pattern p1 that occur within p2 in addition to providing binding occurrences for all the variables of p1 and p2

unrebind :: (Alpha p1, Alpha p2) => Rebind p1 p2 -> (p1, p2) Source

unrebind p is the elimination form for Rebind. It is not monadic (unlike unbind) because a Rebind pattern can only occur somewhere in a pattern position of a Bind, and therefore unbind must have already been called and all names apropriately freshened.

newtype Embed t Source

Embed allows for terms to be embedded within patterns. Such embedded terms do not bind names along with the rest of the pattern. For examples, see the tutorial or examples directories.

If t is a term type, then Embed t is a pattern type.

Embed is not abstract since it involves no binding, and hence it is safe to manipulate directly. To create and destruct Embed terms, you may use the Embed constructor directly. (You may also use the functions embed and unembed, which additionally can construct or destruct any number of enclosing Shifts at the same time.)

Constructors

Embed t 

Instances

Subst c a => Subst c (Embed a) 
Eq t => Eq (Embed t) 
Ord t => Ord (Embed t) 
Show a => Show (Embed a) 
Generic (Embed t) 
NFData t => NFData (Embed t) 
Alpha t => Alpha (Embed t) 
IsEmbed (Embed t) 
type Rep (Embed t) 
type Embedded (Embed t) = t 

class IsEmbed e where Source

Associated Types

type Embedded e :: * Source

The term type embedded in the embedding e

Methods

embedded :: (Profunctor p, Functor f) => p (Embedded e) (f (Embedded e)) -> p e (f e) Source

Insert or extract the embedded term. If you're not using the lens library, see embed and unembed otherwise embedded is an isomorphism that you can use with lens. embedded :: Iso' (Embedded e) e

Instances

embed :: IsEmbed e => Embedded e -> e Source

Embeds a term in an Embed, or an Embed under some number of Shift constructors.

unembed :: IsEmbed e => e -> Embedded e Source

unembed p extracts the term embedded in the pattern p.

Recursive bindings

data Rec p Source

If p is a pattern type, then Rec p is also a pattern type, which is recursive in the sense that p may bind names in terms embedded within itself. Useful for encoding e.g. lectrec and Agda's dot notation.

Instances

Subst c p => Subst c (Rec p) 
Eq p => Eq (Rec p) 
Show a => Show (Rec a) 
Generic (Rec p) 
NFData p => NFData (Rec p) 
Alpha p => Alpha (Rec p) 
type Rep (Rec p) 

rec :: Alpha p => p -> Rec p Source

Constructor for recursive patterns.

unrec :: Alpha p => Rec p -> p Source

Destructor for recursive patterns.

newtype TRec p Source

TRec is a standalone variant of Rec: the only difference is that whereas Rec p is a pattern type, TRec p is a term type. It is isomorphic to Bind (Rec p) ().

Note that TRec corresponds to Pottier's abstraction construct from alpha-Caml. In this context, Embed t corresponds to alpha-Caml's inner t, and Shift (Embed t) corresponds to alpha-Caml's outer t.

Constructors

TRec (Bind (Rec p) ()) 

Instances

(Alpha p, Subst c p) => Subst c (TRec p) 
Show a => Show (TRec a) 
Generic (TRec p) 
Alpha p => Alpha (TRec p) 
type Rep (TRec p) 

trec :: Alpha p => p -> TRec p Source

Constructor for recursive abstractions.

untrec :: (Alpha p, Fresh m) => TRec p -> m p Source

Destructor for recursive abstractions which picks globally fresh names for the binders.

luntrec :: (Alpha p, LFresh m) => TRec p -> m p Source

Destructor for recursive abstractions which picks locally fresh names for binders (see LFresh).