Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- newtype PosP (b :: BinP) = PosP {}
- data PosP' (n :: Nat) (b :: BinP) where
- top :: SBinPI b => PosP b
- pop :: (SBinPI a, Pred b ~ 'BP a, Succ a ~ b) => PosP a -> PosP b
- explicitShow :: PosP b -> String
- explicitShow' :: PosP' n b -> String
- explicitShowsPrec :: Int -> PosP b -> ShowS
- explicitShowsPrec' :: Int -> PosP' n b -> ShowS
- toNatural :: PosP b -> Natural
- toNatural' :: forall n b. SNatI n => PosP' n b -> Natural
- boring :: PosP 'BE
- weakenRight1 :: SBinPI b => PosP b -> PosP (Succ b)
- weakenRight1' :: forall b n. SBinP b -> PosP' n b -> PosP' n (Succ b)
- universe :: forall b. SBinPI b => [PosP b]
- universe' :: forall b n. (SNatI n, SBinPI b) => [PosP' n b]
Documentation
newtype 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 # | |
data PosP' (n :: Nat) (b :: BinP) where Source #
Instances
SNatI n => GShow (PosP' n :: BinP -> Type) Source # | Since: 0.1.3 |
Defined in Data.BinP.PosP gshowsPrec :: forall (a :: k). Int -> PosP' n a -> ShowS # | |
(SNatI n, SBinPI b) => Arbitrary (PosP' n b) Source # | |
SNatI n => CoArbitrary (PosP' n b) Source # | |
Defined in Data.BinP.PosP coarbitrary :: PosP' n b -> Gen b0 -> Gen b0 # | |
(SNatI n, SBinPI b) => Function (PosP' n b) Source # | |
(SNatI n, SBinPI b) => Bounded (PosP' n b) Source # | |
SNatI n => Show (PosP' n b) Source # | |
NFData (PosP' n b) Source # | Since: 0.1.2 |
Defined in Data.BinP.PosP | |
Eq (PosP' n b) Source # | |
Ord (PosP' n b) Source # | |
Defined in Data.BinP.PosP |
Top & Pop
Showing
explicitShow :: PosP b -> String Source #
explicitShow' :: PosP' n b -> String Source #