Browse Source

A bit more parsing, still not done

Getty Ritter 8 years ago
parent
commit
7ff674d3e0
1 changed files with 29 additions and 9 deletions
  1. 29 9
      Data/Eben.hs

+ 29 - 9
Data/Eben.hs

@@ -1,4 +1,5 @@
 {-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ViewPatterns #-}
 
 module Data.Eben where
 
@@ -12,23 +13,42 @@ import           Data.List (sortOn)
 import           Data.Map.Strict (Map)
 import qualified Data.Map as M
 import           Data.Monoid ((<>))
+import           Data.Word (Word8)
 
 data Value
   = List [Value]
   | Dict (Map B.ByteString Value)
-  | String B.ByteString
   | Integer Int64
   | Float Float
+  | String B.ByteString
     deriving (Eq, Show, Read)
 
-decode :: ByteString -> Either String Value
-decode bs = case BS.uncons bs of
-  ('l', rs) -> ()
-  ('d', rs) -> ()
-  ('i', rs) -> ()
-  ('f', rs) -> ()
-  (i  , rs)
-    | isDigit i -> 
+decode :: ByteString -> Maybe (Value, ByteString)
+decode bs = go
+  where go = case BS.uncons bs of
+          Just (108, rs) -> decodeList
+          Just (100, rs) -> decodeDict
+          Just (105, rs) -> decodeInt
+          Just (102, rs) -> decodeFloat
+          Just (i  , rs)
+            | isDigit (fromIntegral i) ->
+              let (is, rs')   = BS.break (== 58) rs
+                  len         = toNum (toDigit i) is
+                  (str, rs'') = BS.splitAt len (BS.tail rs')
+              in Just (String (BS.toStrict str), rs'')
+            | otherwise -> Nothing
+
+isDigit :: Word8 -> Bool
+isDigit n = n >= 48 && n <= 57
+
+toDigit :: Word8 -> Int64
+toDigit n = fromIntegral n - 48
+
+toNum :: Int64 -> ByteString -> Int64
+toNum n (BS.uncons->Just(b, bs)) =
+  toNum (n * 10 + fromIntegral b) bs
+toNum n _ = n
+
 
 encode :: Value -> ByteString
 encode = BL.toLazyByteString . go