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

LicenseBSD-like (see LICENSE)
MaintainerStephanie Weirich <sweirich@cis.upenn.edu>
PortabilityGHC only
Safe HaskellNone
LanguageHaskell2010

Unbound.LocallyNameless.Name

Contents

Description

An implementation of names in a locally nameless representation.

Synopsis

Name types

data Name a Source #

Names are things that get bound. This type is intentionally abstract; to create a Name you can use string2Name or integer2Name. The type parameter is a tag, or sort, which tells us what sorts of things this name may stand for. The sort must be a representable type, i.e. an instance of the Rep type class from the RepLib generic programming framework.

To hide the sort of a name, use AnyName.

Constructors

Nm (R a) (String, Integer) 
Bn (R a) Integer Integer 
Instances
(Rep a, Sat (ctx (R a)), Sat (ctx (String, Integer)), Sat (ctx Integer)) => Rep1 ctx (Name a) Source # 
Instance details

Defined in Unbound.LocallyNameless.Name

Methods

rep1 :: R1 ctx (Name a) #

Rep a => Subst b (Name a) Source # 
Instance details

Defined in Unbound.LocallyNameless.Subst

Methods

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

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

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

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

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

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

Eq (Name a) Source # 
Instance details

Defined in Unbound.LocallyNameless.Name

Methods

(==) :: Name a -> Name a -> Bool #

(/=) :: Name a -> Name a -> Bool #

Ord (Name a) Source # 
Instance details

Defined in Unbound.LocallyNameless.Name

Methods

compare :: Name a -> Name a -> Ordering #

(<) :: Name a -> Name a -> Bool #

(<=) :: Name a -> Name a -> Bool #

(>) :: Name a -> Name a -> Bool #

(>=) :: Name a -> Name a -> Bool #

max :: Name a -> Name a -> Name a #

min :: Name a -> Name a -> Name a #

Show (Name a) Source # 
Instance details

Defined in Unbound.LocallyNameless.Name

Methods

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

show :: Name a -> String #

showList :: [Name a] -> ShowS #

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

Defined in Unbound.LocallyNameless.Name

Methods

rep :: R (Name a) #

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

Defined in Unbound.LocallyNameless.Types

Methods

put :: Name a -> Put #

get :: Get (Name a) #

putList :: [Name a] -> Put #

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

Defined in Unbound.LocallyNameless.Alpha

Methods

swaps' :: AlphaCtx -> Perm AnyName -> Name a -> Name a Source #

fv' :: Collection f => AlphaCtx -> Name a -> f AnyName Source #

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

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

aeq' :: AlphaCtx -> Name a -> Name a -> Bool Source #

acompare' :: AlphaCtx -> Name a -> Name a -> Ordering Source #

close :: Alpha b => AlphaCtx -> b -> Name a -> Name a Source #

open :: Alpha b => AlphaCtx -> b -> Name a -> Name a Source #

isPat :: Name a -> Maybe [AnyName] Source #

isTerm :: Name a -> Bool Source #

isEmbed :: Name a -> Bool Source #

nthpatrec :: Name a -> NthCont Source #

findpatrec :: Name a -> AnyName -> FindResult Source #

data AnyName Source #

A name with a hidden (existentially quantified) sort. To hide the sort of a name, use the AnyName constructor directly; to extract a name with a hidden sort, use toSortedName.

Constructors

Rep a => AnyName (Name a) 
Instances
Eq AnyName Source # 
Instance details

Defined in Unbound.LocallyNameless.Name

Methods

(==) :: AnyName -> AnyName -> Bool #

(/=) :: AnyName -> AnyName -> Bool #

Ord AnyName Source # 
Instance details

Defined in Unbound.LocallyNameless.Name

Show AnyName Source # 
Instance details

Defined in Unbound.LocallyNameless.Name

Rep AnyName Source # 
Instance details

Defined in Unbound.LocallyNameless.Name

Methods

rep :: R AnyName #

Alpha AnyName Source # 
Instance details

Defined in Unbound.LocallyNameless.Alpha

Rep1 ctx AnyName Source # 
Instance details

Defined in Unbound.LocallyNameless.Name

Methods

rep1 :: R1 ctx AnyName #

Subst b AnyName Source # 
Instance details

Defined in Unbound.LocallyNameless.Subst

Constructing and destructing free names

integer2Name :: Rep a => Integer -> Name a Source #

Create a free Name from an Integer.

string2Name :: Rep a => String -> Name a Source #

Create a free Name from a String.

s2n :: Rep a => String -> Name a Source #

Convenient synonym for string2Name.

makeName :: Rep a => String -> Integer -> Name a Source #

Create a free Name from a String and an Integer index.

name2Integer :: Name a -> Integer Source #

Get the integer index of a Name.

name2String :: Name a -> String Source #

Get the string part of a Name.

anyName2Integer :: AnyName -> Integer Source #

Get the integer index of an AnyName.

anyName2String :: AnyName -> String Source #

Get the string part of an AnyName.

Sorts

toSortedName :: Rep a => AnyName -> Maybe (Name a) Source #

Cast a name with an existentially hidden sort to an explicitly sorted name.

translate :: Rep b => Name a -> Name b Source #

Change the sort of a name.

getR :: Name a -> R a Source #

Determine the sort of a Name.

Utility

isBound :: Name a -> Bool Source #

Test whether a name is a bound variable (i.e. a reference to some binding site, represented as a de Bruijn index). Normal users of the library should not need this function, as it is impossible to encounter a bound name when using the abstract interface provided by Unbound.LocallyNameless.

isFree :: Name a -> Bool Source #

Test whether a name is a free variable. Normal users of the library should not need this function, as all the names encountered will be free variables when using the abstract interface provided by Unbound.LocallyNameless.

Representations

Automatically generated representation objects.

rR :: forall a. Rep a => R (R a) Source #

rR1 :: forall ctx a. Rep a => R1 ctx (R a) Source #

rName :: forall a. Rep a => R (Name a) Source #

rName1 :: forall ctx a. Rep a => (ctx (R a), ctx (String, Integer)) -> (ctx (R a), ctx Integer, ctx Integer) -> R1 ctx (Name a) Source #

rAnyName1 :: forall ctx. R1 ctx AnyName Source #

Orphan instances

Rep a => Rep1 ctx (R a) Source # 
Instance details

Methods

rep1 :: R1 ctx (R a) #

Rep a => Rep (R a) Source # 
Instance details

Methods

rep :: R (R a) #