gdritter repos eben / 7ff674d
A bit more parsing, still not done Getty Ritter 8 years ago
1 changed file(s) with 29 addition(s) and 9 deletion(s). Collapse all Expand all
11 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE ViewPatterns #-}
23
34 module Data.Eben where
45
1213 import Data.Map.Strict (Map)
1314 import qualified Data.Map as M
1415 import Data.Monoid ((<>))
16 import Data.Word (Word8)
1517
1618 data Value
1719 = List [Value]
1820 | Dict (Map B.ByteString Value)
19 | String B.ByteString
2021 | Integer Int64
2122 | Float Float
23 | String B.ByteString
2224 deriving (Eq, Show, Read)
2325
24 decode :: ByteString -> Either String Value
25 decode bs = case BS.uncons bs of
26 ('l', rs) -> ()
27 ('d', rs) -> ()
28 ('i', rs) -> ()
29 ('f', rs) -> ()
30 (i , rs)
31 | isDigit i ->
26 decode :: ByteString -> Maybe (Value, ByteString)
27 decode bs = go
28 where go = case BS.uncons bs of
29 Just (108, rs) -> decodeList
30 Just (100, rs) -> decodeDict
31 Just (105, rs) -> decodeInt
32 Just (102, rs) -> decodeFloat
33 Just (i , rs)
34 | isDigit (fromIntegral i) ->
35 let (is, rs') = BS.break (== 58) rs
36 len = toNum (toDigit i) is
37 (str, rs'') = BS.splitAt len (BS.tail rs')
38 in Just (String (BS.toStrict str), rs'')
39 | otherwise -> Nothing
40
41 isDigit :: Word8 -> Bool
42 isDigit n = n >= 48 && n <= 57
43
44 toDigit :: Word8 -> Int64
45 toDigit n = fromIntegral n - 48
46
47 toNum :: Int64 -> ByteString -> Int64
48 toNum n (BS.uncons->Just(b, bs)) =
49 toNum (n * 10 + fromIntegral b) bs
50 toNum n _ = n
51
3252
3353 encode :: Value -> ByteString
3454 encode = BL.toLazyByteString . go