bound-1.0.5: Making de Bruijn Succ Less

Copyright(C) 2013 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell98

Bound.Scope.Simple

Contents

Description

Scope provides a single traditional de Bruijn level and is often used inside of the definition of binders.

Synopsis

Documentation

newtype Scope b f a Source

Scope b f a is an f expression with bound variables in b, and free variables in a

This implements traditional de Bruijn indices, while Scope implements generalized de Bruijn indices.

These traditional indices can be used to test the performance gain of generalized indices.

While this type Scope is identical to EitherT this module focuses on a drop-in replacement for Scope.

Another use case is for syntaxes not stable under substitution, therefore with only a Functor instance and no Monad instance.

Constructors

Scope 

Fields

unscope :: f (Var b a)
 

Instances

MonadTrans (Scope b) 
Bound (Scope b) 
Monad f => Monad (Scope b f)

The monad permits substitution on free variables, while preserving bound variables

Functor f => Functor (Scope b f) 
(Functor f, Monad f) => Applicative (Scope b f) 
Foldable f => Foldable (Scope b f)

toList is provides a list (with duplicates) of the free variables

Traversable f => Traversable (Scope b f) 
(Serial b, Serial1 f) => Serial1 (Scope b f) 
(Hashable b, Monad f, Hashable1 f) => Hashable1 (Scope b f) 
(Functor f, Eq b, Eq1 f) => Eq1 (Scope b f) 
(Functor f, Ord b, Ord1 f) => Ord1 (Scope b f) 
(Functor f, Show b, Show1 f) => Show1 (Scope b f) 
(Functor f, Read b, Read1 f) => Read1 (Scope b f) 
Typeable (* -> (* -> *) -> * -> *) Scope 
(Functor f, Eq b, Eq1 f, Eq a) => Eq (Scope b f a) 
(Typeable * b, Typeable (* -> *) f, Data a, Data (f (Var b a))) => Data (Scope b f a) 
(Functor f, Ord b, Ord1 f, Ord a) => Ord (Scope b f a) 
(Functor f, Read b, Read1 f, Read a) => Read (Scope b f a) 
(Functor f, Show b, Show1 f, Show a) => Show (Scope b f a) 
(Binary b, Serial1 f, Binary a) => Binary (Scope b f a) 
(Serial b, Serial1 f, Serial a) => Serial (Scope b f a) 
(Serialize b, Serial1 f, Serialize a) => Serialize (Scope b f a) 
(Hashable b, Monad f, Hashable1 f, Hashable a) => Hashable (Scope b f a) 

Abstraction

abstract :: Functor f => (a -> Maybe b) -> f a -> Scope b f a Source

Capture some free variables in an expression to yield a Scope with bound variables in b

>>> :m + Data.List
>>> abstract (`elemIndex` "bar") "barry"
Scope [B 0,B 1,B 2,B 2,F 'y']

abstract1 :: (Functor f, Eq a) => a -> f a -> Scope () f a Source

Abstract over a single variable

>>> abstract1 'x' "xyz"
Scope [B (),F 'y',F 'z']

Instantiation

instantiate :: Monad f => (b -> f a) -> Scope b f a -> f a Source

Enter a scope, instantiating all bound variables

>>> :m + Data.List
>>> instantiate (\x -> [toEnum (97 + x)]) $ abstract (`elemIndex` "bar") "barry"
"abccy"

instantiate1 :: Monad f => f a -> Scope n f a -> f a Source

Enter a Scope that binds one variable, instantiating it

>>> instantiate1 "x" $ Scope [B (),F 'y',F 'z']
"xyz"

Alternative names for 'unscope'/'Scope'

fromScope :: Scope b f a -> f (Var b a) Source

fromScope is just another name for unscope and is exported to mimick fromScope. In particular no Monad constraint is required.

toScope :: f (Var b a) -> Scope b f a Source

toScope is just another name for Scope and is exported to mimick toScope. In particular no Monad constraint is required.

Bound variable manipulation

splat :: Monad f => (a -> f c) -> (b -> f c) -> Scope b f a -> f c Source

Perform substitution on both bound and free variables in a Scope.

bindings :: Foldable f => Scope b f a -> [b] Source

Return a list of occurences of the variables bound by this Scope.

mapBound :: Functor f => (b -> b') -> Scope b f a -> Scope b' f a Source

Perform a change of variables on bound variables.

mapScope :: Functor f => (b -> d) -> (a -> c) -> Scope b f a -> Scope d f c Source

Perform a change of variables, reassigning both bound and free variables.

liftMBound :: Monad m => (b -> b') -> Scope b m a -> Scope b' m a Source

Perform a change of variables on bound variables given only a Monad instance

liftMScope :: Monad m => (b -> d) -> (a -> c) -> Scope b m a -> Scope d m c Source

A version of mapScope that can be used when you only have the Monad instance

foldMapBound :: (Foldable f, Monoid r) => (b -> r) -> Scope b f a -> r Source

Obtain a result by collecting information from both bound and free variables

foldMapScope :: (Foldable f, Monoid r) => (b -> r) -> (a -> r) -> Scope b f a -> r Source

Obtain a result by collecting information from both bound and free variables

traverseBound_ :: (Applicative g, Foldable f) => (b -> g d) -> Scope b f a -> g () Source

traverse_ the bound variables in a Scope.

traverseScope_ :: (Applicative g, Foldable f) => (b -> g d) -> (a -> g c) -> Scope b f a -> g () Source

traverse both the variables bound by this scope and any free variables.

mapMBound_ :: (Monad g, Foldable f) => (b -> g d) -> Scope b f a -> g () Source

mapM_ over the variables bound by this scope

mapMScope_ :: (Monad m, Foldable f) => (b -> m d) -> (a -> m c) -> Scope b f a -> m () Source

A traverseScope_ that can be used when you only have a Monad instance

traverseBound :: (Applicative g, Traversable f) => (b -> g c) -> Scope b f a -> g (Scope c f a) Source

Traverse both bound and free variables

traverseScope :: (Applicative g, Traversable f) => (b -> g d) -> (a -> g c) -> Scope b f a -> g (Scope d f c) Source

Traverse both bound and free variables

mapMBound :: (Monad m, Traversable f) => (b -> m c) -> Scope b f a -> m (Scope c f a) Source

mapM over both bound and free variables

mapMScope :: (Monad m, Traversable f) => (b -> m d) -> (a -> m c) -> Scope b f a -> m (Scope d f c) Source

A traverseScope that can be used when you only have a Monad instance

serializeScope :: (Serial1 f, MonadPut m) => (b -> m ()) -> (v -> m ()) -> Scope b f v -> m () Source

deserializeScope :: (Serial1 f, MonadGet m) => m b -> m v -> m (Scope b f v) Source

hoistScope :: (f (Var b a) -> g (Var b a)) -> Scope b f a -> Scope b g a Source

bitraverseScope :: (Bitraversable t, Applicative f) => (k -> f k') -> (a -> f a') -> Scope b (t k) a -> f (Scope b (t k') a') Source

This allows you to bitraverse a Scope.

bitransverseScope :: Applicative f => (forall a a'. (a -> f a') -> t a -> f (u a')) -> forall a a'. (a -> f a') -> Scope b t a -> f (Scope b u a') Source

transverseScope :: Functor f => (forall r. g r -> f (h r)) -> Scope b g a -> f (Scope b h a) Source

This is a higher-order analogue of traverse.

instantiateVars :: Monad t => [a] -> Scope Int t a -> t a Source

instantiate bound variables using a list of new variables