{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UndecidableInstances #-}
module Streamly.Internal.Data.Unboxed
( Unbox(..)
, peekWith
, pokeWith
, MutableByteArray(..)
, touch
, getMutableByteArray#
, pin
, unpin
, newUnpinnedBytes
, newPinnedBytes
, newAlignedPinnedBytes
, nil
, BoundedPtr (..)
, Peeker (..)
, read
, readUnsafe
, skipByte
, runPeeker
, pokeBoundedPtrUnsafe
, pokeBoundedPtr
, genericSizeOf
, genericPeekByteIndex
, genericPokeByteIndex
, PeekRep(..)
, PokeRep(..)
, SizeOfRep(..)
) where
#include "MachDeps.h"
#include "ArrayMacros.h"
import Control.Monad (void, when)
import Data.Complex (Complex((:+)))
import Data.Functor ((<&>))
import Data.Functor.Const (Const(..))
import Data.Functor.Identity (Identity(..))
import Data.Kind (Type)
import Data.Proxy (Proxy (..))
import Foreign.Ptr (IntPtr(..), WordPtr(..))
import GHC.Base (IO(..))
import GHC.Fingerprint.Type (Fingerprint(..))
import GHC.Int (Int16(..), Int32(..), Int64(..), Int8(..))
import GHC.Real (Ratio(..))
import GHC.Stable (StablePtr(..))
import GHC.Word (Word16(..), Word32(..), Word64(..), Word8(..))
#if MIN_VERSION_base(4,15,0)
import GHC.RTS.Flags (IoSubSystem(..))
#endif
import Streamly.Internal.Data.Builder (Builder (..))
import System.IO.Unsafe (unsafePerformIO)
import GHC.Generics
import GHC.Exts
import GHC.TypeLits
import Prelude hiding (read)
data MutableByteArray = MutableByteArray (MutableByteArray# RealWorld)
{-# INLINE getMutableByteArray# #-}
getMutableByteArray# :: MutableByteArray -> MutableByteArray# RealWorld
getMutableByteArray# :: MutableByteArray -> MutableByteArray# RealWorld
getMutableByteArray# (MutableByteArray MutableByteArray# RealWorld
mbarr) = MutableByteArray# RealWorld
mbarr
{-# INLINE touch #-}
touch :: MutableByteArray -> IO ()
touch :: MutableByteArray -> IO ()
touch (MutableByteArray MutableByteArray# RealWorld
contents) =
(State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, () #)) -> IO ())
-> (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s -> case MutableByteArray# RealWorld -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch# MutableByteArray# RealWorld
contents State# RealWorld
s of State# RealWorld
s' -> (# State# RealWorld
s', () #)
{-# INLINE sizeOfMutableByteArray #-}
sizeOfMutableByteArray :: MutableByteArray -> IO Int
sizeOfMutableByteArray :: MutableByteArray -> IO Int
sizeOfMutableByteArray (MutableByteArray MutableByteArray# RealWorld
arr) =
(State# RealWorld -> (# State# RealWorld, Int #)) -> IO Int
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, Int #)) -> IO Int)
-> (State# RealWorld -> (# State# RealWorld, Int #)) -> IO Int
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->
case MutableByteArray# RealWorld
-> State# RealWorld -> (# State# RealWorld, Int# #)
forall d. MutableByteArray# d -> State# d -> (# State# d, Int# #)
getSizeofMutableByteArray# MutableByteArray# RealWorld
arr State# RealWorld
s of
(# State# RealWorld
s1, Int#
i #) -> (# State# RealWorld
s1, Int# -> Int
I# Int#
i #)
{-# NOINLINE nil #-}
nil :: MutableByteArray
nil :: MutableByteArray
nil = IO MutableByteArray -> MutableByteArray
forall a. IO a -> a
unsafePerformIO (IO MutableByteArray -> MutableByteArray)
-> IO MutableByteArray -> MutableByteArray
forall a b. (a -> b) -> a -> b
$ Int -> IO MutableByteArray
newUnpinnedBytes Int
0
{-# INLINE newUnpinnedBytes #-}
newUnpinnedBytes :: Int -> IO MutableByteArray
newUnpinnedBytes :: Int -> IO MutableByteArray
newUnpinnedBytes Int
nbytes | Int
nbytes Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
[Char] -> IO MutableByteArray
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"newUnpinnedBytes: size must be >= 0"
newUnpinnedBytes (I# Int#
nbytes) = (State# RealWorld -> (# State# RealWorld, MutableByteArray #))
-> IO MutableByteArray
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, MutableByteArray #))
-> IO MutableByteArray)
-> (State# RealWorld -> (# State# RealWorld, MutableByteArray #))
-> IO MutableByteArray
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->
case Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray# Int#
nbytes State# RealWorld
s of
(# State# RealWorld
s', MutableByteArray# RealWorld
mbarr# #) ->
let c :: MutableByteArray
c = MutableByteArray# RealWorld -> MutableByteArray
MutableByteArray MutableByteArray# RealWorld
mbarr#
in (# State# RealWorld
s', MutableByteArray
c #)
{-# INLINE newPinnedBytes #-}
newPinnedBytes :: Int -> IO MutableByteArray
newPinnedBytes :: Int -> IO MutableByteArray
newPinnedBytes Int
nbytes | Int
nbytes Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
[Char] -> IO MutableByteArray
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"newPinnedBytes: size must be >= 0"
newPinnedBytes (I# Int#
nbytes) = (State# RealWorld -> (# State# RealWorld, MutableByteArray #))
-> IO MutableByteArray
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, MutableByteArray #))
-> IO MutableByteArray)
-> (State# RealWorld -> (# State# RealWorld, MutableByteArray #))
-> IO MutableByteArray
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->
case Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newPinnedByteArray# Int#
nbytes State# RealWorld
s of
(# State# RealWorld
s', MutableByteArray# RealWorld
mbarr# #) ->
let c :: MutableByteArray
c = MutableByteArray# RealWorld -> MutableByteArray
MutableByteArray MutableByteArray# RealWorld
mbarr#
in (# State# RealWorld
s', MutableByteArray
c #)
{-# INLINE newAlignedPinnedBytes #-}
newAlignedPinnedBytes :: Int -> Int -> IO MutableByteArray
newAlignedPinnedBytes :: Int -> Int -> IO MutableByteArray
newAlignedPinnedBytes Int
nbytes Int
_align | Int
nbytes Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
[Char] -> IO MutableByteArray
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"newAlignedPinnedBytes: size must be >= 0"
newAlignedPinnedBytes (I# Int#
nbytes) (I# Int#
align) = (State# RealWorld -> (# State# RealWorld, MutableByteArray #))
-> IO MutableByteArray
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, MutableByteArray #))
-> IO MutableByteArray)
-> (State# RealWorld -> (# State# RealWorld, MutableByteArray #))
-> IO MutableByteArray
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->
case Int#
-> Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
forall d.
Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
newAlignedPinnedByteArray# Int#
nbytes Int#
align State# RealWorld
s of
(# State# RealWorld
s', MutableByteArray# RealWorld
mbarr# #) ->
let c :: MutableByteArray
c = MutableByteArray# RealWorld -> MutableByteArray
MutableByteArray MutableByteArray# RealWorld
mbarr#
in (# State# RealWorld
s', MutableByteArray
c #)
{-# INLINE isPinned #-}
isPinned :: MutableByteArray -> Bool
isPinned :: MutableByteArray -> Bool
isPinned (MutableByteArray MutableByteArray# RealWorld
arr#) =
let pinnedInt :: Int
pinnedInt = Int# -> Int
I# (MutableByteArray# RealWorld -> Int#
forall d. MutableByteArray# d -> Int#
isMutableByteArrayPinned# MutableByteArray# RealWorld
arr#)
in Int
pinnedInt Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1
{-# INLINE cloneMutableArrayWith# #-}
cloneMutableArrayWith#
:: (Int# -> State# RealWorld -> (# State# RealWorld
, MutableByteArray# RealWorld #))
-> MutableByteArray# RealWorld
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
cloneMutableArrayWith# :: (Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #))
-> MutableByteArray# RealWorld
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
cloneMutableArrayWith# Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
alloc# MutableByteArray# RealWorld
arr# State# RealWorld
s# =
case MutableByteArray# RealWorld
-> State# RealWorld -> (# State# RealWorld, Int# #)
forall d. MutableByteArray# d -> State# d -> (# State# d, Int# #)
getSizeofMutableByteArray# MutableByteArray# RealWorld
arr# State# RealWorld
s# of
(# State# RealWorld
s1#, Int#
i# #) ->
case Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
alloc# Int#
i# State# RealWorld
s1# of
(# State# RealWorld
s2#, MutableByteArray# RealWorld
arr1# #) ->
case MutableByteArray# RealWorld
-> Int#
-> MutableByteArray# RealWorld
-> Int#
-> Int#
-> State# RealWorld
-> State# RealWorld
forall d.
MutableByteArray# d
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
copyMutableByteArray# MutableByteArray# RealWorld
arr# Int#
0# MutableByteArray# RealWorld
arr1# Int#
0# Int#
i# State# RealWorld
s2# of
State# RealWorld
s3# -> (# State# RealWorld
s3#, MutableByteArray# RealWorld
arr1# #)
{-# INLINE pin #-}
pin :: MutableByteArray -> IO MutableByteArray
pin :: MutableByteArray -> IO MutableByteArray
pin arr :: MutableByteArray
arr@(MutableByteArray MutableByteArray# RealWorld
marr#) =
if MutableByteArray -> Bool
isPinned MutableByteArray
arr
then MutableByteArray -> IO MutableByteArray
forall (m :: * -> *) a. Monad m => a -> m a
return MutableByteArray
arr
else (State# RealWorld -> (# State# RealWorld, MutableByteArray #))
-> IO MutableByteArray
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO
((State# RealWorld -> (# State# RealWorld, MutableByteArray #))
-> IO MutableByteArray)
-> (State# RealWorld -> (# State# RealWorld, MutableByteArray #))
-> IO MutableByteArray
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s# ->
case (Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #))
-> MutableByteArray# RealWorld
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
cloneMutableArrayWith# Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newPinnedByteArray# MutableByteArray# RealWorld
marr# State# RealWorld
s# of
(# State# RealWorld
s1#, MutableByteArray# RealWorld
marr1# #) -> (# State# RealWorld
s1#, MutableByteArray# RealWorld -> MutableByteArray
MutableByteArray MutableByteArray# RealWorld
marr1# #)
{-# INLINE unpin #-}
unpin :: MutableByteArray -> IO MutableByteArray
unpin :: MutableByteArray -> IO MutableByteArray
unpin arr :: MutableByteArray
arr@(MutableByteArray MutableByteArray# RealWorld
marr#) =
if Bool -> Bool
not (MutableByteArray -> Bool
isPinned MutableByteArray
arr)
then MutableByteArray -> IO MutableByteArray
forall (m :: * -> *) a. Monad m => a -> m a
return MutableByteArray
arr
else (State# RealWorld -> (# State# RealWorld, MutableByteArray #))
-> IO MutableByteArray
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO
((State# RealWorld -> (# State# RealWorld, MutableByteArray #))
-> IO MutableByteArray)
-> (State# RealWorld -> (# State# RealWorld, MutableByteArray #))
-> IO MutableByteArray
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s# ->
case (Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #))
-> MutableByteArray# RealWorld
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
cloneMutableArrayWith# Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray# MutableByteArray# RealWorld
marr# State# RealWorld
s# of
(# State# RealWorld
s1#, MutableByteArray# RealWorld
marr1# #) -> (# State# RealWorld
s1#, MutableByteArray# RealWorld -> MutableByteArray
MutableByteArray MutableByteArray# RealWorld
marr1# #)
class Unbox a where
sizeOf :: Proxy a -> Int
default sizeOf :: (SizeOfRep (Rep a)) => Proxy a -> Int
sizeOf = Proxy a -> Int
forall a. SizeOfRep (Rep a) => Proxy a -> Int
genericSizeOf
peekByteIndex :: Int -> MutableByteArray -> IO a
default peekByteIndex :: (Generic a, PeekRep (Rep a)) =>
Int -> MutableByteArray -> IO a
peekByteIndex Int
i MutableByteArray
arr = MutableByteArray -> Int -> IO a
forall a.
(Generic a, PeekRep (Rep a)) =>
MutableByteArray -> Int -> IO a
genericPeekByteIndex MutableByteArray
arr Int
i
pokeByteIndex :: Int -> MutableByteArray -> a -> IO ()
default pokeByteIndex :: (Generic a, PokeRep (Rep a)) =>
Int -> MutableByteArray -> a -> IO ()
pokeByteIndex Int
i MutableByteArray
arr = MutableByteArray -> Int -> a -> IO ()
forall a.
(Generic a, PokeRep (Rep a)) =>
MutableByteArray -> Int -> a -> IO ()
genericPokeByteIndex MutableByteArray
arr Int
i
#define DERIVE_UNBOXED(_type, _constructor, _readArray, _writeArray, _sizeOf) \
instance Unbox _type where { \
; {-# INLINE peekByteIndex #-} \
; peekByteIndex (I# n) (MutableByteArray mbarr) = IO $ \s -> \
case _readArray mbarr n s of \
{ (# s1, i #) -> (# s1, _constructor i #) } \
; {-# INLINE pokeByteIndex #-} \
; pokeByteIndex (I# n) (MutableByteArray mbarr) (_constructor val) = \
IO $ \s -> (# _writeArray mbarr n val s, () #) \
; {-# INLINE sizeOf #-} \
; sizeOf _ = _sizeOf \
}
#define DERIVE_WRAPPED_UNBOX(_constraint, _type, _constructor, _innerType) \
instance _constraint Unbox _type where \
; {-# INLINE peekByteIndex #-} \
; peekByteIndex i arr = _constructor <$> peekByteIndex i arr \
; {-# INLINE pokeByteIndex #-} \
; pokeByteIndex i arr (_constructor a) = pokeByteIndex i arr a \
; {-# INLINE sizeOf #-} \
; sizeOf _ = SIZE_OF(_innerType)
#define DERIVE_BINARY_UNBOX(_constraint, _type, _constructor, _innerType) \
instance _constraint Unbox _type where { \
; {-# INLINE peekByteIndex #-} \
; peekByteIndex i arr = \
peekByteIndex i arr >>= \
(\p1 -> peekByteIndex (i + SIZE_OF(_innerType)) arr \
<&> _constructor p1) \
; {-# INLINE pokeByteIndex #-} \
; pokeByteIndex i arr (_constructor p1 p2) = \
pokeByteIndex i arr p1 >> \
pokeByteIndex (i + SIZE_OF(_innerType)) arr p2 \
; {-# INLINE sizeOf #-} \
; sizeOf _ = 2 * SIZE_OF(_innerType) \
}
DERIVE_UNBOXED( Char
, C#
, readWord8ArrayAsWideChar#
, writeWord8ArrayAsWideChar#
, SIZEOF_HSCHAR)
DERIVE_UNBOXED( Int8
, I8#
, readInt8Array#
, writeInt8Array#
, 1)
DERIVE_UNBOXED( Int16
, I16#
, readWord8ArrayAsInt16#
, writeWord8ArrayAsInt16#
, 2)
DERIVE_UNBOXED( Int32
, I32#
, readWord8ArrayAsInt32#
, writeWord8ArrayAsInt32#
, 4)
DERIVE_UNBOXED( Int
, I#
, readWord8ArrayAsInt#
, writeWord8ArrayAsInt#
, SIZEOF_HSINT)
DERIVE_UNBOXED( Int64
, I64#
, readWord8ArrayAsInt64#
, writeWord8ArrayAsInt64#
, 8)
DERIVE_UNBOXED( Word
, W#
, readWord8ArrayAsWord#
, writeWord8ArrayAsWord#
, SIZEOF_HSWORD)
DERIVE_UNBOXED( Word8
, W8#
, readWord8Array#
, writeWord8Array#
, 1)
DERIVE_UNBOXED( Word16
, W16#
, readWord8ArrayAsWord16#
, writeWord8ArrayAsWord16#
, 2)
DERIVE_UNBOXED( Word32
, W32#
, readWord8ArrayAsWord32#
, writeWord8ArrayAsWord32#
, 4)
DERIVE_UNBOXED( Word64
, W64#
, readWord8ArrayAsWord64#
, writeWord8ArrayAsWord64#
, 8)
DERIVE_UNBOXED( Double
, D#
, readWord8ArrayAsDouble#
, writeWord8ArrayAsDouble#
, SIZEOF_HSDOUBLE)
DERIVE_UNBOXED( Float
, F#
, readWord8ArrayAsFloat#
, writeWord8ArrayAsFloat#
, SIZEOF_HSFLOAT)
DERIVE_UNBOXED( (StablePtr a)
, StablePtr
, readWord8ArrayAsStablePtr#
, writeWord8ArrayAsStablePtr#
, SIZEOF_HSSTABLEPTR)
DERIVE_UNBOXED( (Ptr a)
, Ptr
, readWord8ArrayAsAddr#
, writeWord8ArrayAsAddr#
, SIZEOF_HSPTR)
DERIVE_UNBOXED( (FunPtr a)
, FunPtr
, readWord8ArrayAsAddr#
, writeWord8ArrayAsAddr#
, SIZEOF_HSFUNPTR)
DERIVE_WRAPPED_UNBOX(,IntPtr,IntPtr,Int)
DERIVE_WRAPPED_UNBOX(,WordPtr,WordPtr,Word)
DERIVE_WRAPPED_UNBOX(Unbox a =>,(Identity a),Identity,a)
#if MIN_VERSION_base(4,14,0)
DERIVE_WRAPPED_UNBOX(Unbox a =>,(Down a),Down,a)
#endif
DERIVE_WRAPPED_UNBOX(Unbox a =>,(Const a b),Const,a)
DERIVE_BINARY_UNBOX(forall a. Unbox a =>,(Complex a),(:+),a)
DERIVE_BINARY_UNBOX(forall a. Unbox a =>,(Ratio a),(:%),a)
DERIVE_BINARY_UNBOX(,Fingerprint,Fingerprint,Word64)
instance Unbox () where
{-# INLINE peekByteIndex #-}
peekByteIndex :: Int -> MutableByteArray -> IO ()
peekByteIndex Int
_ MutableByteArray
_ = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
{-# INLINE pokeByteIndex #-}
pokeByteIndex :: Int -> MutableByteArray -> () -> IO ()
pokeByteIndex Int
_ MutableByteArray
_ ()
_ = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
{-# INLINE sizeOf #-}
sizeOf :: Proxy () -> Int
sizeOf Proxy ()
_ = Int
1
#if MIN_VERSION_base(4,15,0)
instance Unbox IoSubSystem where
{-# INLINE peekByteIndex #-}
peekByteIndex i arr = toEnum <$> peekByteIndex i arr
{-# INLINE pokeByteIndex #-}
pokeByteIndex i arr a = pokeByteIndex i arr (fromEnum a)
{-# INLINE sizeOf #-}
sizeOf _ = sizeOf (Proxy :: Proxy Int)
#endif
instance Unbox Bool where
{-# INLINE peekByteIndex #-}
peekByteIndex :: Int -> MutableByteArray -> IO Bool
peekByteIndex Int
i MutableByteArray
arr = do
Int8
res <- Int -> MutableByteArray -> IO Int8
forall a. Unbox a => Int -> MutableByteArray -> IO a
peekByteIndex Int
i MutableByteArray
arr
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ Int8
res Int8 -> Int8 -> Bool
forall a. Eq a => a -> a -> Bool
/= (Int8
0 :: Int8)
{-# INLINE pokeByteIndex #-}
pokeByteIndex :: Int -> MutableByteArray -> Bool -> IO ()
pokeByteIndex Int
i MutableByteArray
arr Bool
a =
if Bool
a
then Int -> MutableByteArray -> Int8 -> IO ()
forall a. Unbox a => Int -> MutableByteArray -> a -> IO ()
pokeByteIndex Int
i MutableByteArray
arr (Int8
1 :: Int8)
else Int -> MutableByteArray -> Int8 -> IO ()
forall a. Unbox a => Int -> MutableByteArray -> a -> IO ()
pokeByteIndex Int
i MutableByteArray
arr (Int8
0 :: Int8)
{-# INLINE sizeOf #-}
sizeOf :: Proxy Bool -> Int
sizeOf Proxy Bool
_ = Int
1
{-# INLINE peekWith #-}
peekWith :: Unbox a => MutableByteArray -> Int -> IO a
peekWith :: MutableByteArray -> Int -> IO a
peekWith MutableByteArray
arr Int
i = Int -> MutableByteArray -> IO a
forall a. Unbox a => Int -> MutableByteArray -> IO a
peekByteIndex Int
i MutableByteArray
arr
{-# INLINE pokeWith #-}
pokeWith :: Unbox a => MutableByteArray -> Int -> a -> IO ()
pokeWith :: MutableByteArray -> Int -> a -> IO ()
pokeWith MutableByteArray
arr Int
i = Int -> MutableByteArray -> a -> IO ()
forall a. Unbox a => Int -> MutableByteArray -> a -> IO ()
pokeByteIndex Int
i MutableByteArray
arr
data BoundedPtr =
BoundedPtr
MutableByteArray
Int
Int
newtype Peeker a = Peeker (Builder BoundedPtr IO a)
deriving (a -> Peeker b -> Peeker a
(a -> b) -> Peeker a -> Peeker b
(forall a b. (a -> b) -> Peeker a -> Peeker b)
-> (forall a b. a -> Peeker b -> Peeker a) -> Functor Peeker
forall a b. a -> Peeker b -> Peeker a
forall a b. (a -> b) -> Peeker a -> Peeker b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Peeker b -> Peeker a
$c<$ :: forall a b. a -> Peeker b -> Peeker a
fmap :: (a -> b) -> Peeker a -> Peeker b
$cfmap :: forall a b. (a -> b) -> Peeker a -> Peeker b
Functor, Functor Peeker
a -> Peeker a
Functor Peeker
-> (forall a. a -> Peeker a)
-> (forall a b. Peeker (a -> b) -> Peeker a -> Peeker b)
-> (forall a b c.
(a -> b -> c) -> Peeker a -> Peeker b -> Peeker c)
-> (forall a b. Peeker a -> Peeker b -> Peeker b)
-> (forall a b. Peeker a -> Peeker b -> Peeker a)
-> Applicative Peeker
Peeker a -> Peeker b -> Peeker b
Peeker a -> Peeker b -> Peeker a
Peeker (a -> b) -> Peeker a -> Peeker b
(a -> b -> c) -> Peeker a -> Peeker b -> Peeker c
forall a. a -> Peeker a
forall a b. Peeker a -> Peeker b -> Peeker a
forall a b. Peeker a -> Peeker b -> Peeker b
forall a b. Peeker (a -> b) -> Peeker a -> Peeker b
forall a b c. (a -> b -> c) -> Peeker a -> Peeker b -> Peeker c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: Peeker a -> Peeker b -> Peeker a
$c<* :: forall a b. Peeker a -> Peeker b -> Peeker a
*> :: Peeker a -> Peeker b -> Peeker b
$c*> :: forall a b. Peeker a -> Peeker b -> Peeker b
liftA2 :: (a -> b -> c) -> Peeker a -> Peeker b -> Peeker c
$cliftA2 :: forall a b c. (a -> b -> c) -> Peeker a -> Peeker b -> Peeker c
<*> :: Peeker (a -> b) -> Peeker a -> Peeker b
$c<*> :: forall a b. Peeker (a -> b) -> Peeker a -> Peeker b
pure :: a -> Peeker a
$cpure :: forall a. a -> Peeker a
$cp1Applicative :: Functor Peeker
Applicative, Applicative Peeker
a -> Peeker a
Applicative Peeker
-> (forall a b. Peeker a -> (a -> Peeker b) -> Peeker b)
-> (forall a b. Peeker a -> Peeker b -> Peeker b)
-> (forall a. a -> Peeker a)
-> Monad Peeker
Peeker a -> (a -> Peeker b) -> Peeker b
Peeker a -> Peeker b -> Peeker b
forall a. a -> Peeker a
forall a b. Peeker a -> Peeker b -> Peeker b
forall a b. Peeker a -> (a -> Peeker b) -> Peeker b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> Peeker a
$creturn :: forall a. a -> Peeker a
>> :: Peeker a -> Peeker b -> Peeker b
$c>> :: forall a b. Peeker a -> Peeker b -> Peeker b
>>= :: Peeker a -> (a -> Peeker b) -> Peeker b
$c>>= :: forall a b. Peeker a -> (a -> Peeker b) -> Peeker b
$cp1Monad :: Applicative Peeker
Monad)
{-# INLINE readUnsafe #-}
readUnsafe :: Unbox a => Peeker a
readUnsafe :: Peeker a
readUnsafe = Builder BoundedPtr IO a -> Peeker a
forall a. Builder BoundedPtr IO a -> Peeker a
Peeker ((BoundedPtr -> IO (BoundedPtr, a)) -> Builder BoundedPtr IO a
forall s (m :: * -> *) a. (s -> m (s, a)) -> Builder s m a
Builder BoundedPtr -> IO (BoundedPtr, a)
forall a. Unbox a => BoundedPtr -> IO (BoundedPtr, a)
step)
where
{-# INLINE step #-}
step :: forall a. Unbox a => BoundedPtr -> IO (BoundedPtr, a)
step :: BoundedPtr -> IO (BoundedPtr, a)
step (BoundedPtr MutableByteArray
arr Int
pos Int
end) = do
let next :: Int
next = Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Proxy a -> Int
forall a. Unbox a => Proxy a -> Int
sizeOf (Proxy a
forall k (t :: k). Proxy t
Proxy :: Proxy a)
a
r <- Int -> MutableByteArray -> IO a
forall a. Unbox a => Int -> MutableByteArray -> IO a
peekByteIndex Int
pos MutableByteArray
arr
(BoundedPtr, a) -> IO (BoundedPtr, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (MutableByteArray -> Int -> Int -> BoundedPtr
BoundedPtr MutableByteArray
arr Int
next Int
end, a
r)
{-# INLINE read #-}
read :: Unbox a => Peeker a
read :: Peeker a
read = Builder BoundedPtr IO a -> Peeker a
forall a. Builder BoundedPtr IO a -> Peeker a
Peeker ((BoundedPtr -> IO (BoundedPtr, a)) -> Builder BoundedPtr IO a
forall s (m :: * -> *) a. (s -> m (s, a)) -> Builder s m a
Builder BoundedPtr -> IO (BoundedPtr, a)
forall a. Unbox a => BoundedPtr -> IO (BoundedPtr, a)
step)
where
{-# INLINE step #-}
step :: forall a. Unbox a => BoundedPtr -> IO (BoundedPtr, a)
step :: BoundedPtr -> IO (BoundedPtr, a)
step (BoundedPtr MutableByteArray
arr Int
pos Int
end) = do
let next :: Int
next = Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Proxy a -> Int
forall a. Unbox a => Proxy a -> Int
sizeOf (Proxy a
forall k (t :: k). Proxy t
Proxy :: Proxy a)
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
next Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
end) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ [Char] -> IO ()
forall a. HasCallStack => [Char] -> a
error [Char]
"peekObject reading beyond limit"
a
r <- Int -> MutableByteArray -> IO a
forall a. Unbox a => Int -> MutableByteArray -> IO a
peekByteIndex Int
pos MutableByteArray
arr
(BoundedPtr, a) -> IO (BoundedPtr, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (MutableByteArray -> Int -> Int -> BoundedPtr
BoundedPtr MutableByteArray
arr Int
next Int
end, a
r)
{-# INLINE skipByte #-}
skipByte :: Peeker ()
skipByte :: Peeker ()
skipByte = Builder BoundedPtr IO () -> Peeker ()
forall a. Builder BoundedPtr IO a -> Peeker a
Peeker ((BoundedPtr -> IO (BoundedPtr, ())) -> Builder BoundedPtr IO ()
forall s (m :: * -> *) a. (s -> m (s, a)) -> Builder s m a
Builder BoundedPtr -> IO (BoundedPtr, ())
step)
where
{-# INLINE step #-}
step :: BoundedPtr -> IO (BoundedPtr, ())
step :: BoundedPtr -> IO (BoundedPtr, ())
step (BoundedPtr MutableByteArray
arr Int
pos Int
end) = do
let next :: Int
next = Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
next Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
end)
(IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ [Char] -> IO ()
forall a. HasCallStack => [Char] -> a
error ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$ [Char]
"skipByte: reading beyond limit. next = "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show Int
next
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" end = " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show Int
end
(BoundedPtr, ()) -> IO (BoundedPtr, ())
forall (m :: * -> *) a. Monad m => a -> m a
return (MutableByteArray -> Int -> Int -> BoundedPtr
BoundedPtr MutableByteArray
arr Int
next Int
end, ())
{-# INLINE runPeeker #-}
runPeeker :: Peeker a -> BoundedPtr -> IO a
runPeeker :: Peeker a -> BoundedPtr -> IO a
runPeeker (Peeker (Builder BoundedPtr -> IO (BoundedPtr, a)
f)) BoundedPtr
ptr = ((BoundedPtr, a) -> a) -> IO (BoundedPtr, a) -> IO a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (BoundedPtr, a) -> a
forall a b. (a, b) -> b
snd (BoundedPtr -> IO (BoundedPtr, a)
f BoundedPtr
ptr)
{-# INLINE pokeBoundedPtrUnsafe #-}
pokeBoundedPtrUnsafe :: forall a. Unbox a => a -> BoundedPtr -> IO BoundedPtr
pokeBoundedPtrUnsafe :: a -> BoundedPtr -> IO BoundedPtr
pokeBoundedPtrUnsafe a
a (BoundedPtr MutableByteArray
arr Int
pos Int
end) = do
let next :: Int
next = Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Proxy a -> Int
forall a. Unbox a => Proxy a -> Int
sizeOf (Proxy a
forall k (t :: k). Proxy t
Proxy :: Proxy a)
Int -> MutableByteArray -> a -> IO ()
forall a. Unbox a => Int -> MutableByteArray -> a -> IO ()
pokeByteIndex Int
pos MutableByteArray
arr a
a
BoundedPtr -> IO BoundedPtr
forall (m :: * -> *) a. Monad m => a -> m a
return (MutableByteArray -> Int -> Int -> BoundedPtr
BoundedPtr MutableByteArray
arr Int
next Int
end)
{-# INLINE pokeBoundedPtr #-}
pokeBoundedPtr :: forall a. Unbox a => a -> BoundedPtr -> IO BoundedPtr
pokeBoundedPtr :: a -> BoundedPtr -> IO BoundedPtr
pokeBoundedPtr a
a (BoundedPtr MutableByteArray
arr Int
pos Int
end) = do
let next :: Int
next = Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Proxy a -> Int
forall a. Unbox a => Proxy a -> Int
sizeOf (Proxy a
forall k (t :: k). Proxy t
Proxy :: Proxy a)
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
next Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
end) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ [Char] -> IO ()
forall a. HasCallStack => [Char] -> a
error [Char]
"pokeBoundedPtr writing beyond limit"
Int -> MutableByteArray -> a -> IO ()
forall a. Unbox a => Int -> MutableByteArray -> a -> IO ()
pokeByteIndex Int
pos MutableByteArray
arr a
a
BoundedPtr -> IO BoundedPtr
forall (m :: * -> *) a. Monad m => a -> m a
return (MutableByteArray -> Int -> Int -> BoundedPtr
BoundedPtr MutableByteArray
arr Int
next Int
end)
type family SumArity (a :: Type -> Type) :: Nat where
SumArity (C1 _ _) = 1
SumArity (f :+: g) = SumArity f + SumArity g
type family TypeErrorMessage (a :: Symbol) :: Constraint where
TypeErrorMessage a = TypeError ('Text a)
type family ArityCheck (b :: Bool) :: Constraint where
ArityCheck 'True = ()
ArityCheck 'False = TypeErrorMessage
"Generic Unbox deriving does not support > 256 constructors."
type MaxArity256 n = ArityCheck (n <=? 255)
class SizeOfRep (f :: Type -> Type) where
sizeOfRep :: f x -> Int
instance SizeOfRep f => SizeOfRep (M1 i c f) where
{-# INLINE sizeOfRep #-}
sizeOfRep :: M1 i c f x -> Int
sizeOfRep M1 i c f x
_ = f Any -> Int
forall (f :: * -> *) x. SizeOfRep f => f x -> Int
sizeOfRep (forall x. f x
forall a. HasCallStack => a
undefined :: f x)
instance Unbox a => SizeOfRep (K1 i a) where
{-# INLINE sizeOfRep #-}
sizeOfRep :: K1 i a x -> Int
sizeOfRep K1 i a x
_ = Proxy a -> Int
forall a. Unbox a => Proxy a -> Int
sizeOf (Proxy a
forall k (t :: k). Proxy t
Proxy :: Proxy a)
instance SizeOfRep V1 where
{-# INLINE sizeOfRep #-}
sizeOfRep :: V1 x -> Int
sizeOfRep = [Char] -> V1 x -> Int
forall a. HasCallStack => [Char] -> a
error [Char]
"sizeOfRep: a value of a Void type must not exist"
instance SizeOfRep U1 where
{-# INLINE sizeOfRep #-}
sizeOfRep :: U1 x -> Int
sizeOfRep U1 x
_ = Int
0
instance (SizeOfRep f, SizeOfRep g) => SizeOfRep (f :*: g) where
{-# INLINE sizeOfRep #-}
sizeOfRep :: (:*:) f g x -> Int
sizeOfRep (:*:) f g x
_ = f Any -> Int
forall (f :: * -> *) x. SizeOfRep f => f x -> Int
sizeOfRep (forall x. f x
forall a. HasCallStack => a
undefined :: f x) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ g Any -> Int
forall (f :: * -> *) x. SizeOfRep f => f x -> Int
sizeOfRep (forall x. g x
forall a. HasCallStack => a
undefined :: g x)
class SizeOfRepSum (f :: Type -> Type) where
sizeOfRepSum :: f x -> Int
instance SizeOfRep a => SizeOfRepSum (C1 c a) where
{-# INLINE sizeOfRepSum #-}
sizeOfRepSum :: C1 c a x -> Int
sizeOfRepSum = C1 c a x -> Int
forall (f :: * -> *) x. SizeOfRep f => f x -> Int
sizeOfRep
instance (SizeOfRepSum f, SizeOfRepSum g) => SizeOfRepSum (f :+: g) where
{-# INLINE sizeOfRepSum #-}
sizeOfRepSum :: (:+:) f g x -> Int
sizeOfRepSum (:+:) f g x
_ =
Int -> Int -> Int
forall a. Ord a => a -> a -> a
max (f Any -> Int
forall (f :: * -> *) x. SizeOfRepSum f => f x -> Int
sizeOfRepSum (forall x. f x
forall a. HasCallStack => a
undefined :: f x)) (g Any -> Int
forall (f :: * -> *) x. SizeOfRepSum f => f x -> Int
sizeOfRepSum (forall x. g x
forall a. HasCallStack => a
undefined :: g x))
instance (MaxArity256 (SumArity (f :+: g)), SizeOfRepSum f, SizeOfRepSum g) =>
SizeOfRep (f :+: g) where
{-# INLINE sizeOfRep #-}
sizeOfRep :: (:+:) f g x -> Int
sizeOfRep (:+:) f g x
_ =
Proxy Word8 -> Int
forall a. Unbox a => Proxy a -> Int
sizeOf (Proxy Word8
forall k (t :: k). Proxy t
Proxy :: Proxy Word8) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
Int -> Int -> Int
forall a. Ord a => a -> a -> a
max (f Any -> Int
forall (f :: * -> *) x. SizeOfRepSum f => f x -> Int
sizeOfRepSum (forall x. f x
forall a. HasCallStack => a
undefined :: f x))
(g Any -> Int
forall (f :: * -> *) x. SizeOfRepSum f => f x -> Int
sizeOfRepSum (forall x. g x
forall a. HasCallStack => a
undefined :: g x))
{-# INLINE genericSizeOf #-}
genericSizeOf :: forall a. (SizeOfRep (Rep a)) => Proxy a -> Int
genericSizeOf :: Proxy a -> Int
genericSizeOf Proxy a
_ =
let s :: Int
s = Rep a Any -> Int
forall (f :: * -> *) x. SizeOfRep f => f x -> Int
sizeOfRep (forall x. Rep a x
forall a. HasCallStack => a
undefined :: Rep a x)
in if Int
s Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
1 else Int
s
class PokeRep (f :: Type -> Type) where
pokeRep :: f a -> BoundedPtr -> IO BoundedPtr
instance PokeRep f => PokeRep (M1 i c f) where
{-# INLINE pokeRep #-}
pokeRep :: M1 i c f a -> BoundedPtr -> IO BoundedPtr
pokeRep M1 i c f a
f = f a -> BoundedPtr -> IO BoundedPtr
forall (f :: * -> *) a.
PokeRep f =>
f a -> BoundedPtr -> IO BoundedPtr
pokeRep (M1 i c f a -> f a
forall i (c :: Meta) k (f :: k -> *) (p :: k). M1 i c f p -> f p
unM1 M1 i c f a
f)
instance Unbox a => PokeRep (K1 i a) where
{-# INLINE pokeRep #-}
pokeRep :: K1 i a a -> BoundedPtr -> IO BoundedPtr
pokeRep K1 i a a
a = a -> BoundedPtr -> IO BoundedPtr
forall a. Unbox a => a -> BoundedPtr -> IO BoundedPtr
pokeBoundedPtr (K1 i a a -> a
forall i c k (p :: k). K1 i c p -> c
unK1 K1 i a a
a)
instance PokeRep V1 where
{-# INLINE pokeRep #-}
pokeRep :: V1 a -> BoundedPtr -> IO BoundedPtr
pokeRep = [Char] -> V1 a -> BoundedPtr -> IO BoundedPtr
forall a. HasCallStack => [Char] -> a
error [Char]
"pokeRep: a value of a Void type should not exist"
instance PokeRep U1 where
{-# INLINE pokeRep #-}
pokeRep :: U1 a -> BoundedPtr -> IO BoundedPtr
pokeRep U1 a
_ BoundedPtr
x = BoundedPtr -> IO BoundedPtr
forall (f :: * -> *) a. Applicative f => a -> f a
pure BoundedPtr
x
instance (PokeRep f, PokeRep g) => PokeRep (f :*: g) where
{-# INLINE pokeRep #-}
pokeRep :: (:*:) f g a -> BoundedPtr -> IO BoundedPtr
pokeRep (f a
f :*: g a
g) BoundedPtr
ptr = f a -> BoundedPtr -> IO BoundedPtr
forall (f :: * -> *) a.
PokeRep f =>
f a -> BoundedPtr -> IO BoundedPtr
pokeRep f a
f BoundedPtr
ptr IO BoundedPtr -> (BoundedPtr -> IO BoundedPtr) -> IO BoundedPtr
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= g a -> BoundedPtr -> IO BoundedPtr
forall (f :: * -> *) a.
PokeRep f =>
f a -> BoundedPtr -> IO BoundedPtr
pokeRep g a
g
class KnownNat n => PokeRepSum (n :: Nat) (f :: Type -> Type) where
pokeRepSum :: Proxy n -> f a -> BoundedPtr -> IO BoundedPtr
instance (KnownNat n, PokeRep a) => PokeRepSum n (C1 c a) where
{-# INLINE pokeRepSum #-}
pokeRepSum :: Proxy n -> C1 c a a -> BoundedPtr -> IO BoundedPtr
pokeRepSum Proxy n
_ C1 c a a
x BoundedPtr
ptr = do
Word8 -> BoundedPtr -> IO BoundedPtr
forall a. Unbox a => a -> BoundedPtr -> IO BoundedPtr
pokeBoundedPtr (Integer -> Word8
forall a. Num a => Integer -> a
fromInteger (Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)) :: Word8) BoundedPtr
ptr
IO BoundedPtr -> (BoundedPtr -> IO BoundedPtr) -> IO BoundedPtr
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= C1 c a a -> BoundedPtr -> IO BoundedPtr
forall (f :: * -> *) a.
PokeRep f =>
f a -> BoundedPtr -> IO BoundedPtr
pokeRep C1 c a a
x
instance (KnownNat n, PokeRepSum n f, PokeRepSum (n + SumArity f) g)
=> PokeRepSum n (f :+: g) where
{-# INLINE pokeRepSum #-}
pokeRepSum :: Proxy n -> (:+:) f g a -> BoundedPtr -> IO BoundedPtr
pokeRepSum Proxy n
_ (L1 f a
x) BoundedPtr
ptr =
Proxy n -> f a -> BoundedPtr -> IO BoundedPtr
forall (n :: Nat) (f :: * -> *) a.
PokeRepSum n f =>
Proxy n -> f a -> BoundedPtr -> IO BoundedPtr
pokeRepSum (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n) f a
x BoundedPtr
ptr
pokeRepSum Proxy n
_ (R1 g a
x) BoundedPtr
ptr =
Proxy (n + SumArity f) -> g a -> BoundedPtr -> IO BoundedPtr
forall (n :: Nat) (f :: * -> *) a.
PokeRepSum n f =>
Proxy n -> f a -> BoundedPtr -> IO BoundedPtr
pokeRepSum (Proxy (n + SumArity f)
forall k (t :: k). Proxy t
Proxy :: Proxy (n + SumArity f)) g a
x BoundedPtr
ptr
instance (MaxArity256 (SumArity (f :+: g)), PokeRepSum 0 (f :+: g)) =>
PokeRep (f :+: g) where
{-# INLINE pokeRep #-}
pokeRep :: (:+:) f g a -> BoundedPtr -> IO BoundedPtr
pokeRep = Proxy 0 -> (:+:) f g a -> BoundedPtr -> IO BoundedPtr
forall (n :: Nat) (f :: * -> *) a.
PokeRepSum n f =>
Proxy n -> f a -> BoundedPtr -> IO BoundedPtr
pokeRepSum (Proxy 0
forall k (t :: k). Proxy t
Proxy :: Proxy 0)
{-# INLINE genericPokeObject #-}
genericPokeObject :: (Generic a, PokeRep (Rep a)) =>
a -> BoundedPtr -> IO BoundedPtr
genericPokeObject :: a -> BoundedPtr -> IO BoundedPtr
genericPokeObject a
a = Rep a Any -> BoundedPtr -> IO BoundedPtr
forall (f :: * -> *) a.
PokeRep f =>
f a -> BoundedPtr -> IO BoundedPtr
pokeRep (a -> Rep a Any
forall a x. Generic a => a -> Rep a x
from a
a)
genericPokeObj :: (Generic a, PokeRep (Rep a)) => a -> BoundedPtr -> IO ()
genericPokeObj :: a -> BoundedPtr -> IO ()
genericPokeObj a
a BoundedPtr
ptr = IO BoundedPtr -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO BoundedPtr -> IO ()) -> IO BoundedPtr -> IO ()
forall a b. (a -> b) -> a -> b
$ a -> BoundedPtr -> IO BoundedPtr
forall a.
(Generic a, PokeRep (Rep a)) =>
a -> BoundedPtr -> IO BoundedPtr
genericPokeObject a
a BoundedPtr
ptr
{-# INLINE genericPokeByteIndex #-}
genericPokeByteIndex :: (Generic a, PokeRep (Rep a)) =>
MutableByteArray -> Int -> a -> IO ()
genericPokeByteIndex :: MutableByteArray -> Int -> a -> IO ()
genericPokeByteIndex MutableByteArray
arr Int
index a
x = do
Int
end <- MutableByteArray -> IO Int
sizeOfMutableByteArray MutableByteArray
arr
a -> BoundedPtr -> IO ()
forall a. (Generic a, PokeRep (Rep a)) => a -> BoundedPtr -> IO ()
genericPokeObj a
x (MutableByteArray -> Int -> Int -> BoundedPtr
BoundedPtr MutableByteArray
arr Int
index Int
end)
class PeekRep (f :: Type -> Type) where
peekRep :: Peeker (f x)
instance PeekRep f => PeekRep (M1 i c f) where
{-# INLINE peekRep #-}
peekRep :: Peeker (M1 i c f x)
peekRep = (f x -> M1 i c f x) -> Peeker (f x) -> Peeker (M1 i c f x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f x -> M1 i c f x
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 Peeker (f x)
forall (f :: * -> *) x. PeekRep f => Peeker (f x)
peekRep
instance Unbox a => PeekRep (K1 i a) where
{-# INLINE peekRep #-}
peekRep :: Peeker (K1 i a x)
peekRep = (a -> K1 i a x) -> Peeker a -> Peeker (K1 i a x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> K1 i a x
forall k i c (p :: k). c -> K1 i c p
K1 Peeker a
forall a. Unbox a => Peeker a
read
instance PeekRep V1 where
{-# INLINE peekRep #-}
peekRep :: Peeker (V1 x)
peekRep = [Char] -> Peeker (V1 x)
forall a. HasCallStack => [Char] -> a
error [Char]
"peekRep: a value of a Void type should not exist"
instance PeekRep U1 where
{-# INLINE peekRep #-}
peekRep :: Peeker (U1 x)
peekRep = U1 x -> Peeker (U1 x)
forall (f :: * -> *) a. Applicative f => a -> f a
pure U1 x
forall k (p :: k). U1 p
U1
instance (PeekRep f, PeekRep g) => PeekRep (f :*: g) where
{-# INLINE peekRep #-}
peekRep :: Peeker ((:*:) f g x)
peekRep = f x -> g x -> (:*:) f g x
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(:*:) (f x -> g x -> (:*:) f g x)
-> Peeker (f x) -> Peeker (g x -> (:*:) f g x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peeker (f x)
forall (f :: * -> *) x. PeekRep f => Peeker (f x)
peekRep Peeker (g x -> (:*:) f g x) -> Peeker (g x) -> Peeker ((:*:) f g x)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Peeker (g x)
forall (f :: * -> *) x. PeekRep f => Peeker (f x)
peekRep
class KnownNat n => PeekRepSum (n :: Nat) (f :: Type -> Type) where
peekRepSum :: Proxy n -> Word8 -> Peeker (f a)
instance (KnownNat n, PeekRep a) => PeekRepSum n (C1 c a) where
{-# INLINE peekRepSum #-}
peekRepSum :: Proxy n -> Word8 -> Peeker (C1 c a a)
peekRepSum Proxy n
_ Word8
tag
| Word8
tag Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
curTag = Peeker (C1 c a a)
forall (f :: * -> *) x. PeekRep f => Peeker (f x)
peekRep
| Word8
tag Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
> Word8
curTag =
[Char] -> Peeker (C1 c a a)
forall a. HasCallStack => [Char] -> a
error ([Char] -> Peeker (C1 c a a)) -> [Char] -> Peeker (C1 c a a)
forall a b. (a -> b) -> a -> b
$ [Char]
"Unbox instance peek: Constructor tag index "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Word8 -> [Char]
forall a. Show a => a -> [Char]
show Word8
tag [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" out of range, max tag index is "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Word8 -> [Char]
forall a. Show a => a -> [Char]
show Word8
curTag
| Bool
otherwise = [Char] -> Peeker (C1 c a a)
forall a. HasCallStack => [Char] -> a
error [Char]
"peekRepSum: bug"
where
curTag :: Word8
curTag = Integer -> Word8
forall a. Num a => Integer -> a
fromInteger (Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n))
instance (KnownNat n, PeekRepSum n f, PeekRepSum (n + SumArity f) g)
=> PeekRepSum n (f :+: g) where
{-# INLINE peekRepSum #-}
peekRepSum :: Proxy n -> Word8 -> Peeker ((:+:) f g a)
peekRepSum Proxy n
curProxy Word8
tag
| Word8
tag Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
firstRightTag =
f a -> (:+:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 (f a -> (:+:) f g a) -> Peeker (f a) -> Peeker ((:+:) f g a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy n -> Word8 -> Peeker (f a)
forall (n :: Nat) (f :: * -> *) a.
PeekRepSum n f =>
Proxy n -> Word8 -> Peeker (f a)
peekRepSum Proxy n
curProxy Word8
tag
| Bool
otherwise =
g a -> (:+:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 (g a -> (:+:) f g a) -> Peeker (g a) -> Peeker ((:+:) f g a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy (n + SumArity f) -> Word8 -> Peeker (g a)
forall (n :: Nat) (f :: * -> *) a.
PeekRepSum n f =>
Proxy n -> Word8 -> Peeker (f a)
peekRepSum (Proxy (n + SumArity f)
forall k (t :: k). Proxy t
Proxy :: Proxy (n + SumArity f)) Word8
tag
where
firstRightTag :: Word8
firstRightTag = Integer -> Word8
forall a. Num a => Integer -> a
fromInteger (Proxy (n + SumArity f) -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy (n + SumArity f)
forall k (t :: k). Proxy t
Proxy :: Proxy (n + SumArity f)))
instance (MaxArity256 (SumArity (f :+: g)), PeekRepSum 0 (f :+: g))
=> PeekRep (f :+: g) where
{-# INLINE peekRep #-}
peekRep :: Peeker ((:+:) f g x)
peekRep = do
Word8
tag <- Peeker Word8
forall a. Unbox a => Peeker a
read
Proxy 0 -> Word8 -> Peeker ((:+:) f g x)
forall (n :: Nat) (f :: * -> *) a.
PeekRepSum n f =>
Proxy n -> Word8 -> Peeker (f a)
peekRepSum (Proxy 0
forall k (t :: k). Proxy t
Proxy :: Proxy 0) Word8
tag
{-# INLINE genericPeeker #-}
genericPeeker :: (Generic a, PeekRep (Rep a)) => Peeker a
genericPeeker :: Peeker a
genericPeeker = Rep a Any -> a
forall a x. Generic a => Rep a x -> a
to (Rep a Any -> a) -> Peeker (Rep a Any) -> Peeker a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peeker (Rep a Any)
forall (f :: * -> *) x. PeekRep f => Peeker (f x)
peekRep
{-# INLINE genericPeekBoundedPtr #-}
genericPeekBoundedPtr :: (Generic a, PeekRep (Rep a)) => BoundedPtr -> IO a
genericPeekBoundedPtr :: BoundedPtr -> IO a
genericPeekBoundedPtr = Peeker a -> BoundedPtr -> IO a
forall a. Peeker a -> BoundedPtr -> IO a
runPeeker Peeker a
forall a. (Generic a, PeekRep (Rep a)) => Peeker a
genericPeeker
{-# INLINE genericPeekByteIndex #-}
genericPeekByteIndex :: (Generic a, PeekRep (Rep a)) =>
MutableByteArray -> Int -> IO a
genericPeekByteIndex :: MutableByteArray -> Int -> IO a
genericPeekByteIndex MutableByteArray
arr Int
index = do
Int
end <- MutableByteArray -> IO Int
sizeOfMutableByteArray MutableByteArray
arr
BoundedPtr -> IO a
forall a. (Generic a, PeekRep (Rep a)) => BoundedPtr -> IO a
genericPeekBoundedPtr (MutableByteArray -> Int -> Int -> BoundedPtr
BoundedPtr MutableByteArray
arr Int
index Int
end)