{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FunctionalDependencies #-}

-- | The generalisation of a JSON object.
module Text.JSON.JSONLike
(
  JSONLike(..)
) where

import Data.ByteString
import qualified Data.Trie as T
import Text.JSONb
import qualified Text.JSON as J
import Text.JSON.Types

-- | The generalisation of a JSON object.
class JSONLike j s a o f | j -> s, j -> a, j -> o, o -> f where
  -- | Deconstructs a JSON object.
  foldJSON ::
    x -- ^ If a JSON null value.
    -> x -- ^ If a JSON true value.
    -> x -- ^ If a JSON false value.
    -> (Rational -> x) -- ^ If a JSON number value.
    -> (s -> x) -- ^ If a JSON string value.
    -> (a j -> x) -- ^ If a JSON array value.
    -> (o j -> x) -- ^ If a JSON object value.
    -> j
    -> x
  -- | Constructs a JSON null value.
  jnull ::
    j
  -- | Constructs a JSON true value.
  jtrue ::
    j
  -- | Constructs a JSON false value.
  jfalse ::
    j
  -- | Constructs a JSON number value from the given rational.
  jnumber ::
    Rational
    -> j
  -- | Constructs a JSON string value from the given string.
  jstring ::
    s
    -> j
  -- | Constructs a JSON array value from the given array.
  jarray ::
    a j
    -> j
  -- | Constructs a JSON object value from the given object.
  jobject ::
    o j
    -> j

instance JSONLike JSON ByteString [] T.Trie ByteString where
  foldJSON n _ _ _ _ _ _ Null =
    n
  foldJSON _ t f _ _ _ _ (Boolean b) =
    if b then t else f
  foldJSON _ _ _ r _ _ _ (Number r') =
    r r'
  foldJSON _ _ _ _ s _ _ (String s') =
    s s'
  foldJSON _ _ _ _ _ a _ (Array a') =
    a a'
  foldJSON _ _ _ _ _ _ o (Object o') =
    o o'
  jnull =
    Null
  jtrue =
    Boolean True
  jfalse =
    Boolean False
  jnumber =
    Number
  jstring =
    String
  jarray =
    Array
  jobject =
    Object

instance JSONLike J.JSValue [Char] [] J.JSObject [Char] where
  foldJSON n _ _ _ _ _ _ J.JSNull =
    n
  foldJSON _ t f _ _ _ _ (J.JSBool b) =
    if b then t else f
  foldJSON _ _ _ r _ _ _ (J.JSRational _ r') =
    r r'
  foldJSON _ _ _ _ s _ _ (J.JSString (JSONString s')) =
    s s'
  foldJSON _ _ _ _ _ a _ (J.JSArray a') =
    a a'
  foldJSON _ _ _ _ _ _ o (J.JSObject o') =
    o o'
  jnull =
    J.JSNull
  jtrue =
    J.JSBool True
  jfalse =
    J.JSBool False
  jnumber =
    J.JSRational False
  jstring =
    J.JSString . JSONString
  jarray =
    J.JSArray
  jobject =
    J.JSObject

-- orphan instance
instance Functor J.JSObject where
  fmap f =
    J.toJSObject . fmap (fmap f) . J.fromJSObject