Add readChunksFromToWith, read ranges from Handle

This commit is contained in:
Ranjeet Ranjan 2020-11-11 21:42:15 +05:30 committed by Harendra Kumar
parent 2842d5089c
commit debc6a95d4
3 changed files with 83 additions and 3 deletions

View File

@ -79,6 +79,7 @@ module Streamly.FileSystem.Handle
, readWithBufferOf
, readChunks
, readChunksWithBufferOf
, readChunksFromToWith
-- ** Writing
-- | 'TextEncoding', 'NewLineMode', and 'Buffering' options of the

View File

@ -105,7 +105,7 @@ import Foreign.ForeignPtr (withForeignPtr)
import Foreign.Ptr (minusPtr, plusPtr)
import Foreign.Storable (Storable(..))
import GHC.ForeignPtr (mallocPlainForeignPtrBytes)
import System.IO (Handle, hGetBufSome, hPutBuf)
import System.IO (Handle, SeekMode(..), hGetBufSome, hPutBuf, hSeek)
import Prelude hiding (read)
import Streamly.Internal.BaseCompat
@ -257,9 +257,32 @@ readChunksWithBufferOf = Unfold step return
--
--
{-# INLINE_NORMAL readChunksFromToWith #-}
readChunksFromToWith :: -- MonadIO m =>
readChunksFromToWith :: MonadIO m =>
Unfold m (Int, Int, Int, Handle) (Array Word8)
readChunksFromToWith = undefined
readChunksFromToWith = Unfold step inject
where
inject (from, to, buffSize, h) = do
liftIO $ hSeek h AbsoluteSeek $ fromIntegral from
return (to - from + 1, buffSize, h)
{-# INLINE_LATE step #-}
step (remaining, buffSize, h) =
if remaining <= 0
then return D.Stop
else
do
arr <- getChunk (min buffSize remaining) h
return $
case A.length arr of
0 -> D.Stop
len ->
if (remaining - len) >= 0
then
D.Yield arr (remaining - len, buffSize, h)
else
error "Bug: getChunk returned array length more than expected"
-- XXX read 'Array a' instead of Word8
--

View File

@ -61,6 +61,9 @@ testData = "This is the test data for FileSystem.Handle ??`!@#$%^&*~~))`]"
testDataLarge :: String
testDataLarge = concat $ replicate 6000 testData
testBinData :: String
testBinData = "01234567890123456789012345678901234567890123456789"
executor :: (Handle -> SerialT IO Char) -> IO (SerialT IO Char)
executor f =
withSystemTempDirectory "fs_handle" $ \fp -> do
@ -152,6 +155,53 @@ testWriteWithChunk =
let arr = Array.fromList ls
return (testDataLarge == utf8ToString arr)
testReadChunksFromToWith :: Int -> Int -> Int -> String -> Property
testReadChunksFromToWith from to buffSize expRes =
monadicIO $ do
res <- run go
assert res
where
go =
withSystemTempDirectory "fs_handle" $ \fp -> do
let fpathRead = fp </> "tmp_read.txt"
writeFile fpathRead testBinData
h <- openFile fpathRead ReadMode
ls <- Stream.toList $
Stream.unfold
Handle.readChunksFromToWith
(from, to, buffSize, h)
return ( expRes == show ls)
-- Test for first byte
testReadChunksFromToWithFirstByte :: Property
testReadChunksFromToWithFirstByte = testReadChunksFromToWith 0 0 15 "[[48]]"
-- Test for second byte
testReadChunksFromToWithSecondByte :: Property
testReadChunksFromToWithSecondByte = testReadChunksFromToWith 1 1 15 "[[49]]"
-- Test for second to 10th bytes
testReadChunksFromToWithSecondToTenthBytes :: Property
testReadChunksFromToWithSecondToTenthBytes =
testReadChunksFromToWith 1 10 15 "[[49,50,51,52,53,54,55,56,57,48]]"
-- Test for offset of buffer size
testReadChunksFromToWithBuffSizeOffset :: Property
testReadChunksFromToWithBuffSizeOffset =
testReadChunksFromToWith 15 25 15 "[[53,54,55,56,57,48,49,50,51,52,53]]"
-- Test with multi buffer size
testReadChunksFromToWithMultiBuff :: Property
testReadChunksFromToWithMultiBuff =
testReadChunksFromToWith
5 22 5 "[[53,54,55,56,57],[48,49,50,51,52],[53,54,55,56,57],[48,49,50]]"
testReadChunksFromToWithRangeInvalid :: Property
testReadChunksFromToWithRangeInvalid = testReadChunksFromToWith 15 5 15 "[]"
moduleName :: String
moduleName = "FileSystem.Handle"
@ -166,6 +216,12 @@ main =
prop "readWithBufferOf" $ testRead readWithBufferFromHandle
prop "readChunks" $ testRead readChunksFromHandle
prop "readChunksWithBufferOf" $ testRead readChunksWithBuffer
prop "readChunksFromToWithFirstByte" testReadChunksFromToWithFirstByte
prop "readChunksFromToWithSecondByte" testReadChunksFromToWithSecondByte
prop "readChunksFromToWithSecondToTenthBytes" testReadChunksFromToWithSecondToTenthBytes
prop "readChunksFromToWithBuffSizeOffset" testReadChunksFromToWithBuffSizeOffset
prop "readChunksFromToWithMultiBuff" testReadChunksFromToWithMultiBuff
prop "readChunksFromToWithRangeInvalid" testReadChunksFromToWithRangeInvalid
describe "Write To Handle" $ do
prop "write" $ testWrite Handle.write
prop "writeWithBufferOf" $ testWrite $ Handle.writeWithBufferOf 1024