Rename peekByteIndex/pokeByteIndex to peekAt/pokeAt

This commit is contained in:
Harendra Kumar 2023-11-25 11:43:07 +05:30
parent 7cb856b7e6
commit 1efeed403b
16 changed files with 148 additions and 139 deletions

View File

@ -44,8 +44,8 @@ import Streamly.Benchmark.Data.Serialize.RecNonCompatible
#ifdef USE_UNBOX
#define SERIALIZE_CLASS Unbox
#define DERIVE_CLASS(typ) $(deriveUnbox [d|instance Unbox typ|])
#define SERIALIZE_OP pokeByteIndex
#define DESERIALIZE_OP peekByteIndex
#define SERIALIZE_OP pokeAt
#define DESERIALIZE_OP peekAt
#else
#define SERIALIZE_CLASS Serialize
#define DERIVE_CLASS(typ) $(deriveSerialize [d|instance Serialize typ|])

View File

@ -220,7 +220,7 @@ readerUnsafe = Unfold step inject
--
-- This should be safe as the array contents are guaranteed to be
-- evaluated/written to before we peek at them.
let !x = unsafeInlineIO $ peekByteIndex p contents
let !x = unsafeInlineIO $ peekAt p contents
let !p1 = INDEX_NEXT(p,a)
return $ D.Yield x (ArrayUnsafe contents end p1)
@ -243,7 +243,7 @@ getIndexRev i arr =
$ do
let elemPtr = RINDEX_OF(arrEnd arr, i, a)
if i >= 0 && elemPtr >= arrStart arr
then Just <$> peekByteIndex elemPtr (arrContents arr)
then Just <$> peekAt elemPtr (arrContents arr)
else return Nothing
-- |
@ -404,7 +404,7 @@ getIndex i arr =
$ do
let elemPtr = INDEX_OF(arrStart arr, i, a)
if i >= 0 && INDEX_VALID(elemPtr, arrEnd arr, a)
then Just <$> peekByteIndex elemPtr (arrContents arr)
then Just <$> peekAt elemPtr (arrContents arr)
else return Nothing
-- | Given a stream of array indices, read the elements on those indices from

View File

@ -501,8 +501,8 @@ toListFB c n Array{..} = go arrStart
-- accumulating the list and fusing better with the pure consumers.
--
-- This should be safe as the array contents are guaranteed to be
-- evaluated/written to before we peekByteIndex at them.
let !x = unsafeInlineIO $ peekByteIndex p arrContents
-- evaluated/written to before we peekAt at them.
let !x = unsafeInlineIO $ peekAt p arrContents
in c x (go (INDEX_NEXT(p,a)))
-- | Convert an 'Array' into a list.
@ -703,7 +703,7 @@ _toStreamD_ size Array{..} = D.Stream step arrStart
{-# INLINE_LATE step #-}
step _ p | p == arrEnd = return D.Stop
step _ p = liftIO $ do
x <- peekByteIndex p arrContents
x <- peekAt p arrContents
return $ D.Yield x (p + size)
{-

View File

@ -124,7 +124,7 @@ fromFold (Fold.Fold fstep finitial _ ffinal) =
assert (cur == end) (return ())
return $ Partial 0 fs
goArray !_ !cur !fs = do
x <- liftIO $ peekByteIndex cur contents
x <- liftIO $ peekAt cur contents
res <- fstep fs x
let elemSize = SIZE_OF(a)
next = INDEX_NEXT(cur,a)
@ -163,7 +163,7 @@ fromParserD (ParserD.Parser step1 initial1 extract1) =
else return $ st (arrRem + n) fs1
goArray !_ !cur !fs = do
x <- liftIO $ peekByteIndex cur contents
x <- liftIO $ peekAt cur contents
res <- step1 fs x
let elemSize = SIZE_OF(a)
next = INDEX_NEXT(cur,a)

View File

@ -56,7 +56,7 @@ newtype IORef a = IORef MutByteArray
newIORef :: forall a. Unbox a => a -> IO (IORef a)
newIORef x = do
var <- MBA.new (sizeOf (Proxy :: Proxy a))
pokeByteIndex 0 var x
pokeAt 0 var x
return $ IORef var
-- | Write a value to an 'IORef'.
@ -64,14 +64,14 @@ newIORef x = do
-- /Pre-release/
{-# INLINE writeIORef #-}
writeIORef :: Unbox a => IORef a -> a -> IO ()
writeIORef (IORef var) = pokeByteIndex 0 var
writeIORef (IORef var) = pokeAt 0 var
-- | Read a value from an 'IORef'.
--
-- /Pre-release/
{-# INLINE readIORef #-}
readIORef :: Unbox a => IORef a -> IO a
readIORef (IORef var) = peekByteIndex 0 var
readIORef (IORef var) = peekAt 0 var
-- | Modify the value of an 'IORef' using a function with strict application.
--

View File

@ -500,7 +500,7 @@ putIndexUnsafe :: forall m a. (MonadIO m, Unbox a)
putIndexUnsafe i MutArray{..} x = do
let index = INDEX_OF(arrStart, i, a)
assert (i >= 0 && INDEX_VALID(index, arrEnd, a)) (return ())
liftIO $ pokeByteIndex index arrContents x
liftIO $ pokeAt index arrContents x
invalidIndex :: String -> Int -> a
invalidIndex label i =
@ -518,7 +518,7 @@ putIndex :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> a -> m ()
putIndex i MutArray{..} x = do
let index = INDEX_OF(arrStart,i,a)
if i >= 0 && INDEX_VALID(index,arrEnd,a)
then liftIO $ pokeByteIndex index arrContents x
then liftIO $ pokeAt index arrContents x
else invalidIndex "putIndex" i
-- | Write an input stream of (index, value) pairs to an array. Throws an
@ -544,9 +544,9 @@ modifyIndexUnsafe :: forall m a b. (MonadIO m, Unbox a) =>
modifyIndexUnsafe i MutArray{..} f = liftIO $ do
let index = INDEX_OF(arrStart,i,a)
assert (i >= 0 && INDEX_NEXT(index,a) <= arrEnd) (return ())
r <- peekByteIndex index arrContents
r <- peekAt index arrContents
let (x, res) = f r
pokeByteIndex index arrContents x
pokeAt index arrContents x
return res
-- | Modify a given index of an array using a modifier function.
@ -558,9 +558,9 @@ modifyIndex i MutArray{..} f = do
let index = INDEX_OF(arrStart,i,a)
if i >= 0 && INDEX_VALID(index,arrEnd,a)
then liftIO $ do
r <- peekByteIndex index arrContents
r <- peekAt index arrContents
let (x, res) = f r
pokeByteIndex index arrContents x
pokeAt index arrContents x
return res
else invalidIndex "modifyIndex" i
@ -594,8 +594,8 @@ modify MutArray{..} f = liftIO $
go i =
when (INDEX_VALID(i,arrEnd,a)) $ do
r <- peekByteIndex i arrContents
pokeByteIndex i arrContents (f r)
r <- peekAt i arrContents
pokeAt i arrContents (f r)
go (INDEX_NEXT(i,a))
-- XXX We could specify the number of bytes to swap instead of Proxy. Need
@ -609,10 +609,10 @@ swapArrayByteIndices ::
-> Int
-> IO ()
swapArrayByteIndices _ arrContents i1 i2 = do
r1 <- peekByteIndex i1 arrContents
r2 <- peekByteIndex i2 arrContents
pokeByteIndex i1 arrContents (r2 :: a)
pokeByteIndex i2 arrContents (r1 :: a)
r1 <- peekAt i1 arrContents
r2 <- peekAt i2 arrContents
pokeAt i1 arrContents (r2 :: a)
pokeAt i2 arrContents (r1 :: a)
-- | Swap the elements at two indices without validating the indices.
--
@ -889,7 +889,7 @@ rightSize arr@MutArray{..} = do
snocNewEnd :: (MonadIO m, Unbox a) => Int -> MutArray a -> a -> m (MutArray a)
snocNewEnd newEnd arr@MutArray{..} x = liftIO $ do
assert (newEnd <= arrBound) (return ())
pokeByteIndex arrEnd arrContents x
pokeAt arrEnd arrContents x
return $ arr {arrEnd = newEnd}
-- | Really really unsafe, appends the element into the first array, may
@ -1003,7 +1003,7 @@ getIndexUnsafe :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m a
getIndexUnsafe i MutArray{..} = do
let index = INDEX_OF(arrStart,i,a)
assert (i >= 0 && INDEX_VALID(index,arrEnd,a)) (return ())
liftIO $ peekByteIndex index arrContents
liftIO $ peekAt index arrContents
-- | /O(1)/ Lookup the element at the given index. Index starts from 0.
--
@ -1012,7 +1012,7 @@ getIndex :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m (Maybe a)
getIndex i MutArray{..} = do
let index = INDEX_OF(arrStart,i,a)
if i >= 0 && INDEX_VALID(index,arrEnd,a)
then liftIO $ Just <$> peekByteIndex index arrContents
then liftIO $ Just <$> peekAt index arrContents
else return Nothing
-- | /O(1)/ Lookup the element at the given index from the end of the array.
@ -1025,7 +1025,7 @@ getIndexRev :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m a
getIndexRev i MutArray{..} = do
let index = RINDEX_OF(arrEnd,i,a)
if i >= 0 && index >= arrStart
then liftIO $ peekByteIndex index arrContents
then liftIO $ peekAt index arrContents
else invalidIndex "getIndexRev" i
data GetIndicesState contents start end st =
@ -1165,7 +1165,7 @@ partitionBy f arr@MutArray{..} = liftIO $ do
-- Invariant low < high on entry, and on return as well
moveHigh low high = do
h <- peekByteIndex high arrContents
h <- peekAt high arrContents
if f h
then
-- Correctly classified, continue the loop
@ -1185,7 +1185,7 @@ partitionBy f arr@MutArray{..} = liftIO $ do
-- low <= high
-- Both low and high are valid locations within the array
go low high = do
l <- peekByteIndex low arrContents
l <- peekAt low arrContents
if f l
then
-- low is wrongly classified
@ -1196,8 +1196,8 @@ partitionBy f arr@MutArray{..} = liftIO $ do
case r of
Nothing -> return low
Just (high1, h) -> do -- low < high1
pokeByteIndex low arrContents h
pokeByteIndex high1 arrContents l
pokeAt low arrContents h
pokeAt high1 arrContents l
let low1 = INDEX_NEXT(low,a)
high2 = INDEX_PREV(high1,a)
if low1 <= high2
@ -1331,7 +1331,7 @@ chunksOfAs ps n (D.Stream step state) =
r <- step (adaptState gst) st
case r of
D.Yield x s -> do
liftIO $ pokeByteIndex end contents x
liftIO $ pokeAt end contents x
let end1 = INDEX_NEXT(end,a)
return $
if end1 >= bound
@ -1418,7 +1418,7 @@ flattenArrays (D.Stream step state) = D.Stream step' (OuterLoop state)
return $ D.Skip $ OuterLoop st
step' _ (InnerLoop st contents p end) = do
x <- liftIO $ peekByteIndex p contents
x <- liftIO $ peekAt p contents
return $ D.Yield x (InnerLoop st contents (INDEX_NEXT(p,a)) end)
-- | Use the "readerRev" unfold instead.
@ -1448,7 +1448,7 @@ flattenArraysRev (D.Stream step state) = D.Stream step' (OuterLoop state)
return $ D.Skip $ OuterLoop st
step' _ (InnerLoop st contents p start) = do
x <- liftIO $ peekByteIndex p contents
x <- liftIO $ peekAt p contents
let cur = INDEX_PREV(p,a)
return $ D.Yield x (InnerLoop st contents cur start)
@ -1487,7 +1487,7 @@ producerWith liftio = Producer step (return . toArrayUnsafe) extract
-- few actions for correctness and execution order sanity. We want
-- the peek to occur right here and not lazily at some later point
-- because we want the peek to be ordered with respect to the touch.
!x <- liftio $ peekByteIndex cur contents
!x <- liftio $ peekAt cur contents
return $ D.Yield x (ArrayUnsafe contents (INDEX_NEXT(cur,a)) end)
extract = return . fromArrayUnsafe
@ -1518,7 +1518,7 @@ readerRevWith liftio = Unfold step inject
{-# INLINE_LATE step #-}
step (ArrayUnsafe _ start p) | p < start = return D.Stop
step (ArrayUnsafe contents start p) = do
!x <- liftio $ peekByteIndex p contents
!x <- liftio $ peekAt p contents
return $ D.Yield x (ArrayUnsafe contents start (INDEX_PREV(p,a)))
-- | Unfold an array into a stream in reverse order.
@ -1549,7 +1549,7 @@ toListFB c n MutArray{..} = go arrStart
-- evaluated/written to before we peek at them.
-- XXX
let !x = unsafeInlineIO $ do
r <- peekByteIndex arrContents p
r <- peekAt arrContents p
return r
in c x (go (PTR_NEXT(p,a)))
-}
@ -1566,7 +1566,7 @@ toList MutArray{..} = liftIO $ go arrStart
go p | assert (p <= arrEnd) (p == arrEnd) = return []
go p = do
x <- peekByteIndex p arrContents
x <- peekAt p arrContents
(:) x <$> go (INDEX_NEXT(p,a))
{-# INLINE_NORMAL toStreamDWith #-}
@ -1580,7 +1580,7 @@ toStreamDWith liftio MutArray{..} = D.Stream step arrStart
{-# INLINE_LATE step #-}
step _ p | assert (p <= arrEnd) (p == arrEnd) = return D.Stop
step _ p = liftio $ do
r <- peekByteIndex p arrContents
r <- peekAt p arrContents
return $ D.Yield r (INDEX_NEXT(p,a))
-- | Convert a 'MutArray' into a stream.
@ -1601,7 +1601,7 @@ toStreamKWith liftio MutArray{..} = go arrStart
go p | assert (p <= arrEnd) (p == arrEnd) = K.nil
| otherwise =
let elemM = peekByteIndex p arrContents
let elemM = peekAt p arrContents
in liftio elemM `K.consM` go (INDEX_NEXT(p,a))
{-# INLINE toStreamK #-}
@ -1621,7 +1621,7 @@ toStreamDRevWith liftio MutArray{..} =
{-# INLINE_LATE step #-}
step _ p | p < arrStart = return D.Stop
step _ p = liftio $ do
r <- peekByteIndex p arrContents
r <- peekAt p arrContents
return $ D.Yield r (INDEX_PREV(p,a))
-- | Convert a 'MutArray' into a stream in reverse order.
@ -1644,7 +1644,7 @@ toStreamKRevWith liftio MutArray {..} =
go p | p < arrStart = K.nil
| otherwise =
let elemM = peekByteIndex p arrContents
let elemM = peekAt p arrContents
in liftio elemM `K.consM` go (INDEX_PREV(p,a))
{-# INLINE toStreamKRev #-}
@ -1712,7 +1712,7 @@ writeAppendNUnsafe n action =
return $ toArrayUnsafe arr1
step (ArrayUnsafe contents start end) x = do
liftIO $ pokeByteIndex end contents x
liftIO $ pokeAt end contents x
return $ ArrayUnsafe contents start (INDEX_NEXT(end,a))
-- | Append @n@ elements to an existing array. Any free space left in the array
@ -1772,7 +1772,7 @@ writeNWithUnsafe alloc n = fromArrayUnsafe <$> FL.foldlM' step initial
initial = toArrayUnsafe <$> alloc (max n 0)
step (ArrayUnsafe contents start end) x = do
liftIO $ pokeByteIndex end contents x
liftIO $ pokeAt end contents x
return
$ ArrayUnsafe contents start (INDEX_NEXT(end,a))
@ -1855,7 +1855,7 @@ writeRevNWithUnsafe alloc n = fromArrayUnsafe <$> FL.foldlM' step initial
step (ArrayUnsafe contents start end) x = do
let ptr = INDEX_PREV(start,a)
liftIO $ pokeByteIndex ptr contents x
liftIO $ pokeAt ptr contents x
return
$ ArrayUnsafe contents ptr end
@ -1994,7 +1994,7 @@ fromStreamDNAs ps limit str = do
where
fwrite arrContents ptr x = do
liftIO $ pokeByteIndex ptr arrContents x
liftIO $ pokeAt ptr arrContents x
return $ INDEX_NEXT(ptr,a)
-- | Use the 'writeN' fold instead.
@ -2416,7 +2416,7 @@ strip eq arr@MutArray{..} = liftIO $ do
getStart cur = do
if cur < arrEnd
then do
r <- peekByteIndex cur arrContents
r <- peekAt cur arrContents
if eq r
then getStart (INDEX_NEXT(cur,a))
else return cur
@ -2426,7 +2426,7 @@ strip eq arr@MutArray{..} = liftIO $ do
if cur > low
then do
let prev = INDEX_PREV(cur,a)
r <- peekByteIndex prev arrContents
r <- peekAt prev arrContents
if eq r
then getLast prev low
else return cur

View File

@ -404,7 +404,7 @@ adaptCWith pstep initial extract cont !offset0 !usedCount !input = do
go !_ !cur !pst | cur >= end =
onContinue ((end - start) `div` SIZE_OF(a)) pst
go !_ !cur !pst = do
let !x = unsafeInlineIO $ peekByteIndex cur contents
let !x = unsafeInlineIO $ peekAt cur contents
pRes <- pstep pst x
let elemSize = SIZE_OF(a)
next = INDEX_NEXT(cur,a)

View File

@ -79,7 +79,7 @@ import Foreign.Storable
import Foreign.ForeignPtr (ForeignPtr, withForeignPtr, touchForeignPtr)
import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr)
import Foreign.Ptr (plusPtr, minusPtr, castPtr)
import Streamly.Internal.Data.Unbox as Unboxed (Unbox(peekByteIndex))
import Streamly.Internal.Data.Unbox as Unboxed (Unbox(peekAt))
import GHC.ForeignPtr (mallocPlainForeignPtrAlignedBytes)
import GHC.Ptr (Ptr(..))
import Streamly.Internal.Data.MutArray.Type (MutArray)
@ -411,7 +411,7 @@ unsafeEqArrayN Ring{..} rh A.Array{..} nBytes
check p i = do
(relem :: Word8) <- peek p
aelem <- peekByteIndex i w8Contents
aelem <- peekAt i w8Contents
if relem == aelem
then go (p `plusPtr` 1) (i + 1)
else return False
@ -445,7 +445,7 @@ unsafeEqArray Ring{..} rh A.Array{..} =
check p i = do
(relem :: Word8) <- peek p
aelem <- peekByteIndex i w8Contents
aelem <- peekAt i w8Contents
if relem == aelem
then go (p `plusPtr` 1) (i + 1)
else return False

View File

@ -341,7 +341,7 @@ xorCmp tag off arr =
go8 i = do
let wIntegral = litIntegral i
[|xor (unsafeInlineIO
(Unbox.peekByteIndex
(Unbox.peekAt
($(varE off) + $(litIntegral i))
$(varE arr)))
($(wIntegral) :: Word8) .|.
@ -355,7 +355,7 @@ xorCmp tag off arr =
litIntegral
(shiftAdd w8_w16 [tag !! i, tag !! (i + 1)] :: Word16)
[|xor (unsafeInlineIO
(Unbox.peekByteIndex
(Unbox.peekAt
($(varE off) + $(litIntegral i))
$(varE arr)))
($(wIntegral) :: Word16) .|.
@ -375,7 +375,7 @@ xorCmp tag off arr =
, tag !! (i + 3)
] :: Word32)
[|xor (unsafeInlineIO
(Unbox.peekByteIndex
(Unbox.peekAt
($(varE off) + $(litIntegral i))
$(varE arr)))
($(wIntegral) :: Word32) .|.
@ -399,7 +399,7 @@ xorCmp tag off arr =
, tag !! (i + 7)
])
[|xor (unsafeInlineIO
(Unbox.peekByteIndex
(Unbox.peekAt
($(varE off) + $(litIntegral i))
$(varE arr)))
($(wIntegral) :: Word64) .|.

View File

@ -228,7 +228,7 @@ headerValue (SimpleDataCon _ fields) =
serializeWithSize :: Serialize a => Int -> MutByteArray -> a -> IO Int
serializeWithSize off arr val = do
off1 <- serialize (off + 4) arr val
Unbox.pokeByteIndex off arr (int_w32 (off1 - off - 4) :: Word32)
Unbox.pokeAt off arr (int_w32 (off1 - off - 4) :: Word32)
pure off1
mkRecSerializeExpr :: Name -> SimpleDataCon -> Q Exp
@ -245,7 +245,7 @@ mkRecSerializeExpr initialOffset (con@(SimpleDataCon cname fields)) = do
$(varP (makeI 0)) <- $(serializeW8List afterHLen _arr hval)
let $(openConstructor cname (length fields)) = $(varE _val)
finalOff <- $(mkSerializeExprFields 'serializeWithSize fields)
Unbox.pokeByteIndex
Unbox.pokeAt
$(varE initialOffset)
$(varE _arr)
((fromIntegral :: Int -> Word32)

View File

@ -189,7 +189,7 @@ deserializeUnsafe off arr sz =
in do
-- Keep likely path in the straight branch.
if (next <= sz)
then Unbox.peekByteIndex off arr >>= \val -> pure (next, val)
then Unbox.peekAt off arr >>= \val -> pure (next, val)
else error
$ "deserialize: accessing array at offset = "
++ show (next - 1)
@ -203,7 +203,7 @@ serializeUnsafe off arr val =
#ifdef DEBUG
checkBounds "serialize" next arr
#endif
Unbox.pokeByteIndex off arr val
Unbox.pokeAt off arr val
pure next
#define DERIVE_SERIALIZE_FROM_UNBOX(_type) \
@ -262,7 +262,7 @@ instance forall a. Serialize a => Serialize [a] where
serialize off arr val = do
let off1 = off + Unbox.sizeOf (Proxy :: Proxy Int64)
let pokeList acc o [] =
Unbox.pokeByteIndex off arr (acc :: Int64) >> pure o
Unbox.pokeAt off arr (acc :: Int64) >> pure o
pokeList acc o (x:xs) = do
o1 <- serialize o arr x
pokeList (acc + 1) o1 xs

View File

@ -162,9 +162,9 @@ import Streamly.Internal.Data.MutByteArray.Type (MutByteArray(..))
-- have multiple constructors of different sizes, the size of a sum type is
-- computed as the maximum required by any constructor.
--
-- The 'peekByteIndex' operation reads as many bytes from the mutable byte
-- The 'peekAt' operation reads as many bytes from the mutable byte
-- array as the @size@ of the data type and builds a Haskell data type from
-- these bytes. 'pokeByteIndex' operation converts a Haskell data type to its
-- these bytes. 'pokeAt' operation converts a Haskell data type to its
-- binary representation which consists of @size@ bytes and then stores
-- these bytes into the mutable byte array. These operations do not check the
-- bounds of the array, the user of the type class is expected to check the
@ -214,15 +214,15 @@ import Streamly.Internal.Data.MutByteArray.Type (MutByteArray(..))
-- >>> :{
-- instance Unbox Object where
-- sizeOf _ = 16
-- peekByteIndex i arr = do
-- peekAt i arr = do
-- -- Check the array bounds
-- x0 <- peekByteIndex i arr
-- x1 <- peekByteIndex (i + 8) arr
-- x0 <- peekAt i arr
-- x1 <- peekAt (i + 8) arr
-- return $ Object x0 x1
-- pokeByteIndex i arr (Object x0 x1) = do
-- pokeAt i arr (Object x0 x1) = do
-- -- Check the array bounds
-- pokeByteIndex i arr x0
-- pokeByteIndex (i + 8) arr x1
-- pokeAt i arr x0
-- pokeAt (i + 8) arr x1
-- :}
--
class Unbox a where
@ -233,40 +233,49 @@ class Unbox a where
default sizeOf :: (SizeOfRep (Rep a)) => Proxy a -> Int
sizeOf = genericSizeOf
-- | @peekByteIndex byte-index array@ reads an element of type @a@ from the
-- the given the byte index in the array.
-- | @peekAt byte-offset array@ reads an element of type @a@ from the
-- the given the byte offset in the array.
--
-- IMPORTANT: The implementation of this interface may not check the bounds
-- of the array, the caller must not assume that.
peekByteIndex :: Int -> MutByteArray -> IO a
peekAt :: Int -> MutByteArray -> IO a
{-# INLINE peekByteIndex #-}
default peekByteIndex :: (Generic a, PeekRep (Rep a)) =>
{-# INLINE peekAt #-}
default peekAt :: (Generic a, PeekRep (Rep a)) =>
Int -> MutByteArray -> IO a
peekByteIndex i arr = genericPeekByteIndex arr i
peekAt i arr = genericPeekByteIndex arr i
-- | @pokeByteIndex byte-index array@ writes an element of type @a@ to the
-- the given the byte index in the array.
peekByteIndex :: Int -> MutByteArray -> IO a
peekByteIndex = peekAt
-- | @pokeAt byte-offset array@ writes an element of type @a@ to the
-- the given the byte offset in the array.
--
-- IMPORTANT: The implementation of this interface may not check the bounds
-- of the array, the caller must not assume that.
pokeByteIndex :: Int -> MutByteArray -> a -> IO ()
pokeAt :: Int -> MutByteArray -> a -> IO ()
{-# INLINE pokeByteIndex #-}
default pokeByteIndex :: (Generic a, PokeRep (Rep a)) =>
pokeByteIndex :: Int -> MutByteArray -> a -> IO ()
pokeByteIndex = pokeAt
{-# INLINE pokeAt #-}
default pokeAt :: (Generic a, PokeRep (Rep a)) =>
Int -> MutByteArray -> a -> IO ()
pokeByteIndex i arr = genericPokeByteIndex arr i
pokeAt i arr = genericPokeByteIndex arr i
{-# DEPRECATED peekByteIndex "Use peekAt." #-}
{-# DEPRECATED pokeByteIndex "Use pokeAt." #-}
-- XXX Add asserts to check bounds
#define DERIVE_UNBOXED(_type, _constructor, _readArray, _writeArray, _sizeOf) \
instance Unbox _type where { \
; {-# INLINE peekByteIndex #-} \
; peekByteIndex (I# n) (MutByteArray mbarr) = IO $ \s -> \
; {-# INLINE peekAt #-} \
; peekAt (I# n) (MutByteArray mbarr) = IO $ \s -> \
case _readArray mbarr n s of \
{ (# s1, i #) -> (# s1, _constructor i #) } \
; {-# INLINE pokeByteIndex #-} \
; pokeByteIndex (I# n) (MutByteArray mbarr) (_constructor val) = \
; {-# INLINE pokeAt #-} \
; pokeAt (I# n) (MutByteArray mbarr) (_constructor val) = \
IO $ \s -> (# _writeArray mbarr n val s, () #) \
; {-# INLINE sizeOf #-} \
; sizeOf _ = _sizeOf \
@ -274,24 +283,24 @@ instance Unbox _type where { \
#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 peekAt #-} \
; peekAt i arr = _constructor <$> peekAt i arr \
; {-# INLINE pokeAt #-} \
; pokeAt i arr (_constructor a) = pokeAt 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 \
; {-# INLINE peekAt #-} \
; peekAt i arr = \
peekAt i arr >>= \
(\p1 -> peekAt (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 pokeAt #-} \
; pokeAt i arr (_constructor p1 p2) = \
pokeAt i arr p1 >> \
pokeAt (i + SIZE_OF(_innerType)) arr p2 \
; {-# INLINE sizeOf #-} \
; sizeOf _ = 2 * SIZE_OF(_innerType) \
}
@ -413,11 +422,11 @@ DERIVE_BINARY_UNBOX(,Fingerprint,Fingerprint,Word64)
instance Unbox () where
{-# INLINE peekByteIndex #-}
peekByteIndex _ _ = return ()
{-# INLINE peekAt #-}
peekAt _ _ = return ()
{-# INLINE pokeByteIndex #-}
pokeByteIndex _ _ _ = return ()
{-# INLINE pokeAt #-}
pokeAt _ _ _ = return ()
{-# INLINE sizeOf #-}
sizeOf _ = 1
@ -425,11 +434,11 @@ instance Unbox () where
#if MIN_VERSION_base(4,15,0)
instance Unbox IoSubSystem where
{-# INLINE peekByteIndex #-}
peekByteIndex i arr = toEnum <$> peekByteIndex i arr
{-# INLINE peekAt #-}
peekAt i arr = toEnum <$> peekAt i arr
{-# INLINE pokeByteIndex #-}
pokeByteIndex i arr a = pokeByteIndex i arr (fromEnum a)
{-# INLINE pokeAt #-}
pokeAt i arr a = pokeAt i arr (fromEnum a)
{-# INLINE sizeOf #-}
sizeOf _ = sizeOf (Proxy :: Proxy Int)
@ -437,16 +446,16 @@ instance Unbox IoSubSystem where
instance Unbox Bool where
{-# INLINE peekByteIndex #-}
peekByteIndex i arr = do
res <- peekByteIndex i arr
{-# INLINE peekAt #-}
peekAt i arr = do
res <- peekAt i arr
return $ res /= (0 :: Int8)
{-# INLINE pokeByteIndex #-}
pokeByteIndex i arr a =
{-# INLINE pokeAt #-}
pokeAt i arr a =
if a
then pokeByteIndex i arr (1 :: Int8)
else pokeByteIndex i arr (0 :: Int8)
then pokeAt i arr (1 :: Int8)
else pokeAt i arr (0 :: Int8)
{-# INLINE sizeOf #-}
sizeOf _ = 1
@ -489,7 +498,7 @@ readUnsafe = Peeker (Builder step)
++ show next
++ " end = " ++ show end
#endif
r <- peekByteIndex pos arr
r <- peekAt pos arr
return (r, BoundedPtr arr next end)
{-# INLINE read #-}
@ -506,7 +515,7 @@ read = Peeker (Builder step)
$ error $ "read: reading beyond limit. next = "
++ show next
++ " end = " ++ show end
r <- peekByteIndex pos arr
r <- peekAt pos arr
return (r, BoundedPtr arr next end)
{-# INLINE skipByte #-}
@ -551,7 +560,7 @@ pokeBoundedPtrUnsafe a (BoundedPtr arr pos end) = do
++ show next
++ " end = " ++ show end
#endif
pokeByteIndex pos arr a
pokeAt pos arr a
return (BoundedPtr arr next end)
{-# INLINE pokeBoundedPtr #-}
@ -559,7 +568,7 @@ pokeBoundedPtr :: forall a. Unbox a => a -> BoundedPtr -> IO BoundedPtr
pokeBoundedPtr a (BoundedPtr arr pos end) = do
let next = pos + sizeOf (Proxy :: Proxy a)
when (next > end) $ error "pokeBoundedPtr writing beyond limit"
pokeByteIndex pos arr a
pokeAt pos arr a
return (BoundedPtr arr next end)
--------------------------------------------------------------------------------

View File

@ -252,7 +252,7 @@ mkPeekExprOne tagSize (DataCon cname _ _ fields) =
where
peekField i = [|peekByteIndex $(varE (mkOffsetName i)) $(varE _arr)|]
peekField i = [|peekAt $(varE (mkOffsetName i)) $(varE _arr)|]
mkPeekExpr :: Type -> [DataCon] -> Q Exp
mkPeekExpr headTy cons =
@ -266,7 +266,7 @@ mkPeekExpr headTy cons =
doE
[ bindS
(varP _tag)
[|peekByteIndex $(varE _initialOffset) $(varE _arr)|]
[|peekAt $(varE _initialOffset) $(varE _arr)|]
, noBindS
(caseE
(sigE (varE _tag) (conT tagType))
@ -299,7 +299,7 @@ mkPokeExprTag tagType tagVal = pokeTag
where
pokeTag =
[|pokeByteIndex
[|pokeAt
$(varE _initialOffset)
$(varE _arr)
$((sigE (litE (IntegerL (fromIntegral tagVal))) (conT tagType)))|]
@ -317,7 +317,7 @@ mkPokeExprFields tagSize fields = do
numFields = length fields
pokeField i =
[|pokeByteIndex
[|pokeAt
$(varE (mkOffsetName i))
$(varE _arr)
$(varE (mkFieldName i))|]
@ -402,9 +402,9 @@ deriveUnboxInternal headTy cons mkDec = do
-- none
[ -- PragmaD (InlineP 'sizeOf Inline FunLike AllPhases)
FunD 'sizeOf [Clause [WildP] (NormalB sizeOfMethod) []]
, PragmaD (InlineP 'peekByteIndex Inline FunLike AllPhases)
, PragmaD (InlineP 'peekAt Inline FunLike AllPhases)
, FunD
'peekByteIndex
'peekAt
[ Clause
(if isUnitType cons
then [WildP, WildP]
@ -412,9 +412,9 @@ deriveUnboxInternal headTy cons mkDec = do
(NormalB peekMethod)
[]
]
, PragmaD (InlineP 'pokeByteIndex Inline FunLike AllPhases)
, PragmaD (InlineP 'pokeAt Inline FunLike AllPhases)
, FunD
'pokeByteIndex
'pokeAt
[ Clause
(if isUnitType cons
then [WildP, WildP, WildP]

View File

@ -116,7 +116,7 @@ import Streamly.Internal.Data.Stream (Stream)
import Streamly.Internal.Data.Stream (Step (..))
import Streamly.Internal.Data.SVar.Type (adaptState)
import Streamly.Internal.Data.Tuple.Strict (Tuple'(..))
import Streamly.Internal.Data.Unbox (Unbox(peekByteIndex))
import Streamly.Internal.Data.Unbox (Unbox(peekAt))
import Streamly.Internal.Data.Unfold.Type (Unfold(..))
import Streamly.Internal.System.IO (unsafeInlineIO)
@ -746,7 +746,7 @@ decodeUtf8ArraysWithD cfm (D.Stream step state) =
| p == end = do
return $ Skip $ OuterLoop st Nothing
step' _ _ (InnerLoopDecodeInit st contents p end) = do
x <- liftIO $ peekByteIndex p contents
x <- liftIO $ peekAt p contents
-- Note: It is important to use a ">" instead of a "<=" test here for
-- GHC to generate code layout for default branch prediction for the
-- common case. This is fragile and might change with the compiler
@ -780,7 +780,7 @@ decodeUtf8ArraysWithD cfm (D.Stream step state) =
step' _ _ (InnerLoopDecoding st _ p end sv cp)
| p == end = return $ Skip $ OuterLoop st (Just (sv, cp))
step' table _ (InnerLoopDecoding st contents p end statePtr codepointPtr) = do
x <- liftIO $ peekByteIndex p contents
x <- liftIO $ peekAt p contents
let (Tuple' sv cp) = decode1 table statePtr codepointPtr x
return $
case sv of

View File

@ -46,8 +46,8 @@ import Test.Hspec as H
#else
#define PEEK(i, arr, sz) peekByteIndexWithNextOff i arr
#define POKE(i, arr, val) pokeByteIndexWithNextOff i arr val
#define PEEK(i, arr, sz) peekAtWithNextOff i arr
#define POKE(i, arr, val) pokeAtWithNextOff i arr val
#define TYPE_CLASS Unbox
#ifdef USE_TH
@ -70,23 +70,23 @@ import Test.Hspec as H
#ifndef USE_SERIALIZE
peekByteIndexWithNextOff ::
peekAtWithNextOff ::
forall a. Unbox a
=> Int
-> MutByteArray
-> IO (Int, a)
peekByteIndexWithNextOff i arr = do
val <- peekByteIndex i arr
peekAtWithNextOff i arr = do
val <- peekAt i arr
pure (i + sizeOf (Proxy :: Proxy a), val)
pokeByteIndexWithNextOff ::
pokeAtWithNextOff ::
forall a. Unbox a
=> Int
-> MutByteArray
-> a
-> IO Int
pokeByteIndexWithNextOff i arr val = do
pokeByteIndex i arr val
pokeAtWithNextOff i arr val = do
pokeAt i arr val
pure $ i + sizeOf (Proxy :: Proxy a)
#endif

View File

@ -30,8 +30,8 @@ testSerialization ::
-> IO ()
testSerialization val = do
arr <- MBA.new (sizeOf (Proxy :: Proxy a))
pokeByteIndex 0 arr val
peekByteIndex 0 arr `shouldReturn` val
pokeAt 0 arr val
peekAt 0 arr `shouldReturn` val
-- Size is also implicitly tested while serializing and deserializing.
checkSizeOf :: forall a. Unbox a => Proxy a -> Int -> IO ()