{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FunctionalDependencies #-} -- | Parsing JSON object values. module Text.JSON.JSONParse ( JSONParse(..) , parseJSON' ) where import Data.ByteString import Text.JSONb import qualified Text.JSON as J import qualified Text.HJson as H import qualified Data.Aeson.Types as A import Data.Aeson.Parser import qualified Data.Attoparsec as AP import Text.JSON.Parsec import qualified Text.Parsec.Prim as P import qualified Text.Parsec.Error as E -- | Parsing JSON object values. class JSONParse j p e | j -> p, j -> e where -- | Parses a value into either an error or a JSON object. parseJSON :: String -- ^ Source name. -> p -- ^ The value to parse. -> Either e j -- ^ Either error or a JSON object. instance JSONParse JSON ByteString [Char] where parseJSON = const decode instance JSONParse J.JSValue [Char] ParseError where parseJSON = parse p_jvalue instance JSONParse H.Json [Char] E.ParseError where parseJSON = P.runP H.jsonParser [] instance JSONParse A.Value ByteString (Either ([String], String) (ByteString -> AP.Result A.Value)) where parseJSON _ z = case AP.parse value z of AP.Fail _ r s -> Left (Left (r, s)) AP.Partial c -> Left (Right c) AP.Done _ x -> Right x -- | Parse a value with an empty source name. parseJSON' :: JSONParse j p e => p -- ^ The value to parse. -> Either e j -- ^ Either error or a JSON object. parseJSON' = parseJSON []