{-# LANGUAGE CPP          #-}
{-# LANGUAGE MagicHash    #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE RankNTypes   #-}

-- |
-- Module      : Codec.CBOR.Decoding
-- Copyright   : (c) Duncan Coutts 2015-2017
-- License     : BSD3-style (see LICENSE.txt)
--
-- Maintainer  : duncan@community.haskell.org
-- Stability   : experimental
-- Portability : non-portable (GHC extensions)
--
-- High level API for decoding values that were encoded with the
-- "Codec.CBOR.Encoding" module, using a 'Monad'
-- based interface.
--
module Codec.CBOR.Decoding
  ( -- * Decode primitive operations
    Decoder
  , DecodeAction(..)
  , liftST
  , getDecodeAction

  -- ** Read input tokens
  , decodeWord          -- :: Decoder s Word
  , decodeWord8         -- :: Decoder s Word8
  , decodeWord16        -- :: Decoder s Word16
  , decodeWord32        -- :: Decoder s Word32
  , decodeWord64        -- :: Decoder s Word64
  , decodeNegWord       -- :: Decoder s Word
  , decodeNegWord64     -- :: Decoder s Word64
  , decodeInt           -- :: Decoder s Int
  , decodeInt8          -- :: Decoder s Int8
  , decodeInt16         -- :: Decoder s Int16
  , decodeInt32         -- :: Decoder s Int32
  , decodeInt64         -- :: Decoder s Int64
  , decodeInteger       -- :: Decoder s Integer
  , decodeFloat         -- :: Decoder s Float
  , decodeDouble        -- :: Decoder s Double
  , decodeBytes         -- :: Decoder s ByteString
  , decodeBytesIndef    -- :: Decoder s ()
  , decodeByteArray     -- :: Decoder s ByteArray
  , decodeString        -- :: Decoder s Text
  , decodeStringIndef   -- :: Decoder s ()
  , decodeUtf8ByteArray -- :: Decoder s ByteArray
  , decodeListLen       -- :: Decoder s Int
  , decodeListLenIndef  -- :: Decoder s ()
  , decodeMapLen        -- :: Decoder s Int
  , decodeMapLenIndef   -- :: Decoder s ()
  , decodeTag           -- :: Decoder s Word
  , decodeTag64         -- :: Decoder s Word64
  , decodeBool          -- :: Decoder s Bool
  , decodeNull          -- :: Decoder s ()
  , decodeSimple        -- :: Decoder s Word8

  -- ** Specialised Read input token operations
  , decodeWordOf        -- :: Word -> Decoder s ()
  , decodeListLenOf     -- :: Int  -> Decoder s ()

  -- ** Branching operations
--, decodeBytesOrIndef
--, decodeStringOrIndef
  , decodeListLenOrIndef -- :: Decoder s (Maybe Int)
  , decodeMapLenOrIndef  -- :: Decoder s (Maybe Int)
  , decodeBreakOr        -- :: Decoder s Bool

  -- ** Inspecting the token type
  , peekTokenType        -- :: Decoder s TokenType
  , TokenType(..)

  -- ** Special operations
  , peekAvailable        -- :: Decoder s Int
  , ByteOffset
  , peekByteOffset       -- :: Decoder s ByteOffset
  , decodeWithByteSpan

  -- ** Canonical CBOR
  -- $canonical
  , decodeWordCanonical      -- :: Decoder s Word
  , decodeWord8Canonical     -- :: Decoder s Word8
  , decodeWord16Canonical    -- :: Decoder s Word16
  , decodeWord32Canonical    -- :: Decoder s Word32
  , decodeWord64Canonical    -- :: Decoder s Word64
  , decodeNegWordCanonical   -- :: Decoder s Word
  , decodeNegWord64Canonical -- :: Decoder s Word64
  , decodeIntCanonical       -- :: Decoder s Int
  , decodeInt8Canonical      -- :: Decoder s Int8
  , decodeInt16Canonical     -- :: Decoder s Int16
  , decodeInt32Canonical     -- :: Decoder s Int32
  , decodeInt64Canonical     -- :: Decoder s Int64
  , decodeBytesCanonical -- :: Decoder s ByteString
  , decodeByteArrayCanonical -- :: Decoder s ByteArray
  , decodeStringCanonical -- :: Decoder s Text
  , decodeUtf8ByteArrayCanonical -- :: Decoder s ByteArray
  , decodeListLenCanonical -- :: Decoder s Int
  , decodeMapLenCanonical -- :: Decoder s Int
  , decodeTagCanonical   -- :: Decoder s Word
  , decodeTag64Canonical -- :: Decoder s Word64
  , decodeIntegerCanonical -- :: Decoder s Integer
  , decodeFloat16Canonical -- :: Decoder s Float
  , decodeFloatCanonical   -- :: Decoder s Float
  , decodeDoubleCanonical  -- :: Decoder s Double
  , decodeSimpleCanonical  -- :: Decoder s Word8
  , decodeWordCanonicalOf    -- :: Word -> Decoder s ()
  , decodeListLenCanonicalOf -- :: Int  -> Decoder s ()

  -- * Sequence operations
  , decodeSequenceLenIndef -- :: ...
  , decodeSequenceLenN     -- :: ...
  ) where

#include "cbor.h"

import           GHC.Exts
import           GHC.Word
import           GHC.Int
import           Data.Text (Text)
import           Data.ByteString (ByteString)
import           Control.Applicative
import           Control.Monad.ST
import qualified Control.Monad.Fail as Fail

import           Codec.CBOR.ByteArray (ByteArray)

import           Prelude hiding (decodeFloat)


-- | A continuation-based decoder, used for decoding values that were
-- previously encoded using the "Codec.CBOR.Encoding"
-- module. As 'Decoder' has a 'Monad' instance, you can easily
-- write 'Decoder's monadically for building your deserialisation
-- logic.
--
-- @since 0.2.0.0
newtype Decoder s a = Decoder {
       Decoder s a
-> forall r.
   (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
runDecoder :: forall r. (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
     }

-- | An action, representing a step for a decoder to taken and a
-- continuation to invoke with the expected value.
--
-- @since 0.2.0.0
data DecodeAction s a
    = ConsumeWord    (Word# -> ST s (DecodeAction s a))
    | ConsumeWord8   (Word# -> ST s (DecodeAction s a))
    | ConsumeWord16  (Word# -> ST s (DecodeAction s a))
    | ConsumeWord32  (Word# -> ST s (DecodeAction s a))
    | ConsumeNegWord (Word# -> ST s (DecodeAction s a))
    | ConsumeInt     (Int#  -> ST s (DecodeAction s a))
    | ConsumeInt8    (Int#  -> ST s (DecodeAction s a))
    | ConsumeInt16   (Int#  -> ST s (DecodeAction s a))
    | ConsumeInt32   (Int#  -> ST s (DecodeAction s a))
    | ConsumeListLen (Int#  -> ST s (DecodeAction s a))
    | ConsumeMapLen  (Int#  -> ST s (DecodeAction s a))
    | ConsumeTag     (Word# -> ST s (DecodeAction s a))

-- 64bit variants for 32bit machines
#if defined(ARCH_32bit)
    | ConsumeWord64    (Word64# -> ST s (DecodeAction s a))
    | ConsumeNegWord64 (Word64# -> ST s (DecodeAction s a))
    | ConsumeInt64     (Int64#  -> ST s (DecodeAction s a))
    | ConsumeListLen64 (Int64#  -> ST s (DecodeAction s a))
    | ConsumeMapLen64  (Int64#  -> ST s (DecodeAction s a))
    | ConsumeTag64     (Word64# -> ST s (DecodeAction s a))
#endif

    | ConsumeInteger       (Integer   -> ST s (DecodeAction s a))
    | ConsumeFloat         (Float#    -> ST s (DecodeAction s a))
    | ConsumeDouble        (Double#   -> ST s (DecodeAction s a))
    | ConsumeBytes         (ByteString-> ST s (DecodeAction s a))
    | ConsumeByteArray     (ByteArray -> ST s (DecodeAction s a))
    | ConsumeString        (Text      -> ST s (DecodeAction s a))
    | ConsumeUtf8ByteArray (ByteArray -> ST s (DecodeAction s a))
    | ConsumeBool          (Bool      -> ST s (DecodeAction s a))
    | ConsumeSimple        (Word#     -> ST s (DecodeAction s a))

    | ConsumeBytesIndef   (ST s (DecodeAction s a))
    | ConsumeStringIndef  (ST s (DecodeAction s a))
    | ConsumeListLenIndef (ST s (DecodeAction s a))
    | ConsumeMapLenIndef  (ST s (DecodeAction s a))
    | ConsumeNull         (ST s (DecodeAction s a))

    | ConsumeListLenOrIndef (Int# -> ST s (DecodeAction s a))
    | ConsumeMapLenOrIndef  (Int# -> ST s (DecodeAction s a))
    | ConsumeBreakOr        (Bool -> ST s (DecodeAction s a))

    | PeekTokenType  (TokenType -> ST s (DecodeAction s a))
    | PeekAvailable  (Int#      -> ST s (DecodeAction s a))
#if defined(ARCH_32bit)
    | PeekByteOffset (Int64#    -> ST s (DecodeAction s a))
#else
    | PeekByteOffset (Int#      -> ST s (DecodeAction s a))
#endif

      -- All the canonical variants
    | ConsumeWordCanonical    (Word# -> ST s (DecodeAction s a))
    | ConsumeWord8Canonical   (Word# -> ST s (DecodeAction s a))
    | ConsumeWord16Canonical  (Word# -> ST s (DecodeAction s a))
    | ConsumeWord32Canonical  (Word# -> ST s (DecodeAction s a))
    | ConsumeNegWordCanonical (Word# -> ST s (DecodeAction s a))
    | ConsumeIntCanonical     (Int#  -> ST s (DecodeAction s a))
    | ConsumeInt8Canonical    (Int#  -> ST s (DecodeAction s a))
    | ConsumeInt16Canonical   (Int#  -> ST s (DecodeAction s a))
    | ConsumeInt32Canonical   (Int#  -> ST s (DecodeAction s a))
    | ConsumeListLenCanonical (Int#  -> ST s (DecodeAction s a))
    | ConsumeMapLenCanonical  (Int#  -> ST s (DecodeAction s a))
    | ConsumeTagCanonical     (Word# -> ST s (DecodeAction s a))

#if defined(ARCH_32bit)
    | ConsumeWord64Canonical    (Word64# -> ST s (DecodeAction s a))
    | ConsumeNegWord64Canonical (Word64# -> ST s (DecodeAction s a))
    | ConsumeInt64Canonical     (Int64#  -> ST s (DecodeAction s a))
    | ConsumeListLen64Canonical (Int64#  -> ST s (DecodeAction s a))
    | ConsumeMapLen64Canonical  (Int64#  -> ST s (DecodeAction s a))
    | ConsumeTag64Canonical     (Word64# -> ST s (DecodeAction s a))
#endif

    | ConsumeIntegerCanonical       (Integer -> ST s (DecodeAction s a))
    | ConsumeFloat16Canonical       (Float#  -> ST s (DecodeAction s a))
    | ConsumeFloatCanonical         (Float#  -> ST s (DecodeAction s a))
    | ConsumeDoubleCanonical        (Double# -> ST s (DecodeAction s a))
    | ConsumeBytesCanonical         (ByteString-> ST s (DecodeAction s a))
    | ConsumeByteArrayCanonical     (ByteArray -> ST s (DecodeAction s a))
    | ConsumeStringCanonical        (Text      -> ST s (DecodeAction s a))
    | ConsumeUtf8ByteArrayCanonical (ByteArray -> ST s (DecodeAction s a))
    | ConsumeSimpleCanonical        (Word#   -> ST s (DecodeAction s a))

    | Fail String
    | Done a

-- | The type of a token, which a decoder can ask for at
-- an arbitrary time.
--
-- @since 0.2.0.0
data TokenType
  = TypeUInt
  | TypeUInt64
  | TypeNInt
  | TypeNInt64
  | TypeInteger
  | TypeFloat16
  | TypeFloat32
  | TypeFloat64
  | TypeBytes
  | TypeBytesIndef
  | TypeString
  | TypeStringIndef
  | TypeListLen
  | TypeListLen64
  | TypeListLenIndef
  | TypeMapLen
  | TypeMapLen64
  | TypeMapLenIndef
  | TypeTag
  | TypeTag64
  | TypeBool
  | TypeNull
  | TypeSimple
  | TypeBreak
  | TypeInvalid
  deriving (TokenType -> TokenType -> Bool
(TokenType -> TokenType -> Bool)
-> (TokenType -> TokenType -> Bool) -> Eq TokenType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TokenType -> TokenType -> Bool
$c/= :: TokenType -> TokenType -> Bool
== :: TokenType -> TokenType -> Bool
$c== :: TokenType -> TokenType -> Bool
Eq, Eq TokenType
Eq TokenType
-> (TokenType -> TokenType -> Ordering)
-> (TokenType -> TokenType -> Bool)
-> (TokenType -> TokenType -> Bool)
-> (TokenType -> TokenType -> Bool)
-> (TokenType -> TokenType -> Bool)
-> (TokenType -> TokenType -> TokenType)
-> (TokenType -> TokenType -> TokenType)
-> Ord TokenType
TokenType -> TokenType -> Bool
TokenType -> TokenType -> Ordering
TokenType -> TokenType -> TokenType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TokenType -> TokenType -> TokenType
$cmin :: TokenType -> TokenType -> TokenType
max :: TokenType -> TokenType -> TokenType
$cmax :: TokenType -> TokenType -> TokenType
>= :: TokenType -> TokenType -> Bool
$c>= :: TokenType -> TokenType -> Bool
> :: TokenType -> TokenType -> Bool
$c> :: TokenType -> TokenType -> Bool
<= :: TokenType -> TokenType -> Bool
$c<= :: TokenType -> TokenType -> Bool
< :: TokenType -> TokenType -> Bool
$c< :: TokenType -> TokenType -> Bool
compare :: TokenType -> TokenType -> Ordering
$ccompare :: TokenType -> TokenType -> Ordering
$cp1Ord :: Eq TokenType
Ord, Int -> TokenType
TokenType -> Int
TokenType -> [TokenType]
TokenType -> TokenType
TokenType -> TokenType -> [TokenType]
TokenType -> TokenType -> TokenType -> [TokenType]
(TokenType -> TokenType)
-> (TokenType -> TokenType)
-> (Int -> TokenType)
-> (TokenType -> Int)
-> (TokenType -> [TokenType])
-> (TokenType -> TokenType -> [TokenType])
-> (TokenType -> TokenType -> [TokenType])
-> (TokenType -> TokenType -> TokenType -> [TokenType])
-> Enum TokenType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: TokenType -> TokenType -> TokenType -> [TokenType]
$cenumFromThenTo :: TokenType -> TokenType -> TokenType -> [TokenType]
enumFromTo :: TokenType -> TokenType -> [TokenType]
$cenumFromTo :: TokenType -> TokenType -> [TokenType]
enumFromThen :: TokenType -> TokenType -> [TokenType]
$cenumFromThen :: TokenType -> TokenType -> [TokenType]
enumFrom :: TokenType -> [TokenType]
$cenumFrom :: TokenType -> [TokenType]
fromEnum :: TokenType -> Int
$cfromEnum :: TokenType -> Int
toEnum :: Int -> TokenType
$ctoEnum :: Int -> TokenType
pred :: TokenType -> TokenType
$cpred :: TokenType -> TokenType
succ :: TokenType -> TokenType
$csucc :: TokenType -> TokenType
Enum, TokenType
TokenType -> TokenType -> Bounded TokenType
forall a. a -> a -> Bounded a
maxBound :: TokenType
$cmaxBound :: TokenType
minBound :: TokenType
$cminBound :: TokenType
Bounded, Int -> TokenType -> ShowS
[TokenType] -> ShowS
TokenType -> String
(Int -> TokenType -> ShowS)
-> (TokenType -> String)
-> ([TokenType] -> ShowS)
-> Show TokenType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TokenType] -> ShowS
$cshowList :: [TokenType] -> ShowS
show :: TokenType -> String
$cshow :: TokenType -> String
showsPrec :: Int -> TokenType -> ShowS
$cshowsPrec :: Int -> TokenType -> ShowS
Show)

-- | @since 0.2.0.0
instance Functor (Decoder s) where
    {-# INLINE fmap #-}
    fmap :: (a -> b) -> Decoder s a -> Decoder s b
fmap a -> b
f = \Decoder s a
d -> (forall r.
 (b -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s b
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder ((forall r.
  (b -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
 -> Decoder s b)
-> (forall r.
    (b -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s b
forall a b. (a -> b) -> a -> b
$ \b -> ST s (DecodeAction s r)
k -> Decoder s a
-> (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
forall s a.
Decoder s a
-> forall r.
   (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
runDecoder Decoder s a
d (b -> ST s (DecodeAction s r)
k (b -> ST s (DecodeAction s r))
-> (a -> b) -> a -> ST s (DecodeAction s r)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f)

-- | @since 0.2.0.0
instance Applicative (Decoder s) where
    {-# INLINE pure #-}
    pure :: a -> Decoder s a
pure = \a
x -> (forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder ((forall r.
  (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
 -> Decoder s a)
-> (forall r.
    (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
forall a b. (a -> b) -> a -> b
$ \a -> ST s (DecodeAction s r)
k -> a -> ST s (DecodeAction s r)
k a
x

    {-# INLINE (<*>) #-}
    <*> :: Decoder s (a -> b) -> Decoder s a -> Decoder s b
(<*>) = \Decoder s (a -> b)
df Decoder s a
dx -> (forall r.
 (b -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s b
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder ((forall r.
  (b -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
 -> Decoder s b)
-> (forall r.
    (b -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s b
forall a b. (a -> b) -> a -> b
$ \b -> ST s (DecodeAction s r)
k ->
                        Decoder s (a -> b)
-> ((a -> b) -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
forall s a.
Decoder s a
-> forall r.
   (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
runDecoder Decoder s (a -> b)
df (\a -> b
f -> Decoder s a
-> (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
forall s a.
Decoder s a
-> forall r.
   (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
runDecoder Decoder s a
dx (\a
x -> b -> ST s (DecodeAction s r)
k (a -> b
f a
x)))

    {-# INLINE (*>) #-}
    *> :: Decoder s a -> Decoder s b -> Decoder s b
(*>) = \Decoder s a
dm Decoder s b
dn -> (forall r.
 (b -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s b
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder ((forall r.
  (b -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
 -> Decoder s b)
-> (forall r.
    (b -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s b
forall a b. (a -> b) -> a -> b
$ \b -> ST s (DecodeAction s r)
k -> Decoder s a
-> (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
forall s a.
Decoder s a
-> forall r.
   (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
runDecoder Decoder s a
dm (\a
_ -> Decoder s b
-> (b -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
forall s a.
Decoder s a
-> forall r.
   (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
runDecoder Decoder s b
dn b -> ST s (DecodeAction s r)
k)

-- | @since 0.2.0.0
instance Monad (Decoder s) where
    return :: a -> Decoder s a
return = a -> Decoder s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure

    {-# INLINE (>>=) #-}
    >>= :: Decoder s a -> (a -> Decoder s b) -> Decoder s b
(>>=) = \Decoder s a
dm a -> Decoder s b
f -> (forall r.
 (b -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s b
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder ((forall r.
  (b -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
 -> Decoder s b)
-> (forall r.
    (b -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s b
forall a b. (a -> b) -> a -> b
$ \b -> ST s (DecodeAction s r)
k -> Decoder s a
-> (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
forall s a.
Decoder s a
-> forall r.
   (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
runDecoder Decoder s a
dm (\a
m -> Decoder s b
-> (b -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
forall s a.
Decoder s a
-> forall r.
   (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
runDecoder (a -> Decoder s b
f a
m) b -> ST s (DecodeAction s r)
k)

    {-# INLINE (>>) #-}
    >> :: Decoder s a -> Decoder s b -> Decoder s b
(>>) = Decoder s a -> Decoder s b -> Decoder s b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>)

#if !MIN_VERSION_base(4,13,0)
    fail = Fail.fail
#endif

-- | @since 0.2.0.0
instance Fail.MonadFail (Decoder s) where
    fail :: String -> Decoder s a
fail String
msg = (forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder ((forall r.
  (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
 -> Decoder s a)
-> (forall r.
    (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
forall a b. (a -> b) -> a -> b
$ \a -> ST s (DecodeAction s r)
_ -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> DecodeAction s r
forall s a. String -> DecodeAction s a
Fail String
msg)

-- | Lift an @ST@ action into a @Decoder@. Useful for, e.g., leveraging
-- in-place mutation to efficiently build a deserialised value.
--
-- @since 0.2.0.0
liftST :: ST s a -> Decoder s a
liftST :: ST s a -> Decoder s a
liftST ST s a
m = (forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder ((forall r.
  (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
 -> Decoder s a)
-> (forall r.
    (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
forall a b. (a -> b) -> a -> b
$ \a -> ST s (DecodeAction s r)
k -> ST s a
m ST s a -> (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> ST s (DecodeAction s r)
k

-- | Given a 'Decoder', give us the 'DecodeAction'
--
-- @since 0.2.0.0
getDecodeAction :: Decoder s a -> ST s (DecodeAction s a)
getDecodeAction :: Decoder s a -> ST s (DecodeAction s a)
getDecodeAction (Decoder forall r. (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
k) = (a -> ST s (DecodeAction s a)) -> ST s (DecodeAction s a)
forall r. (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
k (\a
x -> DecodeAction s a -> ST s (DecodeAction s a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> DecodeAction s a
forall s a. a -> DecodeAction s a
Done a
x))


-- $canonical
--
-- <https://tools.ietf.org/html/rfc7049#section-3.9>
--
-- In general in CBOR there can be multiple representations for the same value,
-- for example the integer @0@ can be represented in 8, 16, 32 or 64 bits. This
-- library always encoded values in the shortest representation but on
-- decoding allows any valid encoding. For some applications it is useful or
-- important to only decode the canonical encoding. The decoder primitives here
-- are to allow applications to implement canonical decoding.
--
-- It is important to note that achieving a canonical representation is /not/
-- simply about using these primitives. For example consider a typical CBOR
-- encoding of a Haskell @Set@ data type. This will be encoded as a CBOR list
-- of the set elements. A typical implementation might be:
--
-- > encodeSet = encodeList . Set.toList
-- > decodeSet = fmap Set.fromList . decodeList
--
-- This /does not/ enforce a canonical encoding. The decoder above will allow
-- set elements in any order. The use of @Set.fromList@ forgets the order.
-- To enforce that the decoder only accepts the canonical encoding it will
-- have to check that the elements in the list are /strictly/ increasing.
-- Similar issues arise in many other data types, wherever there is redundancy
-- in the external representation.
--
-- The decoder primitives in this section are not much more expensive than
-- their normal counterparts. If checking the canonical encoding property is
-- critical then a technique that is more expensive but easier to implement and
-- test is to decode normally, re-encode and check the serialised bytes are the
-- same.

---------------------------------------
-- Read input tokens of various types
--

-- | Decode a 'Word'.
--
-- @since 0.2.0.0
decodeWord :: Decoder s Word
decodeWord :: Decoder s Word
decodeWord = (forall r.
 (Word -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWord (\Word#
w# -> Word -> ST s (DecodeAction s r)
k (Word# -> Word
W# Word#
w#))))
{-# INLINE decodeWord #-}

-- | Decode a 'Word8'.
--
-- @since 0.2.0.0
decodeWord8 :: Decoder s Word8
decodeWord8 :: Decoder s Word8
decodeWord8 = (forall r.
 (Word8 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word8
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word8 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWord8 (\Word#
w# -> Word8 -> ST s (DecodeAction s r)
k (Word# -> Word8
W8# Word#
w#))))
{-# INLINE decodeWord8 #-}

-- | Decode a 'Word16'.
--
-- @since 0.2.0.0
decodeWord16 :: Decoder s Word16
decodeWord16 :: Decoder s Word16
decodeWord16 = (forall r.
 (Word16 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word16
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word16 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWord16 (\Word#
w# -> Word16 -> ST s (DecodeAction s r)
k (Word# -> Word16
W16# Word#
w#))))
{-# INLINE decodeWord16 #-}

-- | Decode a 'Word32'.
--
-- @since 0.2.0.0
decodeWord32 :: Decoder s Word32
decodeWord32 :: Decoder s Word32
decodeWord32 = (forall r.
 (Word32 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word32
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word32 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWord32 (\Word#
w# -> Word32 -> ST s (DecodeAction s r)
k (Word# -> Word32
W32# Word#
w#))))
{-# INLINE decodeWord32 #-}

-- | Decode a 'Word64'.
--
-- @since 0.2.0.0
decodeWord64 :: Decoder s Word64
{-# INLINE decodeWord64 #-}
decodeWord64 :: Decoder s Word64
decodeWord64 =
#if defined(ARCH_64bit)
  (forall r.
 (Word64 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word64
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word64 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWord (\Word#
w# -> Word64 -> ST s (DecodeAction s r)
k (Word# -> Word64
W64# Word#
w#))))
#else
  Decoder (\k -> return (ConsumeWord64 (\w64# -> k (W64# w64#))))
#endif

-- | Decode a negative 'Word'.
--
-- @since 0.2.0.0
decodeNegWord :: Decoder s Word
decodeNegWord :: Decoder s Word
decodeNegWord = (forall r.
 (Word -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeNegWord (\Word#
w# -> Word -> ST s (DecodeAction s r)
k (Word# -> Word
W# Word#
w#))))
{-# INLINE decodeNegWord #-}

-- | Decode a negative 'Word64'.
--
-- @since 0.2.0.0
decodeNegWord64 :: Decoder s Word64
{-# INLINE decodeNegWord64 #-}
decodeNegWord64 :: Decoder s Word64
decodeNegWord64 =
#if defined(ARCH_64bit)
  (forall r.
 (Word64 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word64
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word64 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeNegWord (\Word#
w# -> Word64 -> ST s (DecodeAction s r)
k (Word# -> Word64
W64# Word#
w#))))
#else
  Decoder (\k -> return (ConsumeNegWord64 (\w64# -> k (W64# w64#))))
#endif

-- | Decode an 'Int'.
--
-- @since 0.2.0.0
decodeInt :: Decoder s Int
decodeInt :: Decoder s Int
decodeInt = (forall r.
 (Int -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Int
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInt (\Int#
n# -> Int -> ST s (DecodeAction s r)
k (Int# -> Int
I# Int#
n#))))
{-# INLINE decodeInt #-}

-- | Decode an 'Int8'.
--
-- @since 0.2.0.0
decodeInt8 :: Decoder s Int8
decodeInt8 :: Decoder s Int8
decodeInt8 = (forall r.
 (Int8 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Int8
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int8 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInt8 (\Int#
w# -> Int8 -> ST s (DecodeAction s r)
k (Int# -> Int8
I8# Int#
w#))))
{-# INLINE decodeInt8 #-}

-- | Decode an 'Int16'.
--
-- @since 0.2.0.0
decodeInt16 :: Decoder s Int16
decodeInt16 :: Decoder s Int16
decodeInt16 = (forall r.
 (Int16 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Int16
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int16 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInt16 (\Int#
w# -> Int16 -> ST s (DecodeAction s r)
k (Int# -> Int16
I16# Int#
w#))))
{-# INLINE decodeInt16 #-}

-- | Decode an 'Int32'.
--
-- @since 0.2.0.0
decodeInt32 :: Decoder s Int32
decodeInt32 :: Decoder s Int32
decodeInt32 = (forall r.
 (Int32 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Int32
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int32 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInt32 (\Int#
w# -> Int32 -> ST s (DecodeAction s r)
k (Int# -> Int32
I32# Int#
w#))))
{-# INLINE decodeInt32 #-}

-- | Decode an 'Int64'.
--
-- @since 0.2.0.0
decodeInt64 :: Decoder s Int64
{-# INLINE decodeInt64 #-}
decodeInt64 :: Decoder s Int64
decodeInt64 =
#if defined(ARCH_64bit)
  (forall r.
 (Int64 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Int64
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int64 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInt (\Int#
n# -> Int64 -> ST s (DecodeAction s r)
k (Int# -> Int64
I64# Int#
n#))))
#else
  Decoder (\k -> return (ConsumeInt64 (\n64# -> k (I64# n64#))))
#endif

-- | Decode canonical representation of a 'Word'.
--
-- @since 0.2.0.0
decodeWordCanonical :: Decoder s Word
decodeWordCanonical :: Decoder s Word
decodeWordCanonical = (forall r.
 (Word -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWordCanonical (\Word#
w# -> Word -> ST s (DecodeAction s r)
k (Word# -> Word
W# Word#
w#))))
{-# INLINE decodeWordCanonical #-}

-- | Decode canonical representation of a 'Word8'.
--
-- @since 0.2.0.0
decodeWord8Canonical :: Decoder s Word8
decodeWord8Canonical :: Decoder s Word8
decodeWord8Canonical = (forall r.
 (Word8 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word8
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word8 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWord8Canonical (\Word#
w# -> Word8 -> ST s (DecodeAction s r)
k (Word# -> Word8
W8# Word#
w#))))
{-# INLINE decodeWord8Canonical #-}

-- | Decode canonical representation of a 'Word16'.
--
-- @since 0.2.0.0
decodeWord16Canonical :: Decoder s Word16
decodeWord16Canonical :: Decoder s Word16
decodeWord16Canonical = (forall r.
 (Word16 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word16
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word16 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWord16Canonical (\Word#
w# -> Word16 -> ST s (DecodeAction s r)
k (Word# -> Word16
W16# Word#
w#))))
{-# INLINE decodeWord16Canonical #-}

-- | Decode canonical representation of a 'Word32'.
--
-- @since 0.2.0.0
decodeWord32Canonical :: Decoder s Word32
decodeWord32Canonical :: Decoder s Word32
decodeWord32Canonical = (forall r.
 (Word32 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word32
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word32 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWord32Canonical (\Word#
w# -> Word32 -> ST s (DecodeAction s r)
k (Word# -> Word32
W32# Word#
w#))))
{-# INLINE decodeWord32Canonical #-}

-- | Decode canonical representation of a 'Word64'.
--
-- @since 0.2.0.0
decodeWord64Canonical :: Decoder s Word64
{-# INLINE decodeWord64Canonical #-}
decodeWord64Canonical :: Decoder s Word64
decodeWord64Canonical =
#if defined(ARCH_64bit)
  (forall r.
 (Word64 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word64
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word64 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWordCanonical (\Word#
w# -> Word64 -> ST s (DecodeAction s r)
k (Word# -> Word64
W64# Word#
w#))))
#else
  Decoder (\k -> return (ConsumeWord64Canonical (\w64# -> k (W64# w64#))))
#endif

-- | Decode canonical representation of a negative 'Word'.
--
-- @since 0.2.0.0
decodeNegWordCanonical :: Decoder s Word
decodeNegWordCanonical :: Decoder s Word
decodeNegWordCanonical = (forall r.
 (Word -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeNegWordCanonical (\Word#
w# -> Word -> ST s (DecodeAction s r)
k (Word# -> Word
W# Word#
w#))))
{-# INLINE decodeNegWordCanonical #-}

-- | Decode canonical representation of a negative 'Word64'.
--
-- @since 0.2.0.0
decodeNegWord64Canonical :: Decoder s Word64
{-# INLINE decodeNegWord64Canonical #-}
decodeNegWord64Canonical :: Decoder s Word64
decodeNegWord64Canonical =
#if defined(ARCH_64bit)
  (forall r.
 (Word64 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word64
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word64 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeNegWordCanonical (\Word#
w# -> Word64 -> ST s (DecodeAction s r)
k (Word# -> Word64
W64# Word#
w#))))
#else
  Decoder (\k -> return (ConsumeNegWord64Canonical (\w64# -> k (W64# w64#))))
#endif

-- | Decode canonical representation of an 'Int'.
--
-- @since 0.2.0.0
decodeIntCanonical :: Decoder s Int
decodeIntCanonical :: Decoder s Int
decodeIntCanonical = (forall r.
 (Int -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Int
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeIntCanonical (\Int#
n# -> Int -> ST s (DecodeAction s r)
k (Int# -> Int
I# Int#
n#))))
{-# INLINE decodeIntCanonical #-}

-- | Decode canonical representation of an 'Int8'.
--
-- @since 0.2.0.0
decodeInt8Canonical :: Decoder s Int8
decodeInt8Canonical :: Decoder s Int8
decodeInt8Canonical = (forall r.
 (Int8 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Int8
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int8 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInt8Canonical (\Int#
w# -> Int8 -> ST s (DecodeAction s r)
k (Int# -> Int8
I8# Int#
w#))))
{-# INLINE decodeInt8Canonical #-}

-- | Decode canonical representation of an 'Int16'.
--
-- @since 0.2.0.0
decodeInt16Canonical :: Decoder s Int16
decodeInt16Canonical :: Decoder s Int16
decodeInt16Canonical = (forall r.
 (Int16 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Int16
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int16 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInt16Canonical (\Int#
w# -> Int16 -> ST s (DecodeAction s r)
k (Int# -> Int16
I16# Int#
w#))))
{-# INLINE decodeInt16Canonical #-}

-- | Decode canonical representation of an 'Int32'.
--
-- @since 0.2.0.0
decodeInt32Canonical :: Decoder s Int32
decodeInt32Canonical :: Decoder s Int32
decodeInt32Canonical = (forall r.
 (Int32 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Int32
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int32 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInt32Canonical (\Int#
w# -> Int32 -> ST s (DecodeAction s r)
k (Int# -> Int32
I32# Int#
w#))))
{-# INLINE decodeInt32Canonical #-}

-- | Decode canonical representation of an 'Int64'.
--
-- @since 0.2.0.0
decodeInt64Canonical :: Decoder s Int64
{-# INLINE decodeInt64Canonical #-}
decodeInt64Canonical :: Decoder s Int64
decodeInt64Canonical =
#if defined(ARCH_64bit)
  (forall r.
 (Int64 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Int64
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int64 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeIntCanonical (\Int#
n# -> Int64 -> ST s (DecodeAction s r)
k (Int# -> Int64
I64# Int#
n#))))
#else
  Decoder (\k -> return (ConsumeInt64Canonical (\n64# -> k (I64# n64#))))
#endif

-- | Decode an 'Integer'.
--
-- @since 0.2.0.0
decodeInteger :: Decoder s Integer
decodeInteger :: Decoder s Integer
decodeInteger = (forall r.
 (Integer -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Integer
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Integer -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Integer -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a.
(Integer -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInteger (\Integer
n -> Integer -> ST s (DecodeAction s r)
k Integer
n)))
{-# INLINE decodeInteger #-}

-- | Decode a 'Float'.
--
-- @since 0.2.0.0
decodeFloat :: Decoder s Float
decodeFloat :: Decoder s Float
decodeFloat = (forall r.
 (Float -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Float
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Float -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Float# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Float# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeFloat (\Float#
f# -> Float -> ST s (DecodeAction s r)
k (Float# -> Float
F# Float#
f#))))
{-# INLINE decodeFloat #-}

-- | Decode a 'Double'.
--
-- @since 0.2.0.0
decodeDouble :: Decoder s Double
decodeDouble :: Decoder s Double
decodeDouble = (forall r.
 (Double -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Double
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Double -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Double# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a.
(Double# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeDouble (\Double#
f# -> Double -> ST s (DecodeAction s r)
k (Double# -> Double
D# Double#
f#))))
{-# INLINE decodeDouble #-}

-- | Decode a string of bytes as a 'ByteString'.
--
-- @since 0.2.0.0
decodeBytes :: Decoder s ByteString
decodeBytes :: Decoder s ByteString
decodeBytes = (forall r.
 (ByteString -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s ByteString
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\ByteString -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((ByteString -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a.
(ByteString -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeBytes (\ByteString
bs -> ByteString -> ST s (DecodeAction s r)
k ByteString
bs)))
{-# INLINE decodeBytes #-}

-- | Decode canonical representation of a string of bytes as a 'ByteString'.
--
-- @since 0.2.1.0
decodeBytesCanonical :: Decoder s ByteString
decodeBytesCanonical :: Decoder s ByteString
decodeBytesCanonical = (forall r.
 (ByteString -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s ByteString
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\ByteString -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((ByteString -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a.
(ByteString -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeBytesCanonical (\ByteString
bs -> ByteString -> ST s (DecodeAction s r)
k ByteString
bs)))
{-# INLINE decodeBytesCanonical #-}

-- | Decode a token marking the beginning of an indefinite length
-- set of bytes.
--
-- @since 0.2.0.0
decodeBytesIndef :: Decoder s ()
decodeBytesIndef :: Decoder s ()
decodeBytesIndef = (forall r.
 (() -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s ()
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\() -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return (ST s (DecodeAction s r) -> DecodeAction s r
forall s a. ST s (DecodeAction s a) -> DecodeAction s a
ConsumeBytesIndef (() -> ST s (DecodeAction s r)
k ())))
{-# INLINE decodeBytesIndef #-}

-- | Decode a string of bytes as a 'ByteArray'.
--
-- Also note that this will eagerly copy the content out of the input
-- to ensure that the input does not leak in the event that the 'ByteArray' is
-- live but not forced.
--
-- @since 0.2.0.0
decodeByteArray :: Decoder s ByteArray
decodeByteArray :: Decoder s ByteArray
decodeByteArray = (forall r.
 (ByteArray -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s ByteArray
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\ByteArray -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((ByteArray -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a.
(ByteArray -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeByteArray ByteArray -> ST s (DecodeAction s r)
k))
{-# INLINE decodeByteArray #-}

-- | Decode canonical representation of a string of bytes as a 'ByteArray'.
--
-- Also note that this will eagerly copy the content out of the input
-- to ensure that the input does not leak in the event that the 'ByteArray' is
-- live but not forced.
--
-- @since 0.2.1.0
decodeByteArrayCanonical :: Decoder s ByteArray
decodeByteArrayCanonical :: Decoder s ByteArray
decodeByteArrayCanonical = (forall r.
 (ByteArray -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s ByteArray
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\ByteArray -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((ByteArray -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a.
(ByteArray -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeByteArrayCanonical ByteArray -> ST s (DecodeAction s r)
k))
{-# INLINE decodeByteArrayCanonical #-}

-- | Decode a textual string as a piece of 'Text'.
--
-- @since 0.2.0.0
decodeString :: Decoder s Text
decodeString :: Decoder s Text
decodeString = (forall r.
 (Text -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Text
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Text -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Text -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Text -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeString (\Text
str -> Text -> ST s (DecodeAction s r)
k Text
str)))
{-# INLINE decodeString #-}

-- | Decode canonical representation of a textual string as a piece of 'Text'.
--
-- @since 0.2.1.0
decodeStringCanonical :: Decoder s Text
decodeStringCanonical :: Decoder s Text
decodeStringCanonical = (forall r.
 (Text -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Text
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Text -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Text -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Text -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeStringCanonical (\Text
str -> Text -> ST s (DecodeAction s r)
k Text
str)))
{-# INLINE decodeStringCanonical #-}

-- | Decode a token marking the beginning of an indefinite length
-- string.
--
-- @since 0.2.0.0
decodeStringIndef :: Decoder s ()
decodeStringIndef :: Decoder s ()
decodeStringIndef = (forall r.
 (() -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s ()
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\() -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return (ST s (DecodeAction s r) -> DecodeAction s r
forall s a. ST s (DecodeAction s a) -> DecodeAction s a
ConsumeStringIndef (() -> ST s (DecodeAction s r)
k ())))
{-# INLINE decodeStringIndef #-}

-- | Decode a textual string as UTF-8 encoded 'ByteArray'. Note that
-- the result is not validated to be well-formed UTF-8.
--
-- Also note that this will eagerly copy the content out of the input
-- to ensure that the input does not leak in the event that the 'ByteArray' is
-- live but not forced.
--
-- @since 0.2.0.0
decodeUtf8ByteArray :: Decoder s ByteArray
decodeUtf8ByteArray :: Decoder s ByteArray
decodeUtf8ByteArray = (forall r.
 (ByteArray -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s ByteArray
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\ByteArray -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((ByteArray -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a.
(ByteArray -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeUtf8ByteArray ByteArray -> ST s (DecodeAction s r)
k))
{-# INLINE decodeUtf8ByteArray #-}

-- | Decode canonical representation of a textual string as UTF-8 encoded
-- 'ByteArray'. Note that the result is not validated to be well-formed UTF-8.
--
-- Also note that this will eagerly copy the content out of the input
-- to ensure that the input does not leak in the event that the 'ByteArray' is
-- live but not forced.
--
-- @since 0.2.1.0
decodeUtf8ByteArrayCanonical :: Decoder s ByteArray
decodeUtf8ByteArrayCanonical :: Decoder s ByteArray
decodeUtf8ByteArrayCanonical = (forall r.
 (ByteArray -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s ByteArray
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\ByteArray -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((ByteArray -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a.
(ByteArray -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeUtf8ByteArrayCanonical ByteArray -> ST s (DecodeAction s r)
k))
{-# INLINE decodeUtf8ByteArrayCanonical #-}

-- | Decode the length of a list.
--
-- @since 0.2.0.0
decodeListLen :: Decoder s Int
decodeListLen :: Decoder s Int
decodeListLen = (forall r.
 (Int -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Int
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeListLen (\Int#
n# -> Int -> ST s (DecodeAction s r)
k (Int# -> Int
I# Int#
n#))))
{-# INLINE decodeListLen #-}

-- | Decode canonical representation of the length of a list.
--
-- @since 0.2.0.0
decodeListLenCanonical :: Decoder s Int
decodeListLenCanonical :: Decoder s Int
decodeListLenCanonical = (forall r.
 (Int -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Int
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeListLenCanonical (\Int#
n# -> Int -> ST s (DecodeAction s r)
k (Int# -> Int
I# Int#
n#))))
{-# INLINE decodeListLenCanonical #-}

-- | Decode a token marking the beginning of a list of indefinite
-- length.
--
-- @since 0.2.0.0
decodeListLenIndef :: Decoder s ()
decodeListLenIndef :: Decoder s ()
decodeListLenIndef = (forall r.
 (() -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s ()
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\() -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return (ST s (DecodeAction s r) -> DecodeAction s r
forall s a. ST s (DecodeAction s a) -> DecodeAction s a
ConsumeListLenIndef (() -> ST s (DecodeAction s r)
k ())))
{-# INLINE decodeListLenIndef #-}

-- | Decode the length of a map.
--
-- @since 0.2.0.0
decodeMapLen :: Decoder s Int
decodeMapLen :: Decoder s Int
decodeMapLen = (forall r.
 (Int -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Int
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeMapLen (\Int#
n# -> Int -> ST s (DecodeAction s r)
k (Int# -> Int
I# Int#
n#))))
{-# INLINE decodeMapLen #-}

-- | Decode canonical representation of the length of a map.
--
-- @since 0.2.0.0
decodeMapLenCanonical :: Decoder s Int
decodeMapLenCanonical :: Decoder s Int
decodeMapLenCanonical = (forall r.
 (Int -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Int
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeMapLenCanonical (\Int#
n# -> Int -> ST s (DecodeAction s r)
k (Int# -> Int
I# Int#
n#))))
{-# INLINE decodeMapLenCanonical #-}

-- | Decode a token marking the beginning of a map of indefinite
-- length.
--
-- @since 0.2.0.0
decodeMapLenIndef :: Decoder s ()
decodeMapLenIndef :: Decoder s ()
decodeMapLenIndef = (forall r.
 (() -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s ()
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\() -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return (ST s (DecodeAction s r) -> DecodeAction s r
forall s a. ST s (DecodeAction s a) -> DecodeAction s a
ConsumeMapLenIndef (() -> ST s (DecodeAction s r)
k ())))
{-# INLINE decodeMapLenIndef #-}

-- | Decode an arbitrary tag and return it as a 'Word'.
--
-- @since 0.2.0.0
decodeTag :: Decoder s Word
decodeTag :: Decoder s Word
decodeTag = (forall r.
 (Word -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeTag (\Word#
w# -> Word -> ST s (DecodeAction s r)
k (Word# -> Word
W# Word#
w#))))
{-# INLINE decodeTag #-}

-- | Decode an arbitrary 64-bit tag and return it as a 'Word64'.
--
-- @since 0.2.0.0
decodeTag64 :: Decoder s Word64
{-# INLINE decodeTag64 #-}
decodeTag64 :: Decoder s Word64
decodeTag64 =
#if defined(ARCH_64bit)
  (forall r.
 (Word64 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word64
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word64 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeTag (\Word#
w# -> Word64 -> ST s (DecodeAction s r)
k (Word# -> Word64
W64# Word#
w#))))
#else
  Decoder (\k -> return (ConsumeTag64 (\w64# -> k (W64# w64#))))
#endif

-- | Decode canonical representation of an arbitrary tag and return it as a
-- 'Word'.
--
-- @since 0.2.0.0
decodeTagCanonical :: Decoder s Word
decodeTagCanonical :: Decoder s Word
decodeTagCanonical = (forall r.
 (Word -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeTagCanonical (\Word#
w# -> Word -> ST s (DecodeAction s r)
k (Word# -> Word
W# Word#
w#))))
{-# INLINE decodeTagCanonical #-}

-- | Decode canonical representation of an arbitrary 64-bit tag and return it as
-- a 'Word64'.
--
-- @since 0.2.0.0
decodeTag64Canonical :: Decoder s Word64
{-# INLINE decodeTag64Canonical #-}
decodeTag64Canonical :: Decoder s Word64
decodeTag64Canonical =
#if defined(ARCH_64bit)
  (forall r.
 (Word64 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word64
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word64 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeTagCanonical (\Word#
w# -> Word64 -> ST s (DecodeAction s r)
k (Word# -> Word64
W64# Word#
w#))))
#else
  Decoder (\k -> return (ConsumeTag64Canonical (\w64# -> k (W64# w64#))))
#endif

-- | Decode a bool.
--
-- @since 0.2.0.0
decodeBool :: Decoder s Bool
decodeBool :: Decoder s Bool
decodeBool = (forall r.
 (Bool -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Bool
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Bool -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Bool -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Bool -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeBool (\Bool
b -> Bool -> ST s (DecodeAction s r)
k Bool
b)))
{-# INLINE decodeBool #-}

-- | Decode a nullary value, and return a unit value.
--
-- @since 0.2.0.0
decodeNull :: Decoder s ()
decodeNull :: Decoder s ()
decodeNull = (forall r.
 (() -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s ()
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\() -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return (ST s (DecodeAction s r) -> DecodeAction s r
forall s a. ST s (DecodeAction s a) -> DecodeAction s a
ConsumeNull (() -> ST s (DecodeAction s r)
k ())))
{-# INLINE decodeNull #-}

-- | Decode a 'simple' CBOR value and give back a 'Word8'. You
-- probably don't ever need to use this.
--
-- @since 0.2.0.0
decodeSimple :: Decoder s Word8
decodeSimple :: Decoder s Word8
decodeSimple = (forall r.
 (Word8 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word8
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word8 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeSimple (\Word#
w# -> Word8 -> ST s (DecodeAction s r)
k (Word# -> Word8
W8# Word#
w#))))
{-# INLINE decodeSimple #-}

-- | Decode canonical representation of an 'Integer'.
--
-- @since 0.2.0.0
decodeIntegerCanonical :: Decoder s Integer
decodeIntegerCanonical :: Decoder s Integer
decodeIntegerCanonical = (forall r.
 (Integer -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Integer
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Integer -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Integer -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a.
(Integer -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeIntegerCanonical (\Integer
n -> Integer -> ST s (DecodeAction s r)
k Integer
n)))
{-# INLINE decodeIntegerCanonical #-}

-- | Decode canonical representation of a half-precision 'Float'.
--
-- @since 0.2.0.0
decodeFloat16Canonical :: Decoder s Float
decodeFloat16Canonical :: Decoder s Float
decodeFloat16Canonical = (forall r.
 (Float -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Float
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Float -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Float# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Float# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeFloat16Canonical (\Float#
f# -> Float -> ST s (DecodeAction s r)
k (Float# -> Float
F# Float#
f#))))
{-# INLINE decodeFloat16Canonical #-}

-- | Decode canonical representation of a 'Float'.
--
-- @since 0.2.0.0
decodeFloatCanonical :: Decoder s Float
decodeFloatCanonical :: Decoder s Float
decodeFloatCanonical = (forall r.
 (Float -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Float
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Float -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Float# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Float# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeFloatCanonical (\Float#
f# -> Float -> ST s (DecodeAction s r)
k (Float# -> Float
F# Float#
f#))))
{-# INLINE decodeFloatCanonical #-}

-- | Decode canonical representation of a 'Double'.
--
-- @since 0.2.0.0
decodeDoubleCanonical :: Decoder s Double
decodeDoubleCanonical :: Decoder s Double
decodeDoubleCanonical = (forall r.
 (Double -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Double
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Double -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Double# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a.
(Double# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeDoubleCanonical (\Double#
f# -> Double -> ST s (DecodeAction s r)
k (Double# -> Double
D# Double#
f#))))
{-# INLINE decodeDoubleCanonical #-}

-- | Decode canonical representation of a 'simple' CBOR value and give back a
-- 'Word8'. You probably don't ever need to use this.
--
-- @since 0.2.0.0
decodeSimpleCanonical :: Decoder s Word8
decodeSimpleCanonical :: Decoder s Word8
decodeSimpleCanonical = (forall r.
 (Word8 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Word8
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word8 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeSimpleCanonical (\Word#
w# -> Word8 -> ST s (DecodeAction s r)
k (Word# -> Word8
W8# Word#
w#))))
{-# INLINE decodeSimpleCanonical #-}

--------------------------------------------------------------
-- Specialised read operations: expect a token with a specific value
--

-- | Attempt to decode a word with 'decodeWord', and ensure the word
-- is exactly as expected, or fail.
--
-- @since 0.2.0.0
decodeWordOf :: Word -- ^ Expected value of the decoded word
             -> Decoder s ()
decodeWordOf :: Word -> Decoder s ()
decodeWordOf = Decoder s Word -> Word -> Decoder s ()
forall a (m :: * -> *).
(Show a, Eq a, MonadFail m) =>
m a -> a -> m ()
decodeWordOfHelper Decoder s Word
forall s. Decoder s Word
decodeWord
{-# INLINE decodeWordOf #-}

-- | Attempt to decode a list length using 'decodeListLen', and
-- ensure it is exactly the specified length, or fail.
--
-- @since 0.2.0.0
decodeListLenOf :: Int -> Decoder s ()
decodeListLenOf :: Int -> Decoder s ()
decodeListLenOf = Decoder s Int -> Int -> Decoder s ()
forall a (m :: * -> *).
(Show a, Eq a, MonadFail m) =>
m a -> a -> m ()
decodeListLenOfHelper Decoder s Int
forall s. Decoder s Int
decodeListLen
{-# INLINE decodeListLenOf #-}

-- | Attempt to decode canonical representation of a word with 'decodeWordCanonical',
-- and ensure the word is exactly as expected, or fail.
--
-- @since 0.2.0.0
decodeWordCanonicalOf :: Word -- ^ Expected value of the decoded word
                      -> Decoder s ()
decodeWordCanonicalOf :: Word -> Decoder s ()
decodeWordCanonicalOf = Decoder s Word -> Word -> Decoder s ()
forall a (m :: * -> *).
(Show a, Eq a, MonadFail m) =>
m a -> a -> m ()
decodeWordOfHelper Decoder s Word
forall s. Decoder s Word
decodeWordCanonical
{-# INLINE decodeWordCanonicalOf #-}

-- | Attempt to decode canonical representation of a list length using
-- 'decodeListLenCanonical', and ensure it is exactly the specified length, or
-- fail.
--
-- @since 0.2.0.0
decodeListLenCanonicalOf :: Int -> Decoder s ()
decodeListLenCanonicalOf :: Int -> Decoder s ()
decodeListLenCanonicalOf = Decoder s Int -> Int -> Decoder s ()
forall a (m :: * -> *).
(Show a, Eq a, MonadFail m) =>
m a -> a -> m ()
decodeListLenOfHelper Decoder s Int
forall s. Decoder s Int
decodeListLenCanonical
{-# INLINE decodeListLenCanonicalOf #-}

decodeListLenOfHelper :: (Show a, Eq a, Fail.MonadFail m) => m a -> a -> m ()
decodeListLenOfHelper :: m a -> a -> m ()
decodeListLenOfHelper m a
decodeFun = \a
len -> do
  a
len' <- m a
decodeFun
  if a
len a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
len' then () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
                 else String -> m ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"expected list of length " String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
len
{-# INLINE decodeListLenOfHelper #-}

decodeWordOfHelper :: (Show a, Eq a, Fail.MonadFail m) => m a -> a -> m ()
decodeWordOfHelper :: m a -> a -> m ()
decodeWordOfHelper m a
decodeFun = \a
n -> do
  a
n' <- m a
decodeFun
  if a
n a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
n' then () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
             else String -> m ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"expected word " String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
n
{-# INLINE decodeWordOfHelper #-}

--------------------------------------------------------------
-- Branching operations

-- | Attempt to decode a token for the length of a finite, known list,
-- or an indefinite list. If 'Nothing' is returned, then an
-- indefinite length list occurs afterwords. If @'Just' x@ is
-- returned, then a list of length @x@ is encoded.
--
-- @since 0.2.0.0
decodeListLenOrIndef :: Decoder s (Maybe Int)
decodeListLenOrIndef :: Decoder s (Maybe Int)
decodeListLenOrIndef =
    (forall r.
 (Maybe Int -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s (Maybe Int)
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Maybe Int -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeListLenOrIndef (\Int#
n# ->
                     if Int# -> Int
I# Int#
n# Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0
                       then Maybe Int -> ST s (DecodeAction s r)
k (Int -> Maybe Int
forall a. a -> Maybe a
Just (Int# -> Int
I# Int#
n#))
                       else Maybe Int -> ST s (DecodeAction s r)
k Maybe Int
forall a. Maybe a
Nothing)))
{-# INLINE decodeListLenOrIndef #-}

-- | Attempt to decode a token for the length of a finite, known map,
-- or an indefinite map. If 'Nothing' is returned, then an
-- indefinite length map occurs afterwords. If @'Just' x@ is returned,
-- then a map of length @x@ is encoded.
--
-- @since 0.2.0.0
decodeMapLenOrIndef :: Decoder s (Maybe Int)
decodeMapLenOrIndef :: Decoder s (Maybe Int)
decodeMapLenOrIndef =
    (forall r.
 (Maybe Int -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s (Maybe Int)
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Maybe Int -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeMapLenOrIndef (\Int#
n# ->
                     if Int# -> Int
I# Int#
n# Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0
                       then Maybe Int -> ST s (DecodeAction s r)
k (Int -> Maybe Int
forall a. a -> Maybe a
Just (Int# -> Int
I# Int#
n#))
                       else Maybe Int -> ST s (DecodeAction s r)
k Maybe Int
forall a. Maybe a
Nothing)))
{-# INLINE decodeMapLenOrIndef #-}

-- | Attempt to decode a @Break@ token, and if that was
-- successful, return 'True'. If the token was of any
-- other type, return 'False'.
--
-- @since 0.2.0.0
decodeBreakOr :: Decoder s Bool
decodeBreakOr :: Decoder s Bool
decodeBreakOr = (forall r.
 (Bool -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Bool
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Bool -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Bool -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Bool -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeBreakOr (\Bool
b -> Bool -> ST s (DecodeAction s r)
k Bool
b)))
{-# INLINE decodeBreakOr #-}

--------------------------------------------------------------
-- Special operations

-- | Peek at the current token we're about to decode, and return a
-- 'TokenType' specifying what it is.
--
-- @since 0.2.0.0
peekTokenType :: Decoder s TokenType
peekTokenType :: Decoder s TokenType
peekTokenType = (forall r.
 (TokenType -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s TokenType
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\TokenType -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((TokenType -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a.
(TokenType -> ST s (DecodeAction s a)) -> DecodeAction s a
PeekTokenType (\TokenType
tk -> TokenType -> ST s (DecodeAction s r)
k TokenType
tk)))
{-# INLINE peekTokenType #-}

-- | Peek and return the length of the current buffer that we're
-- running our decoder on.
--
-- @since 0.2.0.0
peekAvailable :: Decoder s Int
peekAvailable :: Decoder s Int
peekAvailable = (forall r.
 (Int -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Int
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
PeekAvailable (\Int#
len# -> Int -> ST s (DecodeAction s r)
k (Int# -> Int
I# Int#
len#))))
{-# INLINE peekAvailable #-}


-- | A 0-based offset within the overall byte sequence that makes up the
-- input to the 'Decoder'.
--
-- This is an 'Int64' since 'Decoder' is incremental and can decode more data
-- than fits in memory at once. This is also compatible with the result type
-- of 'Data.ByteString.Lazy.length'.
--
type ByteOffset = Int64

-- | Get the current 'ByteOffset' in the input byte sequence of the 'Decoder'.
--
-- The 'Decoder' does not provide any facility to get at the input data
-- directly (since that is tricky with an incremental decoder). The next best
-- is this primitive which can be used to keep track of the offset within the
-- input bytes that makes up the encoded form of a term.
--
-- By keeping track of the byte offsets before and after decoding a subterm
-- (a pattern captured by 'decodeWithByteSpan') and if the overall input data
-- is retained then this is enables later retrieving the span of bytes for the
-- subterm.
--
-- @since 0.2.2.0
peekByteOffset :: Decoder s ByteOffset
peekByteOffset :: Decoder s Int64
peekByteOffset = (forall r.
 (Int64 -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s Int64
forall s a.
(forall r.
 (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int64 -> ST s (DecodeAction s r)
k -> DecodeAction s r -> ST s (DecodeAction s r)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int# -> ST s (DecodeAction s r)) -> DecodeAction s r
forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
PeekByteOffset (\Int#
off# -> Int64 -> ST s (DecodeAction s r)
k (Int# -> Int64
I64# Int#
off#))))
{-# INLINE peekByteOffset #-}

-- | This captures the pattern of getting the byte offsets before and after
-- decoding a subterm.
--
-- > !before <- peekByteOffset
-- > x <- decode
-- > !after  <- peekByteOffset
--
decodeWithByteSpan :: Decoder s a -> Decoder s (a, ByteOffset, ByteOffset)
decodeWithByteSpan :: Decoder s a -> Decoder s (a, Int64, Int64)
decodeWithByteSpan Decoder s a
da = do
    !Int64
before <- Decoder s Int64
forall s. Decoder s Int64
peekByteOffset
    a
x <- Decoder s a
da
    !Int64
after  <- Decoder s Int64
forall s. Decoder s Int64
peekByteOffset
    (a, Int64, Int64) -> Decoder s (a, Int64, Int64)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
x, Int64
before, Int64
after)

{-
expectExactly :: Word -> Decoder (Word :#: s) s
expectExactly n = expectExactly_ n done

expectAtLeast :: Word -> Decoder (Word :#: s) (Word :#: s)
expectAtLeast n = expectAtLeast_ n done

ignoreTrailingTerms :: Decoder (a :*: Word :#: s) (a :*: s)
ignoreTrailingTerms = IgnoreTerms done
-}

------------------------------------------------------------------------------
-- Special combinations for sequences
--

-- | Decode an indefinite sequence length.
--
-- @since 0.2.0.0
decodeSequenceLenIndef :: (r -> a -> r)
                       -> r
                       -> (r -> r')
                       -> Decoder s a
                       -> Decoder s r'
decodeSequenceLenIndef :: (r -> a -> r) -> r -> (r -> r') -> Decoder s a -> Decoder s r'
decodeSequenceLenIndef r -> a -> r
f r
z r -> r'
g Decoder s a
get =
    r -> Decoder s r'
go r
z
  where
    go :: r -> Decoder s r'
go !r
acc = do
      Bool
stop <- Decoder s Bool
forall s. Decoder s Bool
decodeBreakOr
      if Bool
stop then r' -> Decoder s r'
forall (m :: * -> *) a. Monad m => a -> m a
return (r' -> Decoder s r') -> r' -> Decoder s r'
forall a b. (a -> b) -> a -> b
$! r -> r'
g r
acc
              else do !a
x <- Decoder s a
get; r -> Decoder s r'
go (r -> a -> r
f r
acc a
x)
{-# INLINE decodeSequenceLenIndef #-}

-- | Decode a sequence length.
--
-- @since 0.2.0.0
decodeSequenceLenN :: (r -> a -> r)
                   -> r
                   -> (r -> r')
                   -> Int
                   -> Decoder s a
                   -> Decoder s r'
decodeSequenceLenN :: (r -> a -> r)
-> r -> (r -> r') -> Int -> Decoder s a -> Decoder s r'
decodeSequenceLenN r -> a -> r
f r
z r -> r'
g Int
c Decoder s a
get =
    r -> Int -> Decoder s r'
forall t. (Eq t, Num t) => r -> t -> Decoder s r'
go r
z Int
c
  where
    go :: r -> t -> Decoder s r'
go !r
acc t
0 = r' -> Decoder s r'
forall (m :: * -> *) a. Monad m => a -> m a
return (r' -> Decoder s r') -> r' -> Decoder s r'
forall a b. (a -> b) -> a -> b
$! r -> r'
g r
acc
    go !r
acc t
n = do !a
x <- Decoder s a
get; r -> t -> Decoder s r'
go (r -> a -> r
f r
acc a
x) (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
1)
{-# INLINE decodeSequenceLenN #-}