module Data.Iteratee.Binary (
Endian (..)
,endianRead2
,endianRead3
,endianRead3i
,endianRead4
,endianRead8
,readWord16be_bs
,readWord16le_bs
,readWord32be_bs
,readWord32le_bs
,readWord64be_bs
,readWord64le_bs
)
where
import Data.Iteratee.Base
import qualified Data.Iteratee.ListLike as I
import qualified Data.ListLike as LL
import qualified Data.ByteString as B
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 = endianReadN e 2 word16'
endianRead3
:: (Nullable s, LL.ListLike s Word8, Monad m)
=> Endian
-> Iteratee s m Word32
endianRead3 e = endianReadN e 3 (word32' . (0:))
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 = endianReadN e 4 word32'
endianRead8
:: (Nullable s, LL.ListLike s Word8, Monad m)
=> Endian
-> Iteratee s m Word64
endianRead8 e = endianReadN e 8 word64'
endianReadN ::
(Nullable s, LL.ListLike s Word8, Monad m)
=> Endian
-> Int
-> ([Word8] -> b)
-> Iteratee s m b
endianReadN MSB n0 cnct = liftI (step n0 [])
where
step !n acc (Chunk c)
| LL.null c = liftI (step n acc)
| LL.length c >= n = let (this,next) = LL.splitAt n c
!result = cnct $ acc ++ LL.toList this
in idone result (Chunk next)
| otherwise = liftI (step (n LL.length c) (acc ++ LL.toList c))
step !n acc (EOF Nothing) = icont (step n acc) (Just $ toException EofException)
step !n acc (EOF (Just e)) = icont (step n acc) (Just e)
endianReadN LSB n0 cnct = liftI (step n0 [])
where
step !n acc (Chunk c)
| LL.null c = liftI (step n acc)
| LL.length c >= n = let (this,next) = LL.splitAt n c
!result = cnct $ reverse (LL.toList this) ++ acc
in idone result (Chunk next)
| otherwise = liftI (step (n LL.length c)
(reverse (LL.toList c) ++ acc))
step !n acc (EOF Nothing) = icont (step n acc)
(Just $ toException EofException)
step !n acc (EOF (Just e)) = icont (step n acc) (Just e)
readWord16be_bs :: Monad m => Iteratee B.ByteString m Word16
readWord16be_bs = endianRead2 MSB
readWord16le_bs :: Monad m => Iteratee B.ByteString m Word16
readWord16le_bs = endianRead2 LSB
readWord32be_bs :: Monad m => Iteratee B.ByteString m Word32
readWord32be_bs = endianRead4 MSB
readWord32le_bs :: Monad m => Iteratee B.ByteString m Word32
readWord32le_bs = endianRead4 LSB
readWord64be_bs :: Monad m => Iteratee B.ByteString m Word64
readWord64be_bs = endianRead8 MSB
readWord64le_bs :: Monad m => Iteratee B.ByteString m Word64
readWord64le_bs = endianRead8 LSB
word16' :: [Word8] -> Word16
word16' [c1,c2] = word16 c1 c2
word16' _ = error "iteratee: internal error in word16'"
word16 :: Word8 -> Word8 -> Word16
word16 c1 c2 = (fromIntegral c1 `shiftL` 8) .|. fromIntegral c2
word32' :: [Word8] -> Word32
word32' [c1,c2,c3,c4] = word32 c1 c2 c3 c4
word32' _ = error "iteratee: internal error in word32'"
word32 :: Word8 -> Word8 -> Word8 -> Word8 -> Word32
word32 c1 c2 c3 c4 =
(fromIntegral c1 `shiftL` 24) .|.
(fromIntegral c2 `shiftL` 16) .|.
(fromIntegral c3 `shiftL` 8) .|.
fromIntegral c4
word64' :: [Word8] -> Word64
word64' [c1,c2,c3,c4,c5,c6,c7,c8] = word64 c1 c2 c3 c4 c5 c6 c7 c8
word64' _ = error "iteratee: internal error in word64'"
word64
:: Word8 -> Word8 -> Word8 -> Word8
-> Word8 -> Word8 -> Word8 -> Word8
-> Word64
word64 c1 c2 c3 c4 c5 c6 c7 c8 =
(fromIntegral c1 `shiftL` 56) .|.
(fromIntegral c2 `shiftL` 48) .|.
(fromIntegral c3 `shiftL` 40) .|.
(fromIntegral c4 `shiftL` 32) .|.
(fromIntegral c5 `shiftL` 24) .|.
(fromIntegral c6 `shiftL` 16) .|.
(fromIntegral c7 `shiftL` 8) .|.
fromIntegral c8