module Data.MutableIter.Binary (
Endian (..),
endianRead2,
endianRead3,
endianRead4
)
where
import Data.MutableIter as I
import qualified Data.MutableIter.IOBuffer as IB
import Data.MutableIter.IOBuffer (IOBuffer)
import Data.Iteratee.Binary (Endian (..))
import Data.Word
import Data.Bits
import Data.Int
import Control.Monad.CatchIO
endianRead2
:: (MonadCatchIO m) =>
Endian
-> MIteratee (IOBuffer r Word8) m Word16
endianRead2 e = do
c1 <- I.head
c2 <- I.head
case e of
MSB -> return $ (fromIntegral c1 `shiftL` 8) .|. fromIntegral c2
LSB -> return $ (fromIntegral c2 `shiftL` 8) .|. fromIntegral c1
endianRead3
:: (MonadCatchIO m) =>
Endian
-> MIteratee (IOBuffer r Word8) m Word32
endianRead3 e = do
c1 <- I.head
c2 <- I.head
c3 <- I.head
case e of
MSB -> return $ (((fromIntegral c1
`shiftL` 8) .|. fromIntegral c2)
`shiftL` 8) .|. fromIntegral c3
LSB ->
let m :: Int32
m = shiftR (shiftL (fromIntegral c3) 24) 8 in
return $ (((fromIntegral c3
`shiftL` 8) .|. fromIntegral c2)
`shiftL` 8) .|. fromIntegral m
endianRead4
:: (MonadCatchIO m) =>
Endian
-> MIteratee (IOBuffer r Word8) m Word32
endianRead4 e = do
c1 <- I.head
c2 <- I.head
c3 <- I.head
c4 <- I.head
case e of
MSB -> return $
(((((fromIntegral c1
`shiftL` 8) .|. fromIntegral c2)
`shiftL` 8) .|. fromIntegral c3)
`shiftL` 8) .|. fromIntegral c4
LSB -> return $
(((((fromIntegral c4
`shiftL` 8) .|. fromIntegral c3)
`shiftL` 8) .|. fromIntegral c2)
`shiftL` 8) .|. fromIntegral c1