Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Positive binary natural numbers. DataKinds
stuff.
Synopsis
- data SBinP (b :: BinP) where
- sbinpToBinP :: forall n. SBinP n -> BinP
- sbinpToNatural :: forall n. SBinP n -> Natural
- class SBinPI (b :: BinP) where
- withSBinP :: SBinP b -> (SBinPI b => r) -> r
- reify :: forall r. BinP -> (forall b. SBinPI b => Proxy b -> r) -> r
- reflect :: forall b proxy. SBinPI b => proxy b -> BinP
- reflectToNum :: forall b proxy a. (SBinPI b, Num a) => proxy b -> a
- eqBinP :: forall a b. (SBinPI a, SBinPI b) => Maybe (a :~: b)
- induction :: forall b f. SBinPI b => f 'BE -> (forall bb. SBinPI bb => f bb -> f ('B0 bb)) -> (forall bb. SBinPI bb => f bb -> f ('B1 bb)) -> f b
- type family Succ (b :: BinP) :: BinP where ...
- withSucc :: forall b r. SBinPI b => Proxy b -> (SBinPI (Succ b) => r) -> r
- type family Plus (a :: BinP) (b :: BinP) :: BinP where ...
- type family ToGHC (b :: BinP) :: Nat where ...
- type family FromGHC (n :: Nat) :: BinP where ...
- type family ToNat (b :: BinP) :: Nat where ...
- type BinP1 = 'BE
- type BinP2 = 'B0 BinP1
- type BinP3 = 'B1 BinP1
- type BinP4 = 'B0 BinP2
- type BinP5 = 'B1 BinP2
- type BinP6 = 'B0 BinP3
- type BinP7 = 'B1 BinP3
- type BinP8 = 'B0 BinP4
- type BinP9 = 'B1 BinP4
Singleton
data SBinP (b :: BinP) where Source #
Singleton of BinP
.
Instances
TestEquality SBinP Source # | |
Defined in Data.Type.BinP |
sbinpToNatural :: forall n. SBinP n -> Natural Source #
Implicit
reflect :: forall b proxy. SBinPI b => proxy b -> BinP Source #
Reflect type-level BinP
to the term level.
reflectToNum :: forall b proxy a. (SBinPI b, Num a) => proxy b -> a Source #
Type equality
Induction
:: forall b f. SBinPI b | |
=> f 'BE | \(P(1)\) |
-> (forall bb. SBinPI bb => f bb -> f ('B0 bb)) | \(\forall b. P(b) \to P(2b)\) |
-> (forall bb. SBinPI bb => f bb -> f ('B1 bb)) | \(\forall b. P(b) \to P(2b + 1)\) |
-> f b |
Induction on BinP
.