Skip to content

Commit

Permalink
Rename write APIs and fix warnings for streamly-0.3.0
Browse files Browse the repository at this point in the history
  • Loading branch information
adithyaov committed Dec 1, 2024
1 parent 207ada5 commit c6f65c9
Show file tree
Hide file tree
Showing 4 changed files with 30 additions and 14 deletions.
24 changes: 16 additions & 8 deletions src/Streamly/External/Text.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,8 +9,8 @@ module Streamly.External.Text

, reader

, unsafeWriteN
, unsafeWrite
, unsafeCreateOf
, unsafeCreate
)
where

Expand Down Expand Up @@ -42,6 +42,14 @@ import Prelude hiding (read)
#define EMPTY MBArr.nil
#endif

#if MIN_VERSION_streamly_core(0,3,0)
#define CREATE_OF Array.createOf
#define CREATE Array.create
#else
#define CREATE_OF Array.writeN
#define CREATE Array.write
#endif

-- | Convert a 'Text' to an array of 'Word8'. It can be done in constant time.
{-# INLINE toArray #-}
toArray :: Text -> Array Word8
Expand Down Expand Up @@ -72,11 +80,11 @@ reader :: Monad m => Unfold m Text Word8
reader = lmap toArray Array.reader

-- | Fold a stream of Word8 to a 'Text' of given size in bytes.
{-# INLINE unsafeWriteN #-}
unsafeWriteN :: MonadIO m => Int -> Fold m Word8 Text
unsafeWriteN i = unsafeFromArray <$> Array.writeN i
{-# INLINE unsafeCreateOf #-}
unsafeCreateOf :: MonadIO m => Int -> Fold m Word8 Text
unsafeCreateOf i = unsafeFromArray <$> CREATE_OF i

-- | Fold a stream of Word8 to a 'Text' of appropriate size.
{-# INLINE unsafeWrite #-}
unsafeWrite :: MonadIO m => Fold m Word8 Text
unsafeWrite = unsafeFromArray <$> Array.write
{-# INLINE unsafeCreate #-}
unsafeCreate :: MonadIO m => Fold m Word8 Text
unsafeCreate = unsafeFromArray <$> CREATE
10 changes: 9 additions & 1 deletion src/Streamly/External/Text/Lazy.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE CPP #-}

module Streamly.External.Text.Lazy
( chunkReader
, reader
Expand Down Expand Up @@ -25,6 +27,12 @@ import qualified Streamly.Data.Stream as Stream

import Prelude hiding (read)

#if MIN_VERSION_streamly_core(0,3,0)
#define UNFOLD_EACH Unfold.unfoldEach
#else
#define UNFOLD_EACH Unfold.many
#endif

-- | Unfold a lazy 'Text' to a stream of 'Array' 'Words'.
{-# INLINE chunkReader #-}
chunkReader :: Monad m => Unfold m Text (Array Word8)
Expand All @@ -37,7 +45,7 @@ chunkReader = Unfold step seed
-- | Unfold a lazy 'Text' to a stream of Word8
{-# INLINE reader #-}
reader :: Monad m => Unfold m Text Word8
reader = Unfold.many Array.reader chunkReader
reader = UNFOLD_EACH Array.reader chunkReader

-- XXX Should this be called readChunks?
-- | Convert a lazy 'Text' to a serial stream of 'Array' 'Word8'.
Expand Down
2 changes: 1 addition & 1 deletion streamly-text.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ library
exposed-modules: Streamly.External.Text
, Streamly.External.Text.Lazy
build-depends: base >=4.7 && <5
, streamly-core >=0.2.0 && <0.2.3
, streamly-core >=0.2.0 && <0.3.1
, text >=2.0 && <2.1.2
hs-source-dirs: src
default-language: Haskell2010
Expand Down
8 changes: 4 additions & 4 deletions test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -75,9 +75,9 @@ main = do
(pure . Strict.unsafeFromArray)
(pure . runIdentity)
pipelinePropStrict
"Strict.unsafeWrite . Strict.reader"
"Strict.unsafeCreate . Strict.reader"
(Stream.unfold Strict.reader)
(Stream.fold Strict.unsafeWrite)
(Stream.fold Strict.unsafeCreate)
id
pipelinePropLazy
"Lazy.unsafeFromChunks . Lazy.toChunks"
Expand All @@ -95,7 +95,7 @@ main = do
Lazy.unsafeFromChunks
(pure . runIdentity)
pipelinePropLazy
"fmap Text.fromStrict . Strict.unsafeWrite . Lazy.reader"
"fmap Text.fromStrict . Strict.unsafeCreate . Lazy.reader"
(Stream.unfold Lazy.reader)
(fmap BSL.fromStrict . Stream.fold Strict.unsafeWrite)
(fmap BSL.fromStrict . Stream.fold Strict.unsafeCreate)
id

0 comments on commit c6f65c9

Please sign in to comment.