summaryrefslogtreecommitdiff
path: root/src/Data/BEncode.hs
diff options
context:
space:
mode:
authorSam T <sta.cs.vsu@gmail.com>2013-04-17 16:46:42 +0400
committerSam T <sta.cs.vsu@gmail.com>2013-04-17 16:46:42 +0400
commit57e5a4f53bc779f373712dd3353c7e9edecd3c32 (patch)
tree4b0d5685bb90f5a853d737bd35163fd2ec72d63b /src/Data/BEncode.hs
parent32900473379545acebfa7d278d8aea99ccf49ab2 (diff)
~ Prettify module a bit.
Diffstat (limited to 'src/Data/BEncode.hs')
-rw-r--r--src/Data/BEncode.hs34
1 files changed, 3 insertions, 31 deletions
diff --git a/src/Data/BEncode.hs b/src/Data/BEncode.hs
index ac1dbaf..e3ae292 100644
--- a/src/Data/BEncode.hs
+++ b/src/Data/BEncode.hs
@@ -1,3 +1,4 @@
1-- TODO: make int's instances platform independent so we can make library portable.
1-- | 2-- |
2-- Copyright : (c) Sam T. 2013 3-- Copyright : (c) Sam T. 2013
3-- License : MIT 4-- License : MIT
@@ -112,10 +113,6 @@ class BEncodable a where
112 fromBEncode :: BEncode -> Result a 113 fromBEncode :: BEncode -> Result a
113 114
114 115
115-- isEncodable :: BEncode -> Bool
116-- bencoding :: Iso a
117-- bencoding = Iso (Right . toBencode) fromBEncode
118
119decodingError :: String -> Result a 116decodingError :: String -> Result a
120decodingError s = Left ("fromBEncode: unable to decode " ++ s) 117decodingError s = Left ("fromBEncode: unable to decode " ++ s)
121{-# INLINE decodingError #-} 118{-# INLINE decodingError #-}
@@ -172,16 +169,6 @@ instance BEncodable Text where
172 fromBEncode b = T.decodeUtf8 <$> fromBEncode b 169 fromBEncode b = T.decodeUtf8 <$> fromBEncode b
173 {-# INLINE fromBEncode #-} 170 {-# INLINE fromBEncode #-}
174 171
175{-
176instance BEncodable Stringwhere
177 toBEncode = BString . BC.pack
178 {-# INLINE toBEncode #-}
179
180 fromBEncode (BString s) = Just (BC.unpack s)
181 fromBEncode _ = Nothing
182 {-# INLINE fromBEncode #-}
183-}
184
185instance BEncodable a => BEncodable [a] where 172instance BEncodable a => BEncodable [a] where
186 {-# SPECIALIZE instance BEncodable [BEncode] #-} 173 {-# SPECIALIZE instance BEncodable [BEncode] #-}
187 174
@@ -289,7 +276,7 @@ decoded = decode >=> fromBEncode
289encoded :: BEncodable a => a -> Lazy.ByteString 276encoded :: BEncodable a => a -> Lazy.ByteString
290encoded = encode . toBEncode 277encoded = encode . toBEncode
291 278
292 279-------------------------------------- internals -------------------------------
293builder :: BEncode -> B.Builder 280builder :: BEncode -> B.Builder
294builder = go 281builder = go
295 where 282 where
@@ -343,19 +330,6 @@ parser = valueP
343 <|> P.decimal 330 <|> P.decimal
344 {-# INLINE integerP #-} 331 {-# INLINE integerP #-}
345 332
346
347-- | Extract raw field from the dict.
348-- Useful for info hash extraction.
349--rawLookup :: ByteString -> Result ByteString
350--rawLookup key = P.parseOnly (P.char 'd' >> go)
351-- where
352-- - go = do
353-- s <- stringP
354-- if s == key
355-- then (
356-- else parser >> go
357
358
359-------------------------------- pretty printing ------------------------------- 333-------------------------------- pretty printing -------------------------------
360printPretty :: BEncode -> IO () 334printPretty :: BEncode -> IO ()
361printPretty = print . pretty 335printPretty = print . pretty
@@ -407,11 +381,9 @@ instance BEncodable Word64 where
407 fromBEncode b = (fromIntegral :: Int -> Word64) <$> fromBEncode b 381 fromBEncode b = (fromIntegral :: Int -> Word64) <$> fromBEncode b
408 {-# INLINE fromBEncode #-} 382 {-# INLINE fromBEncode #-}
409 383
410instance BEncodable Word where 384instance BEncodable Word where -- TODO: make platform independent
411 {-# SPECIALIZE instance BEncodable Word #-} 385 {-# SPECIALIZE instance BEncodable Word #-}
412 toBEncode = toBEncode . (fromIntegral :: Word -> Int) 386 toBEncode = toBEncode . (fromIntegral :: Word -> Int)
413 {-# INLINE toBEncode #-} 387 {-# INLINE toBEncode #-}
414 fromBEncode b = (fromIntegral :: Int -> Word) <$> fromBEncode b 388 fromBEncode b = (fromIntegral :: Int -> Word) <$> fromBEncode b
415 {-# INLINE fromBEncode #-} 389 {-# INLINE fromBEncode #-}
416
417-- todo: platform independent \ No newline at end of file