Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- data Pos (b :: Bin) where
- data PosP (b :: BinP)
- top :: SBinPI b => Pos ('BP b)
- pop :: (SBinPI a, Pred b ~ 'BP a, Succ a ~ b) => Pos ('BP a) -> Pos ('BP b)
- explicitShow :: Pos b -> String
- explicitShowsPrec :: Int -> Pos b -> ShowS
- toNatural :: Pos b -> Natural
- absurd :: Pos 'BZ -> b
- boring :: Pos ('BP 'BE)
- weakenRight1 :: SBinPI b => Pos ('BP b) -> Pos (Succ'' b)
- universe :: forall b. SBinI b => [Pos b]
Documentation
data Pos (b :: Bin) where Source #
Instances
EqP Pos Source # |
Since: 0.1.3 |
GShow Pos Source # | Since: 0.1.3 |
Defined in Data.Bin.Pos gshowsPrec :: forall (a :: k). Int -> Pos a -> ShowS # | |
OrdP Pos Source # |
Since: 0.1.3 |
(SBinPI n, b ~ 'BP n) => Arbitrary (Pos b) Source # | |
CoArbitrary (Pos b) Source # | |
Defined in Data.Bin.Pos coarbitrary :: Pos b -> Gen b0 -> Gen b0 # | |
(SBinPI n, b ~ 'BP n) => Function (Pos b) Source # | |
(SBinPI n, b ~ 'BP n) => Bounded (Pos b) Source # |
|
Show (Pos b) Source # | |
b ~ 'BZ => Absurd (Pos b) Source # | Since: 0.1.2 |
Defined in Data.Bin.Pos | |
b ~ 'BP 'BE => Boring (Pos b) Source # | Since: 0.1.2 |
Defined in Data.Bin.Pos | |
NFData (Pos b) Source # | Since: 0.1.2 |
Defined in Data.Bin.Pos | |
Eq (Pos b) Source # | |
Ord (Pos b) Source # | |
data PosP (b :: BinP) Source #
Instances
EqP PosP Source # | Since: 0.1.3 |
GShow PosP Source # | Since: 0.1.3 |
Defined in Data.BinP.PosP gshowsPrec :: forall (a :: k). Int -> PosP a -> ShowS # | |
OrdP PosP Source # | Since: 0.1.3 |
SBinPI b => Arbitrary (PosP b) Source # | |
CoArbitrary (PosP b) Source # | |
Defined in Data.BinP.PosP coarbitrary :: PosP b -> Gen b0 -> Gen b0 # | |
SBinPI b => Function (PosP b) Source # | |
SBinPI b => Bounded (PosP b) Source # | |
Show (PosP b) Source # | |
b ~ 'BE => Boring (PosP b) Source # | Since: 0.1.2 |
Defined in Data.BinP.PosP | |
NFData (PosP b) Source # | Since: 0.1.2 |
Defined in Data.BinP.PosP | |
Eq (PosP b) Source # | |
Ord (PosP b) Source # | |
Top & Pop
Showing
explicitShow :: Pos b -> String Source #
Conversions
Interesting
Weakening (succ)
weakenRight1 :: SBinPI b => Pos ('BP b) -> Pos (Succ'' b) Source #
Like FS
for Fin
.
Some tests:
>>>
map weakenRight1 $ (universe :: [Pos Bin2])
[1,2]
>>>
map weakenRight1 $ (universe :: [Pos Bin3])
[1,2,3]
>>>
map weakenRight1 $ (universe :: [Pos Bin4])
[1,2,3,4]
>>>
map weakenRight1 $ (universe :: [Pos Bin5])
[1,2,3,4,5]
>>>
map weakenRight1 $ (universe :: [Pos Bin6])
[1,2,3,4,5,6]
Universe
universe :: forall b. SBinI b => [Pos b] Source #
Universe, i.e. all [Pos b]
>>>
universe :: [Pos Bin9]
[0,1,2,3,4,5,6,7,8]
>>>
traverse_ (putStrLn . explicitShow) (universe :: [Pos Bin5])
Pos (PosP (Here WE)) Pos (PosP (There1 (There0 (AtEnd 0b00)))) Pos (PosP (There1 (There0 (AtEnd 0b01)))) Pos (PosP (There1 (There0 (AtEnd 0b10)))) Pos (PosP (There1 (There0 (AtEnd 0b11))))