Safe Haskell | None |
---|---|
Language | Haskell2010 |
Bit getter
Synopsis
- data BitGetState = BitGetState {}
- newBitGetState :: BitOrder -> Buffer -> BitGetState
- isEmpty :: BitGetState -> Bool
- skipBits :: Word -> BitGetState -> BitGetState
- skipBitsToAlignOnWord8 :: BitGetState -> BitGetState
- getBits :: (Integral a, Bits a) => Word -> BitGetState -> a
- getBitsChecked :: (Integral a, Bits a, ReversableBits a) => Word -> Word -> BitGetState -> a
- getBitsBuffer :: Word -> BitGetState -> Buffer
- type BitGet a = BitGetT Identity a
- type BitGetT m a = StateT BitGetState m a
- runBitGet :: BitOrder -> BitGet a -> Buffer -> a
- runBitGetT :: Monad m => BitOrder -> BitGetT m a -> Buffer -> m a
- runBitGetPartialT :: BitOrder -> BitGetT m a -> Buffer -> m (a, BitGetState)
- runBitGetPartial :: BitOrder -> BitGet a -> Buffer -> (a, BitGetState)
- resumeBitGetPartialT :: BitGetT m a -> BitGetState -> m (a, BitGetState)
- resumeBitGetPartial :: BitGet a -> BitGetState -> (a, BitGetState)
- isEmptyM :: Monad m => BitGetT m Bool
- skipBitsM :: Monad m => Word -> BitGetT m ()
- skipBitsToAlignOnWord8M :: Monad m => BitGetT m ()
- getBitsM :: (Integral a, Bits a, Monad m) => Word -> BitGetT m a
- getBitsCheckedM :: (Integral a, Bits a, ReversableBits a, Monad m) => Word -> Word -> BitGetT m a
- getBitBoolM :: Monad m => BitGetT m Bool
- getBitsBSM :: Monad m => Word -> BitGetT m Buffer
- changeBitGetOrder :: Monad m => BitOrder -> BitGetT m ()
- withBitGetOrder :: Monad m => BitOrder -> BitGetT m a -> BitGetT m a
Documentation
data BitGetState Source #
BitGet state
BitGetState | |
|
Instances
Show BitGetState Source # | |
Defined in Haskus.Binary.Bits.Get showsPrec :: Int -> BitGetState -> ShowS # show :: BitGetState -> String # showList :: [BitGetState] -> ShowS # |
newBitGetState :: BitOrder -> Buffer -> BitGetState Source #
Create a new BitGetState
isEmpty :: BitGetState -> Bool Source #
Indicate that the source is empty
skipBits :: Word -> BitGetState -> BitGetState Source #
Skip the given number of bits from the input
skipBitsToAlignOnWord8 :: BitGetState -> BitGetState Source #
Skip the required number of bits to be aligned on 8-bits
getBits :: (Integral a, Bits a) => Word -> BitGetState -> a Source #
Read the given number of bits and put the result in a word
getBitsChecked :: (Integral a, Bits a, ReversableBits a) => Word -> Word -> BitGetState -> a Source #
Perform some checks before calling getBits
Check that the number of bits to read is not greater than the first parameter
getBitsBuffer :: Word -> BitGetState -> Buffer Source #
Read the given number of Word8 and return them in a Buffer
Examples:
BB: xxxABCDE FGHIJKLM NOPxxxxx -> ABCDEFGH IJKLMNOP
LL: LMNOPxxx DEFGHIJK xxxxxABC -> ABCDEFGH IJKLMNOP
BL: xxxPONML KJIHGFED CBAxxxxx -> ABCDEFGH IJKLMNOP
LB: EDCBAxxx MLKJIHGF xxxxxPON -> ABCDEFGH IJKLMNOP
Monadic
type BitGetT m a = StateT BitGetState m a Source #
BitGet monad transformer
runBitGetPartialT :: BitOrder -> BitGetT m a -> Buffer -> m (a, BitGetState) Source #
Evaluate a BitGet monad, return the remaining state
runBitGetPartial :: BitOrder -> BitGet a -> Buffer -> (a, BitGetState) Source #
Evaluate a BitGet monad, return the remaining state
resumeBitGetPartialT :: BitGetT m a -> BitGetState -> m (a, BitGetState) Source #
Resume a BitGet evaluation
resumeBitGetPartial :: BitGet a -> BitGetState -> (a, BitGetState) Source #
Resume a BitGet evaluation
skipBitsM :: Monad m => Word -> BitGetT m () Source #
Skip the given number of bits from the input (monadic version)
skipBitsToAlignOnWord8M :: Monad m => BitGetT m () Source #
Skip the required number of bits to be aligned on 8-bits (monadic version)
getBitsM :: (Integral a, Bits a, Monad m) => Word -> BitGetT m a Source #
Read the given number of bits and put the result in a word
getBitsCheckedM :: (Integral a, Bits a, ReversableBits a, Monad m) => Word -> Word -> BitGetT m a Source #
Perform some checks before calling getBitsM