Safe Haskell | None |
---|---|
Language | Haskell2010 |
A Knot
based implementation of "locally-nameless" terms,
inspired by the bound library
and the technique from Bird & Paterson's
"de Bruijn notation as a nested datatype"
Synopsis
- newtype Scope expr a k = Scope (k # expr (Maybe a))
- _Scope :: forall expr a k expr a k. Iso (Scope expr a k) (Scope expr a k) ((#) k (expr (Maybe a))) ((#) k (expr (Maybe a)))
- data family KWitness k :: (Knot -> Type) -> Type
- newtype ScopeVar (expr :: * -> Knot -> *) a (k :: Knot) = ScopeVar a
- _ScopeVar :: forall expr a k expr a k. Iso (ScopeVar expr a k) (ScopeVar expr a k) a a
- data EmptyScope
- class DeBruijnIndex a where
- deBruijnIndex :: Prism' Int a
- newtype ScopeTypes t v = ScopeTypes (Seq (v # t))
- _ScopeTypes :: forall t v t v. Iso (ScopeTypes t v) (ScopeTypes t v) (Seq ((#) v t)) (Seq ((#) v t))
- class HasScopeTypes v t env where
- scopeTypes :: Lens' env (Tree (ScopeTypes t) v)
Documentation
newtype Scope expr a k Source #
Instances
_Scope :: forall expr a k expr a k. Iso (Scope expr a k) (Scope expr a k) ((#) k (expr (Maybe a))) ((#) k (expr (Maybe a))) Source #
data family KWitness k :: (Knot -> Type) -> Type Source #
KWitness k n
is a witness that n
is a node of k
Instances
newtype ScopeVar (expr :: * -> Knot -> *) a (k :: Knot) Source #
ScopeVar a |
Instances
data EmptyScope Source #
Instances
DeBruijnIndex EmptyScope Source # | |
Defined in AST.Term.NamelessScope | |
InvDeBruijnIndex EmptyScope Source # | |
Defined in AST.Term.NamelessScope.InvDeBruijn deBruijnIndexMax :: Proxy EmptyScope -> Int Source # |
class DeBruijnIndex a where Source #
deBruijnIndex :: Prism' Int a Source #
Instances
DeBruijnIndex EmptyScope Source # | |
Defined in AST.Term.NamelessScope | |
DeBruijnIndex a => DeBruijnIndex (Maybe a) Source # | |
Defined in AST.Term.NamelessScope |
newtype ScopeTypes t v Source #
ScopeTypes (Seq (v # t)) |
Instances
_ScopeTypes :: forall t v t v. Iso (ScopeTypes t v) (ScopeTypes t v) (Seq ((#) v t)) (Seq ((#) v t)) Source #
class HasScopeTypes v t env where Source #
scopeTypes :: Lens' env (Tree (ScopeTypes t) v) Source #
Instances
HasScopeTypes v t (Tree (ScopeTypes t) v) Source # | |
Defined in AST.Term.NamelessScope scopeTypes :: Lens' (Tree (ScopeTypes t) v) (Tree (ScopeTypes t) v) Source # |