- You should have received a copy of the GNU General Public License
- along with FuncTorrent; if not, see <http://www.gnu.org/licenses/>
-}
+{-# LANGUAGE OverloadedStrings #-}
module FuncTorrent.Filesystem
(new
, FilesystemState
- , getBlock
- , putBlock
, getStats
) where
-data Filesystem = Filesystem { pieces :: [Piece]
+import Data.ByteString (ByteString)
+import qualified Data.ByteString.Char8 as BC (take, drop, null)
+import Control.Concurrent.MVar (MVar, newMVar, readMVar)
+import System.IO (FilePath)
+import System.Environment (getEnv)
+
+import FuncTorrent.Metainfo (Metainfo(..), Info(..), FileInfo(..))
+
+data Filesystem = Filesystem { fs :: [File]
, stats :: Stats
-
+ }
+
+newtype FilesystemState = FilesystemState (MVar Filesystem)
+
+data File = File { name :: FilePath
+ , ps :: [Piece]
+ }
+
+data Piece = Piece { hash :: ByteString
+ }
+
+data Block = Block { offset :: Integer
+ , len :: Integer
+ }
+
+data Stats = Stats { read :: Integer
+ , written :: Integer
+ }
+
+new :: Metainfo -> IO FilesystemState
+new m = do
+ home <- getEnv "HOME"
+ let baseDir = home ++ "/Downloads/"
+ files' = files (info m)
+ pieceLen = pieceLength (info m)
+ h = infoHash m
+ numPiecesList = map (\f -> numPieces (lengthInBytes f) pieceLen) files'
+ hashes = snd $ foldl (\(bs, b) a -> (BC.drop (fromIntegral a) bs, b ++ [BC.take (fromIntegral a) bs])) (h, [] :: [ByteString]) (map (* 20) numPiecesList)
+ hss = map (splitN 20) hashes
+ newFile p hs = File { name = p, ps = map Piece hs }
+ fs = map (\(f, hs) -> let p = baseDir ++ (path f)
+ in newFile p hs) (zip files' hss)
+ v <- newMVar (Filesystem fs (Stats 0 0))
+ return (FilesystemState v)
+
+getStats :: FilesystemState -> IO Stats
+getStats (FilesystemState fsState) = do
+ (Filesystem _ stats') <- readMVar fsState
+ return stats'
+
+numPieces :: Integer -> Integer -> Integer
+numPieces fileLen pieceLen | fileLen `mod` pieceLen == 0 = (fileLen `div` pieceLen)
+ | otherwise = (fileLen `div` pieceLen) + 1
+
+splitN :: Int -> ByteString -> [ByteString]
+splitN n bs | BC.null bs = []
+ | otherwise = BC.take n bs : splitN n (BC.drop n bs)
+