module Network.HPACK.Huffman.Bit (
  -- * Bits
    B(..)
  , Bits
  , fromBits
  ) where

import Imports

-- | Data type for Bit.
data B = F -- ^ Zero
       | T -- ^ One
       deriving (B -> B -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: B -> B -> Bool
$c/= :: B -> B -> Bool
== :: B -> B -> Bool
$c== :: B -> B -> Bool
Eq,Eq B
B -> B -> Bool
B -> B -> Ordering
B -> B -> B
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: B -> B -> B
$cmin :: B -> B -> B
max :: B -> B -> B
$cmax :: B -> B -> B
>= :: B -> B -> Bool
$c>= :: B -> B -> Bool
> :: B -> B -> Bool
$c> :: B -> B -> Bool
<= :: B -> B -> Bool
$c<= :: B -> B -> Bool
< :: B -> B -> Bool
$c< :: B -> B -> Bool
compare :: B -> B -> Ordering
$ccompare :: B -> B -> Ordering
Ord,Int -> B -> ShowS
[B] -> ShowS
B -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [B] -> ShowS
$cshowList :: [B] -> ShowS
show :: B -> String
$cshow :: B -> String
showsPrec :: Int -> B -> ShowS
$cshowsPrec :: Int -> B -> ShowS
Show)

-- | Bit stream.
type Bits = [B]

fromBit :: B -> Word8
fromBit :: B -> Word8
fromBit B
F = Word8
0
fromBit B
T = Word8
1

-- | From 'Bits' of length 8 to 'Word8'.
--
-- >>> fromBits [T,F,T,F,T,F,T,F]
-- 170
-- >>> fromBits [F,T,F,T,F,T,F,T]
-- 85
fromBits :: Bits -> Word8
fromBits :: [B] -> Word8
fromBits = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Word8
x Word8
y -> Word8
x forall a. Num a => a -> a -> a
* Word8
2 forall a. Num a => a -> a -> a
+ Word8
y) Word8
0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map B -> Word8
fromBit