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

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

Unbound.Generics.LocallyNameless.Rebind

Description

The pattern Rebind p1 p2 binds the names in p1 and p2 just as (p1, p2) would, however it additionally also brings the names of p1 into scope in p2.

Synopsis

Documentation

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)
          | ...

Constructors

Rebnd p1 p2 

Instances

(Subst c p1, Subst c p2) => Subst c (Rebind p1 p2) Source # 

Methods

isvar :: Rebind p1 p2 -> Maybe (SubstName (Rebind p1 p2) c) Source #

isCoerceVar :: Rebind p1 p2 -> Maybe (SubstCoerce (Rebind p1 p2) c) Source #

subst :: Name c -> c -> Rebind p1 p2 -> Rebind p1 p2 Source #

substs :: [(Name c, c)] -> Rebind p1 p2 -> Rebind p1 p2 Source #

(Eq p2, Eq p1) => Eq (Rebind p1 p2) Source # 

Methods

(==) :: Rebind p1 p2 -> Rebind p1 p2 -> Bool #

(/=) :: Rebind p1 p2 -> Rebind p1 p2 -> Bool #

(Show p1, Show p2) => Show (Rebind p1 p2) Source # 

Methods

showsPrec :: Int -> Rebind p1 p2 -> ShowS #

show :: Rebind p1 p2 -> String #

showList :: [Rebind p1 p2] -> ShowS #

Generic (Rebind p1 p2) Source # 

Associated Types

type Rep (Rebind p1 p2) :: * -> * #

Methods

from :: Rebind p1 p2 -> Rep (Rebind p1 p2) x #

to :: Rep (Rebind p1 p2) x -> Rebind p1 p2 #

(NFData p1, NFData p2) => NFData (Rebind p1 p2) Source # 

Methods

rnf :: Rebind p1 p2 -> () #

(Alpha p1, Alpha p2) => Alpha (Rebind p1 p2) Source # 

Methods

aeq' :: AlphaCtx -> Rebind p1 p2 -> Rebind p1 p2 -> Bool Source #

fvAny' :: (Contravariant f, Applicative f) => AlphaCtx -> (AnyName -> f AnyName) -> Rebind p1 p2 -> f (Rebind p1 p2) Source #

close :: AlphaCtx -> NamePatFind -> Rebind p1 p2 -> Rebind p1 p2 Source #

open :: AlphaCtx -> NthPatFind -> Rebind p1 p2 -> Rebind p1 p2 Source #

isPat :: Rebind p1 p2 -> DisjointSet AnyName Source #

isTerm :: Rebind p1 p2 -> All Source #

isEmbed :: Rebind p1 p2 -> Bool Source #

nthPatFind :: Rebind p1 p2 -> NthPatFind Source #

namePatFind :: Rebind p1 p2 -> NamePatFind Source #

swaps' :: AlphaCtx -> Perm AnyName -> Rebind p1 p2 -> Rebind p1 p2 Source #

lfreshen' :: LFresh m => AlphaCtx -> Rebind p1 p2 -> (Rebind p1 p2 -> Perm AnyName -> m b) -> m b Source #

freshen' :: Fresh m => AlphaCtx -> Rebind p1 p2 -> m (Rebind p1 p2, Perm AnyName) Source #

acompare' :: AlphaCtx -> Rebind p1 p2 -> Rebind p1 p2 -> Ordering Source #

type Rep (Rebind p1 p2) Source # 
type Rep (Rebind p1 p2) = D1 * (MetaData "Rebind" "Unbound.Generics.LocallyNameless.Rebind" "unbound-generics-0.3.3-Bd10VW6EVFQ8rThToStmHN" False) (C1 * (MetaCons "Rebnd" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * p1)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * p2))))