{-# 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 qualified Text.HJson as H
import qualified Data.Aeson.Types as A
import Text.JSON.Types
import qualified Data.Map as M
import qualified Data.Vector as V
import Data.Text

-- | 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

instance JSONPrepend H.Json [Char] where
  (k, v) ->: H.JObject x = H.JObject (M.insert k v x)
  _      ->: x           = x
  k -->>: H.JArray x = H.JArray (k : x)
  _ -->>: x          = x

instance JSONPrepend A.Value Text where
  (k, v) ->: A.Object x = A.Object (M.insert k v x)
  _      ->: x          = x
  k -->>: A.Array x = A.Array (V.cons k x)
  _ -->>: x         = x