library
exposed-modules: FuncTorrent.Bencode,
- FuncTorrent.Fileops,
FuncTorrent.Logger,
FuncTorrent.Metainfo,
FuncTorrent.Network
+++ /dev/null
-module FuncTorrent.Fileops
- (createDummyFile,
- writeFileAtOffset,
- readFileAtOffset
- ) where
-
-import Prelude hiding (writeFile)
-
-import System.IO (withFile, hSeek, IOMode(..), SeekMode(..))
-import System.Directory (doesFileExist)
-import Data.ByteString (ByteString, writeFile, hPut, hGet)
-import qualified Data.ByteString.Char8 as BC (replicate)
-
-createDummyFile :: FilePath -> Int -> IO ()
-createDummyFile path size = do
- dfe <- doesFileExist path
- if dfe
- then return ()
- else
- writeFile path (BC.replicate size '\0')
-
--- write into a file at a specific offet
-writeFileAtOffset :: FilePath -> Integer -> ByteString -> IO ()
-writeFileAtOffset path offset block =
- withFile path ReadWriteMode (\h -> do
- hSeek h AbsoluteSeek offset
- hPut h block)
-readFileAtOffset :: FilePath -> Integer -> Integer -> IO ByteString
-readFileAtOffset path offset len =
- withFile path ReadWriteMode (\h -> do
- hSeek h AbsoluteSeek offset
- hGet h (fromInteger len))
import Safe (headMay)
import FuncTorrent.Metainfo (Info(..), Metainfo(..))
-import FuncTorrent.Utils (splitN, splitNum)
-import FuncTorrent.Fileops (createDummyFile, writeFileAtOffset, readFileAtOffset)
+import FuncTorrent.Utils (splitN, splitNum, createDummyFile, writeFileAtOffset, readFileAtOffset)
import FuncTorrent.PeerMsgs (Peer(..), PeerMsg(..), sendMsg, getMsg, genHandshakeMsg)
data PState = PState { handle :: Handle
-module FuncTorrent.Utils where
+module FuncTorrent.Utils
+ (createDummyFile,
+ writeFileAtOffset,
+ readFileAtOffset,
+ splitNum,
+ splitN
+ )
+ where
+import Prelude hiding (writeFile)
+
+import System.IO (withFile, hSeek, IOMode(..), SeekMode(..))
+import System.Directory (doesFileExist)
+import Data.ByteString (ByteString, writeFile, hPut, hGet)
import qualified Data.ByteString.Char8 as BC
+import qualified Data.ByteString.Char8 as BC (replicate)
splitN :: Int -> BC.ByteString -> [BC.ByteString]
splitN n bs | BC.null bs = []
splitNum n d | n == 0 = []
| n < d = [n]
| otherwise = d : splitNum (n - d) d
+
+createDummyFile :: FilePath -> Int -> IO ()
+createDummyFile path size = do
+ dfe <- doesFileExist path
+ if dfe
+ then return ()
+ else
+ writeFile path (BC.replicate size '\0')
+
+-- write into a file at a specific offet
+writeFileAtOffset :: FilePath -> Integer -> ByteString -> IO ()
+writeFileAtOffset path offset block =
+ withFile path ReadWriteMode (\h -> do
+ hSeek h AbsoluteSeek offset
+ hPut h block)
+readFileAtOffset :: FilePath -> Integer -> Integer -> IO ByteString
+readFileAtOffset path offset len =
+ withFile path ReadWriteMode (\h -> do
+ hSeek h AbsoluteSeek offset
+ hGet h (fromInteger len))