#if __GLASGOW_HASKELL >= 800
#else
#endif
module Data.Aeson.Types.Internal
(
Value(..)
, Encoding(..)
, Series(..)
, Array
, emptyArray, isEmptyArray
, Pair
, Object
, emptyObject
, Parser
, Result(..)
, IResult(..)
, JSONPathElement(..)
, JSONPath
, iparse
, parse
, parseEither
, parseMaybe
, modifyFailure
, formatError
, (<?>)
, object
, Options(..)
, SumEncoding(..)
, defaultOptions
, defaultTaggedObject
, camelTo
, camelTo2
, DotNetTime(..)
) where
import Control.Arrow (first)
import Control.Applicative
import Control.DeepSeq (NFData(..))
import Control.Monad (MonadPlus(..), ap)
import qualified Control.Monad.Fail as Fail
import Data.ByteString.Builder (Builder, char7, toLazyByteString)
import Data.Char (isLower, isUpper, toLower, isAlpha, isAlphaNum)
import Data.Data (Data)
import Data.HashMap.Strict (HashMap)
import Data.Hashable (Hashable(..))
import Data.Semigroup (Semigroup((<>)))
import Data.Scientific (Scientific)
import Data.String (IsString(..))
import Data.Text (Text, pack, unpack)
import Data.Time (UTCTime)
import Data.Time.Format (FormatTime)
import Data.Typeable (Typeable)
import Data.Vector (Vector)
import qualified Data.HashMap.Strict as H
import qualified Data.Scientific as S
import qualified Data.Vector as V
import qualified Language.Haskell.TH.Syntax as TH
#if !MIN_VERSION_base(4,8,0)
import Data.Foldable (Foldable(..))
import Data.Monoid (Monoid(..))
import Data.Traversable (Traversable(..))
#endif
#if !MIN_VERSION_unordered_containers(0,2,6)
import Data.List (foldl', sort)
#endif
data JSONPathElement = Key Text
| Index !Int
deriving (Eq, Show, Typeable)
type JSONPath = [JSONPathElement]
data IResult a = IError JSONPath String
| ISuccess a
deriving (Eq, Show, Typeable)
data Result a = Error String
| Success a
deriving (Eq, Show, Typeable)
instance NFData JSONPathElement where
rnf (Key t) = rnf t
rnf (Index i) = rnf i
instance (NFData a) => NFData (IResult a) where
rnf (ISuccess a) = rnf a
rnf (IError path err) = rnf path `seq` rnf err
instance (NFData a) => NFData (Result a) where
rnf (Success a) = rnf a
rnf (Error err) = rnf err
instance Functor IResult where
fmap f (ISuccess a) = ISuccess (f a)
fmap _ (IError path err) = IError path err
instance Functor Result where
fmap f (Success a) = Success (f a)
fmap _ (Error err) = Error err
instance Monad IResult where
return = pure
ISuccess a >>= k = k a
IError path err >>= _ = IError path err
fail = Fail.fail
instance Fail.MonadFail IResult where
fail err = IError [] err
instance Monad Result where
return = pure
Success a >>= k = k a
Error err >>= _ = Error err
fail = Fail.fail
instance Fail.MonadFail Result where
fail err = Error err
instance Applicative IResult where
pure = ISuccess
(<*>) = ap
instance Applicative Result where
pure = Success
(<*>) = ap
instance MonadPlus IResult where
mzero = fail "mzero"
mplus a@(ISuccess _) _ = a
mplus _ b = b
instance MonadPlus Result where
mzero = fail "mzero"
mplus a@(Success _) _ = a
mplus _ b = b
instance Alternative IResult where
empty = mzero
(<|>) = mplus
instance Alternative Result where
empty = mzero
(<|>) = mplus
instance Semigroup (IResult a) where
(<>) = mplus
instance Monoid (IResult a) where
mempty = fail "mempty"
mappend = (<>)
instance Semigroup (Result a) where
(<>) = mplus
instance Monoid (Result a) where
mempty = fail "mempty"
mappend = (<>)
instance Foldable IResult where
foldMap _ (IError _ _) = mempty
foldMap f (ISuccess y) = f y
foldr _ z (IError _ _) = z
foldr f z (ISuccess y) = f y z
instance Foldable Result where
foldMap _ (Error _) = mempty
foldMap f (Success y) = f y
foldr _ z (Error _) = z
foldr f z (Success y) = f y z
instance Traversable IResult where
traverse _ (IError path err) = pure (IError path err)
traverse f (ISuccess a) = ISuccess <$> f a
instance Traversable Result where
traverse _ (Error err) = pure (Error err)
traverse f (Success a) = Success <$> f a
type Failure f r = JSONPath -> String -> f r
type Success a f r = a -> f r
newtype Parser a = Parser {
runParser :: forall f r.
JSONPath
-> Failure f r
-> Success a f r
-> f r
}
instance Monad Parser where
m >>= g = Parser $ \path kf ks -> let ks' a = runParser (g a) path kf ks
in runParser m path kf ks'
return = pure
fail = Fail.fail
instance Fail.MonadFail Parser where
fail msg = Parser $ \path kf _ks -> kf (reverse path) msg
instance Functor Parser where
fmap f m = Parser $ \path kf ks -> let ks' a = ks (f a)
in runParser m path kf ks'
instance Applicative Parser where
pure a = Parser $ \_path _kf ks -> ks a
(<*>) = apP
instance Alternative Parser where
empty = fail "empty"
(<|>) = mplus
instance MonadPlus Parser where
mzero = fail "mzero"
mplus a b = Parser $ \path kf ks -> let kf' _ _ = runParser b path kf ks
in runParser a path kf' ks
instance Semigroup (Parser a) where
(<>) = mplus
instance Monoid (Parser a) where
mempty = fail "mempty"
mappend = (<>)
apP :: Parser (a -> b) -> Parser a -> Parser b
apP d e = do
b <- d
a <- e
return (b a)
type Object = HashMap Text Value
type Array = Vector Value
data Value = Object !Object
| Array !Array
| String !Text
| Number !Scientific
| Bool !Bool
| Null
deriving (Eq, Read, Show, Typeable, Data)
newtype Encoding = Encoding {
fromEncoding :: Builder
} deriving (Semigroup,Monoid)
instance Show Encoding where
show (Encoding e) = show (toLazyByteString e)
instance Eq Encoding where
Encoding a == Encoding b = toLazyByteString a == toLazyByteString b
instance Ord Encoding where
compare (Encoding a) (Encoding b) =
compare (toLazyByteString a) (toLazyByteString b)
data Series = Empty
| Value Encoding
deriving (Typeable)
instance Semigroup Series where
Empty <> a = a
Value a <> b =
Value $
a <> case b of
Empty -> mempty
Value c -> Encoding (char7 ',') <> c
instance Monoid Series where
mempty = Empty
mappend = (<>)
newtype DotNetTime = DotNetTime {
fromDotNetTime :: UTCTime
} deriving (Eq, Ord, Read, Show, Typeable, FormatTime)
instance NFData Value where
rnf (Object o) = rnf o
rnf (Array a) = V.foldl' (\x y -> rnf y `seq` x) () a
rnf (String s) = rnf s
rnf (Number n) = rnf n
rnf (Bool b) = rnf b
rnf Null = ()
instance IsString Value where
fromString = String . pack
hashValue :: Int -> Value -> Int
#if MIN_VERSION_unordered_containers(0,2,6)
hashValue s (Object o) = s `hashWithSalt` (0::Int) `hashWithSalt` o
#else
hashValue s (Object o) = foldl' hashWithSalt
(s `hashWithSalt` (0::Int)) assocHashesSorted
where
assocHashesSorted = sort [hash k `hashWithSalt` v | (k, v) <- H.toList o]
#endif
hashValue s (Array a) = V.foldl' hashWithSalt
(s `hashWithSalt` (1::Int)) a
hashValue s (String str) = s `hashWithSalt` (2::Int) `hashWithSalt` str
hashValue s (Number n) = s `hashWithSalt` (3::Int) `hashWithSalt` n
hashValue s (Bool b) = s `hashWithSalt` (4::Int) `hashWithSalt` b
hashValue s Null = s `hashWithSalt` (5::Int)
instance Hashable Value where
hashWithSalt = hashValue
instance TH.Lift Value where
lift Null = [| Null |]
lift (Bool b) = [| Bool b |]
lift (Number n) = [| Number (S.scientific c e) |]
where
c = S.coefficient n
e = S.base10Exponent n
lift (String t) = [| String (pack s) |]
where s = unpack t
lift (Array a) = [| Array (V.fromList a') |]
where a' = V.toList a
lift (Object o) = [| Object (H.fromList . map (first pack) $ o') |]
where o' = map (first unpack) . H.toList $ o
emptyArray :: Value
emptyArray = Array V.empty
isEmptyArray :: Value -> Bool
isEmptyArray (Array arr) = V.null arr
isEmptyArray _ = False
emptyObject :: Value
emptyObject = Object H.empty
parse :: (a -> Parser b) -> a -> Result b
parse m v = runParser (m v) [] (const Error) Success
iparse :: (a -> Parser b) -> a -> IResult b
iparse m v = runParser (m v) [] IError ISuccess
parseMaybe :: (a -> Parser b) -> a -> Maybe b
parseMaybe m v = runParser (m v) [] (\_ _ -> Nothing) Just
parseEither :: (a -> Parser b) -> a -> Either String b
parseEither m v = runParser (m v) [] onError Right
where onError path msg = Left (formatError path msg)
formatError :: JSONPath -> String -> String
formatError path msg = "Error in " ++ (format "$" path) ++ ": " ++ msg
where
format :: String -> JSONPath -> String
format pfx [] = pfx
format pfx (Index idx:parts) = format (pfx ++ "[" ++ show idx ++ "]") parts
format pfx (Key key:parts) = format (pfx ++ formatKey key) parts
formatKey :: Text -> String
formatKey key
| isIdentifierKey strKey = "." ++ strKey
| otherwise = "['" ++ escapeKey strKey ++ "']"
where strKey = unpack key
isIdentifierKey :: String -> Bool
isIdentifierKey [] = False
isIdentifierKey (x:xs) = isAlpha x && all isAlphaNum xs
escapeKey :: String -> String
escapeKey = concatMap escapeChar
escapeChar :: Char -> String
escapeChar '\'' = "\\'"
escapeChar '\\' = "\\\\"
escapeChar c = [c]
type Pair = (Text, Value)
object :: [Pair] -> Value
object = Object . H.fromList
(<?>) :: Parser a -> JSONPathElement -> Parser a
p <?> pathElem = Parser $ \path kf ks -> runParser p (pathElem:path) kf ks
modifyFailure :: (String -> String) -> Parser a -> Parser a
modifyFailure f (Parser p) = Parser $ \path kf ks -> p path (\p' m -> kf p' (f m)) ks
data Options = Options
{ fieldLabelModifier :: String -> String
, constructorTagModifier :: String -> String
, allNullaryToStringTag :: Bool
, omitNothingFields :: Bool
, sumEncoding :: SumEncoding
, unwrapUnaryRecords :: Bool
}
instance Show Options where
show Options{..} = "Options {" ++
"fieldLabelModifier =~ " ++
show (fieldLabelModifier "exampleField") ++ ", " ++
"constructorTagModifier =~ " ++
show (constructorTagModifier "ExampleConstructor") ++ ", " ++
"allNullaryToStringTag = " ++ show allNullaryToStringTag ++ ", " ++
"omitNothingFields = " ++ show omitNothingFields ++ ", " ++
"sumEncoding = " ++ show sumEncoding ++ ", " ++
"unwrapUnaryRecords = " ++ show unwrapUnaryRecords ++
"}"
data SumEncoding =
TaggedObject { tagFieldName :: String
, contentsFieldName :: String
}
| ObjectWithSingleField
| TwoElemArray
deriving (Eq, Show)
defaultOptions :: Options
defaultOptions = Options
{ fieldLabelModifier = id
, constructorTagModifier = id
, allNullaryToStringTag = True
, omitNothingFields = False
, sumEncoding = defaultTaggedObject
, unwrapUnaryRecords = False
}
defaultTaggedObject :: SumEncoding
defaultTaggedObject = TaggedObject
{ tagFieldName = "tag"
, contentsFieldName = "contents"
}
camelTo :: Char -> String -> String
camelTo c = lastWasCap True
where
lastWasCap :: Bool
-> String
-> String
lastWasCap _ [] = []
lastWasCap prev (x : xs) = if isUpper x
then if prev
then toLower x : lastWasCap True xs
else c : toLower x : lastWasCap True xs
else x : lastWasCap False xs
camelTo2 :: Char -> String -> String
camelTo2 c = map toLower . go2 . go1
where go1 "" = ""
go1 (x:u:l:xs) | isUpper u && isLower l = x : c : u : l : go1 xs
go1 (x:xs) = x : go1 xs
go2 "" = ""
go2 (l:u:xs) | isLower l && isUpper u = l : c : u : go2 xs
go2 (x:xs) = x : go2 xs