Remove peekWith and pokeWith helper functions in Unbox

This commit is contained in:
Adithya Kumar 2023-07-25 01:02:05 +05:30 committed by Harendra Kumar
parent 39b2790262
commit eee265456e
10 changed files with 69 additions and 92 deletions

View File

@ -114,11 +114,7 @@ import Data.Word (Word8)
import Foreign.C.String (CString)
import Foreign.Ptr (castPtr)
import Foreign.Storable (Storable)
import Streamly.Internal.Data.Unbox
( Unbox
, peekWith
, sizeOf
)
import Streamly.Internal.Data.Unbox (Unbox(..))
import Prelude hiding (length, null, last, map, (!!), read, concat)
import Streamly.Internal.Data.Array.Mut.Type (ArrayUnsafe(..))
@ -239,7 +235,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 $ peekWith contents p
let !x = unsafeInlineIO $ peekByteIndex p contents
let !p1 = INDEX_NEXT(p,a)
return $ D.Yield x (ArrayUnsafe contents end p1)
@ -263,7 +259,7 @@ getIndexRev i arr =
$ do
let elemPtr = RINDEX_OF(arrEnd arr, i, a)
if i >= 0 && elemPtr >= arrStart arr
then Just <$> peekWith (arrContents arr) elemPtr
then Just <$> peekByteIndex elemPtr (arrContents arr)
else return Nothing
-- |
@ -425,7 +421,7 @@ getIndex i arr =
$ do
let elemPtr = INDEX_OF(arrStart arr, i, a)
if i >= 0 && INDEX_VALID(elemPtr, arrEnd arr, a)
then Just <$> peekWith (arrContents arr) elemPtr
then Just <$> peekByteIndex elemPtr (arrContents arr)
else return Nothing
-- | Given a stream of array indices, read the elements on those indices from

View File

@ -235,11 +235,8 @@ import Foreign.C.Types (CSize(..), CInt(..))
import Foreign.Ptr (plusPtr, minusPtr, nullPtr)
import Streamly.Internal.Data.Unbox
( MutableByteArray(..)
, Unbox
, Unbox(..)
, getMutableByteArray#
, peekWith
, pokeWith
, sizeOf
, touch
)
import GHC.Base
@ -497,7 +494,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 $ pokeWith arrContents index x
liftIO $ pokeByteIndex index arrContents x
invalidIndex :: String -> Int -> a
invalidIndex label i =
@ -515,7 +512,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 $ pokeWith arrContents index x
then liftIO $ pokeByteIndex index arrContents x
else invalidIndex "putIndex" i
-- | Write an input stream of (index, value) pairs to an array. Throws an
@ -541,9 +538,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 <- peekWith arrContents index
r <- peekByteIndex index arrContents
let (x, res) = f r
pokeWith arrContents index x
pokeByteIndex index arrContents x
return res
-- | Modify a given index of an array using a modifier function.
@ -555,9 +552,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 <- peekWith arrContents index
r <- peekByteIndex index arrContents
let (x, res) = f r
pokeWith arrContents index x
pokeByteIndex index arrContents x
return res
else invalidIndex "modifyIndex" i
@ -591,8 +588,8 @@ modify MutArray{..} f = liftIO $
go i =
when (INDEX_VALID(i,arrEnd,a)) $ do
r <- peekWith arrContents i
pokeWith arrContents i (f r)
r <- peekByteIndex i arrContents
pokeByteIndex i arrContents (f r)
go (INDEX_NEXT(i,a))
-- XXX We could specify the number of bytes to swap instead of Proxy. Need
@ -606,10 +603,10 @@ swapArrayByteIndices ::
-> Int
-> IO ()
swapArrayByteIndices _ arrContents i1 i2 = do
r1 <- peekWith arrContents i1
r2 <- peekWith arrContents i2
pokeWith arrContents i1 (r2 :: a)
pokeWith arrContents i2 (r1 :: a)
r1 <- peekByteIndex i1 arrContents
r2 <- peekByteIndex i2 arrContents
pokeByteIndex i1 arrContents (r2 :: a)
pokeByteIndex i2 arrContents (r1 :: a)
-- | Swap the elements at two indices without validating the indices.
--
@ -882,7 +879,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 ())
pokeWith arrContents arrEnd x
pokeByteIndex arrEnd arrContents x
return $ arr {arrEnd = newEnd}
-- | Really really unsafe, appends the element into the first array, may
@ -996,7 +993,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 $ peekWith arrContents index
liftIO $ peekByteIndex index arrContents
-- | /O(1)/ Lookup the element at the given index. Index starts from 0.
--
@ -1005,7 +1002,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 <$> peekWith arrContents index
then liftIO $ Just <$> peekByteIndex index arrContents
else return Nothing
-- | /O(1)/ Lookup the element at the given index from the end of the array.
@ -1018,7 +1015,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 $ peekWith arrContents index
then liftIO $ peekByteIndex index arrContents
else invalidIndex "getIndexRev" i
data GetIndicesState contents start end st =
@ -1158,7 +1155,7 @@ partitionBy f arr@MutArray{..} = liftIO $ do
-- Invariant low < high on entry, and on return as well
moveHigh low high = do
h <- peekWith arrContents high
h <- peekByteIndex high arrContents
if f h
then
-- Correctly classified, continue the loop
@ -1178,7 +1175,7 @@ partitionBy f arr@MutArray{..} = liftIO $ do
-- low <= high
-- Both low and high are valid locations within the array
go low high = do
l <- peekWith arrContents low
l <- peekByteIndex low arrContents
if f l
then
-- low is wrongly classified
@ -1189,8 +1186,8 @@ partitionBy f arr@MutArray{..} = liftIO $ do
case r of
Nothing -> return low
Just (high1, h) -> do -- low < high1
pokeWith arrContents low h
pokeWith arrContents high1 l
pokeByteIndex low arrContents h
pokeByteIndex high1 arrContents l
let low1 = INDEX_NEXT(low,a)
high2 = INDEX_PREV(high1,a)
if low1 <= high2
@ -1334,7 +1331,7 @@ chunksOf n (D.Stream step state) =
r <- step (adaptState gst) st
case r of
D.Yield x s -> do
liftIO $ pokeWith contents end x
liftIO $ pokeByteIndex end contents x
let end1 = INDEX_NEXT(end,a)
return $
if end1 >= bound
@ -1396,7 +1393,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 $ peekWith contents p
x <- liftIO $ peekByteIndex p contents
return $ D.Yield x (InnerLoop st contents (INDEX_NEXT(p,a)) end)
-- | Use the "readerRev" unfold instead.
@ -1426,7 +1423,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 $ peekWith contents p
x <- liftIO $ peekByteIndex p contents
let cur = INDEX_PREV(p,a)
return $ D.Yield x (InnerLoop st contents cur start)
@ -1465,7 +1462,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 $ peekWith contents cur
!x <- liftio $ peekByteIndex cur contents
return $ D.Yield x (ArrayUnsafe contents (INDEX_NEXT(cur,a)) end)
extract = return . fromArrayUnsafe
@ -1496,7 +1493,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 $ peekWith contents p
!x <- liftio $ peekByteIndex p contents
return $ D.Yield x (ArrayUnsafe contents start (INDEX_PREV(p,a)))
-- | Unfold an array into a stream in reverse order.
@ -1527,7 +1524,7 @@ toListFB c n MutArray{..} = go arrStart
-- evaluated/written to before we peek at them.
-- XXX
let !x = unsafeInlineIO $ do
r <- peekWith arrContents p
r <- peekByteIndex arrContents p
return r
in c x (go (PTR_NEXT(p,a)))
-}
@ -1544,7 +1541,7 @@ toList MutArray{..} = liftIO $ go arrStart
go p | assert (p <= arrEnd) (p == arrEnd) = return []
go p = do
x <- peekWith arrContents p
x <- peekByteIndex p arrContents
(:) x <$> go (INDEX_NEXT(p,a))
{-# INLINE_NORMAL toStreamDWith #-}
@ -1558,7 +1555,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 <- peekWith arrContents p
r <- peekByteIndex p arrContents
return $ D.Yield r (INDEX_NEXT(p,a))
-- | Convert a 'MutArray' into a stream.
@ -1579,7 +1576,7 @@ toStreamKWith liftio MutArray{..} = go arrStart
go p | assert (p <= arrEnd) (p == arrEnd) = K.nil
| otherwise =
let elemM = peekWith arrContents p
let elemM = peekByteIndex p arrContents
in liftio elemM `K.consM` go (INDEX_NEXT(p,a))
{-# INLINE toStreamK #-}
@ -1599,7 +1596,7 @@ toStreamDRevWith liftio MutArray{..} =
{-# INLINE_LATE step #-}
step _ p | p < arrStart = return D.Stop
step _ p = liftio $ do
r <- peekWith arrContents p
r <- peekByteIndex p arrContents
return $ D.Yield r (INDEX_PREV(p,a))
-- | Convert a 'MutArray' into a stream in reverse order.
@ -1622,7 +1619,7 @@ toStreamKRevWith liftio MutArray {..} =
go p | p < arrStart = K.nil
| otherwise =
let elemM = peekWith arrContents p
let elemM = peekByteIndex p arrContents
in liftio elemM `K.consM` go (INDEX_PREV(p,a))
{-# INLINE toStreamKRev #-}
@ -1690,7 +1687,7 @@ writeAppendNUnsafe n action =
return $ toArrayUnsafe arr1
step (ArrayUnsafe contents start end) x = do
liftIO $ pokeWith contents end x
liftIO $ pokeByteIndex 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
@ -1750,7 +1747,7 @@ writeNWithUnsafe alloc n = fromArrayUnsafe <$> FL.foldlM' step initial
initial = toArrayUnsafe <$> alloc (max n 0)
step (ArrayUnsafe contents start end) x = do
liftIO $ pokeWith contents end x
liftIO $ pokeByteIndex end contents x
return
$ ArrayUnsafe contents start (INDEX_NEXT(end,a))
@ -1806,7 +1803,7 @@ writeRevNWithUnsafe alloc n = fromArrayUnsafe <$> FL.foldlM' step initial
step (ArrayUnsafe contents start end) x = do
let ptr = INDEX_PREV(start,a)
liftIO $ pokeWith contents ptr x
liftIO $ pokeByteIndex ptr contents x
return
$ ArrayUnsafe contents ptr end
@ -1938,7 +1935,7 @@ fromStreamDN limit str = do
where
fwrite arrContents ptr x = do
liftIO $ pokeWith arrContents ptr x
liftIO $ pokeByteIndex ptr arrContents x
return $ INDEX_NEXT(ptr,a)
-- | Create a 'MutArray' from the first N elements of a list. The array is
@ -2328,7 +2325,7 @@ strip eq arr@MutArray{..} = liftIO $ do
getStart cur = do
if cur < arrEnd
then do
r <- peekWith arrContents cur
r <- peekByteIndex cur arrContents
if eq r
then getStart (INDEX_NEXT(cur,a))
else return cur
@ -2338,7 +2335,7 @@ strip eq arr@MutArray{..} = liftIO $ do
if cur > low
then do
let prev = INDEX_PREV(cur,a)
r <- peekWith arrContents prev
r <- peekByteIndex prev arrContents
if eq r
then getLast prev low
else return cur

View File

@ -95,7 +95,7 @@ import GHC.Ptr (Ptr(..))
import Streamly.Internal.Data.Array.Mut.Type (MutArray(..), MutableByteArray)
import Streamly.Internal.Data.Fold.Type (Fold(..))
import Streamly.Internal.Data.Stream.StreamD.Type (Stream)
import Streamly.Internal.Data.Unbox (Unbox, peekWith, sizeOf)
import Streamly.Internal.Data.Unbox (Unbox(..))
import Streamly.Internal.Data.Unfold.Type (Unfold(..))
import Text.Read (readPrec)
@ -447,8 +447,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 peekWith at them.
let !x = unsafeInlineIO $ peekWith arrContents p
-- evaluated/written to before we peekByteIndex at them.
let !x = unsafeInlineIO $ peekByteIndex p arrContents
in c x (go (INDEX_NEXT(p,a)))
-- | Convert an 'Array' into a list.
@ -636,7 +636,7 @@ _toStreamD_ size Array{..} = D.Stream step arrStart
{-# INLINE_LATE step #-}
step _ p | p == arrEnd = return D.Stop
step _ p = liftIO $ do
x <- peekWith arrContents p
x <- peekByteIndex p arrContents
return $ D.Yield x (p + size)
{-

View File

@ -63,7 +63,7 @@ import Control.Exception (assert)
import Control.Monad.IO.Class (MonadIO(..))
import Data.Bifunctor (first)
import Data.Proxy (Proxy(..))
import Streamly.Internal.Data.Unbox (peekWith, sizeOf, Unbox)
import Streamly.Internal.Data.Unbox (Unbox(..))
import GHC.Types (SPEC(..))
import Streamly.Internal.Data.Array.Mut.Type (touch)
import Streamly.Internal.Data.Array.Type (Array(..))
@ -123,7 +123,7 @@ fromFold (Fold.Fold fstep finitial fextract) =
assert (cur == end) (return ())
return $ Partial 0 fs
goArray !_ !cur !fs = do
x <- liftIO $ peekWith contents cur
x <- liftIO $ peekByteIndex cur contents
res <- fstep fs x
let elemSize = SIZE_OF(a)
next = INDEX_NEXT(cur,a)
@ -160,7 +160,7 @@ fromParserD (ParserD.Parser step1 initial1 extract1) =
else return $ st (arrRem + n) fs1
goArray !_ !cur !fs = do
x <- liftIO $ peekWith contents cur
x <- liftIO $ peekByteIndex cur contents
liftIO $ touch contents
res <- step1 fs x
let elemSize = SIZE_OF(a)

View File

@ -42,11 +42,9 @@ import Data.Proxy (Proxy(..))
import Control.Monad.IO.Class (MonadIO(..))
import Streamly.Internal.Data.Unbox
( MutableByteArray(..)
, Unbox
, sizeOf
, peekWith
, pokeWith
, Unbox(..)
, newUnpinnedBytes
, sizeOf
)
import qualified Streamly.Internal.Data.Stream.StreamD.Type as D
@ -61,7 +59,7 @@ newtype IORef a = IORef MutableByteArray
newIORef :: forall a. Unbox a => a -> IO (IORef a)
newIORef x = do
var <- newUnpinnedBytes (sizeOf (Proxy :: Proxy a))
pokeWith var 0 x
pokeByteIndex 0 var x
return $ IORef var
-- | Write a value to an 'IORef'.
@ -69,14 +67,14 @@ newIORef x = do
-- /Pre-release/
{-# INLINE writeIORef #-}
writeIORef :: Unbox a => IORef a -> a -> IO ()
writeIORef (IORef var) = pokeWith var 0
writeIORef (IORef var) = pokeByteIndex 0 var
-- | Read a value from an 'IORef'.
--
-- /Pre-release/
{-# INLINE readIORef #-}
readIORef :: Unbox a => IORef a -> IO a
readIORef (IORef var) = peekWith var 0
readIORef (IORef var) = peekByteIndex 0 var
-- | Modify the value of an 'IORef' using a function with strict application.
--

View File

@ -46,7 +46,7 @@ import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.Proxy (Proxy(..))
import GHC.Types (SPEC(..))
import Streamly.Internal.Data.Array.Type (Array(..))
import Streamly.Internal.Data.Unbox (peekWith, sizeOf, Unbox)
import Streamly.Internal.Data.Unbox (Unbox(..))
import Streamly.Internal.System.IO (unsafeInlineIO)
import qualified Control.Monad.Fail as Fail
@ -430,7 +430,7 @@ parseDToK 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 $ peekWith contents cur
let !x = unsafeInlineIO $ peekByteIndex 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, peekWith)
import Streamly.Internal.Data.Unbox as Unboxed (Unbox(peekByteIndex))
import GHC.ForeignPtr (mallocPlainForeignPtrAlignedBytes)
import GHC.Ptr (Ptr(..))
import Streamly.Internal.Data.Array.Mut.Type (MutArray)
@ -411,7 +411,7 @@ unsafeEqArrayN Ring{..} rh A.Array{..} nBytes
check p i = do
(relem :: Word8) <- peek p
aelem <- peekWith w8Contents i
aelem <- peekByteIndex 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 <- peekWith w8Contents i
aelem <- peekByteIndex i w8Contents
if relem == aelem
then go (p `plusPtr` 1) (i + 1)
else return False

View File

@ -69,7 +69,7 @@ import Control.Exception (assert)
import Control.Monad.IO.Class (MonadIO(..))
import Data.Proxy (Proxy(..))
import Data.Word (Word8)
import Streamly.Internal.Data.Unbox (Unbox, peekWith, sizeOf)
import Streamly.Internal.Data.Unbox (Unbox(..))
import Fusion.Plugin.Types (Fuse(..))
import GHC.Exts (SpecConstrAnnotation(..))
import GHC.Types (SPEC(..))
@ -201,7 +201,7 @@ unlines sep (D.Stream step state) = D.Stream step' (OuterLoop state)
return $ D.Yield sep $ OuterLoop st
step' _ (InnerLoop st contents p end) = do
x <- liftIO $ peekWith contents p
x <- liftIO $ peekByteIndex p contents
return $ D.Yield x (InnerLoop st contents (INDEX_NEXT(p,a)) end)
-------------------------------------------------------------------------------
@ -355,7 +355,7 @@ foldBreakD (FL.Fold fstep initial extract) stream@(D.Stream step state) = do
| cur == end = do
go SPEC s fs
goArray !_ st fp@(Tuple' end contents) !cur !fs = do
x <- liftIO $ peekWith contents cur
x <- liftIO $ peekByteIndex cur contents
res <- fstep fs x
let next = INDEX_NEXT(cur,a)
case res of
@ -388,7 +388,7 @@ foldBreakK (FL.Fold fstep initial extract) stream = do
| cur == end = do
go fs st
goArray !fs st fp@(Tuple' end contents) !cur = do
x <- liftIO $ peekWith contents cur
x <- liftIO $ peekByteIndex cur contents
res <- fstep fs x
let next = INDEX_NEXT(cur,a)
case res of
@ -597,7 +597,7 @@ parseBreakD
| cur == end = do
go SPEC s backBuf pst
gobuf !_ s backBuf fp@(Tuple' end contents) !cur !pst = do
x <- liftIO $ peekWith contents cur
x <- liftIO $ peekByteIndex contents cur
pRes <- pstep pst x
let next = INDEX_NEXT(cur,a)
case pRes of
@ -669,7 +669,7 @@ parseBreakK (PRD.Parser pstep initial extract) stream = do
-- Use strictness on "cur" to keep it unboxed
goArray !pst backBuf st (Array _ cur end) | cur == end = go pst st backBuf
goArray !pst backBuf st (Array contents cur end) = do
x <- liftIO $ peekWith contents cur
x <- liftIO $ peekByteIndex cur contents
pRes <- pstep pst x
let next = INDEX_NEXT(cur,a)
case pRes of
@ -714,7 +714,7 @@ parseBreakK (PRD.Parser pstep initial extract) stream = do
goExtract !pst backBuf (Array _ cur end)
| cur == end = goStop pst backBuf
goExtract !pst backBuf (Array contents cur end) = do
x <- liftIO $ peekWith contents cur
x <- liftIO $ peekByteIndex cur contents
pRes <- pstep pst x
let next = INDEX_NEXT(cur,a)
case pRes of

View File

@ -7,8 +7,6 @@
module Streamly.Internal.Data.Unbox
( Unbox(..)
, peekWith
, pokeWith
, MutableByteArray(..)
, touch
, getMutableByteArray#
@ -482,18 +480,6 @@ instance Unbox Bool where
{-# INLINE sizeOf #-}
sizeOf _ = 1
--------------------------------------------------------------------------------
-- Functions
--------------------------------------------------------------------------------
{-# INLINE peekWith #-}
peekWith :: Unbox a => MutableByteArray -> Int -> IO a
peekWith arr i = peekByteIndex i arr
{-# INLINE pokeWith #-}
pokeWith :: Unbox a => MutableByteArray -> Int -> a -> IO ()
pokeWith arr i = pokeByteIndex i arr
--------------------------------------------------------------------------------
-- Generic deriving
--------------------------------------------------------------------------------

View File

@ -108,7 +108,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 (peekWith)
import Streamly.Internal.Data.Unbox (Unbox(peekByteIndex))
import Streamly.Internal.Data.Unfold.Type (Unfold(..))
import Streamly.Internal.System.IO (unsafeInlineIO)
@ -745,7 +745,7 @@ decodeUtf8ArraysWithD cfm (D.Stream step state) =
| p == end = do
return $ Skip $ OuterLoop st Nothing
step' _ _ (InnerLoopDecodeInit st contents p end) = do
x <- liftIO $ peekWith contents p
x <- liftIO $ peekByteIndex 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
@ -779,7 +779,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 $ peekWith contents p
x <- liftIO $ peekByteIndex p contents
let (Tuple' sv cp) = decode1 table statePtr codepointPtr x
return $
case sv of