module Streamly.Internal.Data.Binary.Decode
( unit
, bool
, ordering
, eqWord8
, word8
, word16be
, word16le
, word32be
, word32le
, word64be
, word64le
, word64host
)
where
import Control.Monad.Catch (MonadCatch, throwM)
import Control.Monad.IO.Class (MonadIO)
import Data.Bits ((.|.), unsafeShiftL)
import Data.Word (Word8, Word16, Word32, Word64)
import Streamly.Internal.Data.Parser (Parser)
import Streamly.Internal.Data.Maybe.Strict (Maybe'(..))
import Streamly.Internal.Data.Tuple.Strict (Tuple' (..))
import qualified Streamly.Internal.Data.Array.Foreign as A
import qualified Streamly.Internal.Data.Parser as PR
import qualified Streamly.Internal.Data.Parser.ParserD as PRD
import qualified Streamly.Internal.Data.Parser.ParserK.Type as PRK
{-# INLINE unit #-}
unit :: MonadCatch m => Parser m Word8 ()
unit :: Parser m Word8 ()
unit = Word8 -> Parser m Word8 Word8
forall (m :: * -> *). MonadCatch m => Word8 -> Parser m Word8 Word8
eqWord8 Word8
0 Parser m Word8 Word8 -> Parser m Word8 () -> Parser m Word8 ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> () -> Parser m Word8 ()
forall (m :: * -> *) b a. MonadCatch m => b -> Parser m a b
PR.fromPure ()
{-# INLINE word8ToBool #-}
word8ToBool :: Word8 -> Either String Bool
word8ToBool :: Word8 -> Either String Bool
word8ToBool Word8
0 = Bool -> Either String Bool
forall a b. b -> Either a b
Right Bool
False
word8ToBool Word8
1 = Bool -> Either String Bool
forall a b. b -> Either a b
Right Bool
True
word8ToBool Word8
w = String -> Either String Bool
forall a b. a -> Either a b
Left (String
"Invalid Bool encoding " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
Prelude.show Word8
w)
{-# INLINE bool #-}
bool :: MonadCatch m => Parser m Word8 Bool
bool :: Parser m Word8 Bool
bool = (Word8 -> Either String Bool) -> Parser m Word8 Bool
forall (m :: * -> *) a b.
MonadCatch m =>
(a -> Either String b) -> Parser m a b
PR.either Word8 -> Either String Bool
word8ToBool
{-# INLINE word8ToOrdering #-}
word8ToOrdering :: Word8 -> Either String Ordering
word8ToOrdering :: Word8 -> Either String Ordering
word8ToOrdering Word8
0 = Ordering -> Either String Ordering
forall a b. b -> Either a b
Right Ordering
LT
word8ToOrdering Word8
1 = Ordering -> Either String Ordering
forall a b. b -> Either a b
Right Ordering
EQ
word8ToOrdering Word8
2 = Ordering -> Either String Ordering
forall a b. b -> Either a b
Right Ordering
GT
word8ToOrdering Word8
w = String -> Either String Ordering
forall a b. a -> Either a b
Left (String
"Invalid Ordering encoding " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
Prelude.show Word8
w)
{-# INLINE ordering #-}
ordering :: MonadCatch m => Parser m Word8 Ordering
ordering :: Parser m Word8 Ordering
ordering = (Word8 -> Either String Ordering) -> Parser m Word8 Ordering
forall (m :: * -> *) a b.
MonadCatch m =>
(a -> Either String b) -> Parser m a b
PR.either Word8 -> Either String Ordering
word8ToOrdering
{-# INLINE eqWord8 #-}
eqWord8 :: MonadCatch m => Word8 -> Parser m Word8 Word8
eqWord8 :: Word8 -> Parser m Word8 Word8
eqWord8 Word8
b = (Word8 -> Bool) -> Parser m Word8 Word8
forall (m :: * -> *) a. MonadCatch m => (a -> Bool) -> Parser m a a
PR.satisfy (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
b)
{-# INLINE word8 #-}
word8 :: MonadCatch m => Parser m Word8 Word8
word8 :: Parser m Word8 Word8
word8 = (Word8 -> Bool) -> Parser m Word8 Word8
forall (m :: * -> *) a. MonadCatch m => (a -> Bool) -> Parser m a a
PR.satisfy (Bool -> Word8 -> Bool
forall a b. a -> b -> a
const Bool
True)
{-# INLINE word16beD #-}
word16beD :: MonadCatch m => PRD.Parser m Word8 Word16
word16beD :: Parser m Word8 Word16
word16beD = (Maybe' Word16 -> Word8 -> m (Step (Maybe' Word16) Word16))
-> m (Initial (Maybe' Word16) Word16)
-> (Maybe' Word16 -> m Word16)
-> Parser m Word8 Word16
forall (m :: * -> *) a b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m b) -> Parser m a b
PRD.Parser Maybe' Word16 -> Word8 -> m (Step (Maybe' Word16) Word16)
forall (m :: * -> *) a a b.
(Monad m, Integral a, Bits a, Bits b, Num a, Num b) =>
Maybe' b -> a -> m (Step (Maybe' a) b)
step m (Initial (Maybe' Word16) Word16)
forall a b. m (Initial (Maybe' a) b)
initial Maybe' Word16 -> m Word16
forall (m :: * -> *) p a. MonadThrow m => p -> m a
extract
where
initial :: m (Initial (Maybe' a) b)
initial = Initial (Maybe' a) b -> m (Initial (Maybe' a) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Initial (Maybe' a) b -> m (Initial (Maybe' a) b))
-> Initial (Maybe' a) b -> m (Initial (Maybe' a) b)
forall a b. (a -> b) -> a -> b
$ Maybe' a -> Initial (Maybe' a) b
forall s b. s -> Initial s b
PRD.IPartial Maybe' a
forall a. Maybe' a
Nothing'
step :: Maybe' b -> a -> m (Step (Maybe' a) b)
step Maybe' b
Nothing' a
a =
Step (Maybe' a) b -> m (Step (Maybe' a) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (Maybe' a) b -> m (Step (Maybe' a) b))
-> Step (Maybe' a) b -> m (Step (Maybe' a) b)
forall a b. (a -> b) -> a -> b
$ Int -> Maybe' a -> Step (Maybe' a) b
forall s b. Int -> s -> Step s b
PRD.Continue Int
0 (a -> Maybe' a
forall a. a -> Maybe' a
Just' (a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a a -> Int -> a
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
8))
step (Just' b
w) a
a =
Step (Maybe' a) b -> m (Step (Maybe' a) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (Maybe' a) b -> m (Step (Maybe' a) b))
-> Step (Maybe' a) b -> m (Step (Maybe' a) b)
forall a b. (a -> b) -> a -> b
$ Int -> b -> Step (Maybe' a) b
forall s b. Int -> b -> Step s b
PRD.Done Int
0 (b
w b -> b -> b
forall a. Bits a => a -> a -> a
.|. a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a)
extract :: p -> m a
extract p
_ = ParseError -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (ParseError -> m a) -> ParseError -> m a
forall a b. (a -> b) -> a -> b
$ String -> ParseError
PRD.ParseError String
"word16be: end of input"
{-# INLINE word16be #-}
word16be :: MonadCatch m => Parser m Word8 Word16
word16be :: Parser m Word8 Word16
word16be = Parser m Word8 Word16 -> Parser m Word8 Word16
forall (m :: * -> *) a b.
MonadCatch m =>
Parser m a b -> Parser m a b
PRK.toParserK Parser m Word8 Word16
forall (m :: * -> *). MonadCatch m => Parser m Word8 Word16
word16beD
{-# INLINE word16leD #-}
word16leD :: MonadCatch m => PRD.Parser m Word8 Word16
word16leD :: Parser m Word8 Word16
word16leD = (Maybe' Word16 -> Word8 -> m (Step (Maybe' Word16) Word16))
-> m (Initial (Maybe' Word16) Word16)
-> (Maybe' Word16 -> m Word16)
-> Parser m Word8 Word16
forall (m :: * -> *) a b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m b) -> Parser m a b
PRD.Parser Maybe' Word16 -> Word8 -> m (Step (Maybe' Word16) Word16)
forall (m :: * -> *) a b a.
(Monad m, Integral a, Bits b, Num a, Num b) =>
Maybe' b -> a -> m (Step (Maybe' a) b)
step m (Initial (Maybe' Word16) Word16)
forall a b. m (Initial (Maybe' a) b)
initial Maybe' Word16 -> m Word16
forall (m :: * -> *) p a. MonadThrow m => p -> m a
extract
where
initial :: m (Initial (Maybe' a) b)
initial = Initial (Maybe' a) b -> m (Initial (Maybe' a) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Initial (Maybe' a) b -> m (Initial (Maybe' a) b))
-> Initial (Maybe' a) b -> m (Initial (Maybe' a) b)
forall a b. (a -> b) -> a -> b
$ Maybe' a -> Initial (Maybe' a) b
forall s b. s -> Initial s b
PRD.IPartial Maybe' a
forall a. Maybe' a
Nothing'
step :: Maybe' b -> a -> m (Step (Maybe' a) b)
step Maybe' b
Nothing' a
a =
Step (Maybe' a) b -> m (Step (Maybe' a) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (Maybe' a) b -> m (Step (Maybe' a) b))
-> Step (Maybe' a) b -> m (Step (Maybe' a) b)
forall a b. (a -> b) -> a -> b
$ Int -> Maybe' a -> Step (Maybe' a) b
forall s b. Int -> s -> Step s b
PRD.Continue Int
0 (a -> Maybe' a
forall a. a -> Maybe' a
Just' (a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a))
step (Just' b
w) a
a =
Step (Maybe' a) b -> m (Step (Maybe' a) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (Maybe' a) b -> m (Step (Maybe' a) b))
-> Step (Maybe' a) b -> m (Step (Maybe' a) b)
forall a b. (a -> b) -> a -> b
$ Int -> b -> Step (Maybe' a) b
forall s b. Int -> b -> Step s b
PRD.Done Int
0 (b
w b -> b -> b
forall a. Bits a => a -> a -> a
.|. a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a b -> Int -> b
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
8)
extract :: p -> m a
extract p
_ = ParseError -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (ParseError -> m a) -> ParseError -> m a
forall a b. (a -> b) -> a -> b
$ String -> ParseError
PRD.ParseError String
"word16le: end of input"
{-# INLINE word16le #-}
word16le :: MonadCatch m => Parser m Word8 Word16
word16le :: Parser m Word8 Word16
word16le = Parser m Word8 Word16 -> Parser m Word8 Word16
forall (m :: * -> *) a b.
MonadCatch m =>
Parser m a b -> Parser m a b
PRK.toParserK Parser m Word8 Word16
forall (m :: * -> *). MonadCatch m => Parser m Word8 Word16
word16leD
{-# INLINE word32beD #-}
word32beD :: MonadCatch m => PRD.Parser m Word8 Word32
word32beD :: Parser m Word8 Word32
word32beD = (Tuple' Word32 Int -> Word8 -> m (Step (Tuple' Word32 Int) Word32))
-> m (Initial (Tuple' Word32 Int) Word32)
-> (Tuple' Word32 Int -> m Word32)
-> Parser m Word8 Word32
forall (m :: * -> *) a b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m b) -> Parser m a b
PRD.Parser Tuple' Word32 Int -> Word8 -> m (Step (Tuple' Word32 Int) Word32)
forall (m :: * -> *) b a.
(Monad m, Bits b, Integral a, Num b) =>
Tuple' b Int -> a -> m (Step (Tuple' b Int) b)
step m (Initial (Tuple' Word32 Int) Word32)
forall b. m (Initial (Tuple' Word32 Int) b)
initial Tuple' Word32 Int -> m Word32
forall (m :: * -> *) p a. MonadThrow m => p -> m a
extract
where
initial :: m (Initial (Tuple' Word32 Int) b)
initial = Initial (Tuple' Word32 Int) b -> m (Initial (Tuple' Word32 Int) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Initial (Tuple' Word32 Int) b
-> m (Initial (Tuple' Word32 Int) b))
-> Initial (Tuple' Word32 Int) b
-> m (Initial (Tuple' Word32 Int) b)
forall a b. (a -> b) -> a -> b
$ Tuple' Word32 Int -> Initial (Tuple' Word32 Int) b
forall s b. s -> Initial s b
PRD.IPartial (Tuple' Word32 Int -> Initial (Tuple' Word32 Int) b)
-> Tuple' Word32 Int -> Initial (Tuple' Word32 Int) b
forall a b. (a -> b) -> a -> b
$ Word32 -> Int -> Tuple' Word32 Int
forall a b. a -> b -> Tuple' a b
Tuple' Word32
0 Int
24
step :: Tuple' b Int -> a -> m (Step (Tuple' b Int) b)
step (Tuple' b
w Int
sh) a
a = Step (Tuple' b Int) b -> m (Step (Tuple' b Int) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (Tuple' b Int) b -> m (Step (Tuple' b Int) b))
-> Step (Tuple' b Int) b -> m (Step (Tuple' b Int) b)
forall a b. (a -> b) -> a -> b
$
if Int
sh Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0
then
let w1 :: b
w1 = b
w b -> b -> b
forall a. Bits a => a -> a -> a
.|. (a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a b -> Int -> b
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
sh)
in Int -> Tuple' b Int -> Step (Tuple' b Int) b
forall s b. Int -> s -> Step s b
PRD.Continue Int
0 (b -> Int -> Tuple' b Int
forall a b. a -> b -> Tuple' a b
Tuple' b
w1 (Int
sh Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
8))
else Int -> b -> Step (Tuple' b Int) b
forall s b. Int -> b -> Step s b
PRD.Done Int
0 (b
w b -> b -> b
forall a. Bits a => a -> a -> a
.|. a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a)
extract :: p -> m a
extract p
_ = ParseError -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (ParseError -> m a) -> ParseError -> m a
forall a b. (a -> b) -> a -> b
$ String -> ParseError
PRD.ParseError String
"word32beD: end of input"
{-# INLINE word32be #-}
word32be :: MonadCatch m => Parser m Word8 Word32
word32be :: Parser m Word8 Word32
word32be = Parser m Word8 Word32 -> Parser m Word8 Word32
forall (m :: * -> *) a b.
MonadCatch m =>
Parser m a b -> Parser m a b
PRK.toParserK Parser m Word8 Word32
forall (m :: * -> *). MonadCatch m => Parser m Word8 Word32
word32beD
{-# INLINE word32leD #-}
word32leD :: MonadCatch m => PRD.Parser m Word8 Word32
word32leD :: Parser m Word8 Word32
word32leD = (Tuple' Word32 Int -> Word8 -> m (Step (Tuple' Word32 Int) Word32))
-> m (Initial (Tuple' Word32 Int) Word32)
-> (Tuple' Word32 Int -> m Word32)
-> Parser m Word8 Word32
forall (m :: * -> *) a b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m b) -> Parser m a b
PRD.Parser Tuple' Word32 Int -> Word8 -> m (Step (Tuple' Word32 Int) Word32)
forall (m :: * -> *) b a.
(Monad m, Bits b, Integral a, Num b) =>
Tuple' b Int -> a -> m (Step (Tuple' b Int) b)
step m (Initial (Tuple' Word32 Int) Word32)
forall b. m (Initial (Tuple' Word32 Int) b)
initial Tuple' Word32 Int -> m Word32
forall (m :: * -> *) p a. MonadThrow m => p -> m a
extract
where
initial :: m (Initial (Tuple' Word32 Int) b)
initial = Initial (Tuple' Word32 Int) b -> m (Initial (Tuple' Word32 Int) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Initial (Tuple' Word32 Int) b
-> m (Initial (Tuple' Word32 Int) b))
-> Initial (Tuple' Word32 Int) b
-> m (Initial (Tuple' Word32 Int) b)
forall a b. (a -> b) -> a -> b
$ Tuple' Word32 Int -> Initial (Tuple' Word32 Int) b
forall s b. s -> Initial s b
PRD.IPartial (Tuple' Word32 Int -> Initial (Tuple' Word32 Int) b)
-> Tuple' Word32 Int -> Initial (Tuple' Word32 Int) b
forall a b. (a -> b) -> a -> b
$ Word32 -> Int -> Tuple' Word32 Int
forall a b. a -> b -> Tuple' a b
Tuple' Word32
0 Int
0
step :: Tuple' b Int -> a -> m (Step (Tuple' b Int) b)
step (Tuple' b
w Int
sh) a
a = Step (Tuple' b Int) b -> m (Step (Tuple' b Int) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (Tuple' b Int) b -> m (Step (Tuple' b Int) b))
-> Step (Tuple' b Int) b -> m (Step (Tuple' b Int) b)
forall a b. (a -> b) -> a -> b
$
let w1 :: b
w1 = b
w b -> b -> b
forall a. Bits a => a -> a -> a
.|. (a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a b -> Int -> b
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
sh)
in if Int
sh Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
24
then Int -> Tuple' b Int -> Step (Tuple' b Int) b
forall s b. Int -> s -> Step s b
PRD.Continue Int
0 (b -> Int -> Tuple' b Int
forall a b. a -> b -> Tuple' a b
Tuple' b
w1 (Int
sh Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
8))
else Int -> b -> Step (Tuple' b Int) b
forall s b. Int -> b -> Step s b
PRD.Done Int
0 b
w1
extract :: p -> m a
extract p
_ = ParseError -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (ParseError -> m a) -> ParseError -> m a
forall a b. (a -> b) -> a -> b
$ String -> ParseError
PRD.ParseError String
"word32leD: end of input"
{-# INLINE word32le #-}
word32le :: MonadCatch m => Parser m Word8 Word32
word32le :: Parser m Word8 Word32
word32le = Parser m Word8 Word32 -> Parser m Word8 Word32
forall (m :: * -> *) a b.
MonadCatch m =>
Parser m a b -> Parser m a b
PRK.toParserK Parser m Word8 Word32
forall (m :: * -> *). MonadCatch m => Parser m Word8 Word32
word32leD
{-# INLINE word64beD #-}
word64beD :: MonadCatch m => PRD.Parser m Word8 Word64
word64beD :: Parser m Word8 Word64
word64beD = (Tuple' Word64 Int -> Word8 -> m (Step (Tuple' Word64 Int) Word64))
-> m (Initial (Tuple' Word64 Int) Word64)
-> (Tuple' Word64 Int -> m Word64)
-> Parser m Word8 Word64
forall (m :: * -> *) a b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m b) -> Parser m a b
PRD.Parser Tuple' Word64 Int -> Word8 -> m (Step (Tuple' Word64 Int) Word64)
forall (m :: * -> *) b a.
(Monad m, Bits b, Integral a, Num b) =>
Tuple' b Int -> a -> m (Step (Tuple' b Int) b)
step m (Initial (Tuple' Word64 Int) Word64)
forall b. m (Initial (Tuple' Word64 Int) b)
initial Tuple' Word64 Int -> m Word64
forall (m :: * -> *) p a. MonadThrow m => p -> m a
extract
where
initial :: m (Initial (Tuple' Word64 Int) b)
initial = Initial (Tuple' Word64 Int) b -> m (Initial (Tuple' Word64 Int) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Initial (Tuple' Word64 Int) b
-> m (Initial (Tuple' Word64 Int) b))
-> Initial (Tuple' Word64 Int) b
-> m (Initial (Tuple' Word64 Int) b)
forall a b. (a -> b) -> a -> b
$ Tuple' Word64 Int -> Initial (Tuple' Word64 Int) b
forall s b. s -> Initial s b
PRD.IPartial (Tuple' Word64 Int -> Initial (Tuple' Word64 Int) b)
-> Tuple' Word64 Int -> Initial (Tuple' Word64 Int) b
forall a b. (a -> b) -> a -> b
$ Word64 -> Int -> Tuple' Word64 Int
forall a b. a -> b -> Tuple' a b
Tuple' Word64
0 Int
56
step :: Tuple' b Int -> a -> m (Step (Tuple' b Int) b)
step (Tuple' b
w Int
sh) a
a = Step (Tuple' b Int) b -> m (Step (Tuple' b Int) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (Tuple' b Int) b -> m (Step (Tuple' b Int) b))
-> Step (Tuple' b Int) b -> m (Step (Tuple' b Int) b)
forall a b. (a -> b) -> a -> b
$
if Int
sh Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0
then
let w1 :: b
w1 = b
w b -> b -> b
forall a. Bits a => a -> a -> a
.|. (a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a b -> Int -> b
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
sh)
in Int -> Tuple' b Int -> Step (Tuple' b Int) b
forall s b. Int -> s -> Step s b
PRD.Continue Int
0 (b -> Int -> Tuple' b Int
forall a b. a -> b -> Tuple' a b
Tuple' b
w1 (Int
sh Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
8))
else Int -> b -> Step (Tuple' b Int) b
forall s b. Int -> b -> Step s b
PRD.Done Int
0 (b
w b -> b -> b
forall a. Bits a => a -> a -> a
.|. a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a)
extract :: p -> m a
extract p
_ = ParseError -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (ParseError -> m a) -> ParseError -> m a
forall a b. (a -> b) -> a -> b
$ String -> ParseError
PRD.ParseError String
"word64beD: end of input"
{-# INLINE word64be #-}
word64be :: MonadCatch m => Parser m Word8 Word64
word64be :: Parser m Word8 Word64
word64be = Parser m Word8 Word64 -> Parser m Word8 Word64
forall (m :: * -> *) a b.
MonadCatch m =>
Parser m a b -> Parser m a b
PRK.toParserK Parser m Word8 Word64
forall (m :: * -> *). MonadCatch m => Parser m Word8 Word64
word64beD
{-# INLINE word64leD #-}
word64leD :: MonadCatch m => PRD.Parser m Word8 Word64
word64leD :: Parser m Word8 Word64
word64leD = (Tuple' Word64 Int -> Word8 -> m (Step (Tuple' Word64 Int) Word64))
-> m (Initial (Tuple' Word64 Int) Word64)
-> (Tuple' Word64 Int -> m Word64)
-> Parser m Word8 Word64
forall (m :: * -> *) a b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m b) -> Parser m a b
PRD.Parser Tuple' Word64 Int -> Word8 -> m (Step (Tuple' Word64 Int) Word64)
forall (m :: * -> *) b a.
(Monad m, Bits b, Integral a, Num b) =>
Tuple' b Int -> a -> m (Step (Tuple' b Int) b)
step m (Initial (Tuple' Word64 Int) Word64)
forall b. m (Initial (Tuple' Word64 Int) b)
initial Tuple' Word64 Int -> m Word64
forall (m :: * -> *) p a. MonadThrow m => p -> m a
extract
where
initial :: m (Initial (Tuple' Word64 Int) b)
initial = Initial (Tuple' Word64 Int) b -> m (Initial (Tuple' Word64 Int) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Initial (Tuple' Word64 Int) b
-> m (Initial (Tuple' Word64 Int) b))
-> Initial (Tuple' Word64 Int) b
-> m (Initial (Tuple' Word64 Int) b)
forall a b. (a -> b) -> a -> b
$ Tuple' Word64 Int -> Initial (Tuple' Word64 Int) b
forall s b. s -> Initial s b
PRD.IPartial (Tuple' Word64 Int -> Initial (Tuple' Word64 Int) b)
-> Tuple' Word64 Int -> Initial (Tuple' Word64 Int) b
forall a b. (a -> b) -> a -> b
$ Word64 -> Int -> Tuple' Word64 Int
forall a b. a -> b -> Tuple' a b
Tuple' Word64
0 Int
0
step :: Tuple' b Int -> a -> m (Step (Tuple' b Int) b)
step (Tuple' b
w Int
sh) a
a = Step (Tuple' b Int) b -> m (Step (Tuple' b Int) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Step (Tuple' b Int) b -> m (Step (Tuple' b Int) b))
-> Step (Tuple' b Int) b -> m (Step (Tuple' b Int) b)
forall a b. (a -> b) -> a -> b
$
let w1 :: b
w1 = b
w b -> b -> b
forall a. Bits a => a -> a -> a
.|. (a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a b -> Int -> b
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
sh)
in if Int
sh Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
56
then Int -> Tuple' b Int -> Step (Tuple' b Int) b
forall s b. Int -> s -> Step s b
PRD.Continue Int
0 (b -> Int -> Tuple' b Int
forall a b. a -> b -> Tuple' a b
Tuple' b
w1 (Int
sh Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
8))
else Int -> b -> Step (Tuple' b Int) b
forall s b. Int -> b -> Step s b
PRD.Done Int
0 b
w1
extract :: p -> m a
extract p
_ = ParseError -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (ParseError -> m a) -> ParseError -> m a
forall a b. (a -> b) -> a -> b
$ String -> ParseError
PRD.ParseError String
"word64leD: end of input"
{-# INLINE word64le #-}
word64le :: MonadCatch m => Parser m Word8 Word64
word64le :: Parser m Word8 Word64
word64le = Parser m Word8 Word64 -> Parser m Word8 Word64
forall (m :: * -> *) a b.
MonadCatch m =>
Parser m a b -> Parser m a b
PRK.toParserK Parser m Word8 Word64
forall (m :: * -> *). MonadCatch m => Parser m Word8 Word64
word64leD
{-# INLINE word64host #-}
word64host :: (MonadIO m, MonadCatch m) => Parser m Word8 Word64
word64host :: Parser m Word8 Word64
word64host =
(Array Word8 -> Word64)
-> Parser m Word8 (Array Word8) -> Parser m Word8 Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Array Word64 -> Int -> Word64) -> Int -> Array Word64 -> Word64
forall a b c. (a -> b -> c) -> b -> a -> c
flip Array Word64 -> Int -> Word64
forall a. Storable a => Array a -> Int -> a
A.unsafeIndex Int
0 (Array Word64 -> Word64)
-> (Array Word8 -> Array Word64) -> Array Word8 -> Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Word8 -> Array Word64
forall a b. Array a -> Array b
A.unsafeCast) (Parser m Word8 (Array Word8) -> Parser m Word8 Word64)
-> Parser m Word8 (Array Word8) -> Parser m Word8 Word64
forall a b. (a -> b) -> a -> b
$ Int -> Fold m Word8 (Array Word8) -> Parser m Word8 (Array Word8)
forall (m :: * -> *) a b.
MonadCatch m =>
Int -> Fold m a b -> Parser m a b
PR.takeEQ Int
8 (Int -> Fold m Word8 (Array Word8)
forall (m :: * -> *) a.
(MonadIO m, Storable a) =>
Int -> Fold m a (Array a)
A.writeN Int
8)