Copyright | (C) 2012 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell98 |
The problem with locally nameless approaches is that original names are
often useful for error reporting, or to allow for the user in an interactive
theorem prover to convey some hint about the domain. A
is a value
Name
n bb
supplemented with a (discardable) name that may be useful for error
reporting purposes. In particular, this name does not participate in
comparisons for equality.
This module is not exported from Bound by default. You need to explicitly
import it, due to the fact that Name
is a pretty common term in other
people's code.
Synopsis
- data Name n b = Name n b
- _Name :: (Profunctor p, Functor f) => p (n, a) (f (m, b)) -> p (Name n a) (f (Name m b))
- name :: Name n b -> n
- abstractName :: Monad f => (a -> Maybe b) -> f a -> Scope (Name a b) f a
- abstract1Name :: (Monad f, Eq a) => a -> f a -> Scope (Name a ()) f a
- abstractEitherName :: Monad f => (a -> Either b c) -> f a -> Scope (Name a b) f c
- instantiateName :: (Monad f, Comonad n) => (b -> f a) -> Scope (n b) f a -> f a
- instantiate1Name :: Monad f => f a -> Scope n f a -> f a
- instantiateEitherName :: (Monad f, Comonad n) => (Either b a -> f c) -> Scope (n b) f a -> f c
Documentation
We track the choice of Name
n
as a forgettable property that does not affect
the result of (==
) or compare
.
To compare names rather than values, use (
instead.on
compare
name
)
Name n b |
Instances
Bitraversable Name Source # | |
Defined in Bound.Name bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Name a b -> f (Name c d) # | |
Bifoldable Name Source # | |
Bifunctor Name Source # | |
Eq2 Name Source # | |
Ord2 Name Source # | |
Defined in Bound.Name | |
Read2 Name Source # | |
Defined in Bound.Name liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Name a b) # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Name a b] # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Name a b) # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Name a b] # | |
Show2 Name Source # | |
Serial2 Name Source # | |
Defined in Bound.Name serializeWith2 :: MonadPut m => (a -> m ()) -> (b -> m ()) -> Name a b -> m () # deserializeWith2 :: MonadGet m => m a -> m b -> m (Name a b) # | |
Hashable2 Name Source # | |
Defined in Bound.Name | |
Functor (Name n) Source # | |
Foldable (Name n) Source # | |
Defined in Bound.Name fold :: Monoid m => Name n m -> m # foldMap :: Monoid m => (a -> m) -> Name n a -> m # foldr :: (a -> b -> b) -> b -> Name n a -> b # foldr' :: (a -> b -> b) -> b -> Name n a -> b # foldl :: (b -> a -> b) -> b -> Name n a -> b # foldl' :: (b -> a -> b) -> b -> Name n a -> b # foldr1 :: (a -> a -> a) -> Name n a -> a # foldl1 :: (a -> a -> a) -> Name n a -> a # elem :: Eq a => a -> Name n a -> Bool # maximum :: Ord a => Name n a -> a # minimum :: Ord a => Name n a -> a # | |
Traversable (Name n) Source # | |
Eq1 (Name b) Source # | |
Ord1 (Name b) Source # | |
Defined in Bound.Name | |
Read b => Read1 (Name b) Source # | |
Defined in Bound.Name | |
Show b => Show1 (Name b) Source # | |
Serial b => Serial1 (Name b) Source # | |
Defined in Bound.Name serializeWith :: MonadPut m => (a -> m ()) -> Name b a -> m () # deserializeWith :: MonadGet m => m a -> m (Name b a) # | |
Comonad (Name n) Source # | |
Hashable1 (Name n) Source # | |
Defined in Bound.Name | |
Generic1 (Name n :: Type -> Type) Source # | |
Eq b => Eq (Name n b) Source # | |
(Data n, Data b) => Data (Name n b) Source # | |
Defined in Bound.Name gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Name n b -> c (Name n b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Name n b) # toConstr :: Name n b -> Constr # dataTypeOf :: Name n b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Name n b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Name n b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Name n b -> Name n b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name n b -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name n b -> r # gmapQ :: (forall d. Data d => d -> u) -> Name n b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Name n b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name n b -> m (Name n b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name n b -> m (Name n b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name n b -> m (Name n b) # | |
Ord b => Ord (Name n b) Source # | |
(Read n, Read b) => Read (Name n b) Source # | |
(Show n, Show b) => Show (Name n b) Source # | |
Generic (Name n b) Source # | |
(Binary b, Binary a) => Binary (Name b a) Source # | |
(Serial b, Serial a) => Serial (Name b a) Source # | |
Defined in Bound.Name | |
(Serialize b, Serialize a) => Serialize (Name b a) Source # | |
(NFData b, NFData a) => NFData (Name b a) Source # | |
Defined in Bound.Name | |
Hashable a => Hashable (Name n a) Source # | |
Defined in Bound.Name | |
type Rep1 (Name n :: Type -> Type) Source # | |
Defined in Bound.Name type Rep1 (Name n :: Type -> Type) = D1 (MetaData "Name" "Bound.Name" "bound-2.0.1-AtZsY3yZaEKLBfeR1JA5NI" False) (C1 (MetaCons "Name" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 n) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1)) | |
type Rep (Name n b) Source # | |
Defined in Bound.Name type Rep (Name n b) = D1 (MetaData "Name" "Bound.Name" "bound-2.0.1-AtZsY3yZaEKLBfeR1JA5NI" False) (C1 (MetaCons "Name" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 n) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b))) |
abstractName :: Monad f => (a -> Maybe b) -> f a -> Scope (Name a b) f a Source #
Abstraction, capturing named bound variables.
abstract1Name :: (Monad f, Eq a) => a -> f a -> Scope (Name a ()) f a Source #
Abstract over a single variable
abstractEitherName :: Monad f => (a -> Either b c) -> f a -> Scope (Name a b) f c Source #
Capture some free variables in an expression to yield
a Scope
with named bound variables. Optionally change the
types of the remaining free variables.
instantiateName :: (Monad f, Comonad n) => (b -> f a) -> Scope (n b) f a -> f a Source #
Enter a scope, instantiating all bound variables, but discarding (comonadic) meta data, like its name
instantiate1Name :: Monad f => f a -> Scope n f a -> f a Source #
Enter a Scope
that binds one (named) variable, instantiating it.
instantiate1Name
=instantiate1