{-# LANGUAGE GeneralizedNewtypeDeriving, FlexibleInstances, FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings, MagicHash, BangPatterns, UndecidableInstances #-}
module Data.BufferBuilder.Json
(
Value
, ToJson (..)
, encodeJson
, JsonString
, ToJsonString (..)
, ObjectBuilder
, emptyObject
, (.=)
, (.=#)
, row
, array
, nullValue
, unsafeValueUtf8Builder
, unsafeStringUtf8Builder
, unsafeAppendUtf8Builder
, unsafeAppendBS
) where
import GHC.Base
import Foreign.Storable
import Control.Monad (when, forM_)
import Data.BufferBuilder.Utf8 (Utf8Builder)
import qualified Data.BufferBuilder.Utf8 as UB
import Data.ByteString (ByteString)
import Data.Monoid hiding ((<>))
import Data.Semigroup
import Data.Text (Text)
import Data.Foldable (Foldable, foldMap)
import qualified Data.Vector as Vector
import qualified Data.Vector.Generic as GVector
import qualified Data.Vector.Primitive as VP
import qualified Data.Vector.Storable as VS
import qualified Data.Vector.Unboxed as VU
import qualified Data.HashMap.Strict as HashMap
newtype Value = Value { utf8Builder :: Utf8Builder () }
class ToJson a where
toJson :: a -> Value
encodeJson :: ToJson a => a -> ByteString
encodeJson = UB.runUtf8Builder . utf8Builder . toJson
{-# INLINE encodeJson #-}
newtype JsonString = JsonString { unJsonString :: Utf8Builder () }
class ToJson a => ToJsonString a where
toJsonString :: a -> JsonString
data ObjectBuilder = NoPair | Pair !(Utf8Builder ())
instance Semigroup ObjectBuilder where
{-# INLINE (<>) #-}
NoPair <> a = a
a <> NoPair = a
(Pair a) <> (Pair b) = Pair $ do
a
UB.appendChar7 ','
b
instance Monoid ObjectBuilder where
{-# INLINE mempty #-}
mempty = NoPair
{-# INLINE mappend #-}
mappend = (<>)
instance ToJson ObjectBuilder where
{-# INLINE toJson #-}
toJson NoPair = Value $ do
UB.appendChar7 '{'
UB.appendChar7 '}'
toJson (Pair a) = Value $ do
UB.appendChar7 '{'
a
UB.appendChar7 '}'
emptyObject :: Value
emptyObject = toJson NoPair
{-# INLINE emptyObject #-}
row :: (ToJsonString k, ToJson v) => k -> v -> ObjectBuilder
row k v = Pair $ do
unJsonString $ toJsonString k
UB.appendChar7 ':'
utf8Builder $ toJson v
infixr 8 `row`
{-# INLINE row #-}
(.=) :: ToJson a => Text -> a -> ObjectBuilder
a .= b = Pair $ do
UB.appendEscapedJsonText a
UB.appendChar7 ':'
utf8Builder $ toJson b
infixr 8 .=
{-# INLINE (.=) #-}
(.=#) :: ToJson a => Addr# -> a -> ObjectBuilder
a .=# b = Pair $ do
UB.appendEscapedJsonLiteral a
UB.appendChar7 ':'
utf8Builder $ toJson b
infixr 8 .=#
{-# INLINE (.=#) #-}
{-# INLINE writePair #-}
writePair :: (ToJsonString k, ToJson v) => (k, v) -> Utf8Builder ()
writePair (key, value) = do
unJsonString $ toJsonString key
UB.appendChar7 ':'
utf8Builder $ toJson value
instance (ToJsonString k, ToJson v) => ToJson (HashMap.HashMap k v) where
{-# INLINABLE toJson #-}
toJson hm = Value $ do
UB.appendChar7 '{'
case HashMap.toList hm of
[] -> UB.appendChar7 '}'
(x:xs) -> do
writePair x
forM_ xs $ \p -> do
UB.appendChar7 ','
writePair p
UB.appendChar7 '}'
array :: (Foldable t, ToJson a) => t a -> Value
array collection = Value $ do
UB.appendChar7 '['
case foldMap (Pair . utf8Builder . toJson) collection of
NoPair -> return ()
(Pair b) -> b
UB.appendChar7 ']'
{-# INLINABLE array #-}
instance ToJson a => ToJson [a] where
{-# INLINABLE toJson #-}
toJson !ls = Value $ do
UB.appendChar7 '['
case ls of
[] -> UB.appendChar7 ']'
x:xs -> do
utf8Builder $ toJson x
forM_ xs $ \(!e) -> do
UB.appendChar7 ','
utf8Builder $ toJson e
UB.appendChar7 ']'
instance ToJson a => ToJson (Vector.Vector a) where
{-# INLINABLE toJson #-}
toJson = vector
instance (Storable a, ToJson a) => ToJson (VS.Vector a) where
{-# INLINABLE toJson #-}
toJson = vector
instance (VP.Prim a, ToJson a) => ToJson (VP.Vector a) where
{-# INLINABLE toJson #-}
toJson = vector
instance (GVector.Vector VU.Vector a, ToJson a) => ToJson (VU.Vector a) where
{-# INLINABLE toJson #-}
toJson = vector
{-# INLINABLE vector #-}
vector :: (GVector.Vector v a, ToJson a) => v a -> Value
vector !vec = Value $ do
UB.appendChar7 '['
let len = GVector.length vec
when (len /= 0) $ do
utf8Builder $ toJson (vec `GVector.unsafeIndex` 0)
GVector.forM_ (GVector.tail vec) $ \e -> do
UB.appendChar7 ','
utf8Builder $ toJson e
UB.appendChar7 ']'
nullValue :: Value
nullValue = Value $ UB.unsafeAppendLiteralN 4 "null"#
{-# INLINE nullValue #-}
instance ToJson Value where
{-# INLINE toJson #-}
toJson = id
instance ToJson Bool where
{-# INLINE toJson #-}
toJson True = Value $ UB.unsafeAppendLiteralN 4 "true"#
toJson False = Value $ UB.unsafeAppendLiteralN 5 "false"#
instance ToJson a => ToJson (Maybe a) where
{-# INLINE toJson #-}
toJson m = case m of
Nothing -> Value $ UB.unsafeAppendLiteralN 4 "null"#
Just a -> toJson a
instance ToJson Text where
{-# INLINE toJson #-}
toJson text = Value $ UB.appendEscapedJsonText text
instance ToJson Double where
{-# INLINE toJson #-}
toJson a = Value $ UB.appendDecimalDouble a
instance ToJson Int where
{-# INLINE toJson #-}
toJson a = Value $ UB.appendDecimalSignedInt a
instance ToJsonString JsonString where
toJsonString = id
instance ToJson JsonString where
toJson = Value . unJsonString
instance ToJsonString Text where
{-# INLINE toJsonString #-}
toJsonString text = JsonString $ UB.appendEscapedJsonText text
unsafeValueUtf8Builder :: Utf8Builder () -> Value
unsafeValueUtf8Builder = Value
unsafeStringUtf8Builder :: Utf8Builder () -> JsonString
unsafeStringUtf8Builder = JsonString
{-# DEPRECATED unsafeAppendBS "Use unsafeValueUtf8Builder or unsafeStringUtf8Builder instead" #-}
unsafeAppendBS :: ByteString -> Value
unsafeAppendBS bs = Value $ UB.unsafeAppendBS bs
{-# DEPRECATED unsafeAppendUtf8Builder "Use unsafeValueUtf8Builder or unsafeStringUtf8Builder instead" #-}
unsafeAppendUtf8Builder :: Utf8Builder () -> Value
unsafeAppendUtf8Builder = unsafeValueUtf8Builder