module Data.Deserializer
(
Deserializer(..)
, BinaryDeserializer(..)
, CerealDeserializer(..)
, word16H
, word32H
, word64H
, word
, wordL
, wordB
, wordH
, int8
, int16
, int16L
, int16B
, int16H
, int32
, int32L
, int32B
, int32H
, int64
, int64L
, int64B
, int64H
, int
, intL
, intB
, intH
, module Text.Parser.Combinators
, label
, module Text.Parser.LookAhead
, LittleEndianDeserializer(..)
, BigEndianDeserializer(..)
, deserializeIn
, deserializeH
, Deserializable(..)
, getIn
, getL
, getB
, getH
, RestDeserializable(..)
) where
import Prelude hiding (take)
import GHC.Generics (Generic)
import Data.Typeable (Typeable)
import Data.Data (Data)
import Data.Proxy (Proxy(..))
import Data.Endian (Endian(..), swapEndian)
import Data.Word
import Data.Int
import Data.Bits ((.|.), shiftL)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Unsafe as BS
import qualified Data.ByteString.Short as SBS
import qualified Data.ByteString.Lazy as LBS
import qualified Data.ByteString.Builder as BB
import qualified Data.Binary.Get as B
import qualified Data.Binary.Get.Internal as B
import qualified Data.Serialize.Get as S
import Text.Parser.Combinators
import Text.Parser.LookAhead
import Control.Applicative (Applicative(..), Alternative,
(<$>), (<$), (<*>), (*>), (<|>))
import Control.Monad (unless)
class (Monad μ, Parsing μ) ⇒ Deserializer μ where
endian ∷ Proxy μ → Endian
#ifdef WORDS_BIGENDIAN
endian _ = BigEndian
#else
endian _ = LittleEndian
#endif
word8 ∷ μ Word8
word8 = BS.unsafeHead <$> take 1 <?> "word8"
word16 ∷ μ Word16
word16 = getIn (endian (Proxy ∷ Proxy μ))
word32 ∷ μ Word32
word32 = getIn (endian (Proxy ∷ Proxy μ))
word64 ∷ μ Word64
word64 = getIn (endian (Proxy ∷ Proxy μ))
word16L ∷ μ Word16
word16L = (<?> "word16")
$ do bs ← take 2
let l = BS.unsafeIndex bs 0
h = BS.unsafeIndex bs 1
return $ shiftL (fromIntegral h) 8 .|. fromIntegral l
word16B ∷ μ Word16
word16B = swapEndian <$> word16L
word32L ∷ μ Word32
word32L = (<?> "word32")
$ do bs ← take 4
let o₀ = BS.unsafeIndex bs 0
o₁ = BS.unsafeIndex bs 1
o₂ = BS.unsafeIndex bs 2
o₃ = BS.unsafeIndex bs 3
return $ shiftL (fromIntegral o₃) 24
.|. shiftL (fromIntegral o₂) 16
.|. shiftL (fromIntegral o₁) 8
.|. fromIntegral o₀
word32B ∷ μ Word32
word32B = swapEndian <$> word32L
word64L ∷ μ Word64
word64L = (<?> "word64")
$ do bs ← take 8
let o₀ = BS.unsafeIndex bs 0
o₁ = BS.unsafeIndex bs 1
o₂ = BS.unsafeIndex bs 2
o₃ = BS.unsafeIndex bs 3
o₄ = BS.unsafeIndex bs 4
o₅ = BS.unsafeIndex bs 5
o₆ = BS.unsafeIndex bs 6
o₇ = BS.unsafeIndex bs 7
return $ shiftL (fromIntegral o₇) 56
.|. shiftL (fromIntegral o₆) 48
.|. shiftL (fromIntegral o₅) 40
.|. shiftL (fromIntegral o₄) 32
.|. shiftL (fromIntegral o₃) 24
.|. shiftL (fromIntegral o₂) 16
.|. shiftL (fromIntegral o₁) 8
.|. fromIntegral o₀
word64B ∷ μ Word64
word64B = swapEndian <$> word64L
satisfy ∷ (Word8 → Bool) → μ Word8
satisfy p = do w ← word8
if p w then return w
else unexpected (show w)
byte ∷ Word8 → μ Word8
byte w = (<?> "byte " ++ show w)
$ do w' ← word8
if w' == w then return w'
else unexpected (show w')
notByte ∷ Word8 → μ Word8
notByte w = (<?> "not byte " ++ show w)
$ do w' ← word8
if w' == w then unexpected (show w')
else return w'
bytes ∷ BS.ByteString → μ BS.ByteString
bytes bs = (<?> "bytes " ++ show (BS.unpack bs))
$ do bs' ← take (BS.length bs)
if bs' == bs then return bs'
else unexpected (show $ BS.unpack bs')
skip ∷ Int → μ ()
skip n | n <= 0 = pure ()
| otherwise = word8 *> skip (n 1)
ensure ∷ Int → μ BS.ByteString
ensure_ ∷ Int → μ ()
ensure_ = (() <$) . ensure
take ∷ Int → μ BS.ByteString
chunk ∷ μ BS.ByteString
isolate ∷ Int → μ α → μ α
newtype BinaryDeserializer α =
BinaryDeserializer { binaryDeserializer ∷ B.Get α }
deriving (Typeable, Generic, Functor, Applicative,
Alternative, Monad)
instance Parsing BinaryDeserializer where
try p = p
p <?> l = BinaryDeserializer (B.label l (binaryDeserializer p))
skipMany p = ((True <$ p) <|> pure False) >>= \case
True → skipMany p
False → return ()
unexpected = fail
eof = BinaryDeserializer
$ B.isEmpty >>= \case
True → return ()
False → fail "Parsing.eof"
notFollowedBy p = BinaryDeserializer
$ (B.lookAheadE (Left <$> (binaryDeserializer p)) <|>
pure (Right ())) >>= \case
Left e → fail (show e)
Right _ → return ()
instance LookAheadParsing BinaryDeserializer where
lookAhead = BinaryDeserializer . B.lookAhead . binaryDeserializer
instance Deserializer BinaryDeserializer where
word8 = BinaryDeserializer B.getWord8
word16L = BinaryDeserializer B.getWord16le
word16B = BinaryDeserializer B.getWord16be
word32L = BinaryDeserializer B.getWord32le
word32B = BinaryDeserializer B.getWord32be
word64L = BinaryDeserializer B.getWord64le
word64B = BinaryDeserializer B.getWord64be
skip = BinaryDeserializer . B.skip
ensure n = BinaryDeserializer (B.ensureN n *> B.get)
ensure_ = BinaryDeserializer . B.ensureN
take = BinaryDeserializer . B.getByteString
chunk = BinaryDeserializer
$ do bs ← B.get
if BS.null bs
then do
e ← B.isEmpty
if e
then return bs
else B.get
else
return bs
isolate n d = BinaryDeserializer $ B.isolate n (binaryDeserializer d)
newtype CerealDeserializer α =
CerealDeserializer { cerealDeserializer ∷ S.Get α }
deriving (Typeable, Generic, Functor, Applicative,
Alternative, Monad)
instance Parsing CerealDeserializer where
try p = p
p <?> l = CerealDeserializer (S.label l (cerealDeserializer p))
skipMany p = ((True <$ p) <|> pure False) >>= \case
True → skipMany p
False → return ()
unexpected = fail
eof = CerealDeserializer
$ ((False <$ S.lookAheadM (Nothing <$ S.getWord8)) <|>
pure True) >>= \case
True → return ()
False → fail "Parsing.eof"
notFollowedBy p = CerealDeserializer
$ (S.lookAheadE (Left <$> (cerealDeserializer p)) <|>
pure (Right ())) >>= \case
Left e → fail (show e)
Right _ → return ()
instance LookAheadParsing CerealDeserializer where
lookAhead = CerealDeserializer . S.lookAhead . cerealDeserializer
instance Deserializer CerealDeserializer where
word8 = CerealDeserializer S.getWord8
word16L = CerealDeserializer S.getWord16le
word16B = CerealDeserializer S.getWord16be
word32L = CerealDeserializer S.getWord32le
word32B = CerealDeserializer S.getWord32be
word64L = CerealDeserializer S.getWord64le
word64B = CerealDeserializer S.getWord64be
skip = CerealDeserializer . S.skip
ensure = CerealDeserializer . S.ensure
take = CerealDeserializer . S.getBytes
chunk = CerealDeserializer
$ (<|> pure BS.empty)
$ do bs ← S.ensure 1
S.uncheckedSkip (BS.length bs)
return bs
isolate n d = CerealDeserializer (S.isolate n (cerealDeserializer d))
word16H ∷ Deserializer μ ⇒ μ Word16
#ifdef WORDS_BIGENDIAN
word16H = word16B
#else
word16H = word16L
#endif
word32H ∷ Deserializer μ ⇒ μ Word32
#ifdef WORDS_BIGENDIAN
word32H = word32B
#else
word32H = word32L
#endif
word64H ∷ Deserializer μ ⇒ μ Word64
#ifdef WORDS_BIGENDIAN
word64H = word64B
#else
word64H = word64L
#endif
word ∷ Deserializer μ ⇒ μ Word
#if WORD_SIZE_IN_BITS == 32
word = fromIntegral <$> word32
#else
word = fromIntegral <$> word64
#endif
wordL ∷ Deserializer μ ⇒ μ Word
#if WORD_SIZE_IN_BITS == 32
wordL = fromIntegral <$> word32L
#else
wordL = fromIntegral <$> word64L
#endif
wordB ∷ Deserializer μ ⇒ μ Word
#if WORD_SIZE_IN_BITS == 32
wordB = fromIntegral <$> word32B
#else
wordB = fromIntegral <$> word64B
#endif
wordH ∷ Deserializer μ ⇒ μ Word
#ifdef WORDS_BIGENDIAN
wordH = wordB
#else
wordH = wordL
#endif
int8 ∷ Deserializer μ ⇒ μ Int8
int8 = fromIntegral <$> word8
int16 ∷ Deserializer μ ⇒ μ Int16
int16 = fromIntegral <$> word16
int16L ∷ Deserializer μ ⇒ μ Int16
int16L = fromIntegral <$> word16L
int16B ∷ Deserializer μ ⇒ μ Int16
int16B = fromIntegral <$> word16B
int16H ∷ Deserializer μ ⇒ μ Int16
int16H = fromIntegral <$> word16H
int32 ∷ Deserializer μ ⇒ μ Int32
int32 = fromIntegral <$> word32
int32L ∷ Deserializer μ ⇒ μ Int32
int32L = fromIntegral <$> word32L
int32B ∷ Deserializer μ ⇒ μ Int32
int32B = fromIntegral <$> word32B
int32H ∷ Deserializer μ ⇒ μ Int32
int32H = fromIntegral <$> word32H
int64 ∷ Deserializer μ ⇒ μ Int64
int64 = fromIntegral <$> word64
int64L ∷ Deserializer μ ⇒ μ Int64
int64L = fromIntegral <$> word64L
int64B ∷ Deserializer μ ⇒ μ Int64
int64B = fromIntegral <$> word64B
int64H ∷ Deserializer μ ⇒ μ Int64
int64H = fromIntegral <$> word64H
int ∷ Deserializer μ ⇒ μ Int
#if WORD_SIZE_IN_BITS == 32
int = fromIntegral <$> int32
#else
int = fromIntegral <$> int64
#endif
intL ∷ Deserializer μ ⇒ μ Int
#if WORD_SIZE_IN_BITS == 32
intL = fromIntegral <$> int32L
#else
intL = fromIntegral <$> int64L
#endif
intB ∷ Deserializer μ ⇒ μ Int
#if WORD_SIZE_IN_BITS == 32
intB = fromIntegral <$> int32B
#else
intB = fromIntegral <$> int64B
#endif
intH ∷ Deserializer μ ⇒ μ Int
#if WORD_SIZE_IN_BITS == 32
intH = fromIntegral <$> int32H
#else
intH = fromIntegral <$> int64H
#endif
label ∷ Parsing μ ⇒ String → μ α → μ α
label = flip (<?>)
newtype LittleEndianDeserializer μ α =
LittleEndianDeserializer { deserializeL ∷ μ α }
deriving (Typeable, Data, Generic, Functor, Applicative,
Alternative, Monad, Parsing, LookAheadParsing)
instance Deserializer μ ⇒ Deserializer (LittleEndianDeserializer μ) where
endian _ = LittleEndian
word8 = LittleEndianDeserializer word8
word16 = LittleEndianDeserializer word16L
word32 = LittleEndianDeserializer word32L
word64 = LittleEndianDeserializer word64L
word16L = LittleEndianDeserializer word16L
word16B = LittleEndianDeserializer word16B
word32L = LittleEndianDeserializer word32L
word32B = LittleEndianDeserializer word32B
word64L = LittleEndianDeserializer word64L
word64B = LittleEndianDeserializer word64B
satisfy = LittleEndianDeserializer . satisfy
byte = LittleEndianDeserializer . byte
notByte = LittleEndianDeserializer . notByte
bytes = LittleEndianDeserializer . bytes
skip = LittleEndianDeserializer . skip
ensure = LittleEndianDeserializer . ensure
ensure_ = LittleEndianDeserializer . ensure_
take = LittleEndianDeserializer . take
chunk = LittleEndianDeserializer chunk
isolate n = LittleEndianDeserializer . isolate n . deserializeL
newtype BigEndianDeserializer μ α =
BigEndianDeserializer { deserializeB ∷ μ α }
deriving (Typeable, Data, Generic, Functor, Applicative,
Alternative, Monad, Parsing, LookAheadParsing)
instance Deserializer μ ⇒ Deserializer (BigEndianDeserializer μ) where
endian _ = BigEndian
word8 = BigEndianDeserializer word8
word16 = BigEndianDeserializer word16B
word32 = BigEndianDeserializer word32B
word64 = BigEndianDeserializer word64B
word16L = BigEndianDeserializer word16L
word16B = BigEndianDeserializer word16B
word32L = BigEndianDeserializer word32L
word32B = BigEndianDeserializer word32B
word64L = BigEndianDeserializer word64L
word64B = BigEndianDeserializer word64B
satisfy = BigEndianDeserializer . satisfy
byte = BigEndianDeserializer . byte
notByte = BigEndianDeserializer . notByte
bytes = BigEndianDeserializer . bytes
skip = BigEndianDeserializer . skip
ensure = BigEndianDeserializer . ensure
ensure_ = BigEndianDeserializer . ensure_
take = BigEndianDeserializer . take
chunk = BigEndianDeserializer chunk
isolate n = BigEndianDeserializer . isolate n . deserializeB
deserializeIn ∷ Deserializer μ
⇒ Endian → (∀ μ' . (Deserializer μ') ⇒ μ' α) → μ α
deserializeIn LittleEndian = deserializeL
deserializeIn BigEndian = deserializeB
deserializeH ∷ Deserializer μ ⇒ (∀ μ' . (Deserializer μ') ⇒ μ' α) → μ α
#ifdef WORDS_BIGENDIAN
deserializeH = deserializeB
#else
deserializeH = deserializeL
#endif
class Deserializable α where
get ∷ Deserializer μ ⇒ μ α
instance Deserializable Bool where
get = do w ← word8
case w of
0 → return False
1 → return True
_ → unexpected (show w)
instance Deserializable Word8 where
get = word8
instance Deserializable Word16 where
get = word16
instance Deserializable Word32 where
get = word32
instance Deserializable Word64 where
get = word64
instance Deserializable Word where
get = word
instance Deserializable Int8 where
get = int8
instance Deserializable Int16 where
get = int16
instance Deserializable Int32 where
get = int32
instance Deserializable Int64 where
get = int64
instance Deserializable Int where
get = int
instance (Deserializable α, Deserializable β) ⇒ Deserializable (α, β) where
get = (,) <$> get <*> get
instance Deserializable α ⇒ Deserializable (Maybe α) where
get = do w ← word8
case w of
0 → return Nothing
1 → Just <$> get
_ → unexpected (show w)
instance (Deserializable α, Deserializable β)
⇒ Deserializable (Either α β) where
get = do w ← word8
case w of
0 → Left <$> get
1 → Right <$> get
_ → unexpected (show w)
instance Deserializable BS.ByteString where
get = do l ← int <?> "length"
unless (l >= 0) $ unexpected "negative length"
take l <?> "contents"
instance Deserializable SBS.ShortByteString where
get = SBS.toShort <$> get
getIn ∷ (Deserializer μ, Deserializable α) ⇒ Endian → μ α
getIn e = deserializeIn e get
getL ∷ (Deserializer μ, Deserializable α) ⇒ μ α
getL = deserializeL get
getB ∷ (Deserializer μ, Deserializable α) ⇒ μ α
getB = deserializeB get
getH ∷ (Deserializer μ, Deserializable α) ⇒ μ α
#ifdef WORDS_BIGENDIAN
getH = getB
#else
getH = getL
#endif
class RestDeserializable α where
getRest ∷ Deserializer μ ⇒ μ α
instance RestDeserializable BS.ByteString where
getRest = go []
where go acc = do bs ← chunk
if BS.null bs then return $ BS.concat $ reverse acc
else go (bs : acc)
instance RestDeserializable SBS.ShortByteString where
getRest = SBS.toShort <$> getRest
instance RestDeserializable LBS.ByteString where
getRest = go []
where go acc = do bs ← chunk
if BS.null bs then return $ LBS.fromChunks $ reverse acc
else go (bs : acc)
instance RestDeserializable BB.Builder where
getRest = BB.lazyByteString <$> getRest
instance (RestDeserializable α, RestDeserializable β)
⇒ RestDeserializable (Either α β) where
getRest = word8 >>= \case
0 → Left <$> getRest
1 → Right <$> getRest
w → unexpected (show w)
instance (Deserializable α, RestDeserializable β)
⇒ RestDeserializable (α, β) where
getRest = (,) <$> get <*> getRest
instance Deserializable α ⇒ RestDeserializable [α] where
getRest = ([] <$ eof) <|> ((:) <$> get <*> getRest)