module Data.Torrent ( Torrent(..) , TorrentInfo(..) , TorrentFile(..) , readTorrent -- :: ByteString -> Either String Torrent , torrentSize -- :: Torrent -> Int ) where -- import Network.URI import Data.BEncode import Data.BEncode.Parser import System.FilePath import Data.Torrent.SHA1 import qualified Data.ByteString.Char8 as BS import Data.ByteString (ByteString) data Torrent = Torrent { tAnnounce :: String , tAnnounceList :: [String] , tComment :: String , tCreatedBy :: Maybe String , tInfo :: TorrentInfo , tInfoHash :: ByteString } deriving Show data TorrentInfo = SingleFile { tLength :: Int , tName :: String , tPieceLength :: Int , tPieces :: ByteString } | MultiFile { tFiles :: [TorrentFile] , tName :: String , tPieceLength :: Int , tPieces :: ByteString } deriving Show data TorrentFile = TorrentFile { fileLength :: Int , filePath :: FilePath } deriving Show torrentSize :: Torrent -> Int torrentSize torrent = case tInfo torrent of s@SingleFile{} -> tLength s MultiFile{tFiles=files} -> sum (map fileLength files) {- buri :: BParser BEncode -> BParser URI buri p = do str <- bstring p case parseURI str of Nothing -> fail $ "Expected URI: " ++ str Just uri -> return uri -} readTorrent :: ByteString -> Either String Torrent readTorrent inp = case bRead inp of Nothing -> Left "Not BEncoded" Just be -> runParser parseTorrent be parseTorrent :: BParser Torrent parseTorrent = do announce <- bstring $ dict "announce" creator <- optional $ bstring $ dict "created by" info <- dict "info" setInput info name <- bstring $ dict "name" pLen <- bint $ dict "piece length" pieces <- bfaststring $ dict "pieces" torrentInfo <- parseTorrentInfo name pLen pieces let infoHash = sha1 (BS.pack $ bShow info "") return $ Torrent announce [] "" creator torrentInfo infoHash parseTorrentInfo :: String -> Int -> ByteString -> BParser TorrentInfo parseTorrentInfo name pLen pieces = do len <- bint $ dict "length" return $ SingleFile len name pLen pieces <|> do files <- list "files" $ do len <- bint $ dict "length" filePaths <- list "path" $ bstring token return $ TorrentFile len (foldr1 () filePaths) return $ MultiFile files name pLen pieces