{-# LANGUAGE DeriveDataTypeable #-} -- | Base data types and function for escape JSON string -- and renders `Json` to `String`. module Data.JSON2.Types ( Json (..) , Jsons (..) , toString , escJString ) where import Data.Map (Map) import qualified Data.Map as Map (toList) import Data.Typeable (Typeable) import Data.Ratio data Json = JString String | JNumber !Rational | JBool !Bool | JNull | JArray [Json] | JObject (Map String Json) deriving (Eq, Ord, Typeable, Show, Read) type Jsons = [Json] ---------------- Renders JSON to String ------------------------- -- | Renders `Json` to String. toString :: Json -> String toString (JNumber x) | denominator x == 1 = show (numerator x) | otherwise = show (fromRational x :: Double) toString (JBool True) = "true" toString (JBool False) = "false" toString JNull = "null" toString (JString x) = jStr x toString (JArray []) = "[]" toString (JArray (x:xs)) = concat [ "[", toString x, go, "]" ] where go = concat $ map (\x -> "," ++ toString x) xs toString (JObject m) = concat ["{", go (Map.toList m), "}"] where go [] = "" go (x:xs) = go' x ++ concat [go'' v | v <- xs] go' (k, v) = concat [jStr k, ":", toString v] go'' (k, v) = concat [",", jStr k, ":", toString v] jStr x = "\"" ++ escJString x ++ "\"" -- | Escape JSON string. escJString :: String -> String escJString = concat . map (escJChar) escJChar c = case c of '\n' -> "\\n" '\b' -> "\\b" '\f' -> "\\f" '\t' -> "\\t" '\r' -> "\\r" '\\' -> "\\\\" '\"' -> "\\\"" _ -> [c]