]> git.rkrishnan.org Git - functorrent.git/blobdiff - src/FuncTorrent/Bencode.hs
Move Arbitrary instances into another module
[functorrent.git] / src / FuncTorrent / Bencode.hs
index bbeca650a6eca2c8a9b78050f5671ec36de418a9..3a982ec0336da0f8ca5a31bbfb73ed4a29b2d78e 100644 (file)
@@ -1,14 +1,13 @@
 {-# LANGUAGE OverloadedStrings #-}
-module FuncTorrent.Bencode (
-      BVal(..)
-    , InfoDict
-    , bstrToString
-    , bValToInteger
-    , bValToInfoDict
+module FuncTorrent.Bencode
+    (BVal(..)
     , bValToBList
-    , bValToBstr
-    , encode
+    , bValToBytestr
+    , bValToInfoDict
+    , bValToInteger
+    , bstrToString
     , decode
+    , encode
     ) where
 
 import Prelude hiding (length, concat)
@@ -17,14 +16,14 @@ 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.Map.Strict (Map, fromList, toList)
 import Text.ParserCombinators.Parsec
 import qualified Text.Parsec.ByteString as ParsecBS
 
 data BVal = Bint Integer
           | Bstr ByteString
           | Blist [BVal]
-          | Bdict InfoDict
+          | Bdict (Map String BVal)
             deriving (Ord, Eq, Show)
 
 -- getters
@@ -32,22 +31,20 @@ bValToInteger :: BVal -> Maybe Integer
 bValToInteger (Bint x) = Just x
 bValToInteger _        = Nothing
 
-bValToBstr :: BVal  -> Maybe ByteString
-bValToBstr (Bstr bs) = Just bs
-bValToBstr _         = Nothing
+bValToBytestr :: BVal  -> Maybe ByteString
+bValToBytestr (Bstr bs) = Just bs
+bValToBytestr _         = Nothing
 
 bValToBList :: BVal    -> Maybe [BVal]
 bValToBList (Blist lst) = Just lst
 bValToBList _           = Nothing
 
-bValToInfoDict :: BVal     -> Maybe InfoDict
+bValToInfoDict :: BVal     -> Maybe (Map String BVal)
 bValToInfoDict (Bdict dict) = Just dict
 bValToInfoDict _            = Nothing
 
 bstrToString :: BVal -> Maybe String
-bstrToString bval     = unpack <$> bValToBstr bval
-
-type InfoDict = Map String BVal
+bstrToString bval     = unpack <$> bValToBytestr bval
 
 -- $setup
 -- >>> import Data.Either
@@ -62,8 +59,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)
 
@@ -86,8 +82,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
@@ -109,8 +104,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
 --
@@ -122,7 +116,7 @@ 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
                     v <- bencVal
@@ -162,5 +156,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]
+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]