]> git.rkrishnan.org Git - functorrent.git/blobdiff - src/FuncTorrent/Utils.hs
rename tracker response function, Utils, catch exceptions.
[functorrent.git] / src / FuncTorrent / Utils.hs
index e5a4a559eddf28f3d4ecf0ff122f483fe4946e8b..2a2797626527c8bdc7f3f983361bed31f127e129 100644 (file)
@@ -1,7 +1,52 @@
-module FuncTorrent.Utils where
+module FuncTorrent.Utils
+       (createDummyFile,
+        writeFileAtOffset,
+        readFileAtOffset,
+        splitNum,
+        splitN,
+        verifyHash
+       )
+       where
 
+import Prelude hiding (writeFile, take)
+
+import qualified Crypto.Hash.SHA1 as SHA1 (hash)
+import Control.Exception.Base (IOException, try)
+import Data.ByteString (ByteString, writeFile, hPut, hGet, take)
 import qualified Data.ByteString.Char8 as BC
+import System.IO (withFile, hSeek, IOMode(..), SeekMode(..))
+import System.Directory (doesFileExist)
 
 splitN :: Int -> BC.ByteString -> [BC.ByteString]
 splitN n bs | BC.null bs = []
             | otherwise = BC.take n bs : splitN n (BC.drop n bs)
+
+splitNum :: Integer -> Integer -> [Integer]
+splitNum n d | n == 0 = []
+             | n < d = [n]
+             | otherwise = d : splitNum (n - d) d
+
+createDummyFile :: FilePath -> Int -> IO (Either IOException ())
+createDummyFile path size = do
+  dfe <- doesFileExist path
+  if not dfe
+    then do
+    try $ writeFile path (BC.replicate size '\0')
+    else
+    return $ Right ()
+
+-- 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))
+
+verifyHash :: ByteString -> ByteString -> Bool
+verifyHash bs pieceHash =
+  take 20 (SHA1.hash bs) == pieceHash