Use streamly-bytestring
This commit is contained in:
parent
a6036a7aea
commit
7d0ca1c230
@ -31,10 +31,6 @@ library
|
|||||||
System.Posix.Directory.Traversals,
|
System.Posix.Directory.Traversals,
|
||||||
System.Posix.FD
|
System.Posix.FD
|
||||||
c-sources: cbits/dirutils.c
|
c-sources: cbits/dirutils.c
|
||||||
|
|
||||||
other-modules: Streamly.ByteString
|
|
||||||
Streamly.ByteString.Lazy
|
|
||||||
-- other-extensions:
|
|
||||||
build-depends: base >= 4.8 && <5
|
build-depends: base >= 4.8 && <5
|
||||||
, IfElse
|
, IfElse
|
||||||
, bytestring >= 0.10.0.0
|
, bytestring >= 0.10.0.0
|
||||||
@ -43,6 +39,7 @@ library
|
|||||||
, hpath-filepath >= 0.10.2 && < 0.11
|
, hpath-filepath >= 0.10.2 && < 0.11
|
||||||
, safe-exceptions >= 0.1
|
, safe-exceptions >= 0.1
|
||||||
, streamly >= 0.7
|
, streamly >= 0.7
|
||||||
|
, streamly-bytestring >= 0.1
|
||||||
, time >= 1.8
|
, time >= 1.8
|
||||||
, unix >= 2.5
|
, unix >= 2.5
|
||||||
, unix-bytestring
|
, unix-bytestring
|
||||||
|
@ -200,8 +200,8 @@ import HPath
|
|||||||
import HPath.IO.Errors
|
import HPath.IO.Errors
|
||||||
import Prelude hiding (appendFile, readFile, writeFile)
|
import Prelude hiding (appendFile, readFile, writeFile)
|
||||||
import Streamly
|
import Streamly
|
||||||
import Streamly.ByteString
|
import Streamly.External.ByteString
|
||||||
import qualified Streamly.ByteString.Lazy as SL
|
import qualified Streamly.External.ByteString.Lazy as SL
|
||||||
import qualified Streamly.Data.Fold as FL
|
import qualified Streamly.Data.Fold as FL
|
||||||
import Streamly.Memory.Array
|
import Streamly.Memory.Array
|
||||||
import qualified Streamly.FileSystem.Handle as FH
|
import qualified Streamly.FileSystem.Handle as FH
|
||||||
@ -942,7 +942,7 @@ readFileStream :: Path b
|
|||||||
readFileStream (Path fp) = do
|
readFileStream (Path fp) = do
|
||||||
fd <- openFd fp SPI.ReadOnly [] Nothing
|
fd <- openFd fp SPI.ReadOnly [] Nothing
|
||||||
handle <- SPI.fdToHandle fd
|
handle <- SPI.fdToHandle fd
|
||||||
let stream = (S.unfold (SU.finally SIO.hClose FH.readChunks) handle) >>= arrayToByteString
|
let stream = fmap fromArray (S.unfold (SU.finally SIO.hClose FH.readChunks) handle)
|
||||||
pure stream
|
pure stream
|
||||||
|
|
||||||
|
|
||||||
@ -989,7 +989,7 @@ writeFileL (Path fp) fmode lbs = do
|
|||||||
handle <- bracketOnError (openFd fp SPI.WriteOnly [SPDF.oTrunc] fmode) (SPI.closeFd) $ SPI.fdToHandle
|
handle <- bracketOnError (openFd fp SPI.WriteOnly [SPDF.oTrunc] fmode) (SPI.closeFd) $ SPI.fdToHandle
|
||||||
finally (streamlyCopy handle) (SIO.hClose handle)
|
finally (streamlyCopy handle) (SIO.hClose handle)
|
||||||
where
|
where
|
||||||
streamlyCopy tH = S.fold (FH.writeChunks tH) $ SL.fromByteString lbs
|
streamlyCopy tH = S.fold (FH.writeChunks tH) $ SL.toChunks lbs
|
||||||
|
|
||||||
|
|
||||||
-- |Append a given ByteString to a file.
|
-- |Append a given ByteString to a file.
|
||||||
|
@ -1,57 +0,0 @@
|
|||||||
{-# LANGUAGE RankNTypes #-}
|
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
|
||||||
|
|
||||||
module Streamly.ByteString where
|
|
||||||
|
|
||||||
import Control.Monad.IO.Class
|
|
||||||
import Data.ByteString hiding (length)
|
|
||||||
import qualified Data.ByteString as BS
|
|
||||||
import Data.ByteString.Unsafe
|
|
||||||
import Data.Word (Word8)
|
|
||||||
import Foreign.ForeignPtr
|
|
||||||
import Foreign.ForeignPtr.Unsafe
|
|
||||||
import Foreign.Ptr (castPtr, minusPtr, plusPtr)
|
|
||||||
import Prelude hiding (length)
|
|
||||||
import Streamly
|
|
||||||
import Streamly.Internal.Memory.Array.Types
|
|
||||||
import Streamly.Memory.Array
|
|
||||||
import qualified Streamly.Prelude as S
|
|
||||||
|
|
||||||
toByteString ::
|
|
||||||
forall m. (MonadIO m, MonadAsync m)
|
|
||||||
=> SerialT m (Array Word8)
|
|
||||||
-> m ByteString
|
|
||||||
toByteString stream =
|
|
||||||
let xs = S.mapM arrayToByteString stream
|
|
||||||
ys = S.foldlM' (\a b -> pure $ a <> b) mempty xs
|
|
||||||
in ys
|
|
||||||
|
|
||||||
arrayToByteString :: (MonadIO m) => Array Word8 -> m ByteString
|
|
||||||
arrayToByteString arr
|
|
||||||
| length arr == 0 = return mempty
|
|
||||||
arrayToByteString Array {..} =
|
|
||||||
liftIO $
|
|
||||||
withForeignPtr aStart $ \ptr ->
|
|
||||||
unsafePackCStringFinalizer ptr aLen (return ())
|
|
||||||
where
|
|
||||||
aLen =
|
|
||||||
let p = unsafeForeignPtrToPtr aStart
|
|
||||||
in aEnd `minusPtr` p
|
|
||||||
|
|
||||||
byteStringToArray :: (MonadIO m) => ByteString -> m (Array Word8)
|
|
||||||
byteStringToArray bs =
|
|
||||||
liftIO $
|
|
||||||
unsafeUseAsCStringLen
|
|
||||||
bs
|
|
||||||
(\(ptr, _) -> do
|
|
||||||
let endPtr pr = (castPtr pr `plusPtr` (BS.length bs))
|
|
||||||
fptr <- newForeignPtr_ (castPtr ptr)
|
|
||||||
return $ Array {aStart = fptr, aEnd = endPtr ptr, aBound = endPtr ptr})
|
|
||||||
|
|
||||||
fromByteString ::
|
|
||||||
forall m. (MonadIO m)
|
|
||||||
=> ByteString
|
|
||||||
-> m (Array Word8)
|
|
||||||
fromByteString bs = byteStringToArray bs
|
|
@ -1,45 +0,0 @@
|
|||||||
{-# LANGUAGE RankNTypes #-}
|
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
|
||||||
|
|
||||||
module Streamly.ByteString.Lazy where
|
|
||||||
|
|
||||||
import Control.Monad.IO.Class
|
|
||||||
import qualified Data.ByteString as BS
|
|
||||||
import Data.ByteString.Lazy (ByteString, foldlChunks, fromChunks)
|
|
||||||
import Data.ByteString.Unsafe
|
|
||||||
import Data.Word (Word8)
|
|
||||||
import Foreign.ForeignPtr
|
|
||||||
import Foreign.ForeignPtr.Unsafe
|
|
||||||
import Foreign.Ptr (castPtr, minusPtr, plusPtr)
|
|
||||||
import Prelude hiding (length)
|
|
||||||
import Streamly
|
|
||||||
import Streamly.ByteString (arrayToByteString, byteStringToArray)
|
|
||||||
import Streamly.Memory.Array
|
|
||||||
import qualified Streamly.Prelude as S
|
|
||||||
|
|
||||||
toByteString ::
|
|
||||||
forall m. (MonadIO m, MonadAsync m)
|
|
||||||
=> SerialT m (Array Word8)
|
|
||||||
-> m ByteString
|
|
||||||
toByteString stream = do
|
|
||||||
ys :: [BS.ByteString] <- S.toList $ S.mapM arrayToByteString stream
|
|
||||||
pure $ fromChunks ys
|
|
||||||
|
|
||||||
stepFunction ::
|
|
||||||
forall m. (MonadIO m)
|
|
||||||
=> SerialT m (Array Word8)
|
|
||||||
-> BS.ByteString
|
|
||||||
-> SerialT m (Array Word8)
|
|
||||||
stepFunction stream1 bs = do
|
|
||||||
arr <- liftIO $ byteStringToArray bs
|
|
||||||
let stream2 = pure arr
|
|
||||||
stream1 <> stream2
|
|
||||||
|
|
||||||
fromByteString ::
|
|
||||||
forall m. (MonadIO m)
|
|
||||||
=> ByteString
|
|
||||||
-> SerialT m (Array Word8)
|
|
||||||
fromByteString bs = foldlChunks stepFunction mempty bs
|
|
||||||
|
|
Loading…
Reference in New Issue
Block a user