Safe Haskell | None |
---|---|
Language | GHC2021 |
Data.DeBruijn.Thinning
Synopsis
- data (n :: Nat) :<= (m :: Nat) where
- dropAll :: forall (m :: Nat). SNat m -> 'Z :<= m
- toBools :: forall (n :: Nat) (m :: Nat). (n :<= m) -> [Bool]
- fromTh :: forall bs (n :: Nat) (m :: Nat). Bits bs => (n :<= m) -> bs
- fromThRaw :: forall (n :: Nat) (m :: Nat). (n :<= m) -> ThRep
- data SomeTh = SomeTh {}
- fromBools :: Integral i => i -> [Bool] -> SomeTh
- toSomeTh :: (Integral i, Bits bs) => (i, bs) -> SomeTh
- toSomeThRaw :: (SNatRep, ThRep) -> SomeTh
- class Thin (f :: Nat -> Type) where
- type ThRep = Natural
Thinnings
data (n :: Nat) :<= (m :: Nat) where #
Bundled Patterns
pattern KeepAll :: () => n ~ m => n :<= m | |
pattern KeepOne :: () => (Pos n, Pos m) => (Pred n :<= Pred m) -> n :<= m | |
pattern DropOne :: forall m n. () => Pos m => (n :<= Pred m) -> n :<= m |
Existential Wrapper
toSomeThRaw :: (SNatRep, ThRep) -> SomeTh #
The action of thinnings on Nat
-indexed types
class Thin (f :: Nat -> Type) where #
Methods
thin :: forall (n :: Nat) (m :: Nat). (n :<= m) -> f n -> f m #
thick :: forall (n :: Nat) (m :: Nat). (n :<= m) -> f m -> Maybe (f n) #