unbound-0.5.1.1: Generic support for programming with names and binders

LicenseBSD-like (see LICENSE)
MaintainerBrent Yorgey <byorgey@cis.upenn.edu>
Stabilityexperimental
PortabilityGHC only
Safe HaskellNone
LanguageHaskell2010

Unbound.LocallyNameless.Types

Contents

Description

Special type combinators for specifying binding structure.

Synopsis

Documentation

data GenBind order card p t Source #

Generic binding combinator for a pattern p within a term t. Flexible over the order and cardinality of the variables bound in the pattern

Constructors

B p t 
Instances
(Rep order, Rep card, Rep p, Rep t, Sat (ctx p), Sat (ctx t)) => Rep1 ctx (GenBind order card p t) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

rep1 :: R1 ctx (GenBind order card p t) #

(Rep order, Rep card, Alpha p, Alpha t, Subst b p, Subst b t) => Subst b (GenBind order card p t) Source # 
Instance details

Defined in Unbound.LocallyNameless.Subst

Methods

isvar :: GenBind order card p t -> Maybe (SubstName (GenBind order card p t) b) Source #

isCoerceVar :: GenBind order card p t -> Maybe (SubstCoerce (GenBind order card p t) b) Source #

subst :: Name b -> b -> GenBind order card p t -> GenBind order card p t Source #

substs :: [(Name b, b)] -> GenBind order card p t -> GenBind order card p t Source #

substPat :: AlphaCtx -> b -> GenBind order card p t -> GenBind order card p t Source #

substPats :: Proxy b -> AlphaCtx -> [Dyn] -> GenBind order card p t -> GenBind order card p t Source #

(Alpha a, Alpha b, Read a, Read b) => Read (Bind a b) # 
Instance details

Defined in Unbound.LocallyNameless.Ops

Methods

readsPrec :: Int -> ReadS (Bind a b) #

readList :: ReadS [Bind a b] #

readPrec :: ReadPrec (Bind a b) #

readListPrec :: ReadPrec [Bind a b] #

(Show a, Show b) => Show (GenBind order card a b) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

showsPrec :: Int -> GenBind order card a b -> ShowS #

show :: GenBind order card a b -> String #

showList :: [GenBind order card a b] -> ShowS #

(Rep order, Rep card, Rep p, Rep t) => Rep (GenBind order card p t) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

rep :: R (GenBind order card p t) #

(Binary p, Binary t) => Binary (GenBind order card p t) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

put :: GenBind order card p t -> Put #

get :: Get (GenBind order card p t) #

putList :: [GenBind order card p t] -> Put #

(Rep order, Rep card, Alpha p, Alpha t) => Alpha (GenBind order card p t) Source # 
Instance details

Defined in Unbound.LocallyNameless.Alpha

Methods

swaps' :: AlphaCtx -> Perm AnyName -> GenBind order card p t -> GenBind order card p t Source #

fv' :: Collection f => AlphaCtx -> GenBind order card p t -> f AnyName Source #

lfreshen' :: LFresh m => AlphaCtx -> GenBind order card p t -> (GenBind order card p t -> Perm AnyName -> m b) -> m b Source #

freshen' :: Fresh m => AlphaCtx -> GenBind order card p t -> m (GenBind order card p t, Perm AnyName) Source #

aeq' :: AlphaCtx -> GenBind order card p t -> GenBind order card p t -> Bool Source #

acompare' :: AlphaCtx -> GenBind order card p t -> GenBind order card p t -> Ordering Source #

close :: Alpha b => AlphaCtx -> b -> GenBind order card p t -> GenBind order card p t Source #

open :: Alpha b => AlphaCtx -> b -> GenBind order card p t -> GenBind order card p t Source #

isPat :: GenBind order card p t -> Maybe [AnyName] Source #

isTerm :: GenBind order card p t -> Bool Source #

isEmbed :: GenBind order card p t -> Bool Source #

nthpatrec :: GenBind order card p t -> NthCont Source #

findpatrec :: GenBind order card p t -> AnyName -> FindResult Source #

type Bind p t = GenBind StrictOrder StrictCard p t Source #

The most fundamental combinator for expressing binding structure is Bind. The term type Bind p t represents a pattern p paired with a term t, where names in p are bound within t.

Like Name, Bind is also abstract. You can create bindings using bind and take them apart with unbind and friends.

type SetBind p t = GenBind RelaxedOrder StrictCard p t Source #

A variant of Bind where alpha-equivalence allows multiple variables bound in the same pattern to be reordered

type SetPlusBind p t = GenBind RelaxedOrder RelaxedCard p t Source #

A variant of Bind where alpha-equivalence allows multiple variables bound in the same pattern to be reordered, and allows the binding of unused variables For example, { a b c } . a b aeq { b a } . a b

data Rebind p1 p2 Source #

Rebind allows for nested bindings. If p1 and p2 are pattern types, then Rebind p1 p2 is also a pattern type, similar to the pattern type (p1,p2) except that p1 scopes over p2. That is, names within terms embedded in p2 may refer to binders in p1.

Constructors

R p1 p2 
Instances
(Rep p1, Rep p2, Sat (ctx p1), Sat (ctx p2)) => Rep1 ctx (Rebind p1 p2) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

rep1 :: R1 ctx (Rebind p1 p2) #

(Alpha p, Alpha q, Subst b p, Subst b q) => Subst b (Rebind p q) Source # 
Instance details

Defined in Unbound.LocallyNameless.Subst

Methods

isvar :: Rebind p q -> Maybe (SubstName (Rebind p q) b) Source #

isCoerceVar :: Rebind p q -> Maybe (SubstCoerce (Rebind p q) b) Source #

subst :: Name b -> b -> Rebind p q -> Rebind p q Source #

substs :: [(Name b, b)] -> Rebind p q -> Rebind p q Source #

substPat :: AlphaCtx -> b -> Rebind p q -> Rebind p q Source #

substPats :: Proxy b -> AlphaCtx -> [Dyn] -> Rebind p q -> Rebind p q Source #

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

Compare for alpha-equality.

Instance details

Defined in Unbound.LocallyNameless.Ops

Methods

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

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

(Show a, Show b) => Show (Rebind a b) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

showsPrec :: Int -> Rebind a b -> ShowS #

show :: Rebind a b -> String #

showList :: [Rebind a b] -> ShowS #

(Rep p1, Rep p2) => Rep (Rebind p1 p2) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

rep :: R (Rebind p1 p2) #

(Binary p1, Binary p2) => Binary (Rebind p1 p2) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

put :: Rebind p1 p2 -> Put #

get :: Get (Rebind p1 p2) #

putList :: [Rebind p1 p2] -> Put #

(Alpha p, Alpha q) => Alpha (Rebind p q) Source # 
Instance details

Defined in Unbound.LocallyNameless.Alpha

Methods

swaps' :: AlphaCtx -> Perm AnyName -> Rebind p q -> Rebind p q Source #

fv' :: Collection f => AlphaCtx -> Rebind p q -> f AnyName Source #

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

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

aeq' :: AlphaCtx -> Rebind p q -> Rebind p q -> Bool Source #

acompare' :: AlphaCtx -> Rebind p q -> Rebind p q -> Ordering Source #

close :: Alpha b => AlphaCtx -> b -> Rebind p q -> Rebind p q Source #

open :: Alpha b => AlphaCtx -> b -> Rebind p q -> Rebind p q Source #

isPat :: Rebind p q -> Maybe [AnyName] Source #

isTerm :: Rebind p q -> Bool Source #

isEmbed :: Rebind p q -> Bool Source #

nthpatrec :: Rebind p q -> NthCont Source #

findpatrec :: Rebind p q -> AnyName -> FindResult Source #

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.

Constructors

Rec p 
Instances
(Rep p, Sat (ctx p)) => Rep1 ctx (Rec p) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

rep1 :: R1 ctx (Rec p) #

(Alpha p, Subst b p) => Subst b (Rec p) Source # 
Instance details

Defined in Unbound.LocallyNameless.Subst

Methods

isvar :: Rec p -> Maybe (SubstName (Rec p) b) Source #

isCoerceVar :: Rec p -> Maybe (SubstCoerce (Rec p) b) Source #

subst :: Name b -> b -> Rec p -> Rec p Source #

substs :: [(Name b, b)] -> Rec p -> Rec p Source #

substPat :: AlphaCtx -> b -> Rec p -> Rec p Source #

substPats :: Proxy b -> AlphaCtx -> [Dyn] -> Rec p -> Rec p Source #

Show a => Show (Rec a) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

showsPrec :: Int -> Rec a -> ShowS #

show :: Rec a -> String #

showList :: [Rec a] -> ShowS #

Rep p => Rep (Rec p) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

rep :: R (Rec p) #

Alpha p => Alpha (Rec p) Source # 
Instance details

Defined in Unbound.LocallyNameless.Alpha

Methods

swaps' :: AlphaCtx -> Perm AnyName -> Rec p -> Rec p Source #

fv' :: Collection f => AlphaCtx -> Rec p -> f AnyName Source #

lfreshen' :: LFresh m => AlphaCtx -> Rec p -> (Rec p -> Perm AnyName -> m b) -> m b Source #

freshen' :: Fresh m => AlphaCtx -> Rec p -> m (Rec p, Perm AnyName) Source #

aeq' :: AlphaCtx -> Rec p -> Rec p -> Bool Source #

acompare' :: AlphaCtx -> Rec p -> Rec p -> Ordering Source #

close :: Alpha b => AlphaCtx -> b -> Rec p -> Rec p Source #

open :: Alpha b => AlphaCtx -> b -> Rec p -> Rec p Source #

isPat :: Rec p -> Maybe [AnyName] Source #

isTerm :: Rec p -> Bool Source #

isEmbed :: Rec p -> Bool Source #

nthpatrec :: Rec p -> NthCont Source #

findpatrec :: Rec p -> AnyName -> FindResult Source #

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
Show a => Show (TRec a) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

showsPrec :: Int -> TRec a -> ShowS #

show :: TRec a -> String #

showList :: [TRec a] -> ShowS #

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
(Rep t, Sat (ctx t)) => Rep1 ctx (Embed t) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

rep1 :: R1 ctx (Embed t) #

(Alpha t, Subst b t) => Subst b (Embed t) Source # 
Instance details

Defined in Unbound.LocallyNameless.Subst

Methods

isvar :: Embed t -> Maybe (SubstName (Embed t) b) Source #

isCoerceVar :: Embed t -> Maybe (SubstCoerce (Embed t) b) Source #

subst :: Name b -> b -> Embed t -> Embed t Source #

substs :: [(Name b, b)] -> Embed t -> Embed t Source #

substPat :: AlphaCtx -> b -> Embed t -> Embed t Source #

substPats :: Proxy b -> AlphaCtx -> [Dyn] -> Embed t -> Embed t Source #

Eq t => Eq (Embed t) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

(==) :: Embed t -> Embed t -> Bool #

(/=) :: Embed t -> Embed t -> Bool #

Show a => Show (Embed a) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

showsPrec :: Int -> Embed a -> ShowS #

show :: Embed a -> String #

showList :: [Embed a] -> ShowS #

Rep t => Rep (Embed t) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

rep :: R (Embed t) #

Binary p => Binary (Embed p) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

put :: Embed p -> Put #

get :: Get (Embed p) #

putList :: [Embed p] -> Put #

IsEmbed (Embed t) Source # 
Instance details

Defined in Unbound.LocallyNameless.Alpha

Associated Types

type Embedded (Embed t) :: * Source #

Alpha t => Alpha (Embed t) Source # 
Instance details

Defined in Unbound.LocallyNameless.Alpha

type Embedded (Embed t) Source # 
Instance details

Defined in Unbound.LocallyNameless.Alpha

type Embedded (Embed t) = t

newtype Shift p Source #

Shift the scope of an embedded term one level outwards.

Constructors

Shift p 
Instances
(Rep p, Sat (ctx p)) => Rep1 ctx (Shift p) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

rep1 :: R1 ctx (Shift p) #

(Alpha a, Subst b a) => Subst b (Shift a) Source # 
Instance details

Defined in Unbound.LocallyNameless.Subst

Methods

isvar :: Shift a -> Maybe (SubstName (Shift a) b) Source #

isCoerceVar :: Shift a -> Maybe (SubstCoerce (Shift a) b) Source #

subst :: Name b -> b -> Shift a -> Shift a Source #

substs :: [(Name b, b)] -> Shift a -> Shift a Source #

substPat :: AlphaCtx -> b -> Shift a -> Shift a Source #

substPats :: Proxy b -> AlphaCtx -> [Dyn] -> Shift a -> Shift a Source #

Eq p => Eq (Shift p) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

(==) :: Shift p -> Shift p -> Bool #

(/=) :: Shift p -> Shift p -> Bool #

Show a => Show (Shift a) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

showsPrec :: Int -> Shift a -> ShowS #

show :: Shift a -> String #

showList :: [Shift a] -> ShowS #

Rep p => Rep (Shift p) Source # 
Instance details

Defined in Unbound.LocallyNameless.Types

Methods

rep :: R (Shift p) #

IsEmbed e => IsEmbed (Shift e) Source # 
Instance details

Defined in Unbound.LocallyNameless.Alpha

Associated Types

type Embedded (Shift e) :: * Source #

Alpha a => Alpha (Shift a) Source # 
Instance details

Defined in Unbound.LocallyNameless.Alpha

type Embedded (Shift e) Source # 
Instance details

Defined in Unbound.LocallyNameless.Alpha

type Embedded (Shift e) = Embedded e

Pay no attention to the man behind the curtain

These type representation objects are exported so they can be referenced by auto-generated code. Please pretend they do not exist.

rGenBind :: forall order card p t. (Rep order, Rep card, Rep p, Rep t) => R (GenBind order card p t) Source #

rRebind :: forall p1 p2. (Rep p1, Rep p2) => R (Rebind p1 p2) Source #

rEmbed :: forall t. Rep t => R (Embed t) Source #

rRec :: forall p. Rep p => R (Rec p) Source #

rShift :: forall p. Rep p => R (Shift p) Source #

Orphan instances

Rep a => Binary (Name a) Source # 
Instance details

Methods

put :: Name a -> Put #

get :: Get (Name a) #

putList :: [Name a] -> Put #