module Data.Iteratee.Binary (
Endian (..)
,endianRead2
,endianRead3
,endianRead3i
,endianRead4
,endianRead8
)
where
import Data.Iteratee.Base
import qualified Data.Iteratee.ListLike as I
import qualified Data.ListLike as LL
import Data.Word
import Data.Bits
import Data.Int
data Endian = MSB
| LSB
deriving (Eq, Ord, Show, Enum)
endianRead2
:: (Nullable s, LL.ListLike s Word8, Monad m) =>
Endian
-> Iteratee s 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
:: (Nullable s, LL.ListLike s Word8, Monad m) =>
Endian
-> Iteratee s 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 -> return $ (((fromIntegral c3
`shiftL` 8) .|. fromIntegral c2)
`shiftL` 8) .|. fromIntegral c1
endianRead3i
:: (Nullable s, LL.ListLike s Word8, Monad m) =>
Endian
-> Iteratee s m Int32
endianRead3i 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
:: (Nullable s, LL.ListLike s Word8, Monad m) =>
Endian
-> Iteratee s 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
endianRead8
:: (Nullable s, LL.ListLike s Word8, Monad m) =>
Endian
-> Iteratee s m Word64
endianRead8 e = do
c1 <- I.head
c2 <- I.head
c3 <- I.head
c4 <- I.head
c5 <- I.head
c6 <- I.head
c7 <- I.head
c8 <- I.head
case e of
MSB -> return $
(((((((((((((fromIntegral c1
`shiftL` 8) .|. fromIntegral c2)
`shiftL` 8) .|. fromIntegral c3)
`shiftL` 8) .|. fromIntegral c4)
`shiftL` 8) .|. fromIntegral c5)
`shiftL` 8) .|. fromIntegral c6)
`shiftL` 8) .|. fromIntegral c7)
`shiftL` 8) .|. fromIntegral c8
LSB -> return $
(((((((((((((fromIntegral c8
`shiftL` 8) .|. fromIntegral c7)
`shiftL` 8) .|. fromIntegral c6)
`shiftL` 8) .|. fromIntegral c5)
`shiftL` 8) .|. fromIntegral c4)
`shiftL` 8) .|. fromIntegral c3)
`shiftL` 8) .|. fromIntegral c2)
`shiftL` 8) .|. fromIntegral c1