{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FunctionalDependencies, FlexibleContexts #-} -- | The base functions for accessing JSON object fields. module Text.JSON.JSONField ( JSONField(..) ) where import Data.ByteString import qualified Data.Trie as T import Text.JSONb import qualified Text.JSON as J import Text.JSON.Types import Text.JSON.Failure import Control.Failure class JSONField j f | j -> f where field :: Failure (NoSuchField f) m => f -> j -> m j fields :: Failure (ExpectedObject j) m => j -> m [f] -- | Returns the potential object field values of a JSON value. values :: Failure (ExpectedObject j) m => j -> m [j] instance JSONField JSON ByteString where field f (Object o) = case T.lookup f o of Nothing -> failure (NoSuchField f) Just x -> return x field f _ = failure (NoSuchField f) fields (Object o) = return (T.keys o) fields j = failure (ExpectedObject j) values (Object o) = return . fmap snd . T.toList $ o values j = failure (ExpectedObject j) instance JSONField J.JSValue [Char] where field f (J.JSObject (JSONObject o)) = case lookup f o of Nothing -> failure (NoSuchField f) Just x -> return x field f _ = failure (NoSuchField f) fields (J.JSObject (JSONObject o)) = return (fmap fst o) fields j = failure (ExpectedObject j) values (J.JSObject (JSONObject o)) = return (fmap snd o) values j = failure (ExpectedObject j)