| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
Data.Bin
Description
Binary natural numbers, Bin.
This module is designed to be imported qualified.
Synopsis
- data Bin
- toNatural :: Bin -> Natural
- fromNatural :: Natural -> Bin
- toNat :: Bin -> Nat
- fromNat :: Nat -> Bin
- cata :: a -> a -> (a -> a) -> (a -> a) -> Bin -> a
- data BinP
- explicitShow :: Bin -> String
- explicitShowsPrec :: Int -> Bin -> ShowS
- predP :: BinP -> Bin
- mult2 :: Bin -> Bin
- mult2Plus1 :: Bin -> BinP
- andP :: BinP -> BinP -> Bin
- xorP :: BinP -> BinP -> Bin
- complementBitP :: BinP -> Int -> Bin
- clearBitP :: BinP -> Int -> Bin
- bin0 :: Bin
- bin1 :: Bin
- bin2 :: Bin
- bin3 :: Bin
- bin4 :: Bin
- bin5 :: Bin
- bin6 :: Bin
- bin7 :: Bin
- bin8 :: Bin
- bin9 :: Bin
Binary natural numbers
Binary natural numbers.
Numbers are represented in little-endian order, the representation is unique.
>>>mapM_ (putStrLn . explicitShow) [0 .. 7]BZ BP BE BP (B0 BE) BP (B1 BE) BP (B0 (B0 BE)) BP (B1 (B0 BE)) BP (B0 (B1 BE)) BP (B1 (B1 BE))
Instances
| Arbitrary Bin Source # | |
| CoArbitrary Bin Source # | |
| Function Bin Source # | |
| Data Bin Source # | |
| Defined in Data.Bin Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bin -> c Bin # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bin # dataTypeOf :: Bin -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bin) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bin) # gmapT :: (forall b. Data b => b -> b) -> Bin -> Bin # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bin -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bin -> r # gmapQ :: (forall d. Data d => d -> u) -> Bin -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bin -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bin -> m Bin # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bin -> m Bin # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bin -> m Bin # | |
| Bits Bin Source # | |
| Defined in Data.Bin | |
| Enum Bin Source # | 
 
 | 
| Num Bin Source # | 
 
 
 
 | 
| Integral Bin Source # | |
| Real Bin Source # | |
| Defined in Data.Bin Methods toRational :: Bin -> Rational # | |
| Show Bin Source # | To see explicit structure, use  | 
| NFData Bin Source # | |
| Eq Bin Source # | |
| Ord Bin Source # | |
| Hashable Bin Source # | |
| TestEquality SBin Source # | |
| Defined in Data.Type.Bin | |
| EqP Pos Source # | 
 
 Since: 0.1.3 | 
| EqP SBin Source # | Since: 0.1.3 | 
| GNFData SBin Source # | Since: 0.1.2 | 
| Defined in Data.Type.Bin | |
| GEq SBin Source # | Since: 0.1.2 | 
| GShow Pos Source # | Since: 0.1.3 | 
| Defined in Data.Bin.Pos Methods gshowsPrec :: forall (a :: k). Int -> Pos a -> ShowS # | |
| GShow SBin Source # | Since: 0.1.2 | 
| Defined in Data.Type.Bin Methods gshowsPrec :: forall (a :: k). Int -> SBin a -> ShowS # | |
| OrdP Pos Source # | 
 Since: 0.1.3 | 
fromNatural :: Natural -> Bin Source #
Positive natural numbers
Non-zero binary natural numbers.
We could have called this type Bin1,
 but that's used as type alias for promoted BP BE
Instances
| Arbitrary BinP Source # | |
| CoArbitrary BinP Source # | |
| Function BinP Source # | |
| Data BinP Source # | |
| Defined in Data.BinP Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BinP -> c BinP # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BinP # dataTypeOf :: BinP -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BinP) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BinP) # gmapT :: (forall b. Data b => b -> b) -> BinP -> BinP # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BinP -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BinP -> r # gmapQ :: (forall d. Data d => d -> u) -> BinP -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BinP -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BinP -> m BinP # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BinP -> m BinP # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BinP -> m BinP # | |
| Bits BinP Source # | NOTE:  | 
| Defined in Data.BinP Methods (.&.) :: BinP -> BinP -> BinP # (.|.) :: BinP -> BinP -> BinP # complement :: BinP -> BinP # shift :: BinP -> Int -> BinP # rotate :: BinP -> Int -> BinP # setBit :: BinP -> Int -> BinP # clearBit :: BinP -> Int -> BinP # complementBit :: BinP -> Int -> BinP # testBit :: BinP -> Int -> Bool # bitSizeMaybe :: BinP -> Maybe Int # shiftL :: BinP -> Int -> BinP # unsafeShiftL :: BinP -> Int -> BinP # shiftR :: BinP -> Int -> BinP # unsafeShiftR :: BinP -> Int -> BinP # rotateL :: BinP -> Int -> BinP # | |
| Enum BinP Source # | |
| Num BinP Source # | |
| Integral BinP Source # | |
| Real BinP Source # | |
| Defined in Data.BinP Methods toRational :: BinP -> Rational # | |
| Show BinP Source # | |
| NFData BinP Source # | |
| Eq BinP Source # | |
| Ord BinP Source # | 
 
 
 | 
| Hashable BinP Source # | |
| TestEquality SBinP Source # | |
| Defined in Data.Type.BinP | |
| EqP PosP Source # | Since: 0.1.3 | 
| EqP SBinP Source # | Since: 0.1.3 | 
| GNFData SBinP Source # | Since: 0.1.2 | 
| Defined in Data.Type.BinP | |
| GEq SBinP Source # | Since: 0.1.2 | 
| GShow PosP Source # | Since: 0.1.3 | 
| Defined in Data.BinP.PosP Methods gshowsPrec :: forall (a :: k). Int -> PosP a -> ShowS # | |
| GShow SBinP Source # | Since: 0.1.2 | 
| Defined in Data.Type.BinP Methods gshowsPrec :: forall (a :: k). Int -> SBinP a -> ShowS # | |
| OrdP PosP Source # | Since: 0.1.3 | 
| SNatI n => GShow (PosP' n :: BinP -> Type) Source # | Since: 0.1.3 | 
| Defined in Data.BinP.PosP Methods gshowsPrec :: forall (a :: k). Int -> PosP' n a -> ShowS # | |
Showing
explicitShow :: Bin -> String Source #
Extras
mult2Plus1 :: Bin -> BinP Source #