@@ -123,6 +123,7 @@ import Streamly.Internal.Data.Time.Clock
123123 (Clock (Monotonic ), asyncClock , readClock )
124124import Streamly.Internal.Data.Time.Units
125125 (toAbsTime , AbsTime , toRelTime64 , RelTime64 , addToAbsTime64 )
126+ import Streamly.Internal.System.IO (unsafeInlineIO )
126127
127128#ifdef USE_UNFOLDS_EVERYWHERE
128129import qualified Streamly.Internal.Data.Unfold as Unfold
@@ -1143,35 +1144,35 @@ fromFoldableM = Prelude.foldr consM nil
11431144-- From pointers
11441145-------------------------------------------------------------------------------
11451146
1146- -- | Keep reading 'Storable' elements from 'Ptr' onwards.
1147+ -- | Keep reading 'Storable' elements from an immutable 'Ptr' onwards.
11471148--
11481149-- /Unsafe:/ The caller is responsible for safe addressing.
11491150--
11501151-- /Pre-release/
11511152{-# INLINE fromPtr #-}
1152- fromPtr :: forall m a . (MonadIO m , Storable a ) => Ptr a -> Stream m a
1153+ fromPtr :: forall m a . (Monad m , Storable a ) => Ptr a -> Stream m a
11531154fromPtr = Stream step
11541155
11551156 where
11561157
11571158 {-# INLINE_LATE step #-}
11581159 step _ p = do
1159- x <- liftIO $ peek p
1160+ let ! x = unsafeInlineIO $ peek p
11601161 return $ Yield x (PTR_NEXT (p, a))
11611162
1162- -- | Take @n@ 'Storable' elements starting from 'Ptr' onwards.
1163+ -- | Take @n@ 'Storable' elements starting from an immutable 'Ptr' onwards.
11631164--
11641165-- >>> fromPtrN n = Stream.take n . Stream.fromPtr
11651166--
11661167-- /Unsafe:/ The caller is responsible for safe addressing.
11671168--
11681169-- /Pre-release/
11691170{-# INLINE fromPtrN #-}
1170- fromPtrN :: (MonadIO m , Storable a ) => Int -> Ptr a -> Stream m a
1171+ fromPtrN :: (Monad m , Storable a ) => Int -> Ptr a -> Stream m a
11711172fromPtrN n = take n . fromPtr
11721173
1173- -- | Read bytes from an 'Addr#' until a 0 byte is encountered, the 0 byte is
1174- -- not included in the stream.
1174+ -- | Read bytes from an immutable 'Addr#' until a 0 byte is encountered, the 0
1175+ -- byte is not included in the stream.
11751176--
11761177-- >>> :set -XMagicHash
11771178-- >>> fromByteStr# addr = Stream.takeWhile (/= 0) $ Stream.fromPtr $ Ptr addr
@@ -1185,6 +1186,5 @@ fromPtrN n = take n . fromPtr
11851186-- [1,2,3]
11861187--
11871188{-# INLINE fromByteStr# #-}
1188- fromByteStr# :: MonadIO m => Addr # -> Stream m Word8
1189- fromByteStr# addr =
1190- takeWhile (/= 0 ) $ fromPtr $ Ptr addr
1189+ fromByteStr# :: Monad m => Addr # -> Stream m Word8
1190+ fromByteStr# addr = takeWhile (/= 0 ) $ fromPtr $ Ptr addr
0 commit comments