| Copyright | (C) 2015-2016 Oleg Grenrus |
|---|---|
| License | BSD3 |
| Maintainer | Oleg Grenrus <oleg.grenrus@iki.fi> |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Aeson.Extra
Contents
- encodeStrict :: ToJSON a => a -> ByteString
- newtype M a = M {
- getMap :: a
- class FromJSONKey a where
- parseIntegralJSONKey :: Integral a => Text -> Parser a
- class FromJSONMap m k v | m -> k v where
- class ToJSONKey a where
- class ToJSONMap m k v | m -> k v where
- data SymTag s = SymTag
- newtype SingObject s a = SingObject a
- mkSingObject :: Proxy s -> a -> SingObject s a
- getSingObject :: Proxy s -> SingObject s a -> a
- newtype CollapsedList f a = CollapsedList (f a)
- getCollapsedList :: CollapsedList f a -> f a
- parseCollapsedList :: (FromJSON a, FromJSON1 f, Alternative f) => Object -> Text -> Parser (f a)
- newtype U = U {}
- newtype Z = Z {}
- data ValueF a
- type ObjectF a = HashMap Text a
- type ArrayF a = Vector a
- merge :: (forall a. (a -> a -> a) -> ValueF a -> ValueF a -> ValueF a) -> Value -> Value -> Value
- streamDecode :: forall a. FromJSON a => ByteString -> ([a], Maybe String)
- mkValue :: String -> Q Exp
- mkValue' :: String -> Q Exp
- module Data.Aeson.Compat
Strict encoding
encodeStrict :: ToJSON a => a -> ByteString Source #
Like encode, but produces strict ByteString.
Since: 0.2.3.0
Generic maps
A wrapper type to parse arbitrary maps
λ > decode "{\"1\": 1, \"2\": 2}" :: Maybe (M (H.HashMap Int Int))
Just (M {getMap = fromList [(1,1),(2,2)]})class FromJSONKey a where Source #
Minimal complete definition
Methods
parseJSONKey :: Text -> Parser a Source #
Instances
class FromJSONMap m k v | m -> k v where Source #
Minimal complete definition
Instances
| (Eq k, Hashable k, FromJSONKey k, FromJSON v) => FromJSONMap (HashMap k v) k v Source # | |
| (Ord k, FromJSONKey k, FromJSON v) => FromJSONMap (Map k v) k v Source # | |
Symbol tag
Singleton string encoded and decoded as ifself.
λ> encode (SymTag :: SymTag "foobar") "\"foobar\""
decode "\"foobar\"" :: Maybe (SymTag "foobar") Just SymTag
decode "\"foobar\"" :: Maybe (SymTag "barfoo") Nothing
Available with: base >=4.7
Constructors
| SymTag |
Singleton object
newtype SingObject s a Source #
Singleton value object
λ > decode "{\"value\": 42 }" :: Maybe (SingObject "value" Int)
Just (SingObject 42)λ > encode (SingObject 42 :: SingObject "value" Int)
"{\"value\":42}"Available with: base >=4.7
Constructors
| SingObject a |
Instances
| Functor (SingObject s) Source # | |
| Foldable (SingObject s) Source # | |
| Traversable (SingObject s) Source # | |
| KnownSymbol s => FromJSON1 (SingObject s) Source # | |
| KnownSymbol s => ToJSON1 (SingObject s) Source # | |
| Eq a => Eq (SingObject s a) Source # | |
| Ord a => Ord (SingObject s a) Source # | |
| Read a => Read (SingObject s a) Source # | |
| Show a => Show (SingObject s a) Source # | |
| (KnownSymbol s, FromJSON a) => FromJSON (SingObject s a) Source # | |
| (KnownSymbol s, ToJSON a) => ToJSON (SingObject s a) Source # | |
mkSingObject :: Proxy s -> a -> SingObject s a Source #
getSingObject :: Proxy s -> SingObject s a -> a Source #
CollapsedList
newtype CollapsedList f a Source #
Collapsed list, singleton is represented as the value itself in JSON encoding.
λ > decode "null" :: Maybe (CollapsedList [Int] Int) Just (CollapsedList []) λ > decode "42" :: Maybe (CollapsedList [Int] Int) Just (CollapsedList [42]) λ > decode "[1, 2, 3]" :: Maybe (CollapsedList [Int] Int) Just (CollapsedList [1,2,3])
λ > encode (CollapsedList ([] :: [Int])) "null" λ > encode (CollapsedList ([42] :: [Int])) "42" λ > encode (CollapsedList ([1, 2, 3] :: [Int])) "[1,2,3]"
Documentation rely on f Alternative instance behaving like lists'.
Constructors
| CollapsedList (f a) |
Instances
| Functor f => Functor (CollapsedList f) Source # | |
| Foldable f => Foldable (CollapsedList f) Source # | |
| Traversable f => Traversable (CollapsedList f) Source # | |
| (FromJSON1 f, Alternative f) => FromJSON1 (CollapsedList f) Source # | |
| (ToJSON1 f, Foldable f) => ToJSON1 (CollapsedList f) Source # | |
| Eq (f a) => Eq (CollapsedList f a) Source # | |
| Ord (f a) => Ord (CollapsedList f a) Source # | |
| Read (f a) => Read (CollapsedList f a) Source # | |
| Show (f a) => Show (CollapsedList f a) Source # | |
| (FromJSON1 f, Alternative f, FromJSON a) => FromJSON (CollapsedList f a) Source # | |
| (ToJSON1 f, Foldable f, ToJSON a) => ToJSON (CollapsedList f a) Source # | |
getCollapsedList :: CollapsedList f a -> f a Source #
parseCollapsedList :: (FromJSON a, FromJSON1 f, Alternative f) => Object -> Text -> Parser (f a) Source #
Parses possibly collapsed array value from the object's field.
λ > newtype V = V [Int] deriving (Show)
λ > instance FromJSON V where parseJSON = withObject "V" $ \obj -> V <$> parseCollapsedList obj "value"
λ > decode "{}" :: Maybe V
Just (V [])
λ > decode "{\"value\": null}" :: Maybe V
Just (V [])
λ > decode "{\"value\": 42}" :: Maybe V
Just (V [42])
λ > decode "{\"value\": [1, 2, 3, 4]}" :: Maybe V
Just (V [1,2,3,4])UTCTime
A type to parse ZonedTime
Since: aeson-extra-0.2.2.0
Algebra
An algebra of Value
Since: aeson-extra-0.3.1.0
Merge
merge :: (forall a. (a -> a -> a) -> ValueF a -> ValueF a -> ValueF a) -> Value -> Value -> Value Source #
Generic merge.
For example https://lodash.com/docs#merge:
lodashMerge :: Value -> Value -> Value
lodashMerge x y = merge lodashMergeAlg x y
lodashMergeAlg :: (a -> a -> a) -> ValueF a -> ValueF a -> ValueF a
lodashMergeAlg r a' b' = case (a', b') of
(ObjectF a, ObjectF b) -> ObjectF $ alignWith f a b
(ArrayF a, ArrayF b) -> ArrayF $ alignWith f a b
(_, b) -> b
where f (These x y) = r x y
f (This x) = x
f (That x) = x
Since: aeson-extra-0.3.1.0
Stream
streamDecode :: forall a. FromJSON a => ByteString -> ([a], Maybe String) Source #
Lazyly parse ByteString with top-level JSON array.
Note: inspecting result's second field will force the list!
let ~(values, err) = streamDecode bs
traverse_ processValue values
maybe (pure ()) printError err
Since: 0.3.2.0
Template Haskell
mkValue' :: String -> Q Exp Source #
Like mkValue, but replace single quotes with double quotes before.
> $(mkValue' "{'a': 2 }")
Object (fromList [("a",Number 2.0)])Since: aeson-extra-0.3.1.0
Re-exports
module Data.Aeson.Compat