{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FunctionalDependencies #-} -- | Prepending values to existing JSON association values. module Text.JSON.JSONPrepend ( JSONPrepend(..) ) where import Data.ByteString import qualified Data.Trie as T import Text.JSONb import qualified Text.JSON as J import Text.JSON.Types -- | Prepending values to existing JSON association values. class JSONPrepend j s | j -> s where -- | Prepends the given association if the JSON is an object. (->:) :: (s, j) -- ^ The value to prepend if the JSON value is an object. -> j -- ^ The JSON value to prepend to. -> j -- | Prepends the given value if the JSON is an array. (-->>:) :: j -- ^ The value to prepend if the JSON value is an array.. -> j -- ^ The JSON value to prepend to. -> j instance JSONPrepend JSON ByteString where (k, v) ->: Object x = Object (T.insert k v x) _ ->: x = x k -->>: Array x = Array (k : x) _ -->>: x = x instance JSONPrepend J.JSValue [Char] where k ->: (J.JSObject (JSONObject x)) = (J.JSObject (JSONObject (k:x))) _ ->: x = x k -->>: J.JSArray x = J.JSArray (k : x) _ -->>: x = x