summaryrefslogtreecommitdiff
path: root/src/System
diff options
context:
space:
mode:
authorSam T <pxqr.sta@gmail.com>2013-07-17 01:03:04 +0400
committerSam T <pxqr.sta@gmail.com>2013-07-17 01:03:04 +0400
commit33ae6235029ad9d2a9b5726afff13b660783b86a (patch)
treee4a3af3ca177f5dd488bd198e94f5ff9308390b4 /src/System
parentbc1c976e9175b4ac13430ba9c23ea8b099401e9e (diff)
~ Add stubs to nonblocking IO.
Diffstat (limited to 'src/System')
-rw-r--r--src/System/Torrent/Storage.hs71
1 files changed, 52 insertions, 19 deletions
diff --git a/src/System/Torrent/Storage.hs b/src/System/Torrent/Storage.hs
index c355d697..46ea20f1 100644
--- a/src/System/Torrent/Storage.hs
+++ b/src/System/Torrent/Storage.hs
@@ -13,8 +13,6 @@
13-- * As ordinary mmaped file storage - when we need to store 13-- * As ordinary mmaped file storage - when we need to store
14-- data in the filesystem. 14-- data in the filesystem.
15-- 15--
16--
17--
18{-# LANGUAGE DoAndIfThenElse #-} 16{-# LANGUAGE DoAndIfThenElse #-}
19{-# LANGUAGE NamedFieldPuns #-} 17{-# LANGUAGE NamedFieldPuns #-}
20{-# LANGUAGE RecordWildCards #-} 18{-# LANGUAGE RecordWildCards #-}
@@ -29,8 +27,9 @@ module System.Torrent.Storage
29 -- * Modification 27 -- * Modification
30 , getBlk, putBlk, selBlk 28 , getBlk, putBlk, selBlk
31 29
30 -- * TODO expose only File interface!
32 -- * File interface 31 -- * File interface
33 , FD, openFD, closeFD, readFD, readFDAll 32 , FD, openFD, closeFD, readFD, writeFD
34 ) where 33 ) where
35 34
36import Control.Applicative 35import Control.Applicative
@@ -40,9 +39,7 @@ import Control.Monad
40import Control.Monad.Trans 39import Control.Monad.Trans
41 40
42import Data.ByteString as B 41import Data.ByteString as B
43import qualified Data.ByteString.Internal as B
44import qualified Data.ByteString.Lazy as Lazy 42import qualified Data.ByteString.Lazy as Lazy
45import Data.List as L
46import Text.PrettyPrint 43import Text.PrettyPrint
47import System.FilePath 44import System.FilePath
48import System.Directory 45import System.Directory
@@ -227,41 +224,77 @@ interface.
227type Offset = Int 224type Offset = Int
228type Size = Int 225type Size = Int
229 226
230newtype FD = FD { fdData :: ByteString } 227data FD = FD {
228 fdData :: ByteString
229 , fdNoBlock :: Bool
230 }
231 231
232-- TODO implement blocking and non blocking modes?
233 232
233-- TODO return "is dir" error
234-- | This call correspond to open(2) with the following parameters: 234-- | This call correspond to open(2) with the following parameters:
235-- 235--
236-- * OpenMode = ReadOnly; 236-- * OpenMode = ReadOnly;
237-- 237--
238-- * OpenFileFlags = O_NONBLOCK. 238-- * OpenFileFlags = O_NONBLOCK. (not true yet)
239-- 239--
240openFD :: FilePath -> Storage -> IO (Either Errno FD) 240openFD :: FilePath -> Bool -> Storage -> IO (Either Errno FD)
241openFD path Storage {..} 241openFD path nonblock Storage {..}
242 | Just offset <- fileOffset path (tInfo metainfo) 242 | Just offset <- fileOffset path (tInfo metainfo)
243 , Just bs <- lookupRegion (fromIntegral offset) payload 243 , Just bs <- lookupRegion (fromIntegral offset) payload
244 = return $ Right $ FD bs 244 = return $ Right $ FD bs nonblock
245 | otherwise = return $ Left $ eNOENT 245 | otherwise = return $ Left $ eNOENT
246 246
247-- | This call correspond to close(2). 247-- | This call correspond to close(2).
248closeFD :: FD -> IO () 248closeFD :: FD -> IO ()
249closeFD _ = return () 249closeFD _ = return ()
250 250
251-- TODO return "is dir" error 251-- TODO
252-- TODO check if region is not out of bound 252maskRegion :: FD -> Offset -> Size -> Maybe Size
253maskRegion FD {..} offset siz = return siz
254
255-- TODO
256isComplete :: FD -> Offset -> Size -> IO Size
257isComplete _ _ siz = return siz
258
259-- TODO
260enqueueRead :: FD -> Offset -> Size -> IO ()
261enqueueRead _ _ _ = return ()
262
263-- TODO
264readAhead :: FD -> Offset -> Size -> IO ()
265readAhead _ _ _ = return ()
266
267-- TODO
268waitRegion :: FD -> Offset -> Size -> IO ByteString
269waitRegion _ _ _ = return B.empty
270
271-- TODO implement blocking and non blocking modes?
253-- TODO check if region completely downloaded 272-- TODO check if region completely downloaded
254-- TODO if not we could return EAGAIN 273-- TODO if not we could return EAGAIN
255-- TODO enqueue read to piece manager 274-- TODO enqueue read to piece manager
256-- WARN use BS.copy?
257-- | This call correspond to pread(2). 275-- | This call correspond to pread(2).
258readFD :: FD -> Offset -> Size -> IO (Either Errno ByteString) 276readFD :: FD -> Offset -> Size -> IO (Either Errno ByteString)
259readFD FD {..} offset len = do 277readFD fd @ FD {..} offset reqSize =
260 let res = B.take len $ B.drop offset fdData 278 case maskRegion fd offset reqSize of
261 return $ Right res 279 Nothing -> return $ Right B.empty
280 Just expSize -> do
281 availSize <- isComplete fd offset expSize
282 if availSize == expSize then haveAllReg expSize else haveSomeReg expSize
283 where
284 haveAllReg expSize = do
285 readAhead fd offset expSize
286 return $ Right $ slice offset expSize fdData
262 287
263readFDAll :: FD -> IO ByteString 288 haveSomeReg expSize
264readFDAll FD {..} = return fdData 289 | fdNoBlock = return $ Left $ eAGAIN
290 | otherwise = do
291 bs <- waitRegion fd offset expSize
292 readAhead fd offset expSize
293 return $ Right bs
294
295-- TODO
296writeFD :: FD -> ByteString -> Offset -> IO ()
297writeFD FD {..} bs offset = return ()
265 298
266{----------------------------------------------------------------------- 299{-----------------------------------------------------------------------
267 Internal 300 Internal