]> git.rkrishnan.org Git - functorrent.git/blobdiff - src/FuncTorrent/Utils.hs
Fileops merged into Utils module
[functorrent.git] / src / FuncTorrent / Utils.hs
index cf6c2844f2745152b91926c272fab1c664bfabea..de2a4561c36f070c76841f944f0d134616943d19 100644 (file)
@@ -1,6 +1,19 @@
-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 = []
@@ -10,3 +23,23 @@ splitNum :: Integer -> Integer -> [Integer]
 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))