Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Provides one-hole contexts for our universe, but over deep encoded datatypes. These are a bit easier to use computationally.
This module follows the very same structure as Zipper
.
Refer there for further documentation.
Synopsis
- data Ctxs (ki :: kon -> *) (codes :: [[[Atom kon]]]) :: Nat -> Nat -> * where
- data Ctx (ki :: kon -> *) (codes :: [[[Atom kon]]]) :: [[Atom kon]] -> Nat -> * where
- data NPHole (ki :: kon -> *) (codes :: [[[Atom kon]]]) :: Nat -> [Atom kon] -> * where
- getCtxsIx :: Ctxs ki codes iy ix -> Proxy ix
- fillNPHole :: IsNat ix => Fix ki codes ix -> NPHole ki codes ix xs -> PoA ki (Fix ki codes) xs
- fillCtxs :: IsNat ix => Fix ki codes iy -> Ctxs ki codes ix iy -> Fix ki codes ix
- fillCtx :: IsNat ix => Fix ki codes ix -> Ctx ki codes c ix -> Rep ki (Fix ki codes) c
- removeCtxs :: (EqHO ki, IsNat ix) => Ctxs ki codes ix iy -> Fix ki codes ix -> Maybe (Fix ki codes iy)
- removeCtx :: forall ix ki codes c. (EqHO ki, IsNat ix) => Rep ki (Fix ki codes) c -> Ctx ki codes c ix -> Maybe (Fix ki codes ix)
- removeNPHole :: (EqHO ki, IsNat ix) => NPHole ki codes ix xs -> PoA ki (Fix ki codes) xs -> Maybe (Fix ki codes ix)
Documentation
data Ctxs (ki :: kon -> *) (codes :: [[[Atom kon]]]) :: Nat -> Nat -> * where Source #
Analogous to Ctxs
data Ctx (ki :: kon -> *) (codes :: [[[Atom kon]]]) :: [[Atom kon]] -> Nat -> * where Source #
Analogous to Ctx
data NPHole (ki :: kon -> *) (codes :: [[[Atom kon]]]) :: Nat -> [Atom kon] -> * where Source #
Analogous to NPHole
, but uses a deep representation
for generic values.
fillNPHole :: IsNat ix => Fix ki codes ix -> NPHole ki codes ix xs -> PoA ki (Fix ki codes) xs Source #
Given a product with a hole in it, and an element, get back a product
dual of removeNPHole
fillCtxs :: IsNat ix => Fix ki codes iy -> Ctxs ki codes ix iy -> Fix ki codes ix Source #
Given a value that fits in a context, fills the context hole.
removeCtxs :: (EqHO ki, IsNat ix) => Ctxs ki codes ix iy -> Fix ki codes ix -> Maybe (Fix ki codes iy) Source #
Given a value and a context, tries to match to context in the value and, upon success, returns whatever overlaps with the hole.