Copyright | (c) 2014 Aleksey Kliger |
---|---|
License | BSD3 (See LICENSE) |
Maintainer | Aleksey Kliger |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Extensions |
|
Synopsis
- class Show a => Alpha a where
- aeq' :: AlphaCtx -> a -> a -> Bool
- fvAny' :: (Contravariant f, Applicative f) => AlphaCtx -> (AnyName -> f AnyName) -> a -> f a
- close :: AlphaCtx -> NamePatFind -> a -> a
- open :: AlphaCtx -> NthPatFind -> a -> a
- isPat :: a -> DisjointSet AnyName
- isTerm :: a -> All
- isEmbed :: a -> Bool
- nthPatFind :: a -> NthPatFind
- namePatFind :: a -> NamePatFind
- swaps' :: AlphaCtx -> Perm AnyName -> a -> a
- lfreshen' :: LFresh m => AlphaCtx -> a -> (a -> Perm AnyName -> m b) -> m b
- freshen' :: Fresh m => AlphaCtx -> a -> m (a, Perm AnyName)
- acompare' :: AlphaCtx -> a -> a -> Ordering
- newtype DisjointSet a = DisjointSet (Maybe [a])
- inconsistentDisjointSet :: DisjointSet a
- singletonDisjointSet :: a -> DisjointSet a
- isConsistentDisjointSet :: DisjointSet a -> Bool
- isNullDisjointSet :: DisjointSet a -> Bool
- newtype NthPatFind = NthPatFind {
- runNthPatFind :: Integer -> Either Integer AnyName
- newtype NamePatFind = NamePatFind {}
- data AlphaCtx
- ctxLevel :: AlphaCtx -> Integer
- initialCtx :: AlphaCtx
- patternCtx :: AlphaCtx -> AlphaCtx
- termCtx :: AlphaCtx -> AlphaCtx
- isTermCtx :: AlphaCtx -> Bool
- incrLevelCtx :: AlphaCtx -> AlphaCtx
- decrLevelCtx :: AlphaCtx -> AlphaCtx
- isZeroLevelCtx :: AlphaCtx -> Bool
- ctxLevel :: AlphaCtx -> Integer
- gaeq :: GAlpha f => AlphaCtx -> f a -> f a -> Bool
- gfvAny :: (GAlpha f, Contravariant g, Applicative g) => AlphaCtx -> (AnyName -> g AnyName) -> f a -> g (f a)
- gclose :: GAlpha f => AlphaCtx -> NamePatFind -> f a -> f a
- gopen :: GAlpha f => AlphaCtx -> NthPatFind -> f a -> f a
- gisPat :: GAlpha f => f a -> DisjointSet AnyName
- gisTerm :: GAlpha f => f a -> All
- gnthPatFind :: GAlpha f => f a -> NthPatFind
- gnamePatFind :: GAlpha f => f a -> NamePatFind
- gswaps :: GAlpha f => AlphaCtx -> Perm AnyName -> f a -> f a
- gfreshen :: (GAlpha f, Fresh m) => AlphaCtx -> f a -> FFM m (f a, Perm AnyName)
- glfreshen :: (GAlpha f, LFresh m) => AlphaCtx -> f a -> (f a -> Perm AnyName -> m b) -> m b
- gacompare :: GAlpha f => AlphaCtx -> f a -> f a -> Ordering
- data FFM f a
- liftFFM :: Monad m => m a -> FFM m a
- retractFFM :: Monad m => FFM m a -> m a
Name-aware opertions
class Show a => Alpha a where Source #
Types that are instances of Alpha
may participate in name representation.
Minimal instance is entirely empty, provided that your type is an instance of
Generic
.
Nothing
aeq' :: AlphaCtx -> a -> a -> Bool Source #
See aeq
.
fvAny' :: (Contravariant f, Applicative f) => AlphaCtx -> (AnyName -> f AnyName) -> a -> f a Source #
See fvAny
.
fvAny' :: Fold a AnyName
default fvAny' :: (Generic a, GAlpha (Rep a), Contravariant f, Applicative f) => AlphaCtx -> (AnyName -> f AnyName) -> a -> f a Source #
close :: AlphaCtx -> NamePatFind -> a -> a Source #
Replace free names by bound names.
open :: AlphaCtx -> NthPatFind -> a -> a Source #
Replace bound names by free names.
isPat :: a -> DisjointSet AnyName Source #
isPat x
dynamically checks whether x
can be used as a valid pattern.
isPat x
dynamically checks whether x
can be used as a valid term.
isEmbed
is needed internally for the implementation of
isPat
. isEmbed
is true for terms wrapped in Embed
and zero
or more occurrences of Shift
. The default implementation
simply returns False
.
nthPatFind :: a -> NthPatFind Source #
If a
is a pattern, finds the n
th name in the pattern
(starting from zero), returning the number of names encountered
if not found.
default nthPatFind :: (Generic a, GAlpha (Rep a)) => a -> NthPatFind Source #
namePatFind :: a -> NamePatFind Source #
If a
is a pattern, find the index of the given name in the pattern.
default namePatFind :: (Generic a, GAlpha (Rep a)) => a -> NamePatFind Source #
swaps' :: AlphaCtx -> Perm AnyName -> a -> a Source #
See swaps
. Apply
the given permutation of variable names to the given pattern.
lfreshen' :: LFresh m => AlphaCtx -> a -> (a -> Perm AnyName -> m b) -> m b Source #
See freshen
.
default lfreshen' :: (LFresh m, Generic a, GAlpha (Rep a)) => AlphaCtx -> a -> (a -> Perm AnyName -> m b) -> m b Source #
freshen' :: Fresh m => AlphaCtx -> a -> m (a, Perm AnyName) Source #
See freshen
. Rename the free variables
in the given term to be distinct from all other names seen in the monad m
.
default freshen' :: (Generic a, GAlpha (Rep a), Fresh m) => AlphaCtx -> a -> m (a, Perm AnyName) Source #
acompare' :: AlphaCtx -> a -> a -> Ordering Source #
See acompare
. An alpha-respecting total order on terms involving binders.
Instances
Binder variables
newtype DisjointSet a Source #
A DisjointSet a
is a Just
a list of distinct a
s. In addition to a monoidal
structure, a disjoint set also has an annihilator inconsistentDisjointSet
.
inconsistentDisjointSet <> s == inconsistentDisjointSet s <> inconsistentDisjoinSet == inconsistentDisjointSet
DisjointSet (Maybe [a]) |
Instances
inconsistentDisjointSet :: DisjointSet a Source #
Returns a DisjointSet a
that is the annihilator element for the Monoid
instance of DisjointSet
.
singletonDisjointSet :: a -> DisjointSet a Source #
singletonDisjointSet x
a DisjointSet a
that contains the single element x
isConsistentDisjointSet :: DisjointSet a -> Bool Source #
isConsistentDisjointSet
returns True
iff the given disjoint set is not inconsistent.
isNullDisjointSet :: DisjointSet a -> Bool Source #
isNullDisjointSet
return True
iff the given disjoint set is mempty
.
Implementation details
newtype NthPatFind Source #
The result of
is nthPatFind
a iLeft k
where i-k
is the
number of names in pattern a
(with k < i
) or Right x
where x
is the i
th name in a
Instances
Monoid NthPatFind Source # | |
Defined in Unbound.Generics.LocallyNameless.Alpha mempty :: NthPatFind # mappend :: NthPatFind -> NthPatFind -> NthPatFind # mconcat :: [NthPatFind] -> NthPatFind # | |
Semigroup NthPatFind Source # | Since: 0.3.2 |
Defined in Unbound.Generics.LocallyNameless.Alpha (<>) :: NthPatFind -> NthPatFind -> NthPatFind # sconcat :: NonEmpty NthPatFind -> NthPatFind # stimes :: Integral b => b -> NthPatFind -> NthPatFind # |
newtype NamePatFind Source #
The result of
is either namePatFind
a xLeft i
if a
is a pattern that
contains i
free names none of which are x
, or Right j
if x
is the j
th name
in a
Instances
Monoid NamePatFind Source # | |
Defined in Unbound.Generics.LocallyNameless.Alpha mempty :: NamePatFind # mappend :: NamePatFind -> NamePatFind -> NamePatFind # mconcat :: [NamePatFind] -> NamePatFind # | |
Semigroup NamePatFind Source # | Since: 0.3.2 |
Defined in Unbound.Generics.LocallyNameless.Alpha (<>) :: NamePatFind -> NamePatFind -> NamePatFind # sconcat :: NonEmpty NamePatFind -> NamePatFind # stimes :: Integral b => b -> NamePatFind -> NamePatFind # |
Some Alpha
operations need to record information about their
progress. Instances should just pass it through unchanged.
The context records whether we are currently operating on terms or patterns, and how many binding levels we've descended.
initialCtx :: AlphaCtx Source #
The starting context for alpha operations: we are expecting to work on terms and we are under no binders.
patternCtx :: AlphaCtx -> AlphaCtx Source #
Switches to a context where we expect to operate on patterns.
isTermCtx :: AlphaCtx -> Bool Source #
Returns True
iff we are in a context where we expect to see terms.
incrLevelCtx :: AlphaCtx -> AlphaCtx Source #
Increment the number of binders that we are operating under.
decrLevelCtx :: AlphaCtx -> AlphaCtx Source #
Decrement the number of binders that we are operating under.
isZeroLevelCtx :: AlphaCtx -> Bool Source #
Are we operating under no binders?
Internal
gfvAny :: (GAlpha f, Contravariant g, Applicative g) => AlphaCtx -> (AnyName -> g AnyName) -> f a -> g (f a) Source #
gclose :: GAlpha f => AlphaCtx -> NamePatFind -> f a -> f a Source #
gopen :: GAlpha f => AlphaCtx -> NthPatFind -> f a -> f a Source #
gisPat :: GAlpha f => f a -> DisjointSet AnyName Source #
gnthPatFind :: GAlpha f => f a -> NthPatFind Source #
gnamePatFind :: GAlpha f => f a -> NamePatFind Source #
glfreshen :: (GAlpha f, LFresh m) => AlphaCtx -> f a -> (f a -> Perm AnyName -> m b) -> m b Source #
Interal helpers for gfreshen
retractFFM :: Monad m => FFM m a -> m a Source #