module Streamly.Internal.Serialize.FromBytes
(
FromBytes (..)
, unit
, bool
, ordering
, eqWord8
, word8
, word16be
, word16le
, word32be
, word32le
, word64be
, word64le
, word64host
, int8
, int16be
, int16le
, int32be
, int32le
, int64be
, int64le
, float32be
, float32le
, double64be
, double64le
, charLatin1
)
where
import Control.Monad.IO.Class (MonadIO)
import Data.Bits ((.|.), unsafeShiftL)
import Data.Char (chr)
import Data.Int (Int8, Int16, Int32, Int64)
import GHC.Float (castWord32ToFloat, castWord64ToDouble)
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.Data.Array as A
import qualified Streamly.Internal.Data.Array as A
(unsafeIndex, castUnsafe)
import qualified Streamly.Internal.Data.Parser as PR
(fromPure, either, satisfy, takeEQ)
import qualified Streamly.Internal.Data.Parser.ParserD as PRD
(Parser(..), Initial(..), Step(..))
{-# INLINE unit #-}
unit :: Monad m => Parser Word8 m ()
unit :: forall (m :: * -> *). Monad m => Parser Word8 m ()
unit = forall (m :: * -> *). Monad m => Word8 -> Parser Word8 m Word8
eqWord8 Word8
0 forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall (m :: * -> *) b a. Monad m => b -> Parser a m b
PR.fromPure ()
{-# INLINE word8ToBool #-}
word8ToBool :: Word8 -> Either String Bool
word8ToBool :: Word8 -> Either String Bool
word8ToBool Word8
0 = forall a b. b -> Either a b
Right Bool
False
word8ToBool Word8
1 = forall a b. b -> Either a b
Right Bool
True
word8ToBool Word8
w = forall a b. a -> Either a b
Left (String
"Invalid Bool encoding " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
Prelude.show Word8
w)
{-# INLINE bool #-}
bool :: Monad m => Parser Word8 m Bool
bool :: forall (m :: * -> *). Monad m => Parser Word8 m Bool
bool = forall (m :: * -> *) a b.
Monad m =>
(a -> Either String b) -> Parser a m b
PR.either Word8 -> Either String Bool
word8ToBool
{-# INLINE word8ToOrdering #-}
word8ToOrdering :: Word8 -> Either String Ordering
word8ToOrdering :: Word8 -> Either String Ordering
word8ToOrdering Word8
0 = forall a b. b -> Either a b
Right Ordering
LT
word8ToOrdering Word8
1 = forall a b. b -> Either a b
Right Ordering
EQ
word8ToOrdering Word8
2 = forall a b. b -> Either a b
Right Ordering
GT
word8ToOrdering Word8
w = forall a b. a -> Either a b
Left (String
"Invalid Ordering encoding " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
Prelude.show Word8
w)
{-# INLINE ordering #-}
ordering :: Monad m => Parser Word8 m Ordering
ordering :: forall (m :: * -> *). Monad m => Parser Word8 m Ordering
ordering = forall (m :: * -> *) a b.
Monad m =>
(a -> Either String b) -> Parser a m b
PR.either Word8 -> Either String Ordering
word8ToOrdering
{-# INLINE eqWord8 #-}
eqWord8 :: Monad m => Word8 -> Parser Word8 m Word8
eqWord8 :: forall (m :: * -> *). Monad m => Word8 -> Parser Word8 m Word8
eqWord8 Word8
b = forall (m :: * -> *) a. Monad m => (a -> Bool) -> Parser a m a
PR.satisfy (forall a. Eq a => a -> a -> Bool
== Word8
b)
{-# INLINE word8 #-}
word8 :: Monad m => Parser Word8 m Word8
word8 :: forall (m :: * -> *). Monad m => Parser Word8 m Word8
word8 = forall (m :: * -> *) a. Monad m => (a -> Bool) -> Parser a m a
PR.satisfy (forall a b. a -> b -> a
const Bool
True)
{-# INLINE word16beD #-}
word16beD :: Monad m => PRD.Parser Word8 m Word16
word16beD :: forall (m :: * -> *). Monad m => Parser Word8 m Word16
word16beD = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
PRD.Parser 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 forall {a} {b}. m (Initial (Maybe' a) b)
initial forall {m :: * -> *} {p} {s} {b}. Monad m => p -> m (Step s b)
extract
where
initial :: m (Initial (Maybe' a) b)
initial = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
PRD.IPartial forall a. Maybe' a
Nothing'
step :: Maybe' b -> a -> m (Step (Maybe' a) b)
step Maybe' b
Nothing' a
a =
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
PRD.Continue Int
0 (forall a. a -> Maybe' a
Just' (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
8))
step (Just' b
w) a
a =
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
PRD.Done Int
0 (b
w forall a. Bits a => a -> a -> a
.|. forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a)
extract :: p -> m (Step s b)
extract p
_ = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
PRD.Error String
"word16be: end of input"
{-# INLINE word16be #-}
word16be :: Monad m => Parser Word8 m Word16
word16be :: forall (m :: * -> *). Monad m => Parser Word8 m Word16
word16be = forall (m :: * -> *). Monad m => Parser Word8 m Word16
word16beD
{-# INLINE word16leD #-}
word16leD :: Monad m => PRD.Parser Word8 m Word16
word16leD :: forall (m :: * -> *). Monad m => Parser Word8 m Word16
word16leD = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
PRD.Parser forall {m :: * -> *} {a} {b} {a}.
(Monad m, Integral a, Bits b, Num a, Num b) =>
Maybe' b -> a -> m (Step (Maybe' a) b)
step forall {a} {b}. m (Initial (Maybe' a) b)
initial forall {m :: * -> *} {p} {s} {b}. Monad m => p -> m (Step s b)
extract
where
initial :: m (Initial (Maybe' a) b)
initial = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
PRD.IPartial forall a. Maybe' a
Nothing'
step :: Maybe' b -> a -> m (Step (Maybe' a) b)
step Maybe' b
Nothing' a
a =
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
PRD.Continue Int
0 (forall a. a -> Maybe' a
Just' (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a))
step (Just' b
w) a
a =
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
PRD.Done Int
0 (b
w forall a. Bits a => a -> a -> a
.|. forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
8)
extract :: p -> m (Step s b)
extract p
_ = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
PRD.Error String
"word16le: end of input"
{-# INLINE word16le #-}
word16le :: Monad m => Parser Word8 m Word16
word16le :: forall (m :: * -> *). Monad m => Parser Word8 m Word16
word16le = forall (m :: * -> *). Monad m => Parser Word8 m Word16
word16leD
{-# INLINE word32beD #-}
word32beD :: Monad m => PRD.Parser Word8 m Word32
word32beD :: forall (m :: * -> *). Monad m => Parser Word8 m Word32
word32beD = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
PRD.Parser forall {m :: * -> *} {b} {a}.
(Monad m, Bits b, Integral a, Num b) =>
Tuple' b Int -> a -> m (Step (Tuple' b Int) b)
step forall {b}. m (Initial (Tuple' Word32 Int) b)
initial forall {m :: * -> *} {p} {s} {b}. Monad m => p -> m (Step s b)
extract
where
initial :: m (Initial (Tuple' Word32 Int) b)
initial = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
PRD.IPartial forall a b. (a -> b) -> a -> b
$ 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 = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
if Int
sh forall a. Eq a => a -> a -> Bool
/= Int
0
then
let w1 :: b
w1 = b
w forall a. Bits a => a -> a -> a
.|. (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
sh)
in forall s b. Int -> s -> Step s b
PRD.Continue Int
0 (forall a b. a -> b -> Tuple' a b
Tuple' b
w1 (Int
sh forall a. Num a => a -> a -> a
- Int
8))
else forall s b. Int -> b -> Step s b
PRD.Done Int
0 (b
w forall a. Bits a => a -> a -> a
.|. forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a)
extract :: p -> m (Step s b)
extract p
_ = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
PRD.Error String
"word32beD: end of input"
{-# INLINE word32be #-}
word32be :: Monad m => Parser Word8 m Word32
word32be :: forall (m :: * -> *). Monad m => Parser Word8 m Word32
word32be = forall (m :: * -> *). Monad m => Parser Word8 m Word32
word32beD
{-# INLINE word32leD #-}
word32leD :: Monad m => PRD.Parser Word8 m Word32
word32leD :: forall (m :: * -> *). Monad m => Parser Word8 m Word32
word32leD = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
PRD.Parser forall {m :: * -> *} {b} {a}.
(Monad m, Bits b, Integral a, Num b) =>
Tuple' b Int -> a -> m (Step (Tuple' b Int) b)
step forall {b}. m (Initial (Tuple' Word32 Int) b)
initial forall {m :: * -> *} {p} {s} {b}. Monad m => p -> m (Step s b)
extract
where
initial :: m (Initial (Tuple' Word32 Int) b)
initial = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
PRD.IPartial forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> Tuple' a b
Tuple' Word32
0 Int
0
step :: Tuple' b Int -> p -> m (Step (Tuple' b Int) b)
step (Tuple' b
w Int
sh) p
a = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
let w1 :: b
w1 = b
w forall a. Bits a => a -> a -> a
.|. (forall a b. (Integral a, Num b) => a -> b
fromIntegral p
a forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
sh)
in if Int
sh forall a. Eq a => a -> a -> Bool
/= Int
24
then forall s b. Int -> s -> Step s b
PRD.Continue Int
0 (forall a b. a -> b -> Tuple' a b
Tuple' b
w1 (Int
sh forall a. Num a => a -> a -> a
+ Int
8))
else forall s b. Int -> b -> Step s b
PRD.Done Int
0 b
w1
extract :: p -> m (Step s b)
extract p
_ = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
PRD.Error String
"word32leD: end of input"
{-# INLINE word32le #-}
word32le :: Monad m => Parser Word8 m Word32
word32le :: forall (m :: * -> *). Monad m => Parser Word8 m Word32
word32le = forall (m :: * -> *). Monad m => Parser Word8 m Word32
word32leD
{-# INLINE word64beD #-}
word64beD :: Monad m => PRD.Parser Word8 m Word64
word64beD :: forall (m :: * -> *). Monad m => Parser Word8 m Word64
word64beD = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
PRD.Parser forall {m :: * -> *} {b} {a}.
(Monad m, Bits b, Integral a, Num b) =>
Tuple' b Int -> a -> m (Step (Tuple' b Int) b)
step forall {b}. m (Initial (Tuple' Word64 Int) b)
initial forall {m :: * -> *} {p} {s} {b}. Monad m => p -> m (Step s b)
extract
where
initial :: m (Initial (Tuple' Word64 Int) b)
initial = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
PRD.IPartial forall a b. (a -> b) -> a -> b
$ 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 = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
if Int
sh forall a. Eq a => a -> a -> Bool
/= Int
0
then
let w1 :: b
w1 = b
w forall a. Bits a => a -> a -> a
.|. (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
sh)
in forall s b. Int -> s -> Step s b
PRD.Continue Int
0 (forall a b. a -> b -> Tuple' a b
Tuple' b
w1 (Int
sh forall a. Num a => a -> a -> a
- Int
8))
else forall s b. Int -> b -> Step s b
PRD.Done Int
0 (b
w forall a. Bits a => a -> a -> a
.|. forall a b. (Integral a, Num b) => a -> b
fromIntegral a
a)
extract :: p -> m (Step s b)
extract p
_ = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
PRD.Error String
"word64beD: end of input"
{-# INLINE word64be #-}
word64be :: Monad m => Parser Word8 m Word64
word64be :: forall (m :: * -> *). Monad m => Parser Word8 m Word64
word64be = forall (m :: * -> *). Monad m => Parser Word8 m Word64
word64beD
{-# INLINE word64leD #-}
word64leD :: Monad m => PRD.Parser Word8 m Word64
word64leD :: forall (m :: * -> *). Monad m => Parser Word8 m Word64
word64leD = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
PRD.Parser forall {m :: * -> *} {b} {a}.
(Monad m, Bits b, Integral a, Num b) =>
Tuple' b Int -> a -> m (Step (Tuple' b Int) b)
step forall {b}. m (Initial (Tuple' Word64 Int) b)
initial forall {m :: * -> *} {p} {s} {b}. Monad m => p -> m (Step s b)
extract
where
initial :: m (Initial (Tuple' Word64 Int) b)
initial = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
PRD.IPartial forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> Tuple' a b
Tuple' Word64
0 Int
0
step :: Tuple' b Int -> p -> m (Step (Tuple' b Int) b)
step (Tuple' b
w Int
sh) p
a = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
let w1 :: b
w1 = b
w forall a. Bits a => a -> a -> a
.|. (forall a b. (Integral a, Num b) => a -> b
fromIntegral p
a forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
sh)
in if Int
sh forall a. Eq a => a -> a -> Bool
/= Int
56
then forall s b. Int -> s -> Step s b
PRD.Continue Int
0 (forall a b. a -> b -> Tuple' a b
Tuple' b
w1 (Int
sh forall a. Num a => a -> a -> a
+ Int
8))
else forall s b. Int -> b -> Step s b
PRD.Done Int
0 b
w1
extract :: p -> m (Step s b)
extract p
_ = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
PRD.Error String
"word64leD: end of input"
{-# INLINE word64le #-}
word64le :: Monad m => Parser Word8 m Word64
word64le :: forall (m :: * -> *). Monad m => Parser Word8 m Word64
word64le = forall (m :: * -> *). Monad m => Parser Word8 m Word64
word64leD
{-# INLINE int8 #-}
int8 :: Monad m => Parser Word8 m Int8
int8 :: forall (m :: * -> *). Monad m => Parser Word8 m Int8
int8 = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). Monad m => Parser Word8 m Word8
word8
{-# INLINE int16be #-}
int16be :: Monad m => Parser Word8 m Int16
int16be :: forall (m :: * -> *). Monad m => Parser Word8 m Int16
int16be = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). Monad m => Parser Word8 m Word16
word16be
{-# INLINE int16le #-}
int16le :: Monad m => Parser Word8 m Int16
int16le :: forall (m :: * -> *). Monad m => Parser Word8 m Int16
int16le = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). Monad m => Parser Word8 m Word16
word16le
{-# INLINE int32be #-}
int32be :: Monad m => Parser Word8 m Int32
int32be :: forall (m :: * -> *). Monad m => Parser Word8 m Int32
int32be = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). Monad m => Parser Word8 m Word32
word32be
{-# INLINE int32le #-}
int32le :: Monad m => Parser Word8 m Int32
int32le :: forall (m :: * -> *). Monad m => Parser Word8 m Int32
int32le = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). Monad m => Parser Word8 m Word32
word32le
{-# INLINE int64be #-}
int64be :: Monad m => Parser Word8 m Int64
int64be :: forall (m :: * -> *). Monad m => Parser Word8 m Int64
int64be = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). Monad m => Parser Word8 m Word64
word64be
{-# INLINE int64le #-}
int64le :: Monad m => Parser Word8 m Int64
int64le :: forall (m :: * -> *). Monad m => Parser Word8 m Int64
int64le = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). Monad m => Parser Word8 m Word64
word64le
{-# INLINE float32be #-}
float32be :: MonadIO m => Parser Word8 m Float
float32be :: forall (m :: * -> *). MonadIO m => Parser Word8 m Float
float32be = Word32 -> Float
castWord32ToFloat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). Monad m => Parser Word8 m Word32
word32be
{-# INLINE float32le #-}
float32le :: MonadIO m => Parser Word8 m Float
float32le :: forall (m :: * -> *). MonadIO m => Parser Word8 m Float
float32le = Word32 -> Float
castWord32ToFloat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). Monad m => Parser Word8 m Word32
word32le
{-# INLINE double64be #-}
double64be :: MonadIO m => Parser Word8 m Double
double64be :: forall (m :: * -> *). MonadIO m => Parser Word8 m Double
double64be = Word64 -> Double
castWord64ToDouble forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). Monad m => Parser Word8 m Word64
word64be
{-# INLINE double64le #-}
double64le :: MonadIO m => Parser Word8 m Double
double64le :: forall (m :: * -> *). MonadIO m => Parser Word8 m Double
double64le = Word64 -> Double
castWord64ToDouble forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). Monad m => Parser Word8 m Word64
word64le
{-# INLINE charLatin1 #-}
charLatin1 :: Monad m => Parser Word8 m Char
charLatin1 :: forall (m :: * -> *). Monad m => Parser Word8 m Char
charLatin1 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> Char
chr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral) forall (m :: * -> *). Monad m => Parser Word8 m Word8
word8
{-# INLINE word64host #-}
word64host :: MonadIO m => Parser Word8 m Word64
word64host :: forall (m :: * -> *). MonadIO m => Parser Word8 m Word64
word64host =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Unbox a => Int -> Array a -> a
A.unsafeIndex Int
0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Array a -> Array b
A.castUnsafe) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
Int -> Fold m a b -> Parser a m b
PR.takeEQ Int
8 (forall (m :: * -> *) a.
(MonadIO m, Unbox a) =>
Int -> Fold m a (Array a)
A.writeN Int
8)
class FromBytes a where
fromBytes :: Parser Word8 m a