{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE RankNTypes #-}
module Codec.CBOR.Decoding
(
Decoder
, DecodeAction(..)
, liftST
, getDecodeAction
, decodeWord
, decodeWord8
, decodeWord16
, decodeWord32
, decodeWord64
, decodeNegWord
, decodeNegWord64
, decodeInt
, decodeInt8
, decodeInt16
, decodeInt32
, decodeInt64
, decodeInteger
, decodeFloat
, decodeDouble
, decodeBytes
, decodeBytesIndef
, decodeString
, decodeStringIndef
, decodeListLen
, decodeListLenIndef
, decodeMapLen
, decodeMapLenIndef
, decodeTag
, decodeTag64
, decodeBool
, decodeNull
, decodeSimple
, decodeWordOf
, decodeListLenOf
, decodeListLenOrIndef
, decodeMapLenOrIndef
, decodeBreakOr
, peekTokenType
, peekAvailable
, TokenType(..)
, decodeSequenceLenIndef
, decodeSequenceLenN
) where
#include "cbor.h"
import GHC.Exts
import GHC.Word
import GHC.Int
import Data.Text (Text)
import Data.ByteString (ByteString)
import Control.Applicative
import Control.Monad.ST
import qualified Control.Monad.Fail as Fail
import Prelude hiding (decodeFloat)
data Decoder s a = Decoder {
runDecoder :: forall r. (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
}
data DecodeAction s a
= ConsumeWord (Word# -> ST s (DecodeAction s a))
| ConsumeWord8 (Word# -> ST s (DecodeAction s a))
| ConsumeWord16 (Word# -> ST s (DecodeAction s a))
| ConsumeWord32 (Word# -> ST s (DecodeAction s a))
| ConsumeNegWord (Word# -> ST s (DecodeAction s a))
| ConsumeInt (Int# -> ST s (DecodeAction s a))
| ConsumeInt8 (Int# -> ST s (DecodeAction s a))
| ConsumeInt16 (Int# -> ST s (DecodeAction s a))
| ConsumeInt32 (Int# -> ST s (DecodeAction s a))
| ConsumeListLen (Int# -> ST s (DecodeAction s a))
| ConsumeMapLen (Int# -> ST s (DecodeAction s a))
| ConsumeTag (Word# -> ST s (DecodeAction s a))
#if defined(ARCH_32bit)
| ConsumeWord64 (Word64# -> ST s (DecodeAction s a))
| ConsumeNegWord64 (Word64# -> ST s (DecodeAction s a))
| ConsumeInt64 (Int64# -> ST s (DecodeAction s a))
| ConsumeListLen64 (Int64# -> ST s (DecodeAction s a))
| ConsumeMapLen64 (Int64# -> ST s (DecodeAction s a))
| ConsumeTag64 (Word64# -> ST s (DecodeAction s a))
#endif
| ConsumeInteger (Integer -> ST s (DecodeAction s a))
| ConsumeFloat (Float# -> ST s (DecodeAction s a))
| ConsumeDouble (Double# -> ST s (DecodeAction s a))
| ConsumeBytes (ByteString -> ST s (DecodeAction s a))
| ConsumeString (Text -> ST s (DecodeAction s a))
| ConsumeBool (Bool -> ST s (DecodeAction s a))
| ConsumeSimple (Word# -> ST s (DecodeAction s a))
| ConsumeBytesIndef (ST s (DecodeAction s a))
| ConsumeStringIndef (ST s (DecodeAction s a))
| ConsumeListLenIndef (ST s (DecodeAction s a))
| ConsumeMapLenIndef (ST s (DecodeAction s a))
| ConsumeNull (ST s (DecodeAction s a))
| ConsumeListLenOrIndef (Int# -> ST s (DecodeAction s a))
| ConsumeMapLenOrIndef (Int# -> ST s (DecodeAction s a))
| ConsumeBreakOr (Bool -> ST s (DecodeAction s a))
| PeekTokenType (TokenType -> ST s (DecodeAction s a))
| PeekAvailable (Int# -> ST s (DecodeAction s a))
| Fail String
| Done a
data TokenType
= TypeUInt
| TypeUInt64
| TypeNInt
| TypeNInt64
| TypeInteger
| TypeFloat16
| TypeFloat32
| TypeFloat64
| TypeBytes
| TypeBytesIndef
| TypeString
| TypeStringIndef
| TypeListLen
| TypeListLen64
| TypeListLenIndef
| TypeMapLen
| TypeMapLen64
| TypeMapLenIndef
| TypeTag
| TypeTag64
| TypeBool
| TypeNull
| TypeSimple
| TypeBreak
| TypeInvalid
deriving (Eq, Ord, Enum, Bounded, Show)
instance Functor (Decoder s) where
{-# INLINE fmap #-}
fmap f = \d -> Decoder $ \k -> runDecoder d (k . f)
instance Applicative (Decoder s) where
{-# INLINE pure #-}
pure = \x -> Decoder $ \k -> k x
{-# INLINE (<*>) #-}
(<*>) = \df dx -> Decoder $ \k ->
runDecoder df (\f -> runDecoder dx (\x -> k (f x)))
{-# INLINE (*>) #-}
(*>) = \dm dn -> Decoder $ \k -> runDecoder dm (\_ -> runDecoder dn k)
instance Monad (Decoder s) where
return = pure
{-# INLINE (>>=) #-}
(>>=) = \dm f -> Decoder $ \k -> runDecoder dm (\m -> runDecoder (f m) k)
{-# INLINE (>>) #-}
(>>) = (*>)
fail = Fail.fail
instance Fail.MonadFail (Decoder s) where
fail msg = Decoder $ \_ -> return (Fail msg)
liftST :: ST s a -> Decoder s a
liftST m = Decoder $ \k -> m >>= k
getDecodeAction :: Decoder s a -> ST s (DecodeAction s a)
getDecodeAction (Decoder k) = k (\x -> return (Done x))
decodeWord :: Decoder s Word
decodeWord = Decoder (\k -> return (ConsumeWord (\w# -> k (W# w#))))
{-# INLINE decodeWord #-}
decodeWord8 :: Decoder s Word8
decodeWord8 = Decoder (\k -> return (ConsumeWord8 (\w# -> k (W8# w#))))
{-# INLINE decodeWord8 #-}
decodeWord16 :: Decoder s Word16
decodeWord16 = Decoder (\k -> return (ConsumeWord16 (\w# -> k (W16# w#))))
{-# INLINE decodeWord16 #-}
decodeWord32 :: Decoder s Word32
decodeWord32 = Decoder (\k -> return (ConsumeWord32 (\w# -> k (W32# w#))))
{-# INLINE decodeWord32 #-}
decodeWord64 :: Decoder s Word64
{-# INLINE decodeWord64 #-}
decodeWord64 =
#if defined(ARCH_64bit)
Decoder (\k -> return (ConsumeWord (\w# -> k (W64# w#))))
#else
Decoder (\k -> return (ConsumeWord64 (\w64# -> k (W64# w64#))))
#endif
decodeNegWord :: Decoder s Word
decodeNegWord = Decoder (\k -> return (ConsumeNegWord (\w# -> k (W# w#))))
{-# INLINE decodeNegWord #-}
decodeNegWord64 :: Decoder s Word64
{-# INLINE decodeNegWord64 #-}
decodeNegWord64 =
#if defined(ARCH_64bit)
Decoder (\k -> return (ConsumeNegWord (\w# -> k (W64# w#))))
#else
Decoder (\k -> return (ConsumeNegWord64 (\w64# -> k (W64# w64#))))
#endif
decodeInt :: Decoder s Int
decodeInt = Decoder (\k -> return (ConsumeInt (\n# -> k (I# n#))))
{-# INLINE decodeInt #-}
decodeInt8 :: Decoder s Int8
decodeInt8 = Decoder (\k -> return (ConsumeInt8 (\w# -> k (I8# w#))))
{-# INLINE decodeInt8 #-}
decodeInt16 :: Decoder s Int16
decodeInt16 = Decoder (\k -> return (ConsumeInt16 (\w# -> k (I16# w#))))
{-# INLINE decodeInt16 #-}
decodeInt32 :: Decoder s Int32
decodeInt32 = Decoder (\k -> return (ConsumeInt32 (\w# -> k (I32# w#))))
{-# INLINE decodeInt32 #-}
decodeInt64 :: Decoder s Int64
{-# INLINE decodeInt64 #-}
decodeInt64 =
#if defined(ARCH_64bit)
Decoder (\k -> return (ConsumeInt (\n# -> k (I64# n#))))
#else
Decoder (\k -> return (ConsumeInt64 (\n64# -> k (I64# n64#))))
#endif
decodeInteger :: Decoder s Integer
decodeInteger = Decoder (\k -> return (ConsumeInteger (\n -> k n)))
{-# INLINE decodeInteger #-}
decodeFloat :: Decoder s Float
decodeFloat = Decoder (\k -> return (ConsumeFloat (\f# -> k (F# f#))))
{-# INLINE decodeFloat #-}
decodeDouble :: Decoder s Double
decodeDouble = Decoder (\k -> return (ConsumeDouble (\f# -> k (D# f#))))
{-# INLINE decodeDouble #-}
decodeBytes :: Decoder s ByteString
decodeBytes = Decoder (\k -> return (ConsumeBytes (\bs -> k bs)))
{-# INLINE decodeBytes #-}
decodeBytesIndef :: Decoder s ()
decodeBytesIndef = Decoder (\k -> return (ConsumeBytesIndef (k ())))
{-# INLINE decodeBytesIndef #-}
decodeString :: Decoder s Text
decodeString = Decoder (\k -> return (ConsumeString (\str -> k str)))
{-# INLINE decodeString #-}
decodeStringIndef :: Decoder s ()
decodeStringIndef = Decoder (\k -> return (ConsumeStringIndef (k ())))
{-# INLINE decodeStringIndef #-}
decodeListLen :: Decoder s Int
decodeListLen = Decoder (\k -> return (ConsumeListLen (\n# -> k (I# n#))))
{-# INLINE decodeListLen #-}
decodeListLenIndef :: Decoder s ()
decodeListLenIndef = Decoder (\k -> return (ConsumeListLenIndef (k ())))
{-# INLINE decodeListLenIndef #-}
decodeMapLen :: Decoder s Int
decodeMapLen = Decoder (\k -> return (ConsumeMapLen (\n# -> k (I# n#))))
{-# INLINE decodeMapLen #-}
decodeMapLenIndef :: Decoder s ()
decodeMapLenIndef = Decoder (\k -> return (ConsumeMapLenIndef (k ())))
{-# INLINE decodeMapLenIndef #-}
decodeTag :: Decoder s Word
decodeTag = Decoder (\k -> return (ConsumeTag (\w# -> k (W# w#))))
{-# INLINE decodeTag #-}
decodeTag64 :: Decoder s Word64
{-# INLINE decodeTag64 #-}
decodeTag64 =
#if defined(ARCH_64bit)
Decoder (\k -> return (ConsumeTag (\w# -> k (W64# w#))))
#else
Decoder (\k -> return (ConsumeTag64 (\w64# -> k (W64# w64#))))
#endif
decodeBool :: Decoder s Bool
decodeBool = Decoder (\k -> return (ConsumeBool (\b -> k b)))
{-# INLINE decodeBool #-}
decodeNull :: Decoder s ()
decodeNull = Decoder (\k -> return (ConsumeNull (k ())))
{-# INLINE decodeNull #-}
decodeSimple :: Decoder s Word8
decodeSimple = Decoder (\k -> return (ConsumeSimple (\w# -> k (W8# w#))))
{-# INLINE decodeSimple #-}
decodeWordOf :: Word
-> Decoder s ()
decodeWordOf n = do
n' <- decodeWord
if n == n' then return ()
else fail $ "expected word " ++ show n
{-# INLINE decodeWordOf #-}
decodeListLenOf :: Int -> Decoder s ()
decodeListLenOf len = do
len' <- decodeListLen
if len == len' then return ()
else fail $ "expected list of length " ++ show len
{-# INLINE decodeListLenOf #-}
decodeListLenOrIndef :: Decoder s (Maybe Int)
decodeListLenOrIndef =
Decoder (\k -> return (ConsumeListLenOrIndef (\n# ->
if I# n# >= 0
then k (Just (I# n#))
else k Nothing)))
{-# INLINE decodeListLenOrIndef #-}
decodeMapLenOrIndef :: Decoder s (Maybe Int)
decodeMapLenOrIndef =
Decoder (\k -> return (ConsumeMapLenOrIndef (\n# ->
if I# n# >= 0
then k (Just (I# n#))
else k Nothing)))
{-# INLINE decodeMapLenOrIndef #-}
decodeBreakOr :: Decoder s Bool
decodeBreakOr = Decoder (\k -> return (ConsumeBreakOr (\b -> k b)))
{-# INLINE decodeBreakOr #-}
peekTokenType :: Decoder s TokenType
peekTokenType = Decoder (\k -> return (PeekTokenType (\tk -> k tk)))
{-# INLINE peekTokenType #-}
peekAvailable :: Decoder s Int
peekAvailable = Decoder (\k -> return (PeekAvailable (\len# -> k (I# len#))))
{-# INLINE peekAvailable #-}
decodeSequenceLenIndef :: (r -> a -> r)
-> r
-> (r -> r')
-> Decoder s a
-> Decoder s r'
decodeSequenceLenIndef f z g get =
go z
where
go !acc = do
stop <- decodeBreakOr
if stop then return $! g acc
else do !x <- get; go (f acc x)
{-# INLINE decodeSequenceLenIndef #-}
decodeSequenceLenN :: (r -> a -> r)
-> r
-> (r -> r')
-> Int
-> Decoder s a
-> Decoder s r'
decodeSequenceLenN f z g c get =
go z c
where
go !acc 0 = return $! g acc
go !acc n = do !x <- get; go (f acc x) (n-1)
{-# INLINE decodeSequenceLenN #-}