Move Streamly.FileSystem.Handle to streamly-core

And some formatting changes.
This commit is contained in:
Ranjeet Kumar Ranjan 2022-09-22 17:30:00 +05:30 committed by Harendra Kumar
parent e718389b2c
commit f609af1d01
7 changed files with 42 additions and 64 deletions

View File

@ -131,10 +131,8 @@ import Streamly.Internal.System.IO (defaultChunkSize)
import qualified Streamly.Data.Fold as FL
import qualified Streamly.Data.Array.Unboxed as A
import qualified Streamly.Internal.Data.Array.Unboxed.Type as A
(byteLength, asPtrUnsafe)
import qualified Streamly.Internal.Data.Array.Unboxed.Mut as MArray
(Array(..), newPinnedArrayBytes, asPtrUnsafe)
import qualified Streamly.Internal.Data.Array.Stream.Foreign as AS
import qualified Streamly.Internal.Data.Array.Unboxed.Mut.Type as MArray
import qualified Streamly.Internal.Data.Refold.Type as Refold
import qualified Streamly.Internal.Data.Fold.Type as FL(refoldMany)
import qualified Streamly.Internal.Data.Stream as S
@ -212,8 +210,7 @@ getChunkOf = undefined
-- read may be less than or equal to @size@.
-- @since 0.9.0
{-# INLINE _getChunksWith #-}
_getChunksWith :: (MonadIO m)
=> Int -> Handle -> Stream m (Array Word8)
_getChunksWith :: MonadIO m => Int -> Handle -> Stream m (Array Word8)
_getChunksWith size h = S.fromStreamK go
where
-- XXX use cons/nil instead
@ -231,8 +228,7 @@ _getChunksWith size h = S.fromStreamK go
--
-- @since 0.9.0
{-# INLINE_NORMAL getChunksWith #-}
getChunksWith :: (MonadIO m) =>
Int -> Handle -> Stream m (Array Word8)
getChunksWith :: MonadIO m => Int -> Handle -> Stream m (Array Word8)
getChunksWith size h = S.fromStreamD (D.Stream step ())
where
{-# INLINE_LATE step #-}
@ -313,7 +309,7 @@ readChunksFromToWith = Unfold step inject
--
-- @since 0.9.0
{-# INLINE getChunks #-}
getChunks :: (MonadIO m) => Handle -> Stream m (Array Word8)
getChunks :: MonadIO m => Handle -> Stream m (Array Word8)
getChunks = getChunksWith defaultChunkSize
-- | Unfolds a handle into a stream of 'Word8' arrays. Requests to the IO
@ -362,7 +358,7 @@ readWithBufferOf = readWith
--
-- /Pre-release/
{-# INLINE getBytesWith #-}
getBytesWith :: (MonadIO m) => Int -> Handle -> Stream m Word8
getBytesWith :: MonadIO m => Int -> Handle -> Stream m Word8
getBytesWith size h = AS.concat $ getChunksWith size h
-- TODO
@ -386,7 +382,7 @@ read = UF.many A.read readChunks
--
-- /Pre-release/
{-# INLINE getBytes #-}
getBytes :: (MonadIO m) => Handle -> Stream m Word8
getBytes :: MonadIO m => Handle -> Stream m Word8
getBytes = AS.concat . getChunks
-------------------------------------------------------------------------------
@ -600,7 +596,7 @@ write = toHandleWith A.defaultChunkSize
--
-- @since 0.7.0
{-# INLINE readUtf8 #-}
readUtf8 :: (MonadIO m) => Handle -> Stream m Char
readUtf8 :: MonadIO m => Handle -> Stream m Char
readUtf8 = decodeUtf8 . read
-- |
@ -622,7 +618,7 @@ writeUtf8 h s = write h $ encodeUtf8 s
--
-- @since 0.7.0
{-# INLINE writeUtf8ByLines #-}
writeUtf8ByLines :: (MonadIO m) => Handle -> Stream m Char -> m ()
writeUtf8ByLines :: MonadIO m => Handle -> Stream m Char -> m ()
writeUtf8ByLines = undefined
-- | Read UTF-8 lines from a file handle and apply the specified fold to each
@ -630,7 +626,7 @@ writeUtf8ByLines = undefined
--
-- @since 0.7.0
{-# INLINE readLines #-}
readLines :: (MonadIO m) => Handle -> Fold m Char b -> Stream m b
readLines :: MonadIO m => Handle -> Fold m Char b -> Stream m b
readLines h f = foldLines (readUtf8 h) f
-------------------------------------------------------------------------------

View File

@ -42,7 +42,7 @@ import Prelude hiding (String, lines, words, unlines, unwords)
-- ["lines","this","string","",""]
--
{-# INLINE lines #-}
lines :: (MonadIO m) => Stream m Char -> Stream m (Array Char)
lines :: MonadIO m => Stream m Char -> Stream m (Array Char)
lines = S.lines A.write
-- | Break a string up into a stream of strings, which were delimited
@ -54,7 +54,7 @@ lines = S.lines A.write
-- ["A","newline","is","considered","white","space?"]
--
{-# INLINE words #-}
words :: (MonadIO m) => Stream m Char -> Stream m (Array Char)
words :: MonadIO m => Stream m Char -> Stream m (Array Char)
words = S.words A.write
-- | Flattens the stream of @Array Char@, after appending a terminating
@ -71,7 +71,7 @@ words = S.words A.write
--
-- > unlines . lines /= id
{-# INLINE unlines #-}
unlines :: (MonadIO m) => Stream m (Array Char) -> Stream m Char
unlines :: MonadIO m => Stream m (Array Char) -> Stream m Char
unlines = S.unlines A.read
-- | Flattens the stream of @Array Char@, after appending a separating
@ -88,5 +88,5 @@ unlines = S.unlines A.read
--
-- > unwords . words /= id
{-# INLINE unwords #-}
unwords :: (MonadIO m) => Stream m (Array Char) -> Stream m Char
unwords :: MonadIO m => Stream m (Array Char) -> Stream m Char
unwords = S.unwords A.read

View File

@ -830,8 +830,7 @@ decodeUtf8ArraysD = decodeUtf8ArraysWithD TransliterateCodingFailure
--
-- /Pre-release/
{-# INLINE decodeUtf8Arrays #-}
decodeUtf8Arrays ::
(MonadIO m) => Stream m (Array Word8) -> Stream m Char
decodeUtf8Arrays :: MonadIO m => Stream m (Array Word8) -> Stream m Char
decodeUtf8Arrays =
fromStreamD . decodeUtf8ArraysD . toStreamD
@ -846,7 +845,7 @@ decodeUtf8ArraysD' = decodeUtf8ArraysWithD ErrorOnCodingFailure
--
-- /Pre-release/
{-# INLINE decodeUtf8Arrays' #-}
decodeUtf8Arrays' :: (MonadIO m) => Stream m (Array Word8) -> Stream m Char
decodeUtf8Arrays' :: MonadIO m => Stream m (Array Word8) -> Stream m Char
decodeUtf8Arrays' = fromStreamD . decodeUtf8ArraysD' . toStreamD
{-# INLINE decodeUtf8ArraysD_ #-}
@ -861,7 +860,7 @@ decodeUtf8ArraysD_ = decodeUtf8ArraysWithD DropOnCodingFailure
-- /Pre-release/
{-# INLINE decodeUtf8Arrays_ #-}
decodeUtf8Arrays_ ::
(MonadIO m) => Stream m (Array Word8) -> Stream m Char
MonadIO m => Stream m (Array Word8) -> Stream m Char
decodeUtf8Arrays_ =
fromStreamD . decodeUtf8ArraysD_ . toStreamD
@ -1025,7 +1024,7 @@ encodeObject encode u = Stream.fold Array.write . encode . Stream.unfold u
--
-- /Internal/
{-# INLINE encodeObjects #-}
encodeObjects :: (MonadIO m) =>
encodeObjects :: MonadIO m =>
(Stream m Char -> Stream m Word8)
-> Unfold m a Char
-> Stream m a
@ -1037,8 +1036,10 @@ encodeObjects encode u = Stream.mapM (encodeObject encode u)
--
-- @since 0.8.0
{-# INLINE encodeStrings #-}
encodeStrings :: (MonadIO m) =>
(Stream m Char -> Stream m Word8) -> Stream m String -> Stream m (Array Word8)
encodeStrings :: MonadIO m =>
(Stream m Char -> Stream m Word8)
-> Stream m String
-> Stream m (Array Word8)
encodeStrings encode = encodeObjects encode Unfold.fromList
{-
@ -1116,7 +1117,7 @@ words f m = Stream.fromStreamD $ D.wordsBy isSpace f (Stream.toStreamD m)
--
-- /Pre-release/
{-# INLINE unlines #-}
unlines :: (MonadIO m) => Unfold m a Char -> Stream m a -> Stream m Char
unlines :: MonadIO m => Unfold m a Char -> Stream m a -> Stream m Char
unlines = Stream.interposeSuffix '\n'
-- | Unfold the elements of a stream to character streams using the supplied
@ -1130,5 +1131,5 @@ unlines = Stream.interposeSuffix '\n'
--
-- /Pre-release/
{-# INLINE unwords #-}
unwords :: (MonadIO m) => Unfold m a Char -> Stream m a -> Stream m Char
unwords :: MonadIO m => Unfold m a Char -> Stream m a -> Stream m Char
unwords = Stream.interpose ' '

View File

@ -324,15 +324,17 @@ library
, Streamly.Internal.Data.Array.Unboxed
, Streamly.Internal.Data.Array.Stream.Mut.Foreign
, Streamly.Internal.Data.Array.Stream.Fold.Foreign
, Streamly.Internal.Data.Array.Stream.Foreign
-- streamly-unicode
, Streamly.Internal.Unicode.Stream
, Streamly.Internal.Unicode.String
, Streamly.Internal.Unicode.Char.Parser
, Streamly.Internal.Unicode.Array.Char
-- Filesystem/IO
, Streamly.Internal.FileSystem.Handle
-- Ring Arrays
, Streamly.Internal.Data.Ring.Foreign
, Streamly.Internal.Data.Ring
@ -349,9 +351,8 @@ library
, Streamly.Data.Unfold
, Streamly.Data.Array.Unboxed
, Streamly.Data.Array.Unboxed.Mut
-- Text Processing
, Streamly.Unicode.Stream
, Streamly.FileSystem.Handle
if flag(dev)
exposed-modules:

View File

@ -52,34 +52,16 @@ where
import Control.Monad.IO.Class (MonadIO(..))
import Data.Either (isRight, isLeft, fromLeft, fromRight)
-- import Data.Word (Word8)
-- import Foreign.ForeignPtr (withForeignPtr)
-- import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr)
-- import Foreign.Ptr (minusPtr, plusPtr)
-- import Foreign.Storable (Storable(..))
-- import GHC.ForeignPtr (mallocPlainForeignPtrBytes)
-- import System.IO (Handle, hGetBufSome, hPutBuf)
import Prelude hiding (read)
-- import Streamly.Data.Fold (Fold)
import Streamly.Data.Stream (Stream)
import Streamly.Internal.Data.Unfold.Type (Unfold(..))
-- import Streamly.Internal.Data.Array.Unboxed.Type
-- (Array(..), writeNUnsafe, defaultChunkSize, shrinkToFit,
-- lpackArraysChunksOf)
-- import Streamly.Internal.Data.Stream (Stream)
import Streamly.Internal.Data.Stream.IsStream.Type (IsStream)
-- import Streamly.String (encodeUtf8, decodeUtf8, foldLines)
-- import qualified Streamly.Data.Fold as FL
-- import qualified Streamly.Internal.Data.Fold.Type as FL
import qualified Streamly.Data.Unfold as UF
import qualified Streamly.Internal.Data.Unfold as UF (mapM2)
-- import qualified Streamly.Internal.Data.Array.Stream.Foreign as AS
import qualified Streamly.Internal.Data.Stream.IsStream as S
-- import qualified Streamly.Data.Array.Unboxed as A
-- import qualified Streamly.Internal.Data.Stream.StreamD.Type as D
import qualified Streamly.Data.Stream as S
import qualified System.Directory as Dir
import Prelude hiding (read)
{-
{-# INLINABLE readArrayUpto #-}
readArrayUpto :: Int -> Handle -> IO (Array Word8)
@ -104,8 +86,7 @@ readArrayUpto size h = do
-- The maximum size of a single array is specified by @size@. The actual size
-- read may be less than or equal to @size@.
{-# INLINE _toChunksWithBufferOf #-}
_toChunksWithBufferOf :: (IsStream t, MonadIO m)
=> Int -> Handle -> t m (Array Word8)
_toChunksWithBufferOf :: MonadIO m => Int -> Handle -> Stream m (Array Word8)
_toChunksWithBufferOf size h = go
where
-- XXX use cons/nil instead
@ -121,7 +102,7 @@ _toChunksWithBufferOf size h = go
--
-- @since 0.7.0
{-# INLINE_NORMAL toChunksWithBufferOf #-}
toChunksWithBufferOf :: (IsStream t, MonadIO m) => Int -> Handle -> t m (Array Word8)
toChunksWithBufferOf :: MonadIO m => Int -> Handle -> Stream m (Array Word8)
toChunksWithBufferOf size h = D.fromStreamD (D.Stream step ())
where
{-# INLINE_LATE step #-}
@ -161,7 +142,7 @@ readChunksWithBufferOf = Unfold step return
--
-- @since 0.7.0
{-# INLINE toChunks #-}
toChunks :: (IsStream t, MonadIO m) => Handle -> t m (Array Word8)
toChunks :: MonadIO m => Handle -> Stream m (Array Word8)
toChunks = toChunksWithBufferOf defaultChunkSize
-- | Unfolds a handle into a stream of 'Word8' arrays. Requests to the IO
@ -196,7 +177,7 @@ readWithBufferOf = UF.many readChunksWithBufferOf A.read
--
-- /Pre-release/
{-# INLINE toStreamWithBufferOf #-}
toStreamWithBufferOf :: (IsStream t, MonadIO m) => Int -> Handle -> t m Word8
toStreamWithBufferOf :: MonadIO m => Int -> Handle -> Stream m Word8
toStreamWithBufferOf chunkSize h = AS.concat $ toChunksWithBufferOf chunkSize h
-}
@ -254,7 +235,7 @@ readDirs = fmap (fromLeft undefined) $ UF.filter isLeft readEither
--
-- /Pre-release/
{-# INLINE toStream #-}
toStream :: (IsStream t, MonadIO m) => String -> t m String
toStream :: MonadIO m => String -> Stream m String
toStream = S.unfold read
-- | Read directories as Left and files as Right. Filter out "." and ".."
@ -262,8 +243,7 @@ toStream = S.unfold read
--
-- /Pre-release/
{-# INLINE toEither #-}
toEither :: (IsStream t, MonadIO m)
=> String -> t m (Either String String)
toEither :: MonadIO m => String -> Stream m (Either String String)
toEither = S.unfold readEither
-- | Read files only.
@ -271,7 +251,7 @@ toEither = S.unfold readEither
-- /Internal/
--
{-# INLINE toFiles #-}
toFiles :: (IsStream t, MonadIO m) => String -> t m String
toFiles :: MonadIO m => String -> Stream m String
toFiles = S.unfold readFiles
-- | Read directories only.
@ -279,7 +259,7 @@ toFiles = S.unfold readFiles
-- /Internal/
--
{-# INLINE toDirs #-}
toDirs :: (IsStream t, MonadIO m) => String -> t m String
toDirs :: MonadIO m => String -> Stream m String
toDirs = S.unfold readDirs
{-

View File

@ -219,8 +219,10 @@ extra-source-files:
core/src/Streamly/Data/Unbox.hs
core/src/Streamly/Data/Array/Unboxed.hs
core/src/Streamly/Data/Array/Unboxed/Mut.hs
core/src/Streamly/FileSystem/Handle.hs
core/src/Streamly/Internal/Data/Time/Clock/Darwin.c
core/src/Streamly/Internal/Data/Time/Clock/Windows.c
core/src/Streamly/Internal/FileSystem/Handle.hs
core/src/Streamly/Internal/Unicode/Array/Char.hs
core/src/Streamly/Internal/Unicode/Char/Parser.hs
core/src/Streamly/Internal/Unicode/Stream.hs
@ -491,7 +493,6 @@ library
, Streamly.Internal.Unicode.Char
-- streamly-filesystem
, Streamly.Internal.FileSystem.Handle
, Streamly.Internal.FileSystem.Dir
, Streamly.Internal.FileSystem.File
@ -506,7 +507,6 @@ library
, Streamly.Prelude
-- Filesystem/IO
, Streamly.FileSystem.Handle
, Streamly.Console.Stdio
-- Network/IO