X-Git-Url: https://git.rkrishnan.org/?a=blobdiff_plain;f=src%2FFuncTorrent%2FBencode.hs;h=28f0460a828af94d7d47ca978ed3bf4e290f6980;hb=972e7a451abd851317146c196bc675fd11751fc8;hp=96600e2aa620e16c32de126e530ec9cabc846f1f;hpb=c2c904f57aedbf048e445c39fed43b37ee60f4b1;p=functorrent.git diff --git a/src/FuncTorrent/Bencode.hs b/src/FuncTorrent/Bencode.hs index 96600e2..28f0460 100644 --- a/src/FuncTorrent/Bencode.hs +++ b/src/FuncTorrent/Bencode.hs @@ -1,29 +1,79 @@ +{- + - Copyright (C) 2015-2016 Ramakrishnan Muthukrishnan + - + - This file is part of FuncTorrent. + - + - FuncTorrent is free software; you can redistribute it and/or modify + - it under the terms of the GNU General Public License as published by + - the Free Software Foundation; either version 3 of the License, or + - (at your option) any later version. + - + - FuncTorrent is distributed in the hope that it will be useful, + - but WITHOUT ANY WARRANTY; without even the implied warranty of + - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + - GNU General Public License for more details. + - + - You should have received a copy of the GNU General Public License + - along with FuncTorrent; if not, see + -} + {-# LANGUAGE OverloadedStrings #-} module FuncTorrent.Bencode - (BVal(..), - InfoDict, - bstrToString, - encode, - decode + (BVal(..) + , bValToInteger + , bstrToString + , decode + , encode ) where import Prelude hiding (length, concat) -import Control.Applicative ((<*)) import Data.ByteString (ByteString, length, concat) import Data.ByteString.Char8 (unpack, pack) -import Data.Functor ((<$>)) -import Data.Map.Strict (Map, fromList, keys, (!)) +import Data.Char (isLetter, isAscii) +import Data.Map.Strict (Map, fromList, toList) import Text.ParserCombinators.Parsec import qualified Text.Parsec.ByteString as ParsecBS +import Test.QuickCheck data BVal = Bint Integer | Bstr ByteString | Blist [BVal] - | Bdict InfoDict + | Bdict (Map String BVal) deriving (Ord, Eq, Show) -type InfoDict = Map String BVal +genNonEmptyString :: Gen String +genNonEmptyString = arbitrary `suchThat` (\s -> ((s /= "") && + (all isAscii s) && + (all isLetter s))) + +instance Arbitrary ByteString where + arbitrary = pack <$> arbitrary + +instance Arbitrary BVal where + arbitrary = sized bval + where + bval :: Int -> Gen BVal + bval 0 = oneof [ Bint <$> arbitrary + , Bstr <$> arbitrary] + bval n = oneof [ Bint <$> arbitrary + , Bstr <$> arbitrary + , Blist <$> vectorOf n (bval (n `div` 4)) + , do keys <- vectorOf n genNonEmptyString + vals <- vectorOf n (bval (n `div` 4)) + return $ Bdict $ fromList $ zip keys vals ] + +-- getters +bValToInteger :: BVal -> Maybe Integer +bValToInteger (Bint x) = Just x +bValToInteger _ = Nothing + +bValToBytestr :: BVal -> Maybe ByteString +bValToBytestr (Bstr bs) = Just bs +bValToBytestr _ = Nothing + +bstrToString :: BVal -> Maybe String +bstrToString bval = unpack <$> bValToBytestr bval -- $setup -- >>> import Data.Either @@ -38,8 +88,7 @@ type InfoDict = Map String BVal -- Right "" -- bencStr :: ParsecBS.Parser ByteString -bencStr = do _ <- spaces - ds <- many1 digit <* char ':' +bencStr = do ds <- many1 digit <* char ':' s <- count (read ds) anyChar return (pack s) @@ -62,8 +111,7 @@ bencStr = do _ <- spaces -- >>> isLeft $ parse bencInt "Bint" (pack "i002e") -- True bencInt :: ParsecBS.Parser Integer -bencInt = do _ <- spaces - ds <- between (char 'i') (char 'e') numbers +bencInt = do ds <- between (char 'i') (char 'e') numbers return (read ds) where numbers = do d' <- char '-' <|> digit ds' <- many digit @@ -85,8 +133,7 @@ bencInt = do _ <- spaces -- >>> parse bencList "Blist" (pack "l4:spam4:eggsli42eee") -- Right [Bstr "spam",Bstr "eggs",Blist [Bint 42]] bencList :: ParsecBS.Parser [BVal] -bencList = do _ <- spaces - between (char 'l') (char 'e') (many bencVal) +bencList = between (char 'l') (char 'e') (many bencVal) -- | parse dict -- @@ -98,11 +145,16 @@ bencList = do _ <- spaces -- Right (fromList [("spam",Blist [Bstr "a",Bstr "b"])]) -- >>> parse bencDict "Bdict" (pack "d9:publisher3:bob17:publisher-webpage15:www.example.com18:publisher.location4:homee") -- Right (fromList [("publisher",Bstr "bob"),("publisher-webpage",Bstr "www.example.com"),("publisher.location",Bstr "home")]) -bencDict :: ParsecBS.Parser InfoDict +bencDict :: ParsecBS.Parser (Map String BVal) bencDict = between (char 'd') (char 'e') $ fromList <$> many kvpair - where kvpair = do k <- bencStr + where kvpair = do k <- bdictKey v <- bencVal - return (unpack k, v) + return (k, v) + bdictKey = do + ds <- many1 digit <* char ':' + s <- count (read ds) alphaNum + return s + bencVal :: ParsecBS.Parser BVal bencVal = Bstr <$> bencStr <|> @@ -138,10 +190,9 @@ decode = parse bencVal "BVal" encode :: BVal -> ByteString encode (Bstr bs) = pack $ show (length bs) ++ ":" ++ unpack bs encode (Bint i) = pack $ "i" ++ show i ++ "e" -encode (Blist xs) = pack $ "l" ++ unpack (concat $ map encode xs) ++ "e" -encode (Bdict d) = concat [concat ["d", encode . Bstr . pack $ k , encode (d ! k) , "e"] | k <- keys d] - --- getters -bstrToString :: BVal -> Maybe String -bstrToString (Bstr s) = Just $ unpack s -bstrToString _ = Nothing +encode (Blist xs) = concat ["l", concat $ map encode xs, "e"] +encode (Bdict d) = concat ["d", concat kvlist, "e"] + where + kvlist :: [ByteString] + kvlist = [encPair kv | kv <- toList d] + encPair (k, v) = concat [encode (Bstr (pack k)), encode v]