summaryrefslogtreecommitdiff
path: root/src/Data
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2017-01-18 20:11:36 -0500
committerjoe <joe@jerkface.net>2017-01-18 20:11:36 -0500
commita8498921ddf37e864968a3865e3e254352b5d285 (patch)
tree41b709b7ec71efd4e918f0800125599bd86da677 /src/Data
parent5d0791e6ed2e500c08e7dadda39a254c8340cef5 (diff)
Aeson-based pretty-printing of server requests.
Diffstat (limited to 'src/Data')
-rw-r--r--src/Data/BEncode/Pretty.hs75
1 files changed, 75 insertions, 0 deletions
diff --git a/src/Data/BEncode/Pretty.hs b/src/Data/BEncode/Pretty.hs
new file mode 100644
index 00000000..7b0d46a0
--- /dev/null
+++ b/src/Data/BEncode/Pretty.hs
@@ -0,0 +1,75 @@
1{-# LANGUAGE CPP #-}
2module Data.BEncode.Pretty where -- (showBEncode) where
3
4import Data.BEncode.Types
5import qualified Data.ByteString as BS
6import qualified Data.ByteString.Lazy as BL
7import qualified Data.ByteString.Lazy.Char8 as BL8
8import Data.Text (Text)
9import qualified Data.Text as T
10#ifdef BENCODE_AESON
11import Data.BEncode.BDict hiding (map)
12import Data.Aeson.Types hiding (parse)
13import Data.Aeson.Encode.Pretty
14import qualified Data.HashMap.Strict as HashMap
15import qualified Data.Vector as Vector
16import Data.Foldable as Foldable
17import Data.Text.Encoding
18import Text.Printf
19#endif
20
21#ifdef BENCODE_AESON
22
23unhex :: Text -> BS.ByteString
24unhex t = BS.pack $ map unhex1 [0 .. BS.length nibs `div` 2]
25 where
26 nibs = encodeUtf8 t
27 unhex1 i = unnib (BS.index nibs (i * 2)) * 0x10
28 + unnib (BS.index nibs (i * 2 + 1))
29 unnib a | a <= 0x39 = a - 0x30
30 | otherwise = a - (0x41 - 10)
31
32hex :: BS.ByteString -> Text
33hex bs = T.concat $ map (T.pack . printf "%02X") $ BS.unpack bs
34
35quote_chr :: Char
36quote_chr = ' '
37
38quote :: Text -> Text
39quote t = quote_chr `T.cons` t `T.snoc` quote_chr
40
41
42instance ToJSON BValue where
43 toJSON (BInteger x) = Number $ fromIntegral x
44 toJSON (BString s) = String $ either (const $ hex s) quote $ decodeUtf8' s
45 toJSON (BList xs) = Array $ Vector.fromList $ map toJSON xs
46 toJSON (BDict d) = toJSON d
47
48instance ToJSON a => ToJSON (BDictMap a) where
49 toJSON d = Object $ HashMap.fromList $ map convert $ toAscList d
50 where
51 convert (k,v) = (decodeUtf8 k,toJSON v)
52
53instance FromJSON BValue where
54 parseJSON (Number x) = pure $ BInteger (truncate x)
55 parseJSON (Bool x) = pure $ BInteger $ if x then 1 else 0
56 parseJSON (String s)
57 | T.head s==quote_chr = pure $ BString $ encodeUtf8 (T.takeWhile (/=quote_chr) $ T.drop 1 s)
58 | otherwise = pure $ BString $ unhex s
59 parseJSON (Array v) = BList <$> traverse parseJSON (Foldable.toList v)
60 parseJSON (Object d) = BDict <$> parseJSON (Object d)
61 parseJSON (Null) = pure $ BDict Nil
62
63instance FromJSON v => FromJSON (BDictMap v) where
64 parseJSON (Object d) = fromAscList <$> traverse convert (HashMap.toList d)
65 where
66 convert (k,v) = (,) (encodeUtf8 k) <$> parseJSON v
67 parseJSON _ = fail "Not a BDict"
68#endif
69
70showBEncode :: BValue -> BL.ByteString
71#ifdef BENCODE_AESON
72showBEncode b = encodePretty $ toJSON b
73#else
74showBEncode b = BL8.pack (show b)
75#endif