Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- data Wk ctx ctx' where
- wk1 :: Wk ctx (S ctx)
- compWk :: Wk a b -> Wk b c -> Wk a c
- weakenIdx :: Wk ctx ctx' -> Idx ctx -> Idx ctx'
- contractIdx :: Wk ctx ctx' -> Idx ctx' -> Maybe (Idx ctx)
- weakenSize :: Wk ctx ctx' -> Size ctx -> Size ctx'
- contractSize :: Wk ctx ctx' -> Size ctx' -> Size ctx
- weakenEnv :: Wk ctx ctx' -> Env ctx' a -> Env ctx a
- setWeakenEnv :: Wk ctx ctx' -> Env ctx a -> Env ctx' a -> Env ctx' a
- overWeakenEnv :: Wk ctx ctx' -> (Env ctx a -> Env ctx a) -> Env ctx' a -> Env ctx' a
Documentation
data Wk ctx ctx' where Source #
Weakenings, order preserving embeddings.
Wk n m
could be represented as m
bit field with popCount of n
.
Constructor names make sense when you look at the implementation of weakenEnv
.
Note: usually 'ViewWk is defined as
data Wk ctx ctx' where WkNil :: Wk EmptyCtx EmptyCtx KeepWk :: Wk ctx ctx' -> Wk (S ctx) (S ctx') SkipWk :: Wk ctx ctx' -> Wk ctx (S ctx')
However that representation doesn't allow to make
without knowing the size of context.
Therefore we morally use a representation closer towkId
:: 'ViewWk ctx ctx
dataWk
ctx ctx' whereIdWk
:: Wk ctx ctxKeepWk
:: Wk ctx ctx' -> Wk (S ctx) (S ctx')SkipWk
:: Wk ctx ctx' -> Wk ctx (S ctx')
But we keep an invariant that identity weakenings are always represented by IdWk
.
>>>
KeepWk IdWk
IdWk
And KeepWk
pattern doesn't match on identity weakenings.
>>>
case IdWk :: Wk Ctx2 Ctx2 of { KeepWk _ -> "keep"; SkipWk _ -> "skip"; IdWk -> "id" } :: String
"id"
pattern SkipWk :: () => b ~ S b' => Wk a b' -> Wk a b | |
pattern KeepWk :: () => (a ~ S a', b ~ S b') => Wk a' b' -> Wk a b |
Instances
IdxMapping Identity Wk Source # | |
Defined in DeBruijn.Ren mapIdx :: forall (ctx :: Ctx) (ctx' :: Ctx). Wk ctx ctx' -> Idx ctx -> Identity (Idx ctx') Source # keep :: forall (ctx :: Ctx) (ctx' :: Ctx). Wk ctx ctx' -> Wk (S ctx) (S ctx') Source # weakenIdxMapping :: forall (ctx :: Ctx) (ctx' :: Ctx) (ctx'' :: Ctx). Wk ctx ctx' -> Wk ctx' ctx'' -> Wk ctx ctx'' Source # | |
Show (Wk ctx ctx') Source # | |
Eq (Wk ctx ctx') Source # | |
Combinators
Index weakening
contractIdx :: Wk ctx ctx' -> Idx ctx' -> Maybe (Idx ctx) Source #
Contract Idx
, i.e. map index from larger to smaller context.
>>>
contractIdx wk1 (IS IZ)
Just 0
>>>
contractIdx wk1 IZ
Nothing
>>>
contractIdx (SkipWk (KeepWk wk1)) <$> [IZ, IS IZ, IS (IS IZ), IS (IS IZ), IS (IS (IS IZ)), IS (IS (IS (IS IZ)))]
[Nothing,Just 0,Nothing,Nothing,Just 1,Just 2]
Size weakening
Environment contraction
setWeakenEnv :: Wk ctx ctx' -> Env ctx a -> Env ctx' a -> Env ctx' a Source #
setWeakenEnv
and weakenEnv
together form a lens.
>>>
setWeakenEnv (IdWk & SkipWk & KeepWk) (EmptyEnv :> 'a' :> 'b') (EmptyEnv :> 'x' :> 'y' :> 'z')
EmptyEnv :> 'a' :> 'y' :> 'b'
overWeakenEnv :: Wk ctx ctx' -> (Env ctx a -> Env ctx a) -> Env ctx' a -> Env ctx' a Source #
Setter made from setWeakenEnv
and weakenEnv
.
>>>
overWeakenEnv (IdWk & SkipWk & KeepWk) (fmap toUpper) (EmptyEnv :> 'a' :> 'x' :> 'y' :> 'z')
EmptyEnv :> 'A' :> 'X' :> 'y' :> 'Z'