{-# LANGUAGE BangPatterns           #-}
{-# LANGUAGE CPP                    #-}
{-# LANGUAGE DeriveDataTypeable     #-}
{-# LANGUAGE FlexibleContexts       #-}
{-# LANGUAGE FlexibleInstances      #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MagicHash              #-}
{-# LANGUAGE MultiParamTypeClasses  #-}
{-# LANGUAGE OverloadedStrings      #-}
{-# LANGUAGE RankNTypes             #-}
#if __GLASGOW_HASKELL__ < 900
{-# OPTIONS_GHC -funfolding-keeness-factor=2.0 #-}
#endif
module Codec.CBOR.Read
  ( deserialiseFromBytes         
  , deserialiseFromBytesWithSize 
  , deserialiseIncremental       
  , DeserialiseFailure(..)
  , IDecode(..)
  , ByteOffset
  ) where
#include "cbor.h"
#if !MIN_VERSION_base(4,8,0)
import           Control.Applicative
#endif
import           GHC.Int
import           Control.DeepSeq
import           Control.Monad (ap)
import           Control.Monad.ST
import           Data.Array.IArray
import           Data.Array.Unboxed
import qualified Data.Array.Base as A
import           Data.Monoid
import           Data.Bits
import           Data.ByteString                (ByteString)
import qualified Data.ByteString                as BS
import qualified Data.ByteString.Unsafe         as BS
import qualified Data.ByteString.Lazy           as LBS
import qualified Data.ByteString.Lazy.Internal  as LBS
import qualified Data.Text          as T
import qualified Data.Text.Encoding as T
import           Data.Word
import           GHC.Word
#if defined(ARCH_32bit)
import           GHC.IntWord64
#endif
import           GHC.Exts
import           GHC.Float (float2Double)
import           Data.Typeable
import           Control.Exception
import           Prelude hiding (fromIntegral)
import qualified Codec.CBOR.ByteArray as BA
import           Codec.CBOR.Decoding hiding (DecodeAction(Done, Fail))
import           Codec.CBOR.Decoding (DecodeAction)
import qualified Codec.CBOR.Decoding as D
import           Codec.CBOR.Magic
data DeserialiseFailure = DeserialiseFailure ByteOffset String
  deriving (DeserialiseFailure -> DeserialiseFailure -> Bool
(DeserialiseFailure -> DeserialiseFailure -> Bool)
-> (DeserialiseFailure -> DeserialiseFailure -> Bool)
-> Eq DeserialiseFailure
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeserialiseFailure -> DeserialiseFailure -> Bool
== :: DeserialiseFailure -> DeserialiseFailure -> Bool
$c/= :: DeserialiseFailure -> DeserialiseFailure -> Bool
/= :: DeserialiseFailure -> DeserialiseFailure -> Bool
Eq, Int -> DeserialiseFailure -> ShowS
[DeserialiseFailure] -> ShowS
DeserialiseFailure -> String
(Int -> DeserialiseFailure -> ShowS)
-> (DeserialiseFailure -> String)
-> ([DeserialiseFailure] -> ShowS)
-> Show DeserialiseFailure
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DeserialiseFailure -> ShowS
showsPrec :: Int -> DeserialiseFailure -> ShowS
$cshow :: DeserialiseFailure -> String
show :: DeserialiseFailure -> String
$cshowList :: [DeserialiseFailure] -> ShowS
showList :: [DeserialiseFailure] -> ShowS
Show, Typeable)
instance NFData DeserialiseFailure where
  rnf :: DeserialiseFailure -> ()
rnf (DeserialiseFailure ByteOffset
offset String
msg) = ByteOffset -> ()
forall a. NFData a => a -> ()
rnf ByteOffset
offset () -> () -> ()
forall a b. a -> b -> b
`seq` String -> ()
forall a. NFData a => a -> ()
rnf String
msg () -> () -> ()
forall a b. a -> b -> b
`seq` ()
instance Exception DeserialiseFailure where
#if MIN_VERSION_base(4,8,0)
    displayException :: DeserialiseFailure -> String
displayException (DeserialiseFailure ByteOffset
off String
msg) =
      String
"Codec.CBOR: deserialising failed at offset "
           String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteOffset -> String
forall a. Show a => a -> String
show ByteOffset
off String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" : " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg
#endif
data IDecode s a
  = 
    
    
    Partial (Maybe BS.ByteString -> ST s (IDecode s a))
    
    
    
  | Done !BS.ByteString {-# UNPACK #-} !ByteOffset a
    
    
    
    
    
  | Fail !BS.ByteString {-# UNPACK #-} !ByteOffset DeserialiseFailure
deserialiseFromBytes :: (forall s. Decoder s a)
                     -> LBS.ByteString
                     -> Either DeserialiseFailure (LBS.ByteString, a)
deserialiseFromBytes :: forall a.
(forall s. Decoder s a)
-> ByteString -> Either DeserialiseFailure (ByteString, a)
deserialiseFromBytes forall s. Decoder s a
d ByteString
lbs =
    ((ByteString, ByteOffset, a) -> (ByteString, a))
-> Either DeserialiseFailure (ByteString, ByteOffset, a)
-> Either DeserialiseFailure (ByteString, a)
forall a b.
(a -> b)
-> Either DeserialiseFailure a -> Either DeserialiseFailure b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ByteString, ByteOffset, a) -> (ByteString, a)
forall {a} {b} {b}. (a, b, b) -> (a, b)
f (Either DeserialiseFailure (ByteString, ByteOffset, a)
 -> Either DeserialiseFailure (ByteString, a))
-> Either DeserialiseFailure (ByteString, ByteOffset, a)
-> Either DeserialiseFailure (ByteString, a)
forall a b. (a -> b) -> a -> b
$ (forall s. ST s (IDecode s a))
-> ByteString
-> Either DeserialiseFailure (ByteString, ByteOffset, a)
forall a.
(forall s. ST s (IDecode s a))
-> ByteString
-> Either DeserialiseFailure (ByteString, ByteOffset, a)
runIDecode (Decoder s a -> ST s (IDecode s a)
forall s a. Decoder s a -> ST s (IDecode s a)
deserialiseIncremental Decoder s a
forall s. Decoder s a
d) ByteString
lbs
  where f :: (a, b, b) -> (a, b)
f (a
rest, b
_, b
x) = (a
rest, b
x)
deserialiseFromBytesWithSize :: (forall s. Decoder s a)
                             -> LBS.ByteString
                             -> Either DeserialiseFailure (LBS.ByteString, ByteOffset, a)
deserialiseFromBytesWithSize :: forall a.
(forall s. Decoder s a)
-> ByteString
-> Either DeserialiseFailure (ByteString, ByteOffset, a)
deserialiseFromBytesWithSize forall s. Decoder s a
d ByteString
lbs =
    (forall s. ST s (IDecode s a))
-> ByteString
-> Either DeserialiseFailure (ByteString, ByteOffset, a)
forall a.
(forall s. ST s (IDecode s a))
-> ByteString
-> Either DeserialiseFailure (ByteString, ByteOffset, a)
runIDecode (Decoder s a -> ST s (IDecode s a)
forall s a. Decoder s a -> ST s (IDecode s a)
deserialiseIncremental Decoder s a
forall s. Decoder s a
d) ByteString
lbs
runIDecode :: (forall s. ST s (IDecode s a))
           -> LBS.ByteString
           -> Either DeserialiseFailure (LBS.ByteString, ByteOffset, a)
runIDecode :: forall a.
(forall s. ST s (IDecode s a))
-> ByteString
-> Either DeserialiseFailure (ByteString, ByteOffset, a)
runIDecode forall s. ST s (IDecode s a)
d ByteString
lbs =
    (forall s.
 ST s (Either DeserialiseFailure (ByteString, ByteOffset, a)))
-> Either DeserialiseFailure (ByteString, ByteOffset, a)
forall a. (forall s. ST s a) -> a
runST (ByteString
-> IDecode s a
-> ST s (Either DeserialiseFailure (ByteString, ByteOffset, a))
forall s a.
ByteString
-> IDecode s a
-> ST s (Either DeserialiseFailure (ByteString, ByteOffset, a))
go ByteString
lbs (IDecode s a
 -> ST s (Either DeserialiseFailure (ByteString, ByteOffset, a)))
-> ST s (IDecode s a)
-> ST s (Either DeserialiseFailure (ByteString, ByteOffset, a))
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ST s (IDecode s a)
forall s. ST s (IDecode s a)
d)
  where
    go :: LBS.ByteString
       -> IDecode s a
       -> ST s (Either DeserialiseFailure (LBS.ByteString, ByteOffset, a))
    go :: forall s a.
ByteString
-> IDecode s a
-> ST s (Either DeserialiseFailure (ByteString, ByteOffset, a))
go  ByteString
_                  (Fail ByteString
_ ByteOffset
_ DeserialiseFailure
err)  = Either DeserialiseFailure (ByteString, ByteOffset, a)
-> ST s (Either DeserialiseFailure (ByteString, ByteOffset, a))
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (DeserialiseFailure
-> Either DeserialiseFailure (ByteString, ByteOffset, a)
forall a b. a -> Either a b
Left DeserialiseFailure
err)
    go  ByteString
lbs'               (Done ByteString
bs ByteOffset
off a
x) = let rest :: ByteString
rest
                                                   | ByteString -> Bool
BS.null ByteString
bs = ByteString
lbs'
                                                   | Bool
otherwise  = ByteString -> ByteString -> ByteString
LBS.Chunk ByteString
bs ByteString
lbs'
                                             in Either DeserialiseFailure (ByteString, ByteOffset, a)
-> ST s (Either DeserialiseFailure (ByteString, ByteOffset, a))
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return ((ByteString, ByteOffset, a)
-> Either DeserialiseFailure (ByteString, ByteOffset, a)
forall a b. b -> Either a b
Right (ByteString
rest, ByteOffset
off, a
x))
    go  ByteString
LBS.Empty          (Partial  Maybe ByteString -> ST s (IDecode s a)
k)    = Maybe ByteString -> ST s (IDecode s a)
k Maybe ByteString
forall a. Maybe a
Nothing   ST s (IDecode s a)
-> (IDecode s a
    -> ST s (Either DeserialiseFailure (ByteString, ByteOffset, a)))
-> ST s (Either DeserialiseFailure (ByteString, ByteOffset, a))
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString
-> IDecode s a
-> ST s (Either DeserialiseFailure (ByteString, ByteOffset, a))
forall s a.
ByteString
-> IDecode s a
-> ST s (Either DeserialiseFailure (ByteString, ByteOffset, a))
go ByteString
LBS.Empty
    go (LBS.Chunk ByteString
bs ByteString
lbs') (Partial  Maybe ByteString -> ST s (IDecode s a)
k)    = Maybe ByteString -> ST s (IDecode s a)
k (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
bs) ST s (IDecode s a)
-> (IDecode s a
    -> ST s (Either DeserialiseFailure (ByteString, ByteOffset, a)))
-> ST s (Either DeserialiseFailure (ByteString, ByteOffset, a))
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString
-> IDecode s a
-> ST s (Either DeserialiseFailure (ByteString, ByteOffset, a))
forall s a.
ByteString
-> IDecode s a
-> ST s (Either DeserialiseFailure (ByteString, ByteOffset, a))
go ByteString
lbs'
deserialiseIncremental :: Decoder s a -> ST s (IDecode s a)
deserialiseIncremental :: forall s a. Decoder s a -> ST s (IDecode s a)
deserialiseIncremental Decoder s a
decoder = do
    DecodeAction s a
da <- Decoder s a -> ST s (DecodeAction s a)
forall s a. Decoder s a -> ST s (DecodeAction s a)
getDecodeAction Decoder s a
decoder
    IncrementalDecoder s (ByteString, ByteOffset, a)
-> ST s (IDecode s a)
forall s a.
IncrementalDecoder s (ByteString, ByteOffset, a)
-> ST s (IDecode s a)
runIncrementalDecoder (DecodeAction s a
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> IncrementalDecoder s (ByteString, ByteOffset, a)
runDecodeAction DecodeAction s a
da)
newtype IncrementalDecoder s a = IncrementalDecoder {
       forall s a.
IncrementalDecoder s a
-> forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r)
unIncrementalDecoder ::
         forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r)
     }
instance Functor (IncrementalDecoder s) where
    fmap :: forall a b.
(a -> b) -> IncrementalDecoder s a -> IncrementalDecoder s b
fmap a -> b
f IncrementalDecoder s a
a = IncrementalDecoder s a
a IncrementalDecoder s a
-> (a -> IncrementalDecoder s b) -> IncrementalDecoder s b
forall a b.
IncrementalDecoder s a
-> (a -> IncrementalDecoder s b) -> IncrementalDecoder s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= b -> IncrementalDecoder s b
forall a. a -> IncrementalDecoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> IncrementalDecoder s b)
-> (a -> b) -> a -> IncrementalDecoder s b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f
instance Applicative (IncrementalDecoder s) where
    pure :: forall a. a -> IncrementalDecoder s a
pure a
x = (forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r))
-> IncrementalDecoder s a
forall s a.
(forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r))
-> IncrementalDecoder s a
IncrementalDecoder ((forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r))
 -> IncrementalDecoder s a)
-> (forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r))
-> IncrementalDecoder s a
forall a b. (a -> b) -> a -> b
$ \a -> ST s (IDecode s r)
k -> a -> ST s (IDecode s r)
k a
x
    <*> :: forall a b.
IncrementalDecoder s (a -> b)
-> IncrementalDecoder s a -> IncrementalDecoder s b
(<*>) = IncrementalDecoder s (a -> b)
-> IncrementalDecoder s a -> IncrementalDecoder s b
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap
instance Monad (IncrementalDecoder s) where
    return :: forall a. a -> IncrementalDecoder s a
return = a -> IncrementalDecoder s a
forall a. a -> IncrementalDecoder s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
    {-# INLINE (>>=) #-}
    IncrementalDecoder s a
m >>= :: forall a b.
IncrementalDecoder s a
-> (a -> IncrementalDecoder s b) -> IncrementalDecoder s b
>>= a -> IncrementalDecoder s b
f = (forall r. (b -> ST s (IDecode s r)) -> ST s (IDecode s r))
-> IncrementalDecoder s b
forall s a.
(forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r))
-> IncrementalDecoder s a
IncrementalDecoder ((forall r. (b -> ST s (IDecode s r)) -> ST s (IDecode s r))
 -> IncrementalDecoder s b)
-> (forall r. (b -> ST s (IDecode s r)) -> ST s (IDecode s r))
-> IncrementalDecoder s b
forall a b. (a -> b) -> a -> b
$ \b -> ST s (IDecode s r)
k ->
                IncrementalDecoder s a
-> forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r)
forall s a.
IncrementalDecoder s a
-> forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r)
unIncrementalDecoder IncrementalDecoder s a
m ((a -> ST s (IDecode s r)) -> ST s (IDecode s r))
-> (a -> ST s (IDecode s r)) -> ST s (IDecode s r)
forall a b. (a -> b) -> a -> b
$ \a
x ->
                  IncrementalDecoder s b
-> forall r. (b -> ST s (IDecode s r)) -> ST s (IDecode s r)
forall s a.
IncrementalDecoder s a
-> forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r)
unIncrementalDecoder (a -> IncrementalDecoder s b
f a
x) b -> ST s (IDecode s r)
k
runIncrementalDecoder :: IncrementalDecoder s (ByteString, ByteOffset, a)
                      -> ST s (IDecode s a)
runIncrementalDecoder :: forall s a.
IncrementalDecoder s (ByteString, ByteOffset, a)
-> ST s (IDecode s a)
runIncrementalDecoder (IncrementalDecoder forall r.
((ByteString, ByteOffset, a) -> ST s (IDecode s r))
-> ST s (IDecode s r)
f) =
  ((ByteString, ByteOffset, a) -> ST s (IDecode s a))
-> ST s (IDecode s a)
forall r.
((ByteString, ByteOffset, a) -> ST s (IDecode s r))
-> ST s (IDecode s r)
f (\(ByteString
trailing, ByteOffset
off, a
x) -> IDecode s a -> ST s (IDecode s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDecode s a -> ST s (IDecode s a))
-> IDecode s a -> ST s (IDecode s a)
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteOffset -> a -> IDecode s a
forall s a. ByteString -> ByteOffset -> a -> IDecode s a
Done ByteString
trailing ByteOffset
off a
x)
decodeFail :: ByteString -> ByteOffset -> String -> IncrementalDecoder s a
decodeFail :: forall s a.
ByteString -> ByteOffset -> String -> IncrementalDecoder s a
decodeFail ByteString
trailing ByteOffset
off String
msg = (forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r))
-> IncrementalDecoder s a
forall s a.
(forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r))
-> IncrementalDecoder s a
IncrementalDecoder ((forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r))
 -> IncrementalDecoder s a)
-> (forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r))
-> IncrementalDecoder s a
forall a b. (a -> b) -> a -> b
$ \a -> ST s (IDecode s r)
_ -> IDecode s r -> ST s (IDecode s r)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDecode s r -> ST s (IDecode s r))
-> IDecode s r -> ST s (IDecode s r)
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteOffset -> DeserialiseFailure -> IDecode s r
forall s a.
ByteString -> ByteOffset -> DeserialiseFailure -> IDecode s a
Fail ByteString
trailing ByteOffset
off DeserialiseFailure
exn
  where exn :: DeserialiseFailure
exn = ByteOffset -> String -> DeserialiseFailure
DeserialiseFailure ByteOffset
off String
msg
needChunk :: IncrementalDecoder s (Maybe ByteString)
needChunk :: forall s. IncrementalDecoder s (Maybe ByteString)
needChunk = (forall r.
 (Maybe ByteString -> ST s (IDecode s r)) -> ST s (IDecode s r))
-> IncrementalDecoder s (Maybe ByteString)
forall s a.
(forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r))
-> IncrementalDecoder s a
IncrementalDecoder ((forall r.
  (Maybe ByteString -> ST s (IDecode s r)) -> ST s (IDecode s r))
 -> IncrementalDecoder s (Maybe ByteString))
-> (forall r.
    (Maybe ByteString -> ST s (IDecode s r)) -> ST s (IDecode s r))
-> IncrementalDecoder s (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Maybe ByteString -> ST s (IDecode s r)
k -> IDecode s r -> ST s (IDecode s r)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (IDecode s r -> ST s (IDecode s r))
-> IDecode s r -> ST s (IDecode s r)
forall a b. (a -> b) -> a -> b
$ (Maybe ByteString -> ST s (IDecode s r)) -> IDecode s r
forall s a. (Maybe ByteString -> ST s (IDecode s a)) -> IDecode s a
Partial ((Maybe ByteString -> ST s (IDecode s r)) -> IDecode s r)
-> (Maybe ByteString -> ST s (IDecode s r)) -> IDecode s r
forall a b. (a -> b) -> a -> b
$ \Maybe ByteString
mbs -> Maybe ByteString -> ST s (IDecode s r)
k Maybe ByteString
mbs
lift :: ST s a -> IncrementalDecoder s a
lift :: forall s a. ST s a -> IncrementalDecoder s a
lift ST s a
action = (forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r))
-> IncrementalDecoder s a
forall s a.
(forall r. (a -> ST s (IDecode s r)) -> ST s (IDecode s r))
-> IncrementalDecoder s a
IncrementalDecoder (\a -> ST s (IDecode s r)
k -> ST s a
action ST s a -> (a -> ST s (IDecode s r)) -> ST s (IDecode s r)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> ST s (IDecode s r)
k)
runDecodeAction :: DecodeAction s a
                -> IncrementalDecoder s (ByteString, ByteOffset, a)
runDecodeAction :: forall s a.
DecodeAction s a
-> IncrementalDecoder s (ByteString, ByteOffset, a)
runDecodeAction (D.Fail String
msg)        = ByteString
-> ByteOffset
-> String
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
ByteString -> ByteOffset -> String -> IncrementalDecoder s a
decodeFail ByteString
BS.empty ByteOffset
0 String
msg
runDecodeAction (D.Done a
x)          = (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a. a -> IncrementalDecoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
BS.empty, ByteOffset
0, a
x)
runDecodeAction (D.PeekAvailable Int# -> ST s (DecodeAction s a)
k) = ST s (DecodeAction s a) -> IncrementalDecoder s (DecodeAction s a)
forall s a. ST s a -> IncrementalDecoder s a
lift (Int# -> ST s (DecodeAction s a)
k Int#
0#) IncrementalDecoder s (DecodeAction s a)
-> (DecodeAction s a
    -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b.
IncrementalDecoder s a
-> (a -> IncrementalDecoder s b) -> IncrementalDecoder s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= DecodeAction s a
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> IncrementalDecoder s (ByteString, ByteOffset, a)
runDecodeAction
runDecodeAction DecodeAction s a
da = do
    Maybe ByteString
mbs <- IncrementalDecoder s (Maybe ByteString)
forall s. IncrementalDecoder s (Maybe ByteString)
needChunk
    case Maybe ByteString
mbs of
      Maybe ByteString
Nothing -> ByteString
-> ByteOffset
-> String
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
ByteString -> ByteOffset -> String -> IncrementalDecoder s a
decodeFail ByteString
BS.empty ByteOffset
0 String
"end of input"
      Just ByteString
bs -> DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow DecodeAction s a
da ByteString
bs ByteOffset
0
data SlowPath s a
   = FastDone                      {-# UNPACK #-} !ByteString a
   | SlowConsumeTokenBytes         {-# UNPACK #-} !ByteString (ByteString   -> ST s (DecodeAction s a)) {-# UNPACK #-} !Int
   | SlowConsumeTokenByteArray     {-# UNPACK #-} !ByteString (BA.ByteArray -> ST s (DecodeAction s a)) {-# UNPACK #-} !Int
   | SlowConsumeTokenString        {-# UNPACK #-} !ByteString (T.Text       -> ST s (DecodeAction s a)) {-# UNPACK #-} !Int
   | SlowConsumeTokenUtf8ByteArray {-# UNPACK #-} !ByteString (BA.ByteArray -> ST s (DecodeAction s a)) {-# UNPACK #-} !Int
#if defined(ARCH_32bit)
   | SlowPeekByteOffset            {-# UNPACK #-} !ByteString (Int64#       -> ST s (DecodeAction s a))
#else
   | SlowPeekByteOffset            {-# UNPACK #-} !ByteString (Int#         -> ST s (DecodeAction s a))
#endif
   | SlowDecodeAction              {-# UNPACK #-} !ByteString (DecodeAction s a)
   | SlowFail                      {-# UNPACK #-} !ByteString String
go_fast :: ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast :: forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast !ByteString
bs DecodeAction s a
da | ByteString -> Int
BS.length ByteString
bs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
9 = ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeWord Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (W# Word#
w#) -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeWord8 Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (W# Word#
w#) ->
        case Word# -> Word# -> Int#
gtWord# Word#
w# Word#
0xff## of
          Int#
0#                  -> Word# -> ST s (DecodeAction s a)
k Word#
w#  ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                   -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeWord16 Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (W# Word#
w#) ->
        case Word# -> Word# -> Int#
gtWord# Word#
w# Word#
0xffff## of
          Int#
0#                  -> Word# -> ST s (DecodeAction s a)
k Word#
w#  ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                   -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeWord32 Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (W# Word#
w#) ->
#if defined(ARCH_32bit)
                                 k w# >>= go_fast (BS.unsafeDrop sz bs)
#else
        case Word# -> Word# -> Int#
gtWord# Word#
w# Word#
0xffffffff## of
          Int#
0#                  -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                   -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
#endif
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeNegWord Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeNegWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (W# Word#
w#) -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeInt Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeInt (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (I# Int#
n#) -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeInt8 Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeInt (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (I# Int#
n#) ->
        case (Int#
n# Int# -> Int# -> Int#
># Int#
0x7f#) Int# -> Int# -> Int#
`orI#` (Int#
n# Int# -> Int# -> Int#
<# Int#
-0x80#) of
          Int#
0#                  -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                   -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeInt16 Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeInt (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (I# Int#
n#) ->
        case (Int#
n# Int# -> Int# -> Int#
># Int#
0x7fff#) Int# -> Int# -> Int#
`orI#` (Int#
n# Int# -> Int# -> Int#
<# Int#
-0x8000#) of
          Int#
0#                  -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                   -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeInt32 Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeInt (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (I# Int#
n#) ->
#if defined(ARCH_32bit)
                                 k n# >>= go_fast (BS.unsafeDrop sz bs)
#else
        case (Int#
n# Int# -> Int# -> Int#
># Int#
0x7fffffff#) Int# -> Int# -> Int#
`orI#` (Int#
n# Int# -> Int# -> Int#
<# Int#
-0x80000000#) of
          Int#
0#                  -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                   -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
#endif
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeListLen Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeListLen (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (I# Int#
n#) -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeMapLen Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeMapLen (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (I# Int#
n#) -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeTag Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeTag (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (W# Word#
w#) -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeWordCanonical Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz w :: Word
w@(W# Word#
w#)
        | Int -> Word -> Bool
isWordCanonical Int
sz Word
w  -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise             -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeWord8Canonical Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz w :: Word
w@(W# Word#
w#) ->
        case Word# -> Word# -> Int#
gtWord# Word#
w# Word#
0xff## of
          Int#
0# | Int -> Word -> Bool
isWordCanonical Int
sz Word
w  -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                          -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeWord16Canonical Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz w :: Word
w@(W# Word#
w#) ->
        case Word# -> Word# -> Int#
gtWord# Word#
w# Word#
0xffff## of
          Int#
0# | Int -> Word -> Bool
isWordCanonical Int
sz Word
w  -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                          -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeWord32Canonical Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz w :: Word
w@(W# Word#
w#) ->
        case Word# -> Int#
w_out_of_range Word#
w# of
          Int#
0# | Int -> Word -> Bool
isWordCanonical Int
sz Word
w  -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                          -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
  where
    w_out_of_range :: Word# -> Int#
    w_out_of_range :: Word# -> Int#
w_out_of_range Word#
_w# =
#if defined(ARCH_32bit)
      0#
#else
      Word# -> Word# -> Int#
gtWord# Word#
_w# Word#
0xffffffff##
#endif
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeNegWordCanonical Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeNegWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz w :: Word
w@(W# Word#
w#)
        | Int -> Word -> Bool
isWordCanonical Int
sz Word
w  -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise             -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeIntCanonical Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeInt (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz n :: Int
n@(I# Int#
n#)
        | Int -> Int -> Bool
isIntCanonical Int
sz Int
n  -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise            -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeInt8Canonical Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeInt (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz n :: Int
n@(I# Int#
n#) ->
        case (Int#
n# Int# -> Int# -> Int#
># Int#
0x7f#) Int# -> Int# -> Int#
`orI#` (Int#
n# Int# -> Int# -> Int#
<# Int#
-0x80#) of
          Int#
0# | Int -> Int -> Bool
isIntCanonical Int
sz Int
n  -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                         -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeInt16Canonical Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeInt (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz n :: Int
n@(I# Int#
n#) ->
        case (Int#
n# Int# -> Int# -> Int#
># Int#
0x7fff#) Int# -> Int# -> Int#
`orI#` (Int#
n# Int# -> Int# -> Int#
<# Int#
-0x8000#) of
          Int#
0# | Int -> Int -> Bool
isIntCanonical Int
sz Int
n  -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                         -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeInt32Canonical Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeInt (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz n :: Int
n@(I# Int#
n#) ->
        case Int# -> Int#
n_out_of_range Int#
n# of
          Int#
0# | Int -> Int -> Bool
isIntCanonical Int
sz Int
n  -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                         -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
  where
    n_out_of_range :: Int# -> Int#
    n_out_of_range :: Int# -> Int#
n_out_of_range Int#
_n# =
#if defined(ARCH_32bit)
      0#
#else
      (Int#
_n# Int# -> Int# -> Int#
># Int#
0x7fffffff#) Int# -> Int# -> Int#
`orI#` (Int#
_n# Int# -> Int# -> Int#
<# Int#
-0x80000000#)
#endif
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeListLenCanonical Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeListLen (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz n :: Int
n@(I# Int#
n#)
          
        | Int -> Word -> Bool
isWordCanonical Int
sz (Int -> Word
intToWord Int
n)  -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise                         -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeMapLenCanonical Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeMapLen (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz n :: Int
n@(I# Int#
n#)
          
        | Int -> Word -> Bool
isWordCanonical Int
sz (Int -> Word
intToWord Int
n) -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise                        -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeTagCanonical Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeTag (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz w :: Word
w@(W# Word#
w#)
        | Int -> Word -> Bool
isWordCanonical Int
sz Word
w  -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise             -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
#if defined(ARCH_32bit)
go_fast !bs da@(ConsumeWord64 k) =
  case tryConsumeWord64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> go_fast_end bs da
    DecodedToken sz (W64# w#) -> k w# >>= go_fast (BS.unsafeDrop sz bs)
go_fast !bs da@(ConsumeNegWord64 k) =
  case tryConsumeNegWord64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> go_fast_end bs da
    DecodedToken sz (W64# w#) -> k w# >>= go_fast (BS.unsafeDrop sz bs)
go_fast !bs da@(ConsumeInt64 k) =
  case tryConsumeInt64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> go_fast_end bs da
    DecodedToken sz (I64# i#) -> k i# >>= go_fast (BS.unsafeDrop sz bs)
go_fast !bs da@(ConsumeListLen64 k) =
  case tryConsumeListLen64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> go_fast_end bs da
    DecodedToken sz (I64# i#) -> k i# >>= go_fast (BS.unsafeDrop sz bs)
go_fast !bs da@(ConsumeMapLen64 k) =
  case tryConsumeMapLen64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> go_fast_end bs da
    DecodedToken sz (I64# i#) -> k i# >>= go_fast (BS.unsafeDrop sz bs)
go_fast !bs da@(ConsumeTag64 k) =
  case tryConsumeTag64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> go_fast_end bs da
    DecodedToken sz (W64# w#) -> k w# >>= go_fast (BS.unsafeDrop sz bs)
go_fast !bs da@(ConsumeWord64Canonical k) =
  case tryConsumeWord64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> go_fast_end bs da
    DecodedToken sz w@(W64# w#)
      | isWord64Canonical sz w  -> k w# >>= go_fast (BS.unsafeDrop sz bs)
      | otherwise               -> go_fast_end bs da
go_fast !bs da@(ConsumeNegWord64Canonical k) =
  case tryConsumeNegWord64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> go_fast_end bs da
    DecodedToken sz w@(W64# w#)
      | isWord64Canonical sz w  -> k w# >>= go_fast (BS.unsafeDrop sz bs)
      | otherwise               -> go_fast_end bs da
go_fast !bs da@(ConsumeInt64Canonical k) =
  case tryConsumeInt64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> go_fast_end bs da
    DecodedToken sz i@(I64# i#)
      | isInt64Canonical sz i  -> k i# >>= go_fast (BS.unsafeDrop sz bs)
      | otherwise              -> go_fast_end bs da
go_fast !bs da@(ConsumeListLen64Canonical k) =
  case tryConsumeListLen64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> go_fast_end bs da
    DecodedToken sz i@(I64# i#)
        
      | isWord64Canonical sz (int64ToWord64 i) -> k i# >>= go_fast (BS.unsafeDrop sz bs)
      | otherwise                              -> go_fast_end bs da
go_fast !bs da@(ConsumeMapLen64Canonical k) =
  case tryConsumeMapLen64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> go_fast_end bs da
    DecodedToken sz i@(I64# i#)
        
      | isWord64Canonical sz (int64ToWord64 i) -> k i# >>= go_fast (BS.unsafeDrop sz bs)
      | otherwise                              -> go_fast_end bs da
go_fast !bs da@(ConsumeTag64Canonical k) =
  case tryConsumeTag64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> go_fast_end bs da
    DecodedToken sz w@(W64# w#)
      | isWord64Canonical sz w  -> k w# >>= go_fast (BS.unsafeDrop sz bs)
      | otherwise               -> go_fast_end bs da
#endif
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeInteger Integer -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (BigIntToken Integer)
tryConsumeInteger (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
sz (BigIntToken Bool
_ Integer
n) -> Integer -> ST s (DecodeAction s a)
k Integer
n ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
      DecodedToken (BigIntToken Integer)
_                                 -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeFloat Float# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Float
tryConsumeFloat (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Float
DecodeFailure     -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (F# Float#
f#) -> Float# -> ST s (DecodeAction s a)
k Float#
f# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeDouble Double# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Double
tryConsumeDouble (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Double
DecodeFailure     -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (D# Double#
f#) -> Double# -> ST s (DecodeAction s a)
k Double#
f# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeBytes ByteString -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeBytes (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken (LongToken ByteString)
DecodeFailure                   -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (Fits Bool
_ ByteString
bstr)   -> ByteString -> ST s (DecodeAction s a)
k ByteString
bstr ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
      DecodedToken Int
sz (TooLong Bool
_ Int
len) -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (ByteString -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (ByteString -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenBytes
                                                   (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ByteString -> ST s (DecodeAction s a)
k Int
len
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeByteArray ByteArray -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeBytes (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken (LongToken ByteString)
DecodeFailure                 -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (Fits Bool
_ ByteString
str)  -> ByteArray -> ST s (DecodeAction s a)
k (ByteString -> ByteArray
BA.fromByteString ByteString
str) ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
      DecodedToken Int
sz (TooLong Bool
_ Int
len) -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (ByteArray -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (ByteArray -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenByteArray
                                                   (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ByteArray -> ST s (DecodeAction s a)
k Int
len
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeString Text -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeString (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken (LongToken ByteString)
DecodeFailure                   -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (Fits Bool
_ ByteString
str)    -> case ByteString -> Either UnicodeException Text
T.decodeUtf8' ByteString
str of
        Right Text
t -> Text -> ST s (DecodeAction s a)
k Text
t ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        Left UnicodeException
_e -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"invalid UTF8"
      DecodedToken Int
sz (TooLong Bool
_ Int
len) -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (Text -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (Text -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenString
                                                   (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) Text -> ST s (DecodeAction s a)
k Int
len
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeUtf8ByteArray ByteArray -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeString (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken (LongToken ByteString)
DecodeFailure                   -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (Fits Bool
_ ByteString
str)    -> ByteArray -> ST s (DecodeAction s a)
k (ByteString -> ByteArray
BA.fromByteString ByteString
str)
                                         ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
      DecodedToken Int
sz (TooLong Bool
_ Int
len) -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (ByteArray -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (ByteArray -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenUtf8ByteArray
                                                   (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ByteArray -> ST s (DecodeAction s a)
k Int
len
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeBool Bool -> ST s (DecodeAction s a)
k) =
    case Word8 -> DecodedToken Bool
tryConsumeBool (ByteString -> Word8
BS.unsafeHead ByteString
bs) of
      DecodedToken Bool
DecodeFailure     -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz Bool
b -> Bool -> ST s (DecodeAction s a)
k Bool
b ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeSimple Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeSimple (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (W# Word#
w#) -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeIntegerCanonical Integer -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (BigIntToken Integer)
tryConsumeInteger (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
sz (BigIntToken Bool
True Integer
n) -> Integer -> ST s (DecodeAction s a)
k Integer
n ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
      DecodedToken (BigIntToken Integer)
_                                    -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeFloat16Canonical Float# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Float
tryConsumeFloat (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Float
DecodeFailure     -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz f :: Float
f@(F# Float#
f#)
        | Int -> ByteString -> Float -> Bool
isFloat16Canonical Int
sz ByteString
bs Float
f -> Float# -> ST s (DecodeAction s a)
k Float#
f# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise                  -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeFloatCanonical Float# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Float
tryConsumeFloat (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Float
DecodeFailure     -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz f :: Float
f@(F# Float#
f#)
        | Int -> ByteString -> Float -> Bool
isFloatCanonical Int
sz ByteString
bs Float
f -> Float# -> ST s (DecodeAction s a)
k Float#
f# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise                -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeDoubleCanonical Double# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Double
tryConsumeDouble (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Double
DecodeFailure     -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz f :: Double
f@(D# Double#
f#)
        | Int -> ByteString -> Double -> Bool
isDoubleCanonical Int
sz ByteString
bs Double
f -> Double# -> ST s (DecodeAction s a)
k Double#
f# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise                 -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeBytesCanonical ByteString -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeBytes (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
sz (Fits    Bool
True ByteString
bstr) -> ByteString -> ST s (DecodeAction s a)
k ByteString
bstr ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
      DecodedToken Int
sz (TooLong Bool
True Int
len)  ->
        SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (ByteString -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (ByteString -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenBytes (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ByteString -> ST s (DecodeAction s a)
k Int
len
      DecodedToken (LongToken ByteString)
_                                   -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeByteArrayCanonical ByteArray -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeBytes (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
sz (Fits Bool
True ByteString
str)    ->
        ByteArray -> ST s (DecodeAction s a)
k (ByteString -> ByteArray
BA.fromByteString ByteString
str) ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
      DecodedToken Int
sz (TooLong Bool
True Int
len) ->
        SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (ByteArray -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (ByteArray -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenByteArray (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ByteArray -> ST s (DecodeAction s a)
k Int
len
      DecodedToken (LongToken ByteString)
_                                  -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeStringCanonical Text -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeString (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
sz (Fits Bool
True ByteString
str)    -> case ByteString -> Either UnicodeException Text
T.decodeUtf8' ByteString
str of
        Right Text
t -> Text -> ST s (DecodeAction s a)
k Text
t ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        Left UnicodeException
_e -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"invalid UTF8"
      DecodedToken Int
sz (TooLong Bool
True Int
len) ->
        SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (Text -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (Text -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenString (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) Text -> ST s (DecodeAction s a)
k Int
len
      DecodedToken (LongToken ByteString)
_                                  -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeUtf8ByteArrayCanonical ByteArray -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeString (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
sz (Fits Bool
True ByteString
str)    ->
        ByteArray -> ST s (DecodeAction s a)
k (ByteString -> ByteArray
BA.fromByteString ByteString
str) ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
      DecodedToken Int
sz (TooLong Bool
True Int
len) ->
        SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (ByteArray -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (ByteArray -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenUtf8ByteArray (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ByteArray -> ST s (DecodeAction s a)
k Int
len
      DecodedToken (LongToken ByteString)
_                                  -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeSimpleCanonical Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeSimple (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (W# Word#
w#)
        | Int -> Word# -> Bool
isSimpleCanonical Int
sz Word#
w# -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise               -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeBytesIndef ST s (DecodeAction s a)
k) =
    case Word8 -> DecodedToken ()
tryConsumeBytesIndef (ByteString -> Word8
BS.unsafeHead ByteString
bs) of
      DecodedToken ()
DecodeFailure     -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz ()
_ -> ST s (DecodeAction s a)
k ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeStringIndef ST s (DecodeAction s a)
k) =
    case Word8 -> DecodedToken ()
tryConsumeStringIndef (ByteString -> Word8
BS.unsafeHead ByteString
bs) of
      DecodedToken ()
DecodeFailure     -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz ()
_ -> ST s (DecodeAction s a)
k ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeListLenIndef ST s (DecodeAction s a)
k) =
    case Word8 -> DecodedToken ()
tryConsumeListLenIndef (ByteString -> Word8
BS.unsafeHead ByteString
bs) of
      DecodedToken ()
DecodeFailure     -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz ()
_ -> ST s (DecodeAction s a)
k ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeMapLenIndef ST s (DecodeAction s a)
k) =
    case Word8 -> DecodedToken ()
tryConsumeMapLenIndef (ByteString -> Word8
BS.unsafeHead ByteString
bs) of
      DecodedToken ()
DecodeFailure     -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz ()
_ -> ST s (DecodeAction s a)
k ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeNull ST s (DecodeAction s a)
k) =
    case Word8 -> DecodedToken ()
tryConsumeNull (ByteString -> Word8
BS.unsafeHead ByteString
bs) of
      DecodedToken ()
DecodeFailure     -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz ()
_ -> ST s (DecodeAction s a)
k ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeListLenOrIndef Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeListLenOrIndef (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (I# Int#
n#) -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs da :: DecodeAction s a
da@(ConsumeMapLenOrIndef Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeMapLenOrIndef (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
      DecodedToken Int
sz (I# Int#
n#) -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs (ConsumeBreakOr Bool -> ST s (DecodeAction s a)
k) =
    case Word8 -> DecodedToken ()
tryConsumeBreakOr (ByteString -> Word8
BS.unsafeHead ByteString
bs) of
      DecodedToken ()
DecodeFailure     -> Bool -> ST s (DecodeAction s a)
k Bool
False ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast ByteString
bs
      DecodedToken Int
sz ()
_ -> Bool -> ST s (DecodeAction s a)
k Bool
True ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast !ByteString
bs (PeekTokenType TokenType -> ST s (DecodeAction s a)
k) =
    let !hdr :: Word8
hdr  = ByteString -> Word8
BS.unsafeHead ByteString
bs
        !tkty :: TokenType
tkty = Array Word8 TokenType
decodeTokenTypeTable Array Word8 TokenType -> Int -> TokenType
forall i. Ix i => Array i TokenType -> Int -> TokenType
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> Int -> e
`A.unsafeAt` Word8 -> Int
word8ToInt Word8
hdr
    in TokenType -> ST s (DecodeAction s a)
k TokenType
tkty ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast ByteString
bs
go_fast !ByteString
bs (PeekAvailable Int# -> ST s (DecodeAction s a)
k) = Int# -> ST s (DecodeAction s a)
k (case ByteString -> Int
BS.length ByteString
bs of I# Int#
len# -> Int#
len#) ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast ByteString
bs
go_fast !ByteString
bs da :: DecodeAction s a
da@PeekByteOffset{} = ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@D.Fail{} = ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast !ByteString
bs da :: DecodeAction s a
da@D.Done{} = ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs DecodeAction s a
da
go_fast_end :: ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end :: forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end !ByteString
bs (D.Fail String
msg)      = SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
msg
go_fast_end !ByteString
bs (D.Done a
x)        = SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> a -> SlowPath s a
forall s a. ByteString -> a -> SlowPath s a
FastDone ByteString
bs a
x
go_fast_end !ByteString
bs (PeekAvailable Int# -> ST s (DecodeAction s a)
k) = Int# -> ST s (DecodeAction s a)
k (case ByteString -> Int
BS.length ByteString
bs of I# Int#
len# -> Int#
len#) ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs
go_fast_end !ByteString
bs (PeekByteOffset Int# -> ST s (DecodeAction s a)
k) = SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> (Int# -> ST s (DecodeAction s a)) -> SlowPath s a
forall s a.
ByteString -> (Int# -> ST s (DecodeAction s a)) -> SlowPath s a
SlowPeekByteOffset ByteString
bs Int# -> ST s (DecodeAction s a)
k
go_fast_end !ByteString
bs DecodeAction s a
da | ByteString -> Bool
BS.null ByteString
bs = SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> DecodeAction s a -> SlowPath s a
forall s a. ByteString -> DecodeAction s a -> SlowPath s a
SlowDecodeAction ByteString
bs DecodeAction s a
da
go_fast_end !ByteString
bs (ConsumeBreakOr Bool -> ST s (DecodeAction s a)
k) =
    case Word8 -> DecodedToken ()
tryConsumeBreakOr (ByteString -> Word8
BS.unsafeHead ByteString
bs) of
      DecodedToken ()
DecodeFailure     -> Bool -> ST s (DecodeAction s a)
k Bool
False ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs
      DecodedToken Int
sz ()
_ -> Bool -> ST s (DecodeAction s a)
k Bool
True  ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (PeekTokenType TokenType -> ST s (DecodeAction s a)
k) =
    let !hdr :: Word8
hdr  = ByteString -> Word8
BS.unsafeHead ByteString
bs
        !tkty :: TokenType
tkty = Array Word8 TokenType
decodeTokenTypeTable Array Word8 TokenType -> Int -> TokenType
forall i. Ix i => Array i TokenType -> Int -> TokenType
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> Int -> e
`A.unsafeAt` Word8 -> Int
word8ToInt Word8
hdr
    in TokenType -> ST s (DecodeAction s a)
k TokenType
tkty ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs
go_fast_end !ByteString
bs DecodeAction s a
da
    | let !hdr :: Word8
hdr = ByteString -> Word8
BS.unsafeHead ByteString
bs
    , ByteString -> Int
BS.length ByteString
bs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Word8 -> Int
tokenSize Word8
hdr
    = SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> DecodeAction s a -> SlowPath s a
forall s a. ByteString -> DecodeAction s a -> SlowPath s a
SlowDecodeAction ByteString
bs DecodeAction s a
da
go_fast_end !ByteString
bs (ConsumeWord Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected word"
      DecodedToken Int
sz (W# Word#
w#) -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (ConsumeWord8 Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected word8"
      DecodedToken Int
sz (W# Word#
w#) ->
        case Word# -> Word# -> Int#
gtWord# Word#
w# Word#
0xff## of
          Int#
0#                  -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                   -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected word8"
go_fast_end !ByteString
bs (ConsumeWord16 Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected word16"
      DecodedToken Int
sz (W# Word#
w#) ->
        case Word# -> Word# -> Int#
gtWord# Word#
w# Word#
0xffff## of
          Int#
0#                  -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                   -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected word16"
go_fast_end !ByteString
bs (ConsumeWord32 Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected word32"
      DecodedToken Int
sz (W# Word#
w#) ->
#if defined(ARCH_32bit)
                                 k w# >>= go_fast_end (BS.unsafeDrop sz bs)
#else
        case Word# -> Word# -> Int#
gtWord# Word#
w# Word#
0xffffffff## of
          Int#
0#                  -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                   -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected word32"
#endif
go_fast_end !ByteString
bs (ConsumeNegWord Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeNegWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected negative int"
      DecodedToken Int
sz (W# Word#
w#) -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (ConsumeInt Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeInt (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected int"
      DecodedToken Int
sz (I# Int#
n#) -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (ConsumeInt8 Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeInt (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected int8"
      DecodedToken Int
sz (I# Int#
n#) ->
        case (Int#
n# Int# -> Int# -> Int#
># Int#
0x7f#) Int# -> Int# -> Int#
`orI#` (Int#
n# Int# -> Int# -> Int#
<# Int#
-0x80#) of
          Int#
0#                  -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                   -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected int8"
go_fast_end !ByteString
bs (ConsumeInt16 Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeInt (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected int16"
      DecodedToken Int
sz (I# Int#
n#) ->
        case (Int#
n# Int# -> Int# -> Int#
># Int#
0x7fff#) Int# -> Int# -> Int#
`orI#` (Int#
n# Int# -> Int# -> Int#
<# Int#
-0x8000#) of
          Int#
0#                  -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                   -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected int16"
go_fast_end !ByteString
bs (ConsumeInt32 Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeInt (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected int32"
      DecodedToken Int
sz (I# Int#
n#) ->
#if defined(ARCH_32bit)
                                 k n# >>= go_fast_end (BS.unsafeDrop sz bs)
#else
        case (Int#
n# Int# -> Int# -> Int#
># Int#
0x7fffffff#) Int# -> Int# -> Int#
`orI#` (Int#
n# Int# -> Int# -> Int#
<# Int#
-0x80000000#) of
          Int#
0#                  -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Int#
_                   -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected int32"
#endif
go_fast_end !ByteString
bs (ConsumeListLen Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeListLen (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected list len"
      DecodedToken Int
sz (I# Int#
n#) -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (ConsumeMapLen Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeMapLen (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected map len"
      DecodedToken Int
sz (I# Int#
n#) -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (ConsumeTag Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeTag (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected tag"
      DecodedToken Int
sz (W# Word#
w#) -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (ConsumeWordCanonical Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected word"
      DecodedToken Int
sz w :: Word
w@(W# Word#
w#)
        | Int -> Word -> Bool
isWordCanonical Int
sz Word
w  -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise             -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical word"
go_fast_end !ByteString
bs (ConsumeWord8Canonical Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected word8"
      DecodedToken Int
sz w :: Word
w@(W# Word#
w#) -> case Word# -> Word# -> Int#
gtWord# Word#
w# Word#
0xff## of
          Int#
0# | Int -> Word -> Bool
isWordCanonical Int
sz Word
w  -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
             | Bool
otherwise             -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical word8"
          Int#
_                          -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected word8"
go_fast_end !ByteString
bs (ConsumeWord16Canonical Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected word16"
      DecodedToken Int
sz w :: Word
w@(W# Word#
w#) -> case Word# -> Word# -> Int#
gtWord# Word#
w# Word#
0xffff## of
        Int#
0# | Int -> Word -> Bool
isWordCanonical Int
sz Word
w  -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
           | Bool
otherwise             -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical word16"
        Int#
_                          -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected word16"
go_fast_end !ByteString
bs (ConsumeWord32Canonical Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected word32"
      DecodedToken Int
sz w :: Word
w@(W# Word#
w#) -> case Word# -> Int#
w_out_of_range Word#
w# of
        Int#
0# | Int -> Word -> Bool
isWordCanonical Int
sz Word
w  -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
           | Bool
otherwise             -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical word32"
        Int#
_                          -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected word32"
  where
    w_out_of_range :: Word# -> Int#
    w_out_of_range :: Word# -> Int#
w_out_of_range Word#
_w# =
#if defined(ARCH_32bit)
      0#
#else
      Word# -> Word# -> Int#
gtWord# Word#
_w# Word#
0xffffffff##
#endif
go_fast_end !ByteString
bs (ConsumeNegWordCanonical Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeNegWord (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected negative int"
      DecodedToken Int
sz w :: Word
w@(W# Word#
w#)
        | Int -> Word -> Bool
isWordCanonical Int
sz Word
w  -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise             -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical negative int"
go_fast_end !ByteString
bs (ConsumeIntCanonical Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeInt (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected int"
      DecodedToken Int
sz n :: Int
n@(I# Int#
n#)
        | Int -> Int -> Bool
isIntCanonical Int
sz Int
n  -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise            -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical int"
go_fast_end !ByteString
bs (ConsumeInt8Canonical Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeInt (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected int8"
      DecodedToken Int
sz n :: Int
n@(I# Int#
n#) ->
        case (Int#
n# Int# -> Int# -> Int#
># Int#
0x7f#) Int# -> Int# -> Int#
`orI#` (Int#
n# Int# -> Int# -> Int#
<# Int#
-0x80#) of
          Int#
0# | Int -> Int -> Bool
isIntCanonical Int
sz Int
n  -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
             | Bool
otherwise            -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical int8"
          Int#
_                         -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected int8"
go_fast_end !ByteString
bs (ConsumeInt16Canonical Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeInt (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected int16"
      DecodedToken Int
sz n :: Int
n@(I# Int#
n#) ->
        case (Int#
n# Int# -> Int# -> Int#
># Int#
0x7fff#) Int# -> Int# -> Int#
`orI#` (Int#
n# Int# -> Int# -> Int#
<# Int#
-0x8000#) of
          Int#
0# | Int -> Int -> Bool
isIntCanonical Int
sz Int
n  -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
             | Bool
otherwise            -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical int16"
          Int#
_                         -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected int16"
go_fast_end !ByteString
bs (ConsumeInt32Canonical Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeInt (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected int32"
      DecodedToken Int
sz n :: Int
n@(I# Int#
n#) ->
        case Int# -> Int#
n_out_of_range Int#
n# of
          Int#
0# | Int -> Int -> Bool
isIntCanonical Int
sz Int
n  -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
             | Bool
otherwise            -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical int32"
          Int#
_                         -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected int32"
  where
    n_out_of_range :: Int# -> Int#
    n_out_of_range :: Int# -> Int#
n_out_of_range Int#
_n# =
#if defined(ARCH_32bit)
      0#
#else
      (Int#
_n# Int# -> Int# -> Int#
># Int#
0x7fffffff#) Int# -> Int# -> Int#
`orI#` (Int#
_n# Int# -> Int# -> Int#
<# Int#
-0x80000000#)
#endif
go_fast_end !ByteString
bs (ConsumeListLenCanonical Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeListLen (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected list len"
      DecodedToken Int
sz n :: Int
n@(I# Int#
n#)
          
        | Int -> Word -> Bool
isWordCanonical Int
sz (Int -> Word
intToWord Int
n) -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise                        -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical list len"
go_fast_end !ByteString
bs (ConsumeMapLenCanonical Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeMapLen (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected map len"
      DecodedToken Int
sz n :: Int
n@(I# Int#
n#)
          
        | Int -> Word -> Bool
isWordCanonical Int
sz (Int -> Word
intToWord Int
n) -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise                        -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical map len"
go_fast_end !ByteString
bs (ConsumeTagCanonical Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeTag (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected tag"
      DecodedToken Int
sz w :: Word
w@(W# Word#
w#)
        | Int -> Word -> Bool
isWordCanonical Int
sz Word
w  -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise             -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical tag"
#if defined(ARCH_32bit)
go_fast_end !bs (ConsumeWord64 k) =
  case tryConsumeWord64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> return $! SlowFail bs "expected word64"
    DecodedToken sz (W64# w#) -> k w# >>= go_fast_end (BS.unsafeDrop sz bs)
go_fast_end !bs (ConsumeNegWord64 k) =
  case tryConsumeNegWord64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> return $! SlowFail bs "expected negative int"
    DecodedToken sz (W64# w#) -> k w# >>= go_fast_end (BS.unsafeDrop sz bs)
go_fast_end !bs (ConsumeInt64 k) =
  case tryConsumeInt64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> return $! SlowFail bs "expected int64"
    DecodedToken sz (I64# i#) -> k i# >>= go_fast_end (BS.unsafeDrop sz bs)
go_fast_end !bs (ConsumeListLen64 k) =
  case tryConsumeListLen64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> return $! SlowFail bs "expected list len 64"
    DecodedToken sz (I64# i#) -> k i# >>= go_fast_end (BS.unsafeDrop sz bs)
go_fast_end !bs (ConsumeMapLen64 k) =
  case tryConsumeMapLen64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> return $! SlowFail bs "expected map len 64"
    DecodedToken sz (I64# i#) -> k i# >>= go_fast_end (BS.unsafeDrop sz bs)
go_fast_end !bs (ConsumeTag64 k) =
  case tryConsumeTag64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> return $! SlowFail bs "expected tag64"
    DecodedToken sz (W64# w#) -> k w# >>= go_fast_end (BS.unsafeDrop sz bs)
go_fast_end !bs (ConsumeWord64Canonical k) =
  case tryConsumeWord64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> return $! SlowFail bs "expected word64"
    DecodedToken sz w@(W64# w#)
      | isWord64Canonical sz w  -> k w# >>= go_fast_end (BS.unsafeDrop sz bs)
      | otherwise               -> return $! SlowFail bs "non-canonical word64"
go_fast_end !bs (ConsumeNegWord64Canonical k) =
  case tryConsumeNegWord64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> return $! SlowFail bs "expected negative int"
    DecodedToken sz w@(W64# w#)
      | isWord64Canonical sz w  -> k w# >>= go_fast_end (BS.unsafeDrop sz bs)
      | otherwise               -> return $! SlowFail bs "non-canonical negative int"
go_fast_end !bs (ConsumeInt64Canonical k) =
  case tryConsumeInt64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> return $! SlowFail bs "expected int64"
    DecodedToken sz i@(I64# i#)
      | isInt64Canonical sz i  -> k i# >>= go_fast_end (BS.unsafeDrop sz bs)
      | otherwise              -> return $! SlowFail bs "non-canonical int64"
go_fast_end !bs (ConsumeListLen64Canonical k) =
  case tryConsumeListLen64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> return $! SlowFail bs "expected list len 64"
    DecodedToken sz i@(I64# i#)
        
      | isWord64Canonical sz (int64ToWord64 i) ->
          k i# >>= go_fast_end (BS.unsafeDrop sz bs)
      | otherwise ->
          return $! SlowFail bs "non-canonical list len 64"
go_fast_end !bs (ConsumeMapLen64Canonical k) =
  case tryConsumeMapLen64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> return $! SlowFail bs "expected map len 64"
    DecodedToken sz i@(I64# i#)
        
      | isWord64Canonical sz (int64ToWord64 i) ->
          k i# >>= go_fast_end (BS.unsafeDrop sz bs)
      | otherwise ->
          return $! SlowFail bs "non-canonical map len 64"
go_fast_end !bs (ConsumeTag64Canonical k) =
  case tryConsumeTag64 (BS.unsafeHead bs) bs of
    DecodeFailure             -> return $! SlowFail bs "expected tag64"
    DecodedToken sz w@(W64# w#)
      | isWord64Canonical sz w  -> k w# >>= go_fast_end (BS.unsafeDrop sz bs)
      | otherwise               -> return $! SlowFail bs "non-canonical tag64"
#endif
go_fast_end !ByteString
bs (ConsumeInteger Integer -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (BigIntToken Integer)
tryConsumeInteger (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken (BigIntToken Integer)
DecodeFailure                         -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected integer"
      DecodedToken Int
sz (BigIntToken Bool
_ Integer
n)     -> Integer -> ST s (DecodeAction s a)
k Integer
n ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
      DecodedToken Int
sz (BigUIntNeedBody Bool
_ Int
len) -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (ByteString -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (ByteString -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenBytes (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ((Integer -> ST s (DecodeAction s a))
-> ByteString -> ST s (DecodeAction s a)
forall s a.
(Integer -> ST s (DecodeAction s a))
-> ByteString -> ST s (DecodeAction s a)
adjustContBigUIntNeedBody Integer -> ST s (DecodeAction s a)
k) Int
len
      DecodedToken Int
sz (BigNIntNeedBody Bool
_ Int
len) -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (ByteString -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (ByteString -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenBytes (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ((Integer -> ST s (DecodeAction s a))
-> ByteString -> ST s (DecodeAction s a)
forall s a.
(Integer -> ST s (DecodeAction s a))
-> ByteString -> ST s (DecodeAction s a)
adjustContBigNIntNeedBody Integer -> ST s (DecodeAction s a)
k) Int
len
      DecodedToken Int
sz  BigIntToken Integer
BigUIntNeedHeader    -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> DecodeAction s a -> SlowPath s a
forall s a. ByteString -> DecodeAction s a -> SlowPath s a
SlowDecodeAction      (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ((Integer -> ST s (DecodeAction s a)) -> DecodeAction s a
forall s a.
(Integer -> ST s (DecodeAction s a)) -> DecodeAction s a
adjustContBigUIntNeedHeader Integer -> ST s (DecodeAction s a)
k)
      DecodedToken Int
sz  BigIntToken Integer
BigNIntNeedHeader    -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> DecodeAction s a -> SlowPath s a
forall s a. ByteString -> DecodeAction s a -> SlowPath s a
SlowDecodeAction      (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ((Integer -> ST s (DecodeAction s a)) -> DecodeAction s a
forall s a.
(Integer -> ST s (DecodeAction s a)) -> DecodeAction s a
adjustContBigNIntNeedHeader Integer -> ST s (DecodeAction s a)
k)
go_fast_end !ByteString
bs (ConsumeFloat Float# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Float
tryConsumeFloat (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Float
DecodeFailure     -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected float"
      DecodedToken Int
sz (F# Float#
f#) -> Float# -> ST s (DecodeAction s a)
k Float#
f# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (ConsumeDouble Double# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Double
tryConsumeDouble (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Double
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected double"
      DecodedToken Int
sz (D# Double#
f#) -> Double# -> ST s (DecodeAction s a)
k Double#
f# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (ConsumeBytes ByteString -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeBytes (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken (LongToken ByteString)
DecodeFailure                   -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected bytes"
      DecodedToken Int
sz (Fits Bool
_ ByteString
bstr)   -> ByteString -> ST s (DecodeAction s a)
k ByteString
bstr ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
      DecodedToken Int
sz (TooLong Bool
_ Int
len) -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (ByteString -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (ByteString -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenBytes
                                                   (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ByteString -> ST s (DecodeAction s a)
k Int
len
go_fast_end !ByteString
bs (ConsumeByteArray ByteArray -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeBytes (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken (LongToken ByteString)
DecodeFailure                   -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected string"
      DecodedToken Int
sz (Fits Bool
_ ByteString
str)    -> (ByteArray -> ST s (DecodeAction s a)
k (ByteArray -> ST s (DecodeAction s a))
-> ByteArray -> ST s (DecodeAction s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> ByteArray
BA.fromByteString ByteString
str)
                                         ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
      DecodedToken Int
sz (TooLong Bool
_ Int
len) -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (ByteArray -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (ByteArray -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenByteArray
                                                   (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ByteArray -> ST s (DecodeAction s a)
k Int
len
go_fast_end !ByteString
bs (ConsumeString Text -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeString (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken (LongToken ByteString)
DecodeFailure                   -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected string"
      DecodedToken Int
sz (Fits Bool
_ ByteString
str)    -> case ByteString -> Either UnicodeException Text
T.decodeUtf8' ByteString
str of
        Right Text
t -> Text -> ST s (DecodeAction s a)
k Text
t ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        Left UnicodeException
_e -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"invalid UTF8"
      DecodedToken Int
sz (TooLong Bool
_ Int
len) -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (Text -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (Text -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenString
                                                   (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) Text -> ST s (DecodeAction s a)
k Int
len
go_fast_end !ByteString
bs (ConsumeUtf8ByteArray ByteArray -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeString (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken (LongToken ByteString)
DecodeFailure                   -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected string"
      DecodedToken Int
sz (Fits Bool
_ ByteString
str)    -> (ByteArray -> ST s (DecodeAction s a)
k (ByteArray -> ST s (DecodeAction s a))
-> ByteArray -> ST s (DecodeAction s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> ByteArray
BA.fromByteString ByteString
str)
                                         ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
      DecodedToken Int
sz (TooLong Bool
_ Int
len) -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (ByteArray -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (ByteArray -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenUtf8ByteArray
                                                   (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ByteArray -> ST s (DecodeAction s a)
k Int
len
go_fast_end !ByteString
bs (ConsumeBool Bool -> ST s (DecodeAction s a)
k) =
    case Word8 -> DecodedToken Bool
tryConsumeBool (ByteString -> Word8
BS.unsafeHead ByteString
bs) of
      DecodedToken Bool
DecodeFailure     -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected bool"
      DecodedToken Int
sz Bool
b -> Bool -> ST s (DecodeAction s a)
k Bool
b ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (ConsumeSimple Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeSimple (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected simple"
      DecodedToken Int
sz (W# Word#
w#) -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (ConsumeIntegerCanonical Integer -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (BigIntToken Integer)
tryConsumeInteger (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken (BigIntToken Integer)
DecodeFailure                         -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected integer"
      DecodedToken Int
sz (BigIntToken Bool
True Integer
n)  -> Integer -> ST s (DecodeAction s a)
k Integer
n ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
      DecodedToken Int
sz (BigUIntNeedBody Bool
True Int
len) -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (ByteString -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (ByteString -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenBytes
        (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ((Integer -> ST s (DecodeAction s a))
-> ByteString -> ST s (DecodeAction s a)
forall s a.
(Integer -> ST s (DecodeAction s a))
-> ByteString -> ST s (DecodeAction s a)
adjustContCanonicalBigUIntNeedBody Integer -> ST s (DecodeAction s a)
k) Int
len
      DecodedToken Int
sz (BigNIntNeedBody Bool
True Int
len) -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (ByteString -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (ByteString -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenBytes
        (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ((Integer -> ST s (DecodeAction s a))
-> ByteString -> ST s (DecodeAction s a)
forall s a.
(Integer -> ST s (DecodeAction s a))
-> ByteString -> ST s (DecodeAction s a)
adjustContCanonicalBigNIntNeedBody Integer -> ST s (DecodeAction s a)
k) Int
len
      DecodedToken Int
sz  BigIntToken Integer
BigUIntNeedHeader -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> DecodeAction s a -> SlowPath s a
forall s a. ByteString -> DecodeAction s a -> SlowPath s a
SlowDecodeAction
        (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ((Integer -> ST s (DecodeAction s a)) -> DecodeAction s a
forall s a.
(Integer -> ST s (DecodeAction s a)) -> DecodeAction s a
adjustContCanonicalBigUIntNeedHeader Integer -> ST s (DecodeAction s a)
k)
      DecodedToken Int
sz  BigIntToken Integer
BigNIntNeedHeader -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> DecodeAction s a -> SlowPath s a
forall s a. ByteString -> DecodeAction s a -> SlowPath s a
SlowDecodeAction
        (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ((Integer -> ST s (DecodeAction s a)) -> DecodeAction s a
forall s a.
(Integer -> ST s (DecodeAction s a)) -> DecodeAction s a
adjustContCanonicalBigNIntNeedHeader Integer -> ST s (DecodeAction s a)
k)
      DecodedToken (BigIntToken Integer)
_ -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical integer"
go_fast_end !ByteString
bs (ConsumeFloat16Canonical Float# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Float
tryConsumeFloat (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Float
DecodeFailure     -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected float"
      DecodedToken Int
sz f :: Float
f@(F# Float#
f#)
        | Int -> ByteString -> Float -> Bool
isFloat16Canonical Int
sz ByteString
bs Float
f -> Float# -> ST s (DecodeAction s a)
k Float#
f# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise                  -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical float16"
go_fast_end !ByteString
bs (ConsumeFloatCanonical Float# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Float
tryConsumeFloat (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Float
DecodeFailure     -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected float"
      DecodedToken Int
sz f :: Float
f@(F# Float#
f#)
        | Int -> ByteString -> Float -> Bool
isFloatCanonical Int
sz ByteString
bs Float
f -> Float# -> ST s (DecodeAction s a)
k Float#
f# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise                -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical float"
go_fast_end !ByteString
bs (ConsumeDoubleCanonical Double# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Double
tryConsumeDouble (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Double
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected double"
      DecodedToken Int
sz f :: Double
f@(D# Double#
f#)
        | Int -> ByteString -> Double -> Bool
isDoubleCanonical Int
sz ByteString
bs Double
f -> Double# -> ST s (DecodeAction s a)
k Double#
f# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise                 -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical double"
go_fast_end !ByteString
bs (ConsumeBytesCanonical ByteString -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeBytes (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken (LongToken ByteString)
DecodeFailure         -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected bytes"
      DecodedToken Int
sz LongToken ByteString
token -> case LongToken ByteString
token of
        Fits Bool
True ByteString
bstr   -> ByteString -> ST s (DecodeAction s a)
k ByteString
bstr ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        TooLong Bool
True Int
len -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (ByteString -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (ByteString -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenBytes (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ByteString -> ST s (DecodeAction s a)
k Int
len
        LongToken ByteString
_                -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical length prefix"
go_fast_end !ByteString
bs (ConsumeByteArrayCanonical ByteArray -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeBytes (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken (LongToken ByteString)
DecodeFailure         -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected string"
      DecodedToken Int
sz LongToken ByteString
token -> case LongToken ByteString
token of
        Fits Bool
True ByteString
str    ->
          (ByteArray -> ST s (DecodeAction s a)
k (ByteArray -> ST s (DecodeAction s a))
-> ByteArray -> ST s (DecodeAction s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> ByteArray
BA.fromByteString ByteString
str) ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        TooLong Bool
True Int
len ->
           SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (ByteArray -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (ByteArray -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenByteArray (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ByteArray -> ST s (DecodeAction s a)
k Int
len
        LongToken ByteString
_                -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical length prefix"
go_fast_end !ByteString
bs (ConsumeStringCanonical Text -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeString (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken (LongToken ByteString)
DecodeFailure         -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected string"
      DecodedToken Int
sz LongToken ByteString
token -> case LongToken ByteString
token of
        Fits Bool
True ByteString
str    -> case ByteString -> Either UnicodeException Text
T.decodeUtf8' ByteString
str of
          Right Text
t -> Text -> ST s (DecodeAction s a)
k Text
t ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
          Left UnicodeException
_e -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"invalid UTF8"
        TooLong Bool
True Int
len -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (Text -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (Text -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenString (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) Text -> ST s (DecodeAction s a)
k Int
len
        LongToken ByteString
_                -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical length prefix"
go_fast_end !ByteString
bs (ConsumeUtf8ByteArrayCanonical ByteArray -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeString (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken (LongToken ByteString)
DecodeFailure                 -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected string"
      DecodedToken Int
sz LongToken ByteString
token -> case LongToken ByteString
token of
        Fits Bool
True ByteString
str    ->
          (ByteArray -> ST s (DecodeAction s a)
k (ByteArray -> ST s (DecodeAction s a))
-> ByteArray -> ST s (DecodeAction s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> ByteArray
BA.fromByteString ByteString
str) ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        TooLong Bool
True Int
len ->
          SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString
-> (ByteArray -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
forall s a.
ByteString
-> (ByteArray -> ST s (DecodeAction s a)) -> Int -> SlowPath s a
SlowConsumeTokenUtf8ByteArray (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs) ByteArray -> ST s (DecodeAction s a)
k Int
len
        LongToken ByteString
_                ->
          SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical length prefix"
go_fast_end !ByteString
bs (ConsumeSimpleCanonical Word# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Word
tryConsumeSimple (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Word
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected simple"
      DecodedToken Int
sz (W# Word#
w#)
        | Int -> Word# -> Bool
isSimpleCanonical Int
sz Word#
w# -> Word# -> ST s (DecodeAction s a)
k Word#
w# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
        | Bool
otherwise               -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"non-canonical simple"
go_fast_end !ByteString
bs (ConsumeBytesIndef ST s (DecodeAction s a)
k) =
    case Word8 -> DecodedToken ()
tryConsumeBytesIndef (ByteString -> Word8
BS.unsafeHead ByteString
bs) of
      DecodedToken ()
DecodeFailure     -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected bytes start"
      DecodedToken Int
sz ()
_ -> ST s (DecodeAction s a)
k ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (ConsumeStringIndef ST s (DecodeAction s a)
k) =
    case Word8 -> DecodedToken ()
tryConsumeStringIndef (ByteString -> Word8
BS.unsafeHead ByteString
bs) of
      DecodedToken ()
DecodeFailure     -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected string start"
      DecodedToken Int
sz ()
_ -> ST s (DecodeAction s a)
k ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (ConsumeListLenIndef ST s (DecodeAction s a)
k) =
    case Word8 -> DecodedToken ()
tryConsumeListLenIndef (ByteString -> Word8
BS.unsafeHead ByteString
bs) of
      DecodedToken ()
DecodeFailure     -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected list start"
      DecodedToken Int
sz ()
_ -> ST s (DecodeAction s a)
k ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (ConsumeMapLenIndef ST s (DecodeAction s a)
k) =
    case Word8 -> DecodedToken ()
tryConsumeMapLenIndef (ByteString -> Word8
BS.unsafeHead ByteString
bs) of
      DecodedToken ()
DecodeFailure     -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected map start"
      DecodedToken Int
sz ()
_ -> ST s (DecodeAction s a)
k ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (ConsumeNull ST s (DecodeAction s a)
k) =
    case Word8 -> DecodedToken ()
tryConsumeNull (ByteString -> Word8
BS.unsafeHead ByteString
bs) of
      DecodedToken ()
DecodeFailure     -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected null"
      DecodedToken Int
sz ()
_ -> ST s (DecodeAction s a)
k ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (ConsumeListLenOrIndef Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeListLenOrIndef (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected list len or indef"
      DecodedToken Int
sz (I# Int#
n#) -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_fast_end !ByteString
bs (ConsumeMapLenOrIndef Int# -> ST s (DecodeAction s a)
k) =
    case Word8 -> ByteString -> DecodedToken Int
tryConsumeMapLenOrIndef (ByteString -> Word8
BS.unsafeHead ByteString
bs) ByteString
bs of
      DecodedToken Int
DecodeFailure           -> SlowPath s a -> ST s (SlowPath s a)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SlowPath s a -> ST s (SlowPath s a))
-> SlowPath s a -> ST s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> String -> SlowPath s a
forall s a. ByteString -> String -> SlowPath s a
SlowFail ByteString
bs String
"expected map len or indef"
      DecodedToken Int
sz (I# Int#
n#) -> Int# -> ST s (DecodeAction s a)
k Int#
n# ST s (DecodeAction s a)
-> (DecodeAction s a -> ST s (SlowPath s a)) -> ST s (SlowPath s a)
forall a b. ST s a -> (a -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end (Int -> ByteString -> ByteString
BS.unsafeDrop Int
sz ByteString
bs)
go_slow :: DecodeAction s a -> ByteString -> ByteOffset
        -> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow :: forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow DecodeAction s a
da ByteString
bs !ByteOffset
offset = do
  SlowPath s a
slowpath <- ST s (SlowPath s a) -> IncrementalDecoder s (SlowPath s a)
forall s a. ST s a -> IncrementalDecoder s a
lift (ST s (SlowPath s a) -> IncrementalDecoder s (SlowPath s a))
-> ST s (SlowPath s a) -> IncrementalDecoder s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$ ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast ByteString
bs DecodeAction s a
da
  case SlowPath s a
slowpath of
    FastDone ByteString
bs' a
x -> (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a. a -> IncrementalDecoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
bs', ByteOffset
offset', a
x)
      where
        !offset' :: ByteOffset
offset' = ByteOffset
offset ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 (ByteString -> Int
BS.length ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
bs')
    SlowConsumeTokenBytes ByteString
bs' ByteString -> ST s (DecodeAction s a)
k Int
len -> do
      (ByteString
bstr, ByteString
bs'') <- Int
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteString)
forall s.
Int
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteString)
getTokenVarLen Int
len ByteString
bs' ByteOffset
offset'
      ST s (DecodeAction s a) -> IncrementalDecoder s (DecodeAction s a)
forall s a. ST s a -> IncrementalDecoder s a
lift (ByteString -> ST s (DecodeAction s a)
k ByteString
bstr) IncrementalDecoder s (DecodeAction s a)
-> (DecodeAction s a
    -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b.
IncrementalDecoder s a
-> (a -> IncrementalDecoder s b) -> IncrementalDecoder s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \DecodeAction s a
daz -> DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow DecodeAction s a
daz ByteString
bs'' (ByteOffset
offset' ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 Int
len)
      where
        !offset' :: ByteOffset
offset' = ByteOffset
offset ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 (ByteString -> Int
BS.length ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
bs')
    SlowConsumeTokenByteArray ByteString
bs' ByteArray -> ST s (DecodeAction s a)
k Int
len -> do
      (ByteString
bstr, ByteString
bs'') <- Int
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteString)
forall s.
Int
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteString)
getTokenVarLen Int
len ByteString
bs' ByteOffset
offset'
      let !str :: ByteArray
str = ByteString -> ByteArray
BA.fromByteString ByteString
bstr
      ST s (DecodeAction s a) -> IncrementalDecoder s (DecodeAction s a)
forall s a. ST s a -> IncrementalDecoder s a
lift (ByteArray -> ST s (DecodeAction s a)
k ByteArray
str) IncrementalDecoder s (DecodeAction s a)
-> (DecodeAction s a
    -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b.
IncrementalDecoder s a
-> (a -> IncrementalDecoder s b) -> IncrementalDecoder s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \DecodeAction s a
daz -> DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow DecodeAction s a
daz ByteString
bs'' (ByteOffset
offset' ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 Int
len)
      where
        !offset' :: ByteOffset
offset' = ByteOffset
offset ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 (ByteString -> Int
BS.length ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
bs')
    SlowConsumeTokenString ByteString
bs' Text -> ST s (DecodeAction s a)
k Int
len -> do
      (ByteString
bstr, ByteString
bs'') <- Int
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteString)
forall s.
Int
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteString)
getTokenVarLen Int
len ByteString
bs' ByteOffset
offset'
      case ByteString -> Either UnicodeException Text
T.decodeUtf8' ByteString
bstr of
        Right Text
str -> ST s (DecodeAction s a) -> IncrementalDecoder s (DecodeAction s a)
forall s a. ST s a -> IncrementalDecoder s a
lift (Text -> ST s (DecodeAction s a)
k Text
str) IncrementalDecoder s (DecodeAction s a)
-> (DecodeAction s a
    -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b.
IncrementalDecoder s a
-> (a -> IncrementalDecoder s b) -> IncrementalDecoder s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \DecodeAction s a
daz ->
                     DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow DecodeAction s a
daz ByteString
bs'' (ByteOffset
offset' ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 Int
len)
        Left UnicodeException
_e   -> ByteString
-> ByteOffset
-> String
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
ByteString -> ByteOffset -> String -> IncrementalDecoder s a
decodeFail ByteString
bs' ByteOffset
offset' String
"invalid UTF8"
      where
        !offset' :: ByteOffset
offset' = ByteOffset
offset ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 (ByteString -> Int
BS.length ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
bs')
    SlowConsumeTokenUtf8ByteArray ByteString
bs' ByteArray -> ST s (DecodeAction s a)
k Int
len -> do
      (ByteString
bstr, ByteString
bs'') <- Int
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteString)
forall s.
Int
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteString)
getTokenVarLen Int
len ByteString
bs' ByteOffset
offset'
      let !str :: ByteArray
str = ByteString -> ByteArray
BA.fromByteString ByteString
bstr
      ST s (DecodeAction s a) -> IncrementalDecoder s (DecodeAction s a)
forall s a. ST s a -> IncrementalDecoder s a
lift (ByteArray -> ST s (DecodeAction s a)
k ByteArray
str) IncrementalDecoder s (DecodeAction s a)
-> (DecodeAction s a
    -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b.
IncrementalDecoder s a
-> (a -> IncrementalDecoder s b) -> IncrementalDecoder s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \DecodeAction s a
daz -> DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow DecodeAction s a
daz ByteString
bs'' (ByteOffset
offset' ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 Int
len)
      where
        !offset' :: ByteOffset
offset' = ByteOffset
offset ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 (ByteString -> Int
BS.length ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
bs')
    
    SlowDecodeAction ByteString
bs' DecodeAction s a
da' | ByteString -> Bool
BS.null ByteString
bs' -> do
      
      
      Maybe ByteString
mbs <- IncrementalDecoder s (Maybe ByteString)
forall s. IncrementalDecoder s (Maybe ByteString)
needChunk
      case Maybe ByteString
mbs of
        Maybe ByteString
Nothing   -> ByteString
-> ByteOffset
-> String
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
ByteString -> ByteOffset -> String -> IncrementalDecoder s a
decodeFail ByteString
bs' ByteOffset
offset' String
"end of input"
        Just ByteString
bs'' -> DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow DecodeAction s a
da' ByteString
bs'' ByteOffset
offset'
      where
        !offset' :: ByteOffset
offset' = ByteOffset
offset ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 (ByteString -> Int
BS.length ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
bs')
    SlowDecodeAction ByteString
bs' DecodeAction s a
da' ->
      
      
      Bool
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (ByteString -> Int
BS.length ByteString
bs' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Word8 -> Int
tokenSize ((?callStack::CallStack) => ByteString -> Word8
ByteString -> Word8
BS.head ByteString
bs')) (IncrementalDecoder s (ByteString, ByteOffset, a)
 -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b. (a -> b) -> a -> b
$
      DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow_fixup DecodeAction s a
da' ByteString
bs' ByteOffset
offset'
      where
        !offset' :: ByteOffset
offset' = ByteOffset
offset ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 (ByteString -> Int
BS.length ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
bs')
    SlowPeekByteOffset ByteString
bs' Int# -> ST s (DecodeAction s a)
k ->
      ST s (DecodeAction s a) -> IncrementalDecoder s (DecodeAction s a)
forall s a. ST s a -> IncrementalDecoder s a
lift
#if MIN_VERSION_base(4,17,0)
        (Int# -> ST s (DecodeAction s a)
k (Int64# -> Int#
int64ToInt# Int64#
off#))
#else
        (k off#)
#endif
        IncrementalDecoder s (DecodeAction s a)
-> (DecodeAction s a
    -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b.
IncrementalDecoder s a
-> (a -> IncrementalDecoder s b) -> IncrementalDecoder s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \DecodeAction s a
daz -> DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow DecodeAction s a
daz ByteString
bs' ByteOffset
offset'
      where
        !offset' :: ByteOffset
offset'@(I64# Int64#
off#) = ByteOffset
offset ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 (ByteString -> Int
BS.length ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
bs')
    SlowFail ByteString
bs' String
msg -> ByteString
-> ByteOffset
-> String
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
ByteString -> ByteOffset -> String -> IncrementalDecoder s a
decodeFail ByteString
bs' ByteOffset
offset' String
msg
      where
        !offset' :: ByteOffset
offset' = ByteOffset
offset ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 (ByteString -> Int
BS.length ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
bs')
go_slow_fixup :: DecodeAction s a -> ByteString -> ByteOffset
              -> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow_fixup :: forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow_fixup DecodeAction s a
da !ByteString
bs !ByteOffset
offset = do
    let !hdr :: Word8
hdr = (?callStack::CallStack) => ByteString -> Word8
ByteString -> Word8
BS.head ByteString
bs
        !sz :: Int
sz  = Word8 -> Int
tokenSize Word8
hdr
    Maybe ByteString
mbs <- IncrementalDecoder s (Maybe ByteString)
forall s. IncrementalDecoder s (Maybe ByteString)
needChunk
    case Maybe ByteString
mbs of
      Maybe ByteString
Nothing -> ByteString
-> ByteOffset
-> String
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
ByteString -> ByteOffset -> String -> IncrementalDecoder s a
decodeFail ByteString
bs ByteOffset
offset String
"end of input"
      Just ByteString
bs'
          
        | ByteString -> Int
BS.length ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ByteString -> Int
BS.length ByteString
bs' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
sz
       -> DecodeAction s a
-> Int
-> ByteString
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> Int
-> ByteString
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow_overlapped DecodeAction s a
da Int
sz ByteString
bs ByteString
bs' ByteOffset
offset
          
        | Bool
otherwise
       -> DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow_fixup DecodeAction s a
da (ByteString
bs ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
bs') ByteOffset
offset
go_slow_overlapped :: DecodeAction s a -> Int -> ByteString -> ByteString
                   -> ByteOffset
                   -> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow_overlapped :: forall s a.
DecodeAction s a
-> Int
-> ByteString
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow_overlapped DecodeAction s a
da Int
sz ByteString
bs_cur ByteString
bs_next !ByteOffset
offset =
    
    
    
    
    
    Bool
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (ByteString -> Int
BS.length ByteString
bs_cur Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
sz) (IncrementalDecoder s (ByteString, ByteOffset, a)
 -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b. (a -> b) -> a -> b
$
    Bool
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (ByteString -> Int
BS.length ByteString
bs_cur Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ByteString -> Int
BS.length ByteString
bs_next Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
sz) (IncrementalDecoder s (ByteString, ByteOffset, a)
 -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b. (a -> b) -> a -> b
$
    
    
    
    
    let bs_tok :: ByteString
bs_tok   = ByteString
bs_cur ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Int -> ByteString -> ByteString
BS.unsafeTake (Int
sz Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
bs_cur) ByteString
bs_next
        bs' :: ByteString
bs'      =           Int -> ByteString -> ByteString
BS.unsafeDrop (Int
sz Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
bs_cur) ByteString
bs_next
        offset' :: ByteOffset
offset'  = ByteOffset
offset ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 Int
sz in
    
    Bool
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (ByteString -> Int
BS.length ByteString
bs_tok Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
sz) (IncrementalDecoder s (ByteString, ByteOffset, a)
 -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b. (a -> b) -> a -> b
$
    
    Bool
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (ByteString -> Int
BS.length ByteString
bs_cur Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ByteString -> Int
BS.length ByteString
bs_next Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
sz Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ByteString -> Int
BS.length ByteString
bs') (IncrementalDecoder s (ByteString, ByteOffset, a)
 -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b. (a -> b) -> a -> b
$ do
    
    SlowPath s a
slowpath <- ST s (SlowPath s a) -> IncrementalDecoder s (SlowPath s a)
forall s a. ST s a -> IncrementalDecoder s a
lift (ST s (SlowPath s a) -> IncrementalDecoder s (SlowPath s a))
-> ST s (SlowPath s a) -> IncrementalDecoder s (SlowPath s a)
forall a b. (a -> b) -> a -> b
$ ByteString -> DecodeAction s a -> ST s (SlowPath s a)
forall s a. ByteString -> DecodeAction s a -> ST s (SlowPath s a)
go_fast_end ByteString
bs_tok DecodeAction s a
da
    case SlowPath s a
slowpath of
      
      
      SlowDecodeAction ByteString
bs_empty DecodeAction s a
da' ->
        Bool
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (ByteString -> Bool
BS.null ByteString
bs_empty) (IncrementalDecoder s (ByteString, ByteOffset, a)
 -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b. (a -> b) -> a -> b
$
        DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow DecodeAction s a
da' ByteString
bs' ByteOffset
offset'
      
      FastDone ByteString
bs_empty a
x ->
        Bool
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (ByteString -> Bool
BS.null ByteString
bs_empty) (IncrementalDecoder s (ByteString, ByteOffset, a)
 -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b. (a -> b) -> a -> b
$
        (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a. a -> IncrementalDecoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
bs', ByteOffset
offset', a
x)
      SlowConsumeTokenBytes ByteString
bs_empty ByteString -> ST s (DecodeAction s a)
k Int
len ->
        Bool
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (ByteString -> Bool
BS.null ByteString
bs_empty) (IncrementalDecoder s (ByteString, ByteOffset, a)
 -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b. (a -> b) -> a -> b
$ do
        (ByteString
bstr, ByteString
bs'') <- ByteString
-> ByteOffset
-> Int
-> IncrementalDecoder s (ByteString, ByteString)
forall s.
ByteString
-> ByteOffset
-> Int
-> IncrementalDecoder s (ByteString, ByteString)
getTokenShortOrVarLen ByteString
bs' ByteOffset
offset' Int
len
        ST s (DecodeAction s a) -> IncrementalDecoder s (DecodeAction s a)
forall s a. ST s a -> IncrementalDecoder s a
lift (ByteString -> ST s (DecodeAction s a)
k ByteString
bstr) IncrementalDecoder s (DecodeAction s a)
-> (DecodeAction s a
    -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b.
IncrementalDecoder s a
-> (a -> IncrementalDecoder s b) -> IncrementalDecoder s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \DecodeAction s a
daz -> DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow DecodeAction s a
daz ByteString
bs'' (ByteOffset
offset' ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 Int
len)
      SlowConsumeTokenByteArray ByteString
bs_empty ByteArray -> ST s (DecodeAction s a)
k Int
len ->
        Bool
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (ByteString -> Bool
BS.null ByteString
bs_empty) (IncrementalDecoder s (ByteString, ByteOffset, a)
 -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b. (a -> b) -> a -> b
$ do
        (ByteString
bstr, ByteString
bs'') <- ByteString
-> ByteOffset
-> Int
-> IncrementalDecoder s (ByteString, ByteString)
forall s.
ByteString
-> ByteOffset
-> Int
-> IncrementalDecoder s (ByteString, ByteString)
getTokenShortOrVarLen ByteString
bs' ByteOffset
offset' Int
len
        let !ba :: ByteArray
ba = ByteString -> ByteArray
BA.fromByteString ByteString
bstr
        ST s (DecodeAction s a) -> IncrementalDecoder s (DecodeAction s a)
forall s a. ST s a -> IncrementalDecoder s a
lift (ByteArray -> ST s (DecodeAction s a)
k ByteArray
ba) IncrementalDecoder s (DecodeAction s a)
-> (DecodeAction s a
    -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b.
IncrementalDecoder s a
-> (a -> IncrementalDecoder s b) -> IncrementalDecoder s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \DecodeAction s a
daz -> DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow DecodeAction s a
daz ByteString
bs'' (ByteOffset
offset' ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 Int
len)
      SlowConsumeTokenString ByteString
bs_empty Text -> ST s (DecodeAction s a)
k Int
len ->
        Bool
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (ByteString -> Bool
BS.null ByteString
bs_empty) (IncrementalDecoder s (ByteString, ByteOffset, a)
 -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b. (a -> b) -> a -> b
$ do
        (ByteString
bstr, ByteString
bs'') <- ByteString
-> ByteOffset
-> Int
-> IncrementalDecoder s (ByteString, ByteString)
forall s.
ByteString
-> ByteOffset
-> Int
-> IncrementalDecoder s (ByteString, ByteString)
getTokenShortOrVarLen ByteString
bs' ByteOffset
offset' Int
len
        case ByteString -> Either UnicodeException Text
T.decodeUtf8' ByteString
bstr of
          Right Text
str -> ST s (DecodeAction s a) -> IncrementalDecoder s (DecodeAction s a)
forall s a. ST s a -> IncrementalDecoder s a
lift (Text -> ST s (DecodeAction s a)
k Text
str) IncrementalDecoder s (DecodeAction s a)
-> (DecodeAction s a
    -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b.
IncrementalDecoder s a
-> (a -> IncrementalDecoder s b) -> IncrementalDecoder s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \DecodeAction s a
daz ->
                       DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow DecodeAction s a
daz ByteString
bs'' (ByteOffset
offset' ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 Int
len)
          Left UnicodeException
_e   -> ByteString
-> ByteOffset
-> String
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
ByteString -> ByteOffset -> String -> IncrementalDecoder s a
decodeFail ByteString
bs' ByteOffset
offset' String
"invalid UTF8"
      SlowConsumeTokenUtf8ByteArray ByteString
bs_empty ByteArray -> ST s (DecodeAction s a)
k Int
len ->
        Bool
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (ByteString -> Bool
BS.null ByteString
bs_empty) (IncrementalDecoder s (ByteString, ByteOffset, a)
 -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b. (a -> b) -> a -> b
$ do
        (ByteString
bstr, ByteString
bs'') <- ByteString
-> ByteOffset
-> Int
-> IncrementalDecoder s (ByteString, ByteString)
forall s.
ByteString
-> ByteOffset
-> Int
-> IncrementalDecoder s (ByteString, ByteString)
getTokenShortOrVarLen ByteString
bs' ByteOffset
offset' Int
len
        let !ba :: ByteArray
ba = ByteString -> ByteArray
BA.fromByteString ByteString
bstr
        ST s (DecodeAction s a) -> IncrementalDecoder s (DecodeAction s a)
forall s a. ST s a -> IncrementalDecoder s a
lift (ByteArray -> ST s (DecodeAction s a)
k ByteArray
ba) IncrementalDecoder s (DecodeAction s a)
-> (DecodeAction s a
    -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b.
IncrementalDecoder s a
-> (a -> IncrementalDecoder s b) -> IncrementalDecoder s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \DecodeAction s a
daz -> DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow DecodeAction s a
daz ByteString
bs'' (ByteOffset
offset' ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 Int
len)
      SlowPeekByteOffset ByteString
bs_empty Int# -> ST s (DecodeAction s a)
k ->
        Bool
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (ByteString -> Bool
BS.null ByteString
bs_empty) (IncrementalDecoder s (ByteString, ByteOffset, a)
 -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b. (a -> b) -> a -> b
$ do
        ST s (DecodeAction s a) -> IncrementalDecoder s (DecodeAction s a)
forall s a. ST s a -> IncrementalDecoder s a
lift
#if MIN_VERSION_base(4,17,0)
          (Int# -> ST s (DecodeAction s a)
k (Int64# -> Int#
int64ToInt# Int64#
off#))
#else
          (k off#)
#endif
          IncrementalDecoder s (DecodeAction s a)
-> (DecodeAction s a
    -> IncrementalDecoder s (ByteString, ByteOffset, a))
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall a b.
IncrementalDecoder s a
-> (a -> IncrementalDecoder s b) -> IncrementalDecoder s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \DecodeAction s a
daz -> DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
DecodeAction s a
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteOffset, a)
go_slow DecodeAction s a
daz ByteString
bs' ByteOffset
offset'
        where
          !(I64# Int64#
off#) = ByteOffset
offset'
      SlowFail ByteString
bs_unconsumed String
msg ->
        ByteString
-> ByteOffset
-> String
-> IncrementalDecoder s (ByteString, ByteOffset, a)
forall s a.
ByteString -> ByteOffset -> String -> IncrementalDecoder s a
decodeFail (ByteString
bs_unconsumed ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
bs') ByteOffset
offset'' String
msg
        where
          !offset'' :: ByteOffset
offset'' = ByteOffset
offset ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ Int -> ByteOffset
intToInt64 (Int
sz Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
bs_unconsumed)
  where
    {-# INLINE getTokenShortOrVarLen #-}
    getTokenShortOrVarLen :: BS.ByteString
                          -> ByteOffset
                          -> Int
                          -> IncrementalDecoder s (ByteString, ByteString)
    getTokenShortOrVarLen :: forall s.
ByteString
-> ByteOffset
-> Int
-> IncrementalDecoder s (ByteString, ByteString)
getTokenShortOrVarLen ByteString
bs' ByteOffset
offset' Int
len
      | ByteString -> Int
BS.length ByteString
bs' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
len = Int
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteString)
forall s.
Int
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteString)
getTokenVarLen Int
len ByteString
bs' ByteOffset
offset'
      | Bool
otherwise           = let !bstr :: ByteString
bstr = Int -> ByteString -> ByteString
BS.take Int
len ByteString
bs'
                                  !bs'' :: ByteString
bs'' = Int -> ByteString -> ByteString
BS.drop Int
len ByteString
bs'
                               in (ByteString, ByteString)
-> IncrementalDecoder s (ByteString, ByteString)
forall a. a -> IncrementalDecoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
bstr, ByteString
bs'')
getTokenVarLen :: Int -> ByteString -> ByteOffset
               -> IncrementalDecoder s (ByteString, ByteString)
getTokenVarLen :: forall s.
Int
-> ByteString
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteString)
getTokenVarLen Int
len ByteString
bs ByteOffset
offset =
    Bool
-> IncrementalDecoder s (ByteString, ByteString)
-> IncrementalDecoder s (ByteString, ByteString)
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> ByteString -> Int
BS.length ByteString
bs) (IncrementalDecoder s (ByteString, ByteString)
 -> IncrementalDecoder s (ByteString, ByteString))
-> IncrementalDecoder s (ByteString, ByteString)
-> IncrementalDecoder s (ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ do
    Maybe ByteString
mbs <- IncrementalDecoder s (Maybe ByteString)
forall s. IncrementalDecoder s (Maybe ByteString)
needChunk
    case Maybe ByteString
mbs of
      Maybe ByteString
Nothing -> ByteString
-> ByteOffset
-> String
-> IncrementalDecoder s (ByteString, ByteString)
forall s a.
ByteString -> ByteOffset -> String -> IncrementalDecoder s a
decodeFail ByteString
BS.empty ByteOffset
offset String
"end of input"
      Just ByteString
bs'
        | let n :: Int
n = Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
bs
        , ByteString -> Int
BS.length ByteString
bs' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
n ->
            let !tok :: ByteString
tok = ByteString
bs ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Int -> ByteString -> ByteString
BS.unsafeTake Int
n ByteString
bs'
             in (ByteString, ByteString)
-> IncrementalDecoder s (ByteString, ByteString)
forall a. a -> IncrementalDecoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
tok, Int -> ByteString -> ByteString
BS.drop Int
n ByteString
bs')
        | Bool
otherwise -> [ByteString]
-> Int
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteString)
forall s.
[ByteString]
-> Int
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteString)
getTokenVarLenSlow
                         [ByteString
bs',ByteString
bs]
                         (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- (ByteString -> Int
BS.length ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ByteString -> Int
BS.length ByteString
bs'))
                         ByteOffset
offset
getTokenVarLenSlow :: [ByteString] -> Int -> ByteOffset
                   -> IncrementalDecoder s (ByteString, ByteString)
getTokenVarLenSlow :: forall s.
[ByteString]
-> Int
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteString)
getTokenVarLenSlow [ByteString]
bss Int
n ByteOffset
offset = do
    Maybe ByteString
mbs <- IncrementalDecoder s (Maybe ByteString)
forall s. IncrementalDecoder s (Maybe ByteString)
needChunk
    case Maybe ByteString
mbs of
      Maybe ByteString
Nothing -> ByteString
-> ByteOffset
-> String
-> IncrementalDecoder s (ByteString, ByteString)
forall s a.
ByteString -> ByteOffset -> String -> IncrementalDecoder s a
decodeFail ByteString
BS.empty ByteOffset
offset String
"end of input"
      Just ByteString
bs
        | ByteString -> Int
BS.length ByteString
bs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
n ->
            let !tok :: ByteString
tok = [ByteString] -> ByteString
BS.concat ([ByteString] -> [ByteString]
forall a. [a] -> [a]
reverse (Int -> ByteString -> ByteString
BS.unsafeTake Int
n ByteString
bs ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: [ByteString]
bss))
             in (ByteString, ByteString)
-> IncrementalDecoder s (ByteString, ByteString)
forall a. a -> IncrementalDecoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
tok, Int -> ByteString -> ByteString
BS.drop Int
n ByteString
bs)
        | Bool
otherwise -> [ByteString]
-> Int
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteString)
forall s.
[ByteString]
-> Int
-> ByteOffset
-> IncrementalDecoder s (ByteString, ByteString)
getTokenVarLenSlow (ByteString
bsByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
:[ByteString]
bss) (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
bs) ByteOffset
offset
tokenSize :: Word8 -> Int
tokenSize :: Word8 -> Int
tokenSize Word8
hdr =
    Word8 -> Int
word8ToInt (Word8 -> Int) -> Word8 -> Int
forall a b. (a -> b) -> a -> b
$
      UArray Word8 Word8
decodeTableSz UArray Word8 Word8 -> Int -> Word8
forall i. Ix i => UArray i Word8 -> Int -> Word8
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> Int -> e
`A.unsafeAt` (Word8 -> Int
word8ToInt Word8
hdr Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0x1f)
decodeTableSz :: UArray Word8 Word8
decodeTableSz :: UArray Word8 Word8
decodeTableSz =
  (Word8, Word8) -> [(Word8, Word8)] -> UArray Word8 Word8
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(i, e)] -> a i e
array (Word8
0, Word8
0x1f) ([(Word8, Word8)] -> UArray Word8 Word8)
-> [(Word8, Word8)] -> UArray Word8 Word8
forall a b. (a -> b) -> a -> b
$
      [ (Word8 -> Word8 -> Word8
encodeHeader Word8
0 Word8
n, Word8
1) | Word8
n <- [Word8
0..Word8
0x1f] ]
   [(Word8, Word8)] -> [(Word8, Word8)] -> [(Word8, Word8)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
0 Word8
n, Word8
s) | (Word8
n, Word8
s) <- [Word8] -> [Word8] -> [(Word8, Word8)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Word8
24..Word8
27] [Word8
2,Word8
3,Word8
5,Word8
9] ]
decodeTokenTypeTable :: Array Word8 TokenType
decodeTokenTypeTable :: Array Word8 TokenType
decodeTokenTypeTable =
  (Word8, Word8) -> [(Word8, TokenType)] -> Array Word8 TokenType
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(i, e)] -> a i e
array (Word8
forall a. Bounded a => a
minBound, Word8
forall a. Bounded a => a
maxBound) ([(Word8, TokenType)] -> Array Word8 TokenType)
-> [(Word8, TokenType)] -> Array Word8 TokenType
forall a b. (a -> b) -> a -> b
$
    [ (Word8 -> Word8 -> Word8
encodeHeader Word8
0 Word8
n,  TokenType
TypeUInt) | Word8
n <-  [Word8
0..Word8
26] ]
 [(Word8, TokenType)]
-> [(Word8, TokenType)] -> [(Word8, TokenType)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
0 Word8
27, TokenType
TypeUInt64)
    , (Word8 -> Word8 -> Word8
encodeHeader Word8
0 Word8
31, TokenType
TypeInvalid) ]
 [(Word8, TokenType)]
-> [(Word8, TokenType)] -> [(Word8, TokenType)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
1 Word8
n,  TokenType
TypeNInt) | Word8
n <-  [Word8
0..Word8
26] ]
 [(Word8, TokenType)]
-> [(Word8, TokenType)] -> [(Word8, TokenType)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
1 Word8
27, TokenType
TypeNInt64)
    , (Word8 -> Word8 -> Word8
encodeHeader Word8
1 Word8
31, TokenType
TypeInvalid) ]
 [(Word8, TokenType)]
-> [(Word8, TokenType)] -> [(Word8, TokenType)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
2 Word8
n,  TokenType
TypeBytes) | Word8
n <-  [Word8
0..Word8
27] ]
 [(Word8, TokenType)]
-> [(Word8, TokenType)] -> [(Word8, TokenType)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
2 Word8
31, TokenType
TypeBytesIndef) ]
 [(Word8, TokenType)]
-> [(Word8, TokenType)] -> [(Word8, TokenType)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
3 Word8
n,  TokenType
TypeString) | Word8
n <-  [Word8
0..Word8
27] ]
 [(Word8, TokenType)]
-> [(Word8, TokenType)] -> [(Word8, TokenType)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
3 Word8
31, TokenType
TypeStringIndef) ]
 [(Word8, TokenType)]
-> [(Word8, TokenType)] -> [(Word8, TokenType)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
4 Word8
n,  TokenType
TypeListLen) | Word8
n <-  [Word8
0..Word8
26] ]
 [(Word8, TokenType)]
-> [(Word8, TokenType)] -> [(Word8, TokenType)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
4 Word8
27, TokenType
TypeListLen64)
    , (Word8 -> Word8 -> Word8
encodeHeader Word8
4 Word8
31, TokenType
TypeListLenIndef) ]
 [(Word8, TokenType)]
-> [(Word8, TokenType)] -> [(Word8, TokenType)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
5 Word8
n,  TokenType
TypeMapLen) | Word8
n <-  [Word8
0..Word8
26] ]
 [(Word8, TokenType)]
-> [(Word8, TokenType)] -> [(Word8, TokenType)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
5 Word8
27, TokenType
TypeMapLen64)
    , (Word8 -> Word8 -> Word8
encodeHeader Word8
5 Word8
31, TokenType
TypeMapLenIndef) ]
 [(Word8, TokenType)]
-> [(Word8, TokenType)] -> [(Word8, TokenType)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
6 Word8
n,  TokenType
TypeTag) | Word8
n <- Word8
0Word8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
:Word8
1Word8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
:[Word8
4..Word8
26] ]
 [(Word8, TokenType)]
-> [(Word8, TokenType)] -> [(Word8, TokenType)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
6 Word8
2,  TokenType
TypeInteger)
    , (Word8 -> Word8 -> Word8
encodeHeader Word8
6 Word8
3,  TokenType
TypeInteger)
    , (Word8 -> Word8 -> Word8
encodeHeader Word8
6 Word8
27, TokenType
TypeTag64)
    , (Word8 -> Word8 -> Word8
encodeHeader Word8
6 Word8
31, TokenType
TypeInvalid) ]
 [(Word8, TokenType)]
-> [(Word8, TokenType)] -> [(Word8, TokenType)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
7 Word8
n,  TokenType
TypeSimple) | Word8
n <-  [Word8
0..Word8
19] ]
 [(Word8, TokenType)]
-> [(Word8, TokenType)] -> [(Word8, TokenType)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
7 Word8
20, TokenType
TypeBool)
    , (Word8 -> Word8 -> Word8
encodeHeader Word8
7 Word8
21, TokenType
TypeBool)
    , (Word8 -> Word8 -> Word8
encodeHeader Word8
7 Word8
22, TokenType
TypeNull)
    , (Word8 -> Word8 -> Word8
encodeHeader Word8
7 Word8
23, TokenType
TypeSimple)
    , (Word8 -> Word8 -> Word8
encodeHeader Word8
7 Word8
24, TokenType
TypeSimple)
    , (Word8 -> Word8 -> Word8
encodeHeader Word8
7 Word8
25, TokenType
TypeFloat16)
    , (Word8 -> Word8 -> Word8
encodeHeader Word8
7 Word8
26, TokenType
TypeFloat32)
    , (Word8 -> Word8 -> Word8
encodeHeader Word8
7 Word8
27, TokenType
TypeFloat64)
    , (Word8 -> Word8 -> Word8
encodeHeader Word8
7 Word8
31, TokenType
TypeBreak) ]
 [(Word8, TokenType)]
-> [(Word8, TokenType)] -> [(Word8, TokenType)]
forall a. [a] -> [a] -> [a]
++ [ (Word8 -> Word8 -> Word8
encodeHeader Word8
mt Word8
n, TokenType
TypeInvalid) | Word8
mt <- [Word8
0..Word8
7], Word8
n <- [Word8
28..Word8
30] ]
encodeHeader :: Word8 -> Word8 -> Word8
 Word8
mt Word8
ai = Word8
mt Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftL` Int
5 Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.|. Word8
ai
data DecodedToken a = DecodedToken !Int !a | DecodeFailure
  deriving Int -> DecodedToken a -> ShowS
[DecodedToken a] -> ShowS
DecodedToken a -> String
(Int -> DecodedToken a -> ShowS)
-> (DecodedToken a -> String)
-> ([DecodedToken a] -> ShowS)
-> Show (DecodedToken a)
forall a. Show a => Int -> DecodedToken a -> ShowS
forall a. Show a => [DecodedToken a] -> ShowS
forall a. Show a => DecodedToken a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> DecodedToken a -> ShowS
showsPrec :: Int -> DecodedToken a -> ShowS
$cshow :: forall a. Show a => DecodedToken a -> String
show :: DecodedToken a -> String
$cshowList :: forall a. Show a => [DecodedToken a] -> ShowS
showList :: [DecodedToken a] -> ShowS
Show
data LongToken a = Fits Bool  !a
                 | TooLong Bool  !Int
  deriving Int -> LongToken a -> ShowS
[LongToken a] -> ShowS
LongToken a -> String
(Int -> LongToken a -> ShowS)
-> (LongToken a -> String)
-> ([LongToken a] -> ShowS)
-> Show (LongToken a)
forall a. Show a => Int -> LongToken a -> ShowS
forall a. Show a => [LongToken a] -> ShowS
forall a. Show a => LongToken a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> LongToken a -> ShowS
showsPrec :: Int -> LongToken a -> ShowS
$cshow :: forall a. Show a => LongToken a -> String
show :: LongToken a -> String
$cshowList :: forall a. Show a => [LongToken a] -> ShowS
showList :: [LongToken a] -> ShowS
Show
{-# INLINE isFloat16Canonical #-}
isFloat16Canonical :: Int -> BS.ByteString -> Float -> Bool
isFloat16Canonical :: Int -> ByteString -> Float -> Bool
isFloat16Canonical Int
sz ByteString
bs Float
f
  | Int
sz Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
3   = Bool
False
  | Float -> Bool
forall a. RealFloat a => a -> Bool
isNaN Float
f   = ByteString -> Word16
eatTailWord16 ByteString
bs Word16 -> Word16 -> Bool
forall a. Eq a => a -> a -> Bool
== Word16
0x7e00
  | Bool
otherwise = Bool
True
{-# INLINE isFloatCanonical #-}
isFloatCanonical :: Int -> BS.ByteString -> Float -> Bool
isFloatCanonical :: Int -> ByteString -> Float -> Bool
isFloatCanonical Int
sz ByteString
bs Float
f
  | Float -> Bool
forall a. RealFloat a => a -> Bool
isNaN Float
f   = Int
sz Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
3 Bool -> Bool -> Bool
&& ByteString -> Word16
eatTailWord16 ByteString
bs Word16 -> Word16 -> Bool
forall a. Eq a => a -> a -> Bool
== Word16
0x7e00
  | Bool
otherwise = Int
sz Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
5
{-# INLINE isDoubleCanonical #-}
isDoubleCanonical :: Int -> BS.ByteString -> Double -> Bool
isDoubleCanonical :: Int -> ByteString -> Double -> Bool
isDoubleCanonical Int
sz ByteString
bs Double
f
  | Double -> Bool
forall a. RealFloat a => a -> Bool
isNaN Double
f   = Int
sz Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
3 Bool -> Bool -> Bool
&& ByteString -> Word16
eatTailWord16 ByteString
bs Word16 -> Word16 -> Bool
forall a. Eq a => a -> a -> Bool
== Word16
0x7e00
  | Bool
otherwise = Int
sz Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
9
{-# INLINE isWordCanonical #-}
isWordCanonical :: Int -> Word -> Bool
isWordCanonical :: Int -> Word -> Bool
isWordCanonical Int
sz !Word
w
  | Int
sz Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2   = Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
> Word
0x17
  | Int
sz Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
3   = Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
> Word
0xff
  | Int
sz Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
5   = Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
> Word
0xffff
  | Int
sz Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
9   = Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
> Word
0xffffffff
  | Bool
otherwise = Bool
True
{-# INLINE isIntCanonical #-}
isIntCanonical :: Int -> Int -> Bool
isIntCanonical :: Int -> Int -> Bool
isIntCanonical Int
sz Int
i
  | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0     = Int -> Word -> Bool
isWordCanonical Int
sz (Word -> Word
forall a. Bits a => a -> a
complement Word
w)
  | Bool
otherwise = Int -> Word -> Bool
isWordCanonical Int
sz       Word
w
  where
    w :: Word
w = Int -> Word
intToWord Int
i
#if defined(ARCH_32bit)
{-# INLINE isWord64Canonical #-}
isWord64Canonical :: Int -> Word64 -> Bool
isWord64Canonical sz w
  | sz == 2   = w > 0x17)
  | sz == 3   = w > 0xff)
  | sz == 5   = w > 0xffff)
  | sz == 9   = w > 0xffffffff)
  | otherwise = True
{-# INLINE isInt64Canonical #-}
isInt64Canonical :: Int -> Int64# -> Bool
isInt64Canonical sz i#
  | isTrue# (i# `ltInt64#` intToInt64# 0#) = isWord64Canonical sz (not64# w#)
  | otherwise                              = isWord64Canonical sz         w#
  where
    w# = int64ToWord64# i#
#endif
{-# INLINE isSimpleCanonical #-}
isSimpleCanonical :: Int -> Word# -> Bool
isSimpleCanonical :: Int -> Word# -> Bool
isSimpleCanonical Int
2 Word#
w# = Int# -> Bool
isTrue# (Word#
w# Word# -> Word# -> Int#
`gtWord#` Word#
0x17##)
isSimpleCanonical Int
_ Word#
_  = Bool
True 
{-# INLINE tryConsumeWord #-}
tryConsumeWord :: Word8 -> ByteString -> DecodedToken Word
tryConsumeWord :: Word8 -> ByteString -> DecodedToken Word
tryConsumeWord Word8
hdr !ByteString
bs = case Word8 -> Word
word8ToWord Word8
hdr of
  
  Word
0x00 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
0
  Word
0x01 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
1
  Word
0x02 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
2
  Word
0x03 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
3
  Word
0x04 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
4
  Word
0x05 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
5
  Word
0x06 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
6
  Word
0x07 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
7
  Word
0x08 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
8
  Word
0x09 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
9
  Word
0x0a -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
10
  Word
0x0b -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
11
  Word
0x0c -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
12
  Word
0x0d -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
13
  Word
0x0e -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
14
  Word
0x0f -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
15
  Word
0x10 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
16
  Word
0x11 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
17
  Word
0x12 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
18
  Word
0x13 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
19
  Word
0x14 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
20
  Word
0x15 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
21
  Word
0x16 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
22
  Word
0x17 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
23
  Word
0x18 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
2 (Word -> DecodedToken Word) -> Word -> DecodedToken Word
forall a b. (a -> b) -> a -> b
$! Word8 -> Word
word8ToWord  (ByteString -> Word8
eatTailWord8 ByteString
bs)
  Word
0x19 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
3 (Word -> DecodedToken Word) -> Word -> DecodedToken Word
forall a b. (a -> b) -> a -> b
$! Word16 -> Word
word16ToWord (ByteString -> Word16
eatTailWord16 ByteString
bs)
  Word
0x1a -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
5 (Word -> DecodedToken Word) -> Word -> DecodedToken Word
forall a b. (a -> b) -> a -> b
$! Word32 -> Word
word32ToWord (ByteString -> Word32
eatTailWord32 ByteString
bs)
#if defined(ARCH_64bit)
  Word
0x1b -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
9 (Word -> DecodedToken Word) -> Word -> DecodedToken Word
forall a b. (a -> b) -> a -> b
$! Word64 -> Word
word64ToWord (ByteString -> Word64
eatTailWord64 ByteString
bs)
#else
  0x1b -> case word64ToWord (eatTailWord64 bs) of
            Just n  -> DecodedToken 9 n
            Nothing -> DecodeFailure
#endif
  Word
_    -> DecodedToken Word
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeNegWord #-}
tryConsumeNegWord :: Word8 -> ByteString -> DecodedToken Word
tryConsumeNegWord :: Word8 -> ByteString -> DecodedToken Word
tryConsumeNegWord Word8
hdr !ByteString
bs = case Word8 -> Word
word8ToWord Word8
hdr of
  
  Word
0x20 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
0
  Word
0x21 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
1
  Word
0x22 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
2
  Word
0x23 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
3
  Word
0x24 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
4
  Word
0x25 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
5
  Word
0x26 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
6
  Word
0x27 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
7
  Word
0x28 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
8
  Word
0x29 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
9
  Word
0x2a -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
10
  Word
0x2b -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
11
  Word
0x2c -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
12
  Word
0x2d -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
13
  Word
0x2e -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
14
  Word
0x2f -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
15
  Word
0x30 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
16
  Word
0x31 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
17
  Word
0x32 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
18
  Word
0x33 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
19
  Word
0x34 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
20
  Word
0x35 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
21
  Word
0x36 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
22
  Word
0x37 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
23
  Word
0x38 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
2 (Word -> DecodedToken Word) -> Word -> DecodedToken Word
forall a b. (a -> b) -> a -> b
$! (Word8 -> Word
word8ToWord  (ByteString -> Word8
eatTailWord8 ByteString
bs))
  Word
0x39 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
3 (Word -> DecodedToken Word) -> Word -> DecodedToken Word
forall a b. (a -> b) -> a -> b
$! (Word16 -> Word
word16ToWord (ByteString -> Word16
eatTailWord16 ByteString
bs))
  Word
0x3a -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
5 (Word -> DecodedToken Word) -> Word -> DecodedToken Word
forall a b. (a -> b) -> a -> b
$! (Word32 -> Word
word32ToWord (ByteString -> Word32
eatTailWord32 ByteString
bs))
#if defined(ARCH_64bit)
  Word
0x3b -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
9 (Word -> DecodedToken Word) -> Word -> DecodedToken Word
forall a b. (a -> b) -> a -> b
$! (Word64 -> Word
word64ToWord (ByteString -> Word64
eatTailWord64 ByteString
bs))
#else
  0x3b -> case word64ToWord (eatTailWord64 bs) of
            Just n  -> DecodedToken 9 n
            Nothing -> DecodeFailure
#endif
  Word
_    -> DecodedToken Word
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeInt #-}
tryConsumeInt :: Word8 -> ByteString -> DecodedToken Int
tryConsumeInt :: Word8 -> ByteString -> DecodedToken Int
tryConsumeInt Word8
hdr !ByteString
bs = case Word8 -> Word
word8ToWord Word8
hdr of
  
  Word
0x00 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
0
  Word
0x01 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
1
  Word
0x02 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
2
  Word
0x03 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
3
  Word
0x04 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
4
  Word
0x05 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
5
  Word
0x06 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
6
  Word
0x07 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
7
  Word
0x08 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
8
  Word
0x09 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
9
  Word
0x0a -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
10
  Word
0x0b -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
11
  Word
0x0c -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
12
  Word
0x0d -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
13
  Word
0x0e -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
14
  Word
0x0f -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
15
  Word
0x10 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
16
  Word
0x11 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
17
  Word
0x12 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
18
  Word
0x13 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
19
  Word
0x14 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
20
  Word
0x15 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
21
  Word
0x16 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
22
  Word
0x17 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
23
  Word
0x18 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
2 (Int -> DecodedToken Int) -> Int -> DecodedToken Int
forall a b. (a -> b) -> a -> b
$! (Word8 -> Int
word8ToInt  (ByteString -> Word8
eatTailWord8 ByteString
bs))
  Word
0x19 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
3 (Int -> DecodedToken Int) -> Int -> DecodedToken Int
forall a b. (a -> b) -> a -> b
$! (Word16 -> Int
word16ToInt (ByteString -> Word16
eatTailWord16 ByteString
bs))
#if defined(ARCH_64bit)
  Word
0x1a -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
5 (Int -> DecodedToken Int) -> Int -> DecodedToken Int
forall a b. (a -> b) -> a -> b
$! (Word32 -> Int
word32ToInt (ByteString -> Word32
eatTailWord32 ByteString
bs))
#else
  0x1a -> case word32ToInt (eatTailWord32 bs) of
            Just n  -> DecodedToken 5 n
            Nothing -> DecodeFailure
#endif
  Word
0x1b -> case Word64 -> Maybe Int
word64ToInt (ByteString -> Word64
eatTailWord64 ByteString
bs) of
            Just Int
n  -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
9 Int
n
            Maybe Int
Nothing -> DecodedToken Int
forall a. DecodedToken a
DecodeFailure
  
  Word
0x20 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
1)
  Word
0x21 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
2)
  Word
0x22 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
3)
  Word
0x23 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
4)
  Word
0x24 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
5)
  Word
0x25 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
6)
  Word
0x26 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
7)
  Word
0x27 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
8)
  Word
0x28 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
9)
  Word
0x29 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
10)
  Word
0x2a -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
11)
  Word
0x2b -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
12)
  Word
0x2c -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
13)
  Word
0x2d -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
14)
  Word
0x2e -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
15)
  Word
0x2f -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
16)
  Word
0x30 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
17)
  Word
0x31 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
18)
  Word
0x32 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
19)
  Word
0x33 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
20)
  Word
0x34 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
21)
  Word
0x35 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
22)
  Word
0x36 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
23)
  Word
0x37 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
24)
  Word
0x38 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
2 (Int -> DecodedToken Int) -> Int -> DecodedToken Int
forall a b. (a -> b) -> a -> b
$! (-Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Word8 -> Int
word8ToInt  (ByteString -> Word8
eatTailWord8 ByteString
bs))
  Word
0x39 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
3 (Int -> DecodedToken Int) -> Int -> DecodedToken Int
forall a b. (a -> b) -> a -> b
$! (-Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Word16 -> Int
word16ToInt (ByteString -> Word16
eatTailWord16 ByteString
bs))
#if defined(ARCH_64bit)
  Word
0x3a -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
5 (Int -> DecodedToken Int) -> Int -> DecodedToken Int
forall a b. (a -> b) -> a -> b
$! (-Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Word32 -> Int
word32ToInt (ByteString -> Word32
eatTailWord32 ByteString
bs))
#else
  0x3a -> case word32ToInt (eatTailWord32 bs) of
            Just n  -> DecodedToken 5 (-1 - n)
            Nothing -> DecodeFailure
#endif
  Word
0x3b -> case Word64 -> Maybe Int
word64ToInt (ByteString -> Word64
eatTailWord64 ByteString
bs) of
            Just Int
n  -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
9 (-Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n)
            Maybe Int
Nothing -> DecodedToken Int
forall a. DecodedToken a
DecodeFailure
  Word
_    -> DecodedToken Int
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeInteger #-}
tryConsumeInteger :: Word8 -> ByteString -> DecodedToken (BigIntToken Integer)
tryConsumeInteger :: Word8 -> ByteString -> DecodedToken (BigIntToken Integer)
tryConsumeInteger Word8
hdr !ByteString
bs = case Word8 -> Word
word8ToWord Word8
hdr of
  
  Word
0x00 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
0)
  Word
0x01 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
1)
  Word
0x02 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
2)
  Word
0x03 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
3)
  Word
0x04 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
4)
  Word
0x05 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
5)
  Word
0x06 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
6)
  Word
0x07 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
7)
  Word
0x08 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
8)
  Word
0x09 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
9)
  Word
0x0a -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
10)
  Word
0x0b -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
11)
  Word
0x0c -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
12)
  Word
0x0d -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
13)
  Word
0x0e -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
14)
  Word
0x0f -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
15)
  Word
0x10 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
16)
  Word
0x11 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
17)
  Word
0x12 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
18)
  Word
0x13 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
19)
  Word
0x14 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
20)
  Word
0x15 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
21)
  Word
0x16 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
22)
  Word
0x17 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True Integer
23)
  Word
0x18 -> let !w :: Word8
w = ByteString -> Word8
eatTailWord8 ByteString
bs
              sz :: Int
sz = Int
2
          in Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
sz (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken (Int -> Word -> Bool
isWordCanonical Int
sz (Word8 -> Word
word8ToWord Word8
w))    (Integer -> BigIntToken Integer) -> Integer -> BigIntToken Integer
forall a b. (a -> b) -> a -> b
$! Word8 -> Integer
forall a. Integral a => a -> Integer
toInteger Word8
w)
  Word
0x19 -> let !w :: Word16
w = ByteString -> Word16
eatTailWord16 ByteString
bs
              sz :: Int
sz = Int
3
          in Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
sz (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken (Int -> Word -> Bool
isWordCanonical Int
sz (Word16 -> Word
word16ToWord Word16
w))   (Integer -> BigIntToken Integer) -> Integer -> BigIntToken Integer
forall a b. (a -> b) -> a -> b
$! Word16 -> Integer
forall a. Integral a => a -> Integer
toInteger Word16
w)
  Word
0x1a -> let !w :: Word32
w = ByteString -> Word32
eatTailWord32 ByteString
bs
              sz :: Int
sz = Int
5
          in Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
sz (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken (Int -> Word -> Bool
isWordCanonical Int
sz (Word32 -> Word
word32ToWord Word32
w))   (Integer -> BigIntToken Integer) -> Integer -> BigIntToken Integer
forall a b. (a -> b) -> a -> b
$! Word32 -> Integer
forall a. Integral a => a -> Integer
toInteger Word32
w)
  Word
0x1b -> let !w :: Word64
w = ByteString -> Word64
eatTailWord64 ByteString
bs
              sz :: Int
sz = Int
9
#if defined(ARCH_32bit)
          in DecodedToken sz (BigIntToken (isWord64Canonical sz (word64ToWord w)) $! toInteger w)
#else
          in Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
sz (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken (Int -> Word -> Bool
isWordCanonical Int
sz (Word64 -> Word
word64ToWord Word64
w))   (Integer -> BigIntToken Integer) -> Integer -> BigIntToken Integer
forall a b. (a -> b) -> a -> b
$! Word64 -> Integer
forall a. Integral a => a -> Integer
toInteger Word64
w)
#endif
  
  Word
0x20 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
1))
  Word
0x21 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
2))
  Word
0x22 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
3))
  Word
0x23 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
4))
  Word
0x24 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
5))
  Word
0x25 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
6))
  Word
0x26 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
7))
  Word
0x27 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
8))
  Word
0x28 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
9))
  Word
0x29 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
10))
  Word
0x2a -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
11))
  Word
0x2b -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
12))
  Word
0x2c -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
13))
  Word
0x2d -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
14))
  Word
0x2e -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
15))
  Word
0x2f -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
16))
  Word
0x30 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
17))
  Word
0x31 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
18))
  Word
0x32 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
19))
  Word
0x33 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
20))
  Word
0x34 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
21))
  Word
0x35 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
22))
  Word
0x36 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
23))
  Word
0x37 -> Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken Bool
True (-Integer
24))
  Word
0x38 -> let !w :: Word8
w = ByteString -> Word8
eatTailWord8 ByteString
bs
              sz :: Int
sz = Int
2
          in Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
sz (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken (Int -> Word -> Bool
isWordCanonical Int
sz (Word8 -> Word
word8ToWord Word8
w))    (Integer -> BigIntToken Integer) -> Integer -> BigIntToken Integer
forall a b. (a -> b) -> a -> b
$! (-Integer
1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Word8 -> Integer
forall a. Integral a => a -> Integer
toInteger Word8
w))
  Word
0x39 -> let !w :: Word16
w = ByteString -> Word16
eatTailWord16 ByteString
bs
              sz :: Int
sz = Int
3
          in Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
sz (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken (Int -> Word -> Bool
isWordCanonical Int
sz (Word16 -> Word
word16ToWord Word16
w))   (Integer -> BigIntToken Integer) -> Integer -> BigIntToken Integer
forall a b. (a -> b) -> a -> b
$! (-Integer
1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Word16 -> Integer
forall a. Integral a => a -> Integer
toInteger Word16
w))
  Word
0x3a -> let !w :: Word32
w = ByteString -> Word32
eatTailWord32 ByteString
bs
              sz :: Int
sz = Int
5
          in Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
sz (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken (Int -> Word -> Bool
isWordCanonical Int
sz (Word32 -> Word
word32ToWord Word32
w))   (Integer -> BigIntToken Integer) -> Integer -> BigIntToken Integer
forall a b. (a -> b) -> a -> b
$! (-Integer
1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Word32 -> Integer
forall a. Integral a => a -> Integer
toInteger Word32
w))
  Word
0x3b -> let !w :: Word64
w = ByteString -> Word64
eatTailWord64 ByteString
bs
              sz :: Int
sz = Int
9
#if defined(ARCH_32bit)
          in DecodedToken sz (BigIntToken (isWord64Canonical sz (word64ToWord w)) $! (-1 - toInteger w))
#else
          in Int -> BigIntToken Integer -> DecodedToken (BigIntToken Integer)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
sz (Bool -> Integer -> BigIntToken Integer
forall a. Bool -> Integer -> BigIntToken a
BigIntToken (Int -> Word -> Bool
isWordCanonical Int
sz (Word64 -> Word
word64ToWord Word64
w))   (Integer -> BigIntToken Integer) -> Integer -> BigIntToken Integer
forall a b. (a -> b) -> a -> b
$! (-Integer
1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Word64 -> Integer
forall a. Integral a => a -> Integer
toInteger Word64
w))
#endif
  Word
0xc2 -> ByteString -> DecodedToken (BigIntToken Integer)
forall a. ByteString -> DecodedToken (BigIntToken a)
readBigUInt ByteString
bs
  Word
0xc3 -> ByteString -> DecodedToken (BigIntToken Integer)
forall a. ByteString -> DecodedToken (BigIntToken a)
readBigNInt ByteString
bs
  Word
_    -> DecodedToken (BigIntToken Integer)
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeBytes #-}
tryConsumeBytes :: Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeBytes :: Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeBytes Word8
hdr !ByteString
bs = case Word8 -> Word
word8ToWord Word8
hdr of
  
  Word
0x40 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
0 ByteString
bs
  Word
0x41 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
1 ByteString
bs
  Word
0x42 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
2 ByteString
bs
  Word
0x43 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
3 ByteString
bs
  Word
0x44 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
4 ByteString
bs
  Word
0x45 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
5 ByteString
bs
  Word
0x46 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
6 ByteString
bs
  Word
0x47 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
7 ByteString
bs
  Word
0x48 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
8 ByteString
bs
  Word
0x49 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
9 ByteString
bs
  Word
0x4a -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
10 ByteString
bs
  Word
0x4b -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
11 ByteString
bs
  Word
0x4c -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
12 ByteString
bs
  Word
0x4d -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
13 ByteString
bs
  Word
0x4e -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
14 ByteString
bs
  Word
0x4f -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
15 ByteString
bs
  Word
0x50 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
16 ByteString
bs
  Word
0x51 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
17 ByteString
bs
  Word
0x52 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
18 ByteString
bs
  Word
0x53 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
19 ByteString
bs
  Word
0x54 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
20 ByteString
bs
  Word
0x55 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
21 ByteString
bs
  Word
0x56 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
22 ByteString
bs
  Word
0x57 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
23 ByteString
bs
  Word
0x58 -> ByteString -> DecodedToken (LongToken ByteString)
readBytes8  ByteString
bs
  Word
0x59 -> ByteString -> DecodedToken (LongToken ByteString)
readBytes16 ByteString
bs
  Word
0x5a -> ByteString -> DecodedToken (LongToken ByteString)
readBytes32 ByteString
bs
  Word
0x5b -> ByteString -> DecodedToken (LongToken ByteString)
readBytes64 ByteString
bs
  Word
_    -> DecodedToken (LongToken ByteString)
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeString #-}
tryConsumeString :: Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeString :: Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeString Word8
hdr !ByteString
bs = case Word8 -> Word
word8ToWord Word8
hdr of
  
  Word
0x60 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
0 ByteString
bs
  Word
0x61 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
1 ByteString
bs
  Word
0x62 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
2 ByteString
bs
  Word
0x63 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
3 ByteString
bs
  Word
0x64 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
4 ByteString
bs
  Word
0x65 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
5 ByteString
bs
  Word
0x66 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
6 ByteString
bs
  Word
0x67 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
7 ByteString
bs
  Word
0x68 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
8 ByteString
bs
  Word
0x69 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
9 ByteString
bs
  Word
0x6a -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
10 ByteString
bs
  Word
0x6b -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
11 ByteString
bs
  Word
0x6c -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
12 ByteString
bs
  Word
0x6d -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
13 ByteString
bs
  Word
0x6e -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
14 ByteString
bs
  Word
0x6f -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
15 ByteString
bs
  Word
0x70 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
16 ByteString
bs
  Word
0x71 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
17 ByteString
bs
  Word
0x72 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
18 ByteString
bs
  Word
0x73 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
19 ByteString
bs
  Word
0x74 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
20 ByteString
bs
  Word
0x75 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
21 ByteString
bs
  Word
0x76 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
22 ByteString
bs
  Word
0x77 -> Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
23 ByteString
bs
  Word
0x78 -> ByteString -> DecodedToken (LongToken ByteString)
readBytes8  ByteString
bs
  Word
0x79 -> ByteString -> DecodedToken (LongToken ByteString)
readBytes16 ByteString
bs
  Word
0x7a -> ByteString -> DecodedToken (LongToken ByteString)
readBytes32 ByteString
bs
  Word
0x7b -> ByteString -> DecodedToken (LongToken ByteString)
readBytes64 ByteString
bs
  Word
_    -> DecodedToken (LongToken ByteString)
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeListLen #-}
tryConsumeListLen :: Word8 -> ByteString -> DecodedToken Int
tryConsumeListLen :: Word8 -> ByteString -> DecodedToken Int
tryConsumeListLen Word8
hdr !ByteString
bs = case Word8 -> Word
word8ToWord Word8
hdr of
  
  Word
0x80 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
0
  Word
0x81 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
1
  Word
0x82 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
2
  Word
0x83 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
3
  Word
0x84 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
4
  Word
0x85 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
5
  Word
0x86 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
6
  Word
0x87 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
7
  Word
0x88 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
8
  Word
0x89 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
9
  Word
0x8a -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
10
  Word
0x8b -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
11
  Word
0x8c -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
12
  Word
0x8d -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
13
  Word
0x8e -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
14
  Word
0x8f -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
15
  Word
0x90 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
16
  Word
0x91 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
17
  Word
0x92 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
18
  Word
0x93 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
19
  Word
0x94 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
20
  Word
0x95 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
21
  Word
0x96 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
22
  Word
0x97 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
23
  Word
0x98 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
2 (Word8 -> Int
word8ToInt  (ByteString -> Word8
eatTailWord8 ByteString
bs))
  Word
0x99 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
3 (Word16 -> Int
word16ToInt (ByteString -> Word16
eatTailWord16 ByteString
bs))
#if defined(ARCH_64bit)
  Word
0x9a -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
5 (Word32 -> Int
word32ToInt (ByteString -> Word32
eatTailWord32 ByteString
bs))
#else
  0x9a -> case word32ToInt (eatTailWord32 bs) of
            Just n  -> DecodedToken 5 n
            Nothing -> DecodeFailure
#endif
  Word
0x9b -> case Word64 -> Maybe Int
word64ToInt (ByteString -> Word64
eatTailWord64 ByteString
bs) of
            Just Int
n  -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
9 Int
n
            Maybe Int
Nothing -> DecodedToken Int
forall a. DecodedToken a
DecodeFailure
  Word
_    -> DecodedToken Int
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeMapLen #-}
tryConsumeMapLen :: Word8 -> ByteString -> DecodedToken Int
tryConsumeMapLen :: Word8 -> ByteString -> DecodedToken Int
tryConsumeMapLen Word8
hdr !ByteString
bs = case Word8 -> Word
word8ToWord Word8
hdr of
  
  Word
0xa0 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
0
  Word
0xa1 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
1
  Word
0xa2 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
2
  Word
0xa3 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
3
  Word
0xa4 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
4
  Word
0xa5 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
5
  Word
0xa6 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
6
  Word
0xa7 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
7
  Word
0xa8 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
8
  Word
0xa9 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
9
  Word
0xaa -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
10
  Word
0xab -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
11
  Word
0xac -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
12
  Word
0xad -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
13
  Word
0xae -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
14
  Word
0xaf -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
15
  Word
0xb0 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
16
  Word
0xb1 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
17
  Word
0xb2 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
18
  Word
0xb3 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
19
  Word
0xb4 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
20
  Word
0xb5 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
21
  Word
0xb6 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
22
  Word
0xb7 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
23
  Word
0xb8 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
2 (Int -> DecodedToken Int) -> Int -> DecodedToken Int
forall a b. (a -> b) -> a -> b
$! (Word8 -> Int
word8ToInt  (ByteString -> Word8
eatTailWord8 ByteString
bs))
  Word
0xb9 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
3 (Int -> DecodedToken Int) -> Int -> DecodedToken Int
forall a b. (a -> b) -> a -> b
$! (Word16 -> Int
word16ToInt (ByteString -> Word16
eatTailWord16 ByteString
bs))
#if defined(ARCH_64bit)
  Word
0xba -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
5 (Int -> DecodedToken Int) -> Int -> DecodedToken Int
forall a b. (a -> b) -> a -> b
$! (Word32 -> Int
word32ToInt (ByteString -> Word32
eatTailWord32 ByteString
bs))
#else
  0xba -> case word32ToInt (eatTailWord32 bs) of
            Just n  -> DecodedToken 5 n
            Nothing -> DecodeFailure
#endif
  Word
0xbb -> case Word64 -> Maybe Int
word64ToInt (ByteString -> Word64
eatTailWord64 ByteString
bs) of
            Just Int
n  -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
9 Int
n
            Maybe Int
Nothing -> DecodedToken Int
forall a. DecodedToken a
DecodeFailure
  Word
_    -> DecodedToken Int
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeListLenIndef #-}
tryConsumeListLenIndef :: Word8 -> DecodedToken ()
tryConsumeListLenIndef :: Word8 -> DecodedToken ()
tryConsumeListLenIndef Word8
hdr = case Word8 -> Word
word8ToWord Word8
hdr of
  Word
0x9f -> Int -> () -> DecodedToken ()
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 ()
  Word
_    -> DecodedToken ()
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeMapLenIndef #-}
tryConsumeMapLenIndef :: Word8 -> DecodedToken ()
tryConsumeMapLenIndef :: Word8 -> DecodedToken ()
tryConsumeMapLenIndef Word8
hdr = case Word8 -> Word
word8ToWord Word8
hdr of
  Word
0xbf -> Int -> () -> DecodedToken ()
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 ()
  Word
_    -> DecodedToken ()
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeListLenOrIndef #-}
tryConsumeListLenOrIndef :: Word8 -> ByteString -> DecodedToken Int
tryConsumeListLenOrIndef :: Word8 -> ByteString -> DecodedToken Int
tryConsumeListLenOrIndef Word8
hdr !ByteString
bs = case Word8 -> Word
word8ToWord Word8
hdr of
  
  Word
0x80 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
0
  Word
0x81 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
1
  Word
0x82 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
2
  Word
0x83 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
3
  Word
0x84 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
4
  Word
0x85 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
5
  Word
0x86 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
6
  Word
0x87 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
7
  Word
0x88 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
8
  Word
0x89 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
9
  Word
0x8a -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
10
  Word
0x8b -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
11
  Word
0x8c -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
12
  Word
0x8d -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
13
  Word
0x8e -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
14
  Word
0x8f -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
15
  Word
0x90 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
16
  Word
0x91 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
17
  Word
0x92 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
18
  Word
0x93 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
19
  Word
0x94 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
20
  Word
0x95 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
21
  Word
0x96 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
22
  Word
0x97 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
23
  Word
0x98 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
2 (Int -> DecodedToken Int) -> Int -> DecodedToken Int
forall a b. (a -> b) -> a -> b
$! (Word8 -> Int
word8ToInt  (ByteString -> Word8
eatTailWord8 ByteString
bs))
  Word
0x99 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
3 (Int -> DecodedToken Int) -> Int -> DecodedToken Int
forall a b. (a -> b) -> a -> b
$! (Word16 -> Int
word16ToInt (ByteString -> Word16
eatTailWord16 ByteString
bs))
#if defined(ARCH_64bit)
  Word
0x9a -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
5 (Int -> DecodedToken Int) -> Int -> DecodedToken Int
forall a b. (a -> b) -> a -> b
$! (Word32 -> Int
word32ToInt (ByteString -> Word32
eatTailWord32 ByteString
bs))
#else
  0x9a -> case word32ToInt (eatTailWord32 bs) of
            Just n  -> DecodedToken 5 n
            Nothing -> DecodeFailure
#endif
  Word
0x9b -> case Word64 -> Maybe Int
word64ToInt (ByteString -> Word64
eatTailWord64 ByteString
bs) of
            Just Int
n  -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
9 Int
n
            Maybe Int
Nothing -> DecodedToken Int
forall a. DecodedToken a
DecodeFailure
  Word
0x9f -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
1) 
  Word
_    -> DecodedToken Int
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeMapLenOrIndef #-}
tryConsumeMapLenOrIndef :: Word8 -> ByteString -> DecodedToken Int
tryConsumeMapLenOrIndef :: Word8 -> ByteString -> DecodedToken Int
tryConsumeMapLenOrIndef Word8
hdr !ByteString
bs = case Word8 -> Word
word8ToWord Word8
hdr of
  
  Word
0xa0 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
0
  Word
0xa1 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
1
  Word
0xa2 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
2
  Word
0xa3 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
3
  Word
0xa4 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
4
  Word
0xa5 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
5
  Word
0xa6 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
6
  Word
0xa7 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
7
  Word
0xa8 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
8
  Word
0xa9 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
9
  Word
0xaa -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
10
  Word
0xab -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
11
  Word
0xac -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
12
  Word
0xad -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
13
  Word
0xae -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
14
  Word
0xaf -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
15
  Word
0xb0 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
16
  Word
0xb1 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
17
  Word
0xb2 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
18
  Word
0xb3 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
19
  Word
0xb4 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
20
  Word
0xb5 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
21
  Word
0xb6 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
22
  Word
0xb7 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Int
23
  Word
0xb8 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
2 (Int -> DecodedToken Int) -> Int -> DecodedToken Int
forall a b. (a -> b) -> a -> b
$! (Word8 -> Int
word8ToInt  (ByteString -> Word8
eatTailWord8 ByteString
bs))
  Word
0xb9 -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
3 (Int -> DecodedToken Int) -> Int -> DecodedToken Int
forall a b. (a -> b) -> a -> b
$! (Word16 -> Int
word16ToInt (ByteString -> Word16
eatTailWord16 ByteString
bs))
#if defined(ARCH_64bit)
  Word
0xba -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
5 (Int -> DecodedToken Int) -> Int -> DecodedToken Int
forall a b. (a -> b) -> a -> b
$! (Word32 -> Int
word32ToInt (ByteString -> Word32
eatTailWord32 ByteString
bs))
#else
  0xba -> case word32ToInt (eatTailWord32 bs) of
            Just n  -> DecodedToken 5 n
            Nothing -> DecodeFailure
#endif
  Word
0xbb -> case Word64 -> Maybe Int
word64ToInt (ByteString -> Word64
eatTailWord64 ByteString
bs) of
            Just Int
n  -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
9 Int
n
            Maybe Int
Nothing -> DecodedToken Int
forall a. DecodedToken a
DecodeFailure
  Word
0xbf -> Int -> Int -> DecodedToken Int
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 (-Int
1) 
  Word
_    -> DecodedToken Int
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeTag #-}
tryConsumeTag :: Word8 -> ByteString -> DecodedToken Word
tryConsumeTag :: Word8 -> ByteString -> DecodedToken Word
tryConsumeTag Word8
hdr !ByteString
bs = case Word8 -> Word
word8ToWord Word8
hdr of
  
  Word
0xc0 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
0
  Word
0xc1 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
1
  Word
0xc2 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
2
  Word
0xc3 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
3
  Word
0xc4 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
4
  Word
0xc5 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
5
  Word
0xc6 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
6
  Word
0xc7 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
7
  Word
0xc8 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
8
  Word
0xc9 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
9
  Word
0xca -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
10
  Word
0xcb -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
11
  Word
0xcc -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
12
  Word
0xcd -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
13
  Word
0xce -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
14
  Word
0xcf -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
15
  Word
0xd0 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
16
  Word
0xd1 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
17
  Word
0xd2 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
18
  Word
0xd3 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
19
  Word
0xd4 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
20
  Word
0xd5 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
21
  Word
0xd6 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
22
  Word
0xd7 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
23
  Word
0xd8 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
2 (Word -> DecodedToken Word) -> Word -> DecodedToken Word
forall a b. (a -> b) -> a -> b
$! (Word8 -> Word
word8ToWord  (ByteString -> Word8
eatTailWord8 ByteString
bs))
  Word
0xd9 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
3 (Word -> DecodedToken Word) -> Word -> DecodedToken Word
forall a b. (a -> b) -> a -> b
$! (Word16 -> Word
word16ToWord (ByteString -> Word16
eatTailWord16 ByteString
bs))
  Word
0xda -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
5 (Word -> DecodedToken Word) -> Word -> DecodedToken Word
forall a b. (a -> b) -> a -> b
$! (Word32 -> Word
word32ToWord (ByteString -> Word32
eatTailWord32 ByteString
bs))
#if defined(ARCH_64bit)
  Word
0xdb -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
9 (Word -> DecodedToken Word) -> Word -> DecodedToken Word
forall a b. (a -> b) -> a -> b
$! (Word64 -> Word
word64ToWord (ByteString -> Word64
eatTailWord64 ByteString
bs))
#else
  0xdb -> case word64ToWord (eatTailWord64 bs) of
            Just n  -> DecodedToken 9 n
            Nothing -> DecodeFailure
#endif
  Word
_    -> DecodedToken Word
forall a. DecodedToken a
DecodeFailure
#if defined(ARCH_32bit)
tryConsumeWord64 :: Word8 -> ByteString -> DecodedToken Word64
tryConsumeWord64 hdr !bs = case word8ToWord hdr of
  
  0x00 -> DecodedToken 1 0
  0x01 -> DecodedToken 1 1
  0x02 -> DecodedToken 1 2
  0x03 -> DecodedToken 1 3
  0x04 -> DecodedToken 1 4
  0x05 -> DecodedToken 1 5
  0x06 -> DecodedToken 1 6
  0x07 -> DecodedToken 1 7
  0x08 -> DecodedToken 1 8
  0x09 -> DecodedToken 1 9
  0x0a -> DecodedToken 1 10
  0x0b -> DecodedToken 1 11
  0x0c -> DecodedToken 1 12
  0x0d -> DecodedToken 1 13
  0x0e -> DecodedToken 1 14
  0x0f -> DecodedToken 1 15
  0x10 -> DecodedToken 1 16
  0x11 -> DecodedToken 1 17
  0x12 -> DecodedToken 1 18
  0x13 -> DecodedToken 1 19
  0x14 -> DecodedToken 1 20
  0x15 -> DecodedToken 1 21
  0x16 -> DecodedToken 1 22
  0x17 -> DecodedToken 1 23
  0x18 -> DecodedToken 2 $! (word8ToWord64  (eatTailWord8  bs))
  0x19 -> DecodedToken 3 $! (word16ToWord64 (eatTailWord16 bs))
  0x1a -> DecodedToken 5 $! (word32ToWord64 (eatTailWord32 bs))
  0x1b -> DecodedToken 9 $!                 (eatTailWord64 bs)
  _    -> DecodeFailure
{-# INLINE tryConsumeWord64 #-}
tryConsumeNegWord64 :: Word8 -> ByteString -> DecodedToken Word64
tryConsumeNegWord64 hdr !bs = case word8ToWord hdr of
  
  0x20 -> DecodedToken 1 0
  0x21 -> DecodedToken 1 1
  0x22 -> DecodedToken 1 2
  0x23 -> DecodedToken 1 3
  0x24 -> DecodedToken 1 4
  0x25 -> DecodedToken 1 5
  0x26 -> DecodedToken 1 6
  0x27 -> DecodedToken 1 7
  0x28 -> DecodedToken 1 8
  0x29 -> DecodedToken 1 9
  0x2a -> DecodedToken 1 10
  0x2b -> DecodedToken 1 11
  0x2c -> DecodedToken 1 12
  0x2d -> DecodedToken 1 13
  0x2e -> DecodedToken 1 14
  0x2f -> DecodedToken 1 15
  0x30 -> DecodedToken 1 16
  0x31 -> DecodedToken 1 17
  0x32 -> DecodedToken 1 18
  0x33 -> DecodedToken 1 19
  0x34 -> DecodedToken 1 20
  0x35 -> DecodedToken 1 21
  0x36 -> DecodedToken 1 22
  0x37 -> DecodedToken 1 23
  0x38 -> DecodedToken 2 $! (word8ToWord64  (eatTailWord8  bs))
  0x39 -> DecodedToken 3 $! (word16ToWord64 (eatTailWord16 bs))
  0x3a -> DecodedToken 5 $! (word32ToWord64 (eatTailWord32 bs))
  0x3b -> DecodedToken 9 $!                 (eatTailWord64 bs)
  _    -> DecodeFailure
{-# INLINE tryConsumeNegWord64 #-}
tryConsumeInt64 :: Word8 -> ByteString -> DecodedToken Int64
tryConsumeInt64 hdr !bs = case word8ToWord hdr of
  
  0x00 -> DecodedToken 1 0
  0x01 -> DecodedToken 1 1
  0x02 -> DecodedToken 1 2
  0x03 -> DecodedToken 1 3
  0x04 -> DecodedToken 1 4
  0x05 -> DecodedToken 1 5
  0x06 -> DecodedToken 1 6
  0x07 -> DecodedToken 1 7
  0x08 -> DecodedToken 1 8
  0x09 -> DecodedToken 1 9
  0x0a -> DecodedToken 1 10
  0x0b -> DecodedToken 1 11
  0x0c -> DecodedToken 1 12
  0x0d -> DecodedToken 1 13
  0x0e -> DecodedToken 1 14
  0x0f -> DecodedToken 1 15
  0x10 -> DecodedToken 1 16
  0x11 -> DecodedToken 1 17
  0x12 -> DecodedToken 1 18
  0x13 -> DecodedToken 1 19
  0x14 -> DecodedToken 1 20
  0x15 -> DecodedToken 1 21
  0x16 -> DecodedToken 1 22
  0x17 -> DecodedToken 1 23
  0x18 -> DecodedToken 2 $! (word8ToInt64  (eatTailWord8  bs))
  0x19 -> DecodedToken 3 $! (word16ToInt64 (eatTailWord16 bs))
  0x1a -> DecodedToken 5 $! (word32ToInt64 (eatTailWord32 bs))
  0x1b -> case word64ToInt64 (eatTailWord64 bs) of
            Just n  -> DecodedToken 9 n
            Nothing -> DecodeFailure
  
  0x20 -> DecodedToken 1 (-1)
  0x21 -> DecodedToken 1 (-2)
  0x22 -> DecodedToken 1 (-3)
  0x23 -> DecodedToken 1 (-4)
  0x24 -> DecodedToken 1 (-5)
  0x25 -> DecodedToken 1 (-6)
  0x26 -> DecodedToken 1 (-7)
  0x27 -> DecodedToken 1 (-8)
  0x28 -> DecodedToken 1 (-9)
  0x29 -> DecodedToken 1 (-10)
  0x2a -> DecodedToken 1 (-11)
  0x2b -> DecodedToken 1 (-12)
  0x2c -> DecodedToken 1 (-13)
  0x2d -> DecodedToken 1 (-14)
  0x2e -> DecodedToken 1 (-15)
  0x2f -> DecodedToken 1 (-16)
  0x30 -> DecodedToken 1 (-17)
  0x31 -> DecodedToken 1 (-18)
  0x32 -> DecodedToken 1 (-19)
  0x33 -> DecodedToken 1 (-20)
  0x34 -> DecodedToken 1 (-21)
  0x35 -> DecodedToken 1 (-22)
  0x36 -> DecodedToken 1 (-23)
  0x37 -> DecodedToken 1 (-24)
  0x38 -> DecodedToken 2 $! (-1 - word8ToInt64  (eatTailWord8  bs))
  0x39 -> DecodedToken 3 $! (-1 - word16ToInt64 (eatTailWord16 bs))
  0x3a -> DecodedToken 5 $! (-1 - word32ToInt64 (eatTailWord32 bs))
  0x3b -> case word64ToInt64 (eatTailWord64 bs) of
            Just n  -> DecodedToken 9 (-1 - n)
            Nothing -> DecodeFailure
  _    -> DecodeFailure
{-# INLINE tryConsumeInt64 #-}
tryConsumeListLen64 :: Word8 -> ByteString -> DecodedToken Int64
tryConsumeListLen64 hdr !bs = case word8ToWord hdr of
  
  0x80 -> DecodedToken 1 0
  0x81 -> DecodedToken 1 1
  0x82 -> DecodedToken 1 2
  0x83 -> DecodedToken 1 3
  0x84 -> DecodedToken 1 4
  0x85 -> DecodedToken 1 5
  0x86 -> DecodedToken 1 6
  0x87 -> DecodedToken 1 7
  0x88 -> DecodedToken 1 8
  0x89 -> DecodedToken 1 9
  0x8a -> DecodedToken 1 10
  0x8b -> DecodedToken 1 11
  0x8c -> DecodedToken 1 12
  0x8d -> DecodedToken 1 13
  0x8e -> DecodedToken 1 14
  0x8f -> DecodedToken 1 15
  0x90 -> DecodedToken 1 16
  0x91 -> DecodedToken 1 17
  0x92 -> DecodedToken 1 18
  0x93 -> DecodedToken 1 19
  0x94 -> DecodedToken 1 20
  0x95 -> DecodedToken 1 21
  0x96 -> DecodedToken 1 22
  0x97 -> DecodedToken 1 23
  0x98 -> DecodedToken 2 $! (word8ToInt64  (eatTailWord8  bs))
  0x99 -> DecodedToken 3 $! (word16ToInt64 (eatTailWord16 bs))
  0x9a -> DecodedToken 5 $! (word32ToInt64 (eatTailWord32 bs))
  0x9b -> case word64ToInt64 (eatTailWord64 bs) of
            Just n  -> DecodedToken 9 n
            Nothing -> DecodeFailure
  _    -> DecodeFailure
{-# INLINE tryConsumeListLen64 #-}
tryConsumeMapLen64 :: Word8 -> ByteString -> DecodedToken Int64
tryConsumeMapLen64 hdr !bs = case word8ToWord hdr of
  
  0xa0 -> DecodedToken 1 0
  0xa1 -> DecodedToken 1 1
  0xa2 -> DecodedToken 1 2
  0xa3 -> DecodedToken 1 3
  0xa4 -> DecodedToken 1 4
  0xa5 -> DecodedToken 1 5
  0xa6 -> DecodedToken 1 6
  0xa7 -> DecodedToken 1 7
  0xa8 -> DecodedToken 1 8
  0xa9 -> DecodedToken 1 9
  0xaa -> DecodedToken 1 10
  0xab -> DecodedToken 1 11
  0xac -> DecodedToken 1 12
  0xad -> DecodedToken 1 13
  0xae -> DecodedToken 1 14
  0xaf -> DecodedToken 1 15
  0xb0 -> DecodedToken 1 16
  0xb1 -> DecodedToken 1 17
  0xb2 -> DecodedToken 1 18
  0xb3 -> DecodedToken 1 19
  0xb4 -> DecodedToken 1 20
  0xb5 -> DecodedToken 1 21
  0xb6 -> DecodedToken 1 22
  0xb7 -> DecodedToken 1 23
  0xb8 -> DecodedToken 2 $! (word8ToInt64  (eatTailWord8  bs))
  0xb9 -> DecodedToken 3 $! (word16ToInt64 (eatTailWord16 bs))
  0xba -> DecodedToken 5 $! (word32ToInt64 (eatTailWord32 bs))
  0xbb -> case word64ToInt64 (eatTailWord64 bs) of
            Just n  -> DecodedToken 9 n
            Nothing -> DecodeFailure
  _    -> DecodeFailure
{-# INLINE tryConsumeMapLen64 #-}
tryConsumeTag64 :: Word8 -> ByteString -> DecodedToken Word64
tryConsumeTag64 hdr !bs = case word8ToWord hdr of
  
  0xc0 -> DecodedToken 1 0
  0xc1 -> DecodedToken 1 1
  0xc2 -> DecodedToken 1 2
  0xc3 -> DecodedToken 1 3
  0xc4 -> DecodedToken 1 4
  0xc5 -> DecodedToken 1 5
  0xc6 -> DecodedToken 1 6
  0xc7 -> DecodedToken 1 7
  0xc8 -> DecodedToken 1 8
  0xc9 -> DecodedToken 1 9
  0xca -> DecodedToken 1 10
  0xcb -> DecodedToken 1 11
  0xcc -> DecodedToken 1 12
  0xcd -> DecodedToken 1 13
  0xce -> DecodedToken 1 14
  0xcf -> DecodedToken 1 15
  0xd0 -> DecodedToken 1 16
  0xd1 -> DecodedToken 1 17
  0xd2 -> DecodedToken 1 18
  0xd3 -> DecodedToken 1 19
  0xd4 -> DecodedToken 1 20
  0xd5 -> DecodedToken 1 21
  0xd6 -> DecodedToken 1 22
  0xd7 -> DecodedToken 1 23
  0xd8 -> DecodedToken 2 $! (word8ToWord64  (eatTailWord8  bs))
  0xd9 -> DecodedToken 3 $! (word16ToWord64 (eatTailWord16 bs))
  0xda -> DecodedToken 5 $! (word32ToWord64 (eatTailWord32 bs))
  0xdb -> DecodedToken 9 $!                 (eatTailWord64 bs)
  _    -> DecodeFailure
{-# INLINE tryConsumeTag64 #-}
#endif
{-# INLINE tryConsumeFloat #-}
tryConsumeFloat :: Word8 -> ByteString -> DecodedToken Float
tryConsumeFloat :: Word8 -> ByteString -> DecodedToken Float
tryConsumeFloat Word8
hdr !ByteString
bs = case Word8 -> Word
word8ToWord Word8
hdr of
  Word
0xf9 -> Int -> Float -> DecodedToken Float
forall a. Int -> a -> DecodedToken a
DecodedToken Int
3 (Float -> DecodedToken Float) -> Float -> DecodedToken Float
forall a b. (a -> b) -> a -> b
$! (Word16 -> Float
wordToFloat16 (ByteString -> Word16
eatTailWord16 ByteString
bs))
  Word
0xfa -> Int -> Float -> DecodedToken Float
forall a. Int -> a -> DecodedToken a
DecodedToken Int
5 (Float -> DecodedToken Float) -> Float -> DecodedToken Float
forall a b. (a -> b) -> a -> b
$! (Word32 -> Float
wordToFloat32 (ByteString -> Word32
eatTailWord32 ByteString
bs))
  Word
_    -> DecodedToken Float
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeDouble #-}
tryConsumeDouble :: Word8 -> ByteString -> DecodedToken Double
tryConsumeDouble :: Word8 -> ByteString -> DecodedToken Double
tryConsumeDouble Word8
hdr !ByteString
bs = case Word8 -> Word
word8ToWord Word8
hdr of
  Word
0xf9 -> Int -> Double -> DecodedToken Double
forall a. Int -> a -> DecodedToken a
DecodedToken Int
3 (Double -> DecodedToken Double) -> Double -> DecodedToken Double
forall a b. (a -> b) -> a -> b
$! (Float -> Double
float2Double (Float -> Double) -> Float -> Double
forall a b. (a -> b) -> a -> b
$ Word16 -> Float
wordToFloat16 (ByteString -> Word16
eatTailWord16 ByteString
bs))
  Word
0xfa -> Int -> Double -> DecodedToken Double
forall a. Int -> a -> DecodedToken a
DecodedToken Int
5 (Double -> DecodedToken Double) -> Double -> DecodedToken Double
forall a b. (a -> b) -> a -> b
$! (Float -> Double
float2Double (Float -> Double) -> Float -> Double
forall a b. (a -> b) -> a -> b
$ Word32 -> Float
wordToFloat32 (ByteString -> Word32
eatTailWord32 ByteString
bs))
  Word
0xfb -> Int -> Double -> DecodedToken Double
forall a. Int -> a -> DecodedToken a
DecodedToken Int
9 (Double -> DecodedToken Double) -> Double -> DecodedToken Double
forall a b. (a -> b) -> a -> b
$!                (Word64 -> Double
wordToFloat64 (ByteString -> Word64
eatTailWord64 ByteString
bs))
  Word
_    -> DecodedToken Double
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeBool #-}
tryConsumeBool :: Word8 -> DecodedToken Bool
tryConsumeBool :: Word8 -> DecodedToken Bool
tryConsumeBool Word8
hdr = case Word8 -> Word
word8ToWord Word8
hdr of
  Word
0xf4 -> Int -> Bool -> DecodedToken Bool
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Bool
False
  Word
0xf5 -> Int -> Bool -> DecodedToken Bool
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Bool
True
  Word
_    -> DecodedToken Bool
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeSimple #-}
tryConsumeSimple :: Word8 -> ByteString -> DecodedToken Word
tryConsumeSimple :: Word8 -> ByteString -> DecodedToken Word
tryConsumeSimple Word8
hdr !ByteString
bs = case Word8 -> Word
word8ToWord Word8
hdr of
  
  Word
0xe0 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
0
  Word
0xe1 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
1
  Word
0xe2 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
2
  Word
0xe3 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
3
  Word
0xe4 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
4
  Word
0xe5 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
5
  Word
0xe6 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
6
  Word
0xe7 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
7
  Word
0xe8 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
8
  Word
0xe9 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
9
  Word
0xea -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
10
  Word
0xeb -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
11
  Word
0xec -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
12
  Word
0xed -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
13
  Word
0xee -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
14
  Word
0xef -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
15
  Word
0xf0 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
16
  Word
0xf1 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
17
  Word
0xf2 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
18
  Word
0xf3 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
19
  Word
0xf4 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
20
  Word
0xf5 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
21
  Word
0xf6 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
22
  Word
0xf7 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 Word
23
  Word
0xf8 -> Int -> Word -> DecodedToken Word
forall a. Int -> a -> DecodedToken a
DecodedToken Int
2 (Word -> DecodedToken Word) -> Word -> DecodedToken Word
forall a b. (a -> b) -> a -> b
$! (Word8 -> Word
word8ToWord (ByteString -> Word8
eatTailWord8 ByteString
bs))
  Word
_    -> DecodedToken Word
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeBytesIndef #-}
tryConsumeBytesIndef :: Word8 -> DecodedToken ()
tryConsumeBytesIndef :: Word8 -> DecodedToken ()
tryConsumeBytesIndef Word8
hdr = case Word8 -> Word
word8ToWord Word8
hdr of
  Word
0x5f -> Int -> () -> DecodedToken ()
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 ()
  Word
_    -> DecodedToken ()
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeStringIndef #-}
tryConsumeStringIndef :: Word8 -> DecodedToken ()
tryConsumeStringIndef :: Word8 -> DecodedToken ()
tryConsumeStringIndef Word8
hdr = case Word8 -> Word
word8ToWord Word8
hdr of
  Word
0x7f -> Int -> () -> DecodedToken ()
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 ()
  Word
_    -> DecodedToken ()
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeNull #-}
tryConsumeNull :: Word8 -> DecodedToken ()
 Word8
hdr = case Word8 -> Word
word8ToWord Word8
hdr of
  Word
0xf6 -> Int -> () -> DecodedToken ()
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 ()
  Word
_    -> DecodedToken ()
forall a. DecodedToken a
DecodeFailure
{-# INLINE tryConsumeBreakOr #-}
tryConsumeBreakOr :: Word8 -> DecodedToken ()
tryConsumeBreakOr :: Word8 -> DecodedToken ()
tryConsumeBreakOr Word8
hdr = case Word8 -> Word
word8ToWord Word8
hdr of
  Word
0xff -> Int -> () -> DecodedToken ()
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 ()
  Word
_    -> DecodedToken ()
forall a. DecodedToken a
DecodeFailure
{-# INLINE readBytesSmall #-}
readBytesSmall :: Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall :: Int -> ByteString -> DecodedToken (LongToken ByteString)
readBytesSmall Int
n ByteString
bs
  
  | Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
hdrsz Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= ByteString -> Int
BS.length ByteString
bs
  = Int -> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a. Int -> a -> DecodedToken a
DecodedToken (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
hdrsz) (LongToken ByteString -> DecodedToken (LongToken ByteString))
-> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a b. (a -> b) -> a -> b
$ Bool -> ByteString -> LongToken ByteString
forall a. Bool -> a -> LongToken a
Fits Bool
True (ByteString -> LongToken ByteString)
-> ByteString -> LongToken ByteString
forall a b. (a -> b) -> a -> b
$
      Int -> ByteString -> ByteString
BS.unsafeTake Int
n (Int -> ByteString -> ByteString
BS.unsafeDrop Int
hdrsz ByteString
bs)
  
  | Bool
otherwise
  = Int -> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
hdrsz (LongToken ByteString -> DecodedToken (LongToken ByteString))
-> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a b. (a -> b) -> a -> b
$ Bool -> Int -> LongToken ByteString
forall a. Bool -> Int -> LongToken a
TooLong Bool
True Int
n
  where
    hdrsz :: Int
hdrsz = Int
1
{-# INLINE readBytes8 #-}
{-# INLINE readBytes16 #-}
{-# INLINE readBytes32 #-}
{-# INLINE readBytes64 #-}
readBytes8, readBytes16, readBytes32, readBytes64
  :: ByteString -> DecodedToken (LongToken ByteString)
readBytes8 :: ByteString -> DecodedToken (LongToken ByteString)
readBytes8 ByteString
bs
  | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= ByteString -> Int
BS.length ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
hdrsz
  = Int -> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a. Int -> a -> DecodedToken a
DecodedToken (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
hdrsz) (LongToken ByteString -> DecodedToken (LongToken ByteString))
-> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a b. (a -> b) -> a -> b
$ Bool -> ByteString -> LongToken ByteString
forall a. Bool -> a -> LongToken a
Fits Bool
lengthCanonical (ByteString -> LongToken ByteString)
-> ByteString -> LongToken ByteString
forall a b. (a -> b) -> a -> b
$
      Int -> ByteString -> ByteString
BS.unsafeTake Int
n (Int -> ByteString -> ByteString
BS.unsafeDrop Int
hdrsz ByteString
bs)
  
  | Bool
otherwise
  = Int -> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
hdrsz (LongToken ByteString -> DecodedToken (LongToken ByteString))
-> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a b. (a -> b) -> a -> b
$ Bool -> Int -> LongToken ByteString
forall a. Bool -> Int -> LongToken a
TooLong Bool
lengthCanonical Int
n
  where
    hdrsz :: Int
hdrsz           = Int
2
    !n :: Int
n              = Word8 -> Int
word8ToInt (ByteString -> Word8
eatTailWord8 ByteString
bs)
    lengthCanonical :: Bool
lengthCanonical = Int -> Int -> Bool
isIntCanonical Int
hdrsz Int
n
readBytes16 :: ByteString -> DecodedToken (LongToken ByteString)
readBytes16 ByteString
bs
  | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= ByteString -> Int
BS.length ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
hdrsz
  = Int -> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a. Int -> a -> DecodedToken a
DecodedToken (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
hdrsz) (LongToken ByteString -> DecodedToken (LongToken ByteString))
-> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a b. (a -> b) -> a -> b
$ Bool -> ByteString -> LongToken ByteString
forall a. Bool -> a -> LongToken a
Fits Bool
lengthCanonical (ByteString -> LongToken ByteString)
-> ByteString -> LongToken ByteString
forall a b. (a -> b) -> a -> b
$
      Int -> ByteString -> ByteString
BS.unsafeTake Int
n (Int -> ByteString -> ByteString
BS.unsafeDrop Int
hdrsz ByteString
bs)
  
  | Bool
otherwise
  = Int -> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
hdrsz (LongToken ByteString -> DecodedToken (LongToken ByteString))
-> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a b. (a -> b) -> a -> b
$ Bool -> Int -> LongToken ByteString
forall a. Bool -> Int -> LongToken a
TooLong Bool
lengthCanonical Int
n
  where
    hdrsz :: Int
hdrsz           = Int
3
    !n :: Int
n              = Word16 -> Int
word16ToInt (ByteString -> Word16
eatTailWord16 ByteString
bs)
    lengthCanonical :: Bool
lengthCanonical = Int -> Int -> Bool
isIntCanonical Int
hdrsz Int
n
readBytes32 :: ByteString -> DecodedToken (LongToken ByteString)
readBytes32 ByteString
bs = case Word32 -> Int
word32ToInt (ByteString -> Word32
eatTailWord32 ByteString
bs) of
#if defined(ARCH_32bit)
    Just n
#else
    Int
n
#endif
      | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= ByteString -> Int
BS.length ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
hdrsz
                  -> Int -> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a. Int -> a -> DecodedToken a
DecodedToken (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
hdrsz) (LongToken ByteString -> DecodedToken (LongToken ByteString))
-> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a b. (a -> b) -> a -> b
$ Bool -> ByteString -> LongToken ByteString
forall a. Bool -> a -> LongToken a
Fits (Int -> Int -> Bool
isIntCanonical Int
hdrsz Int
n) (ByteString -> LongToken ByteString)
-> ByteString -> LongToken ByteString
forall a b. (a -> b) -> a -> b
$
                       Int -> ByteString -> ByteString
BS.unsafeTake Int
n (Int -> ByteString -> ByteString
BS.unsafeDrop Int
hdrsz ByteString
bs)
      
      | Bool
otherwise -> Int -> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
hdrsz (LongToken ByteString -> DecodedToken (LongToken ByteString))
-> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a b. (a -> b) -> a -> b
$ Bool -> Int -> LongToken ByteString
forall a. Bool -> Int -> LongToken a
TooLong (Int -> Int -> Bool
isIntCanonical Int
hdrsz Int
n) Int
n
#if defined(ARCH_32bit)
    Nothing       -> DecodeFailure
#endif
  where
    hdrsz :: Int
hdrsz = Int
5
readBytes64 :: ByteString -> DecodedToken (LongToken ByteString)
readBytes64 ByteString
bs = case Word64 -> Maybe Int
word64ToInt (ByteString -> Word64
eatTailWord64 ByteString
bs) of
    Just Int
n
      | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= ByteString -> Int
BS.length ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
hdrsz
                  -> Int -> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a. Int -> a -> DecodedToken a
DecodedToken (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
hdrsz) (LongToken ByteString -> DecodedToken (LongToken ByteString))
-> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a b. (a -> b) -> a -> b
$ Bool -> ByteString -> LongToken ByteString
forall a. Bool -> a -> LongToken a
Fits (Int -> Int -> Bool
isIntCanonical Int
hdrsz Int
n) (ByteString -> LongToken ByteString)
-> ByteString -> LongToken ByteString
forall a b. (a -> b) -> a -> b
$
                            Int -> ByteString -> ByteString
BS.unsafeTake Int
n (Int -> ByteString -> ByteString
BS.unsafeDrop Int
hdrsz ByteString
bs)
      
      | Bool
otherwise -> Int -> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
hdrsz (LongToken ByteString -> DecodedToken (LongToken ByteString))
-> LongToken ByteString -> DecodedToken (LongToken ByteString)
forall a b. (a -> b) -> a -> b
$ Bool -> Int -> LongToken ByteString
forall a. Bool -> Int -> LongToken a
TooLong (Int -> Int -> Bool
isIntCanonical Int
hdrsz Int
n) Int
n
    Maybe Int
Nothing       -> DecodedToken (LongToken ByteString)
forall a. DecodedToken a
DecodeFailure
  where
    hdrsz :: Int
hdrsz = Int
9
data BigIntToken a = BigIntToken     Bool  Integer
                   | BigUIntNeedBody Bool  Int
                   | BigNIntNeedBody Bool  Int
                   | 
                   | 
adjustContBigUIntNeedBody, adjustContBigNIntNeedBody
  :: (Integer -> ST s (DecodeAction s a))
  -> (ByteString -> ST s (DecodeAction s a))
adjustContBigUIntNeedBody :: forall s a.
(Integer -> ST s (DecodeAction s a))
-> ByteString -> ST s (DecodeAction s a)
adjustContBigUIntNeedBody Integer -> ST s (DecodeAction s a)
k = \ByteString
bs -> Integer -> ST s (DecodeAction s a)
k (Integer -> ST s (DecodeAction s a))
-> Integer -> ST s (DecodeAction s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> Integer
uintegerFromBytes ByteString
bs
adjustContBigNIntNeedBody :: forall s a.
(Integer -> ST s (DecodeAction s a))
-> ByteString -> ST s (DecodeAction s a)
adjustContBigNIntNeedBody Integer -> ST s (DecodeAction s a)
k = \ByteString
bs -> Integer -> ST s (DecodeAction s a)
k (Integer -> ST s (DecodeAction s a))
-> Integer -> ST s (DecodeAction s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> Integer
nintegerFromBytes ByteString
bs
adjustContCanonicalBigUIntNeedBody, adjustContCanonicalBigNIntNeedBody
  :: (Integer -> ST s (DecodeAction s a))
  -> (ByteString -> ST s (DecodeAction s a))
adjustContCanonicalBigUIntNeedBody :: forall s a.
(Integer -> ST s (DecodeAction s a))
-> ByteString -> ST s (DecodeAction s a)
adjustContCanonicalBigUIntNeedBody Integer -> ST s (DecodeAction s a)
k = \ByteString
bs ->
  if ByteString -> Bool
isBigIntRepCanonical ByteString
bs
  then Integer -> ST s (DecodeAction s a)
k (Integer -> ST s (DecodeAction s a))
-> Integer -> ST s (DecodeAction s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> Integer
uintegerFromBytes ByteString
bs
  else DecodeAction s a -> ST s (DecodeAction s a)
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DecodeAction s a -> ST s (DecodeAction s a))
-> DecodeAction s a -> ST s (DecodeAction s a)
forall a b. (a -> b) -> a -> b
$! String -> DecodeAction s a
forall s a. String -> DecodeAction s a
D.Fail (String
"non-canonical integer")
adjustContCanonicalBigNIntNeedBody :: forall s a.
(Integer -> ST s (DecodeAction s a))
-> ByteString -> ST s (DecodeAction s a)
adjustContCanonicalBigNIntNeedBody Integer -> ST s (DecodeAction s a)
k = \ByteString
bs ->
  if ByteString -> Bool
isBigIntRepCanonical ByteString
bs
  then Integer -> ST s (DecodeAction s a)
k (Integer -> ST s (DecodeAction s a))
-> Integer -> ST s (DecodeAction s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> Integer
nintegerFromBytes ByteString
bs
  else DecodeAction s a -> ST s (DecodeAction s a)
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DecodeAction s a -> ST s (DecodeAction s a))
-> DecodeAction s a -> ST s (DecodeAction s a)
forall a b. (a -> b) -> a -> b
$! String -> DecodeAction s a
forall s a. String -> DecodeAction s a
D.Fail (String
"non-canonical integer")
adjustContBigUIntNeedHeader, adjustContBigNIntNeedHeader
  :: (Integer -> ST s (DecodeAction s a))
  -> DecodeAction s a
 Integer -> ST s (DecodeAction s a)
k = (ByteString -> ST s (DecodeAction s a)) -> DecodeAction s a
forall s a.
(ByteString -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeBytes (\ByteString
bs -> Integer -> ST s (DecodeAction s a)
k (Integer -> ST s (DecodeAction s a))
-> Integer -> ST s (DecodeAction s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> Integer
uintegerFromBytes ByteString
bs)
 Integer -> ST s (DecodeAction s a)
k = (ByteString -> ST s (DecodeAction s a)) -> DecodeAction s a
forall s a.
(ByteString -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeBytes (\ByteString
bs -> Integer -> ST s (DecodeAction s a)
k (Integer -> ST s (DecodeAction s a))
-> Integer -> ST s (DecodeAction s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> Integer
nintegerFromBytes ByteString
bs)
adjustContCanonicalBigUIntNeedHeader, adjustContCanonicalBigNIntNeedHeader
  :: (Integer -> ST s (DecodeAction s a))
  -> DecodeAction s a
 Integer -> ST s (DecodeAction s a)
k = (ByteString -> ST s (DecodeAction s a)) -> DecodeAction s a
forall s a.
(ByteString -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeBytesCanonical ((ByteString -> ST s (DecodeAction s a)) -> DecodeAction s a)
-> (ByteString -> ST s (DecodeAction s a)) -> DecodeAction s a
forall a b. (a -> b) -> a -> b
$ \ByteString
bs ->
  if ByteString -> Bool
isBigIntRepCanonical ByteString
bs
  then Integer -> ST s (DecodeAction s a)
k (Integer -> ST s (DecodeAction s a))
-> Integer -> ST s (DecodeAction s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> Integer
uintegerFromBytes ByteString
bs
  else DecodeAction s a -> ST s (DecodeAction s a)
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DecodeAction s a -> ST s (DecodeAction s a))
-> DecodeAction s a -> ST s (DecodeAction s a)
forall a b. (a -> b) -> a -> b
$! String -> DecodeAction s a
forall s a. String -> DecodeAction s a
D.Fail (String
"non-canonical integer")
 Integer -> ST s (DecodeAction s a)
k = (ByteString -> ST s (DecodeAction s a)) -> DecodeAction s a
forall s a.
(ByteString -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeBytesCanonical ((ByteString -> ST s (DecodeAction s a)) -> DecodeAction s a)
-> (ByteString -> ST s (DecodeAction s a)) -> DecodeAction s a
forall a b. (a -> b) -> a -> b
$ \ByteString
bs ->
  if ByteString -> Bool
isBigIntRepCanonical ByteString
bs
  then Integer -> ST s (DecodeAction s a)
k (Integer -> ST s (DecodeAction s a))
-> Integer -> ST s (DecodeAction s a)
forall a b. (a -> b) -> a -> b
$! ByteString -> Integer
nintegerFromBytes ByteString
bs
  else DecodeAction s a -> ST s (DecodeAction s a)
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DecodeAction s a -> ST s (DecodeAction s a))
-> DecodeAction s a -> ST s (DecodeAction s a)
forall a b. (a -> b) -> a -> b
$! String -> DecodeAction s a
forall s a. String -> DecodeAction s a
D.Fail (String
"non-canonical integer")
{-# INLINE readBigUInt #-}
readBigUInt :: ByteString -> DecodedToken (BigIntToken a)
readBigUInt :: forall a. ByteString -> DecodedToken (BigIntToken a)
readBigUInt ByteString
bs
    | let bs' :: ByteString
bs' = ByteString -> ByteString
BS.unsafeTail ByteString
bs
    , Bool -> Bool
not (ByteString -> Bool
BS.null ByteString
bs')
    , let !hdr :: Word8
hdr = ByteString -> Word8
BS.unsafeHead ByteString
bs'
    , ByteString -> Int
BS.length ByteString
bs' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8 -> Int
tokenSize Word8
hdr
    = case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeBytes Word8
hdr ByteString
bs' of
        DecodedToken (LongToken ByteString)
DecodeFailure                           -> DecodedToken (BigIntToken a)
forall a. DecodedToken a
DecodeFailure
        DecodedToken Int
sz (Fits Bool
canonical ByteString
bstr)   -> Int -> BigIntToken a -> DecodedToken (BigIntToken a)
forall a. Int -> a -> DecodedToken a
DecodedToken (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
sz)
          (Bool -> Integer -> BigIntToken a
forall a. Bool -> Integer -> BigIntToken a
BigIntToken (Bool
canonical Bool -> Bool -> Bool
&& ByteString -> Bool
isBigIntRepCanonical ByteString
bstr)
                       (ByteString -> Integer
uintegerFromBytes ByteString
bstr))
        DecodedToken Int
sz (TooLong Bool
canonical Int
len) ->
          Int -> BigIntToken a -> DecodedToken (BigIntToken a)
forall a. Int -> a -> DecodedToken a
DecodedToken (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
sz) (Bool -> Int -> BigIntToken a
forall a. Bool -> Int -> BigIntToken a
BigUIntNeedBody Bool
canonical Int
len)
    | Bool
otherwise
    = Int -> BigIntToken a -> DecodedToken (BigIntToken a)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 BigIntToken a
forall a. BigIntToken a
BigUIntNeedHeader
{-# INLINE readBigNInt #-}
readBigNInt :: ByteString -> DecodedToken (BigIntToken a)
readBigNInt :: forall a. ByteString -> DecodedToken (BigIntToken a)
readBigNInt ByteString
bs
    | let bs' :: ByteString
bs' = ByteString -> ByteString
BS.unsafeTail ByteString
bs
    , Bool -> Bool
not (ByteString -> Bool
BS.null ByteString
bs')
    , let !hdr :: Word8
hdr = ByteString -> Word8
BS.unsafeHead ByteString
bs'
    , ByteString -> Int
BS.length ByteString
bs' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8 -> Int
tokenSize Word8
hdr
    = case Word8 -> ByteString -> DecodedToken (LongToken ByteString)
tryConsumeBytes Word8
hdr ByteString
bs' of
        DecodedToken (LongToken ByteString)
DecodeFailure                           -> DecodedToken (BigIntToken a)
forall a. DecodedToken a
DecodeFailure
        DecodedToken Int
sz (Fits Bool
canonical ByteString
bstr)   -> Int -> BigIntToken a -> DecodedToken (BigIntToken a)
forall a. Int -> a -> DecodedToken a
DecodedToken (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
sz)
          (Bool -> Integer -> BigIntToken a
forall a. Bool -> Integer -> BigIntToken a
BigIntToken (Bool
canonical Bool -> Bool -> Bool
&& ByteString -> Bool
isBigIntRepCanonical ByteString
bstr)
                       (ByteString -> Integer
nintegerFromBytes ByteString
bstr))
        DecodedToken Int
sz (TooLong Bool
canonical Int
len) ->
          Int -> BigIntToken a -> DecodedToken (BigIntToken a)
forall a. Int -> a -> DecodedToken a
DecodedToken (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
sz) (Bool -> Int -> BigIntToken a
forall a. Bool -> Int -> BigIntToken a
BigNIntNeedBody Bool
canonical Int
len)
    | Bool
otherwise
    = Int -> BigIntToken a -> DecodedToken (BigIntToken a)
forall a. Int -> a -> DecodedToken a
DecodedToken Int
1 BigIntToken a
forall a. BigIntToken a
BigNIntNeedHeader
isBigIntRepCanonical :: ByteString -> Bool
isBigIntRepCanonical :: ByteString -> Bool
isBigIntRepCanonical ByteString
bstr = ByteString -> Int
BS.length ByteString
bstr Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
8 Bool -> Bool -> Bool
&& ByteString -> Word8
BS.unsafeHead ByteString
bstr Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
/= Word8
0x00