-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Fast JSON parsing and encoding -- -- A JSON parsing and encoding library optimized for ease of use and high -- performance. -- -- To get started, see the documentation for the Data.Aeson -- module below. -- -- Parsing performance on a late 2013 MacBook Pro (2.6GHz Core i7), -- running 64-bit GHC 7.10.1, for mostly-English tweets from Twitter's -- JSON search API: -- --
-- withObject "Person" $ \o -> -- Person -- <$> o .: "name" <?> Key "name" -- <*> o .: "age" <?> Key "age" ---- -- (Standard methods like '(.:)' already do this.) -- -- With such annotations, if an error occurs, you will get a JSON Path -- location of that error. -- -- Since 0.10 (>) :: Parser a -> JSONPathElement -> Parser a -- | Annotate an error message with a JSONPath error location. formatError :: JSONPath -> String -> String -- | Convert a value from JSON, failing if the types do not match. ifromJSON :: (FromJSON a) => Value -> IResult a -- | Run a Parser. iparse :: (a -> Parser b) -> a -> IResult b module Data.Aeson.Encoding.Internal -- | An encoding of a JSON value. -- -- tag represents which kind of JSON the Encoding is encoding -- to, we reuse Text and Value as tags here. newtype Encoding' tag Encoding :: Builder -> Encoding' tag -- | Acquire the underlying bytestring builder. [fromEncoding] :: Encoding' tag -> Builder -- | Often used synonnym for Encoding'. type Encoding = Encoding' Value encodingToLazyByteString :: Encoding' a -> ByteString -- | Make Encoding from Builder. -- -- Use with care! You have to make sure that the passed Builder is a -- valid JSON Encoding! unsafeToEncoding :: Builder -> Encoding' a retagEncoding :: Encoding' a -> Encoding' b -- | A series of values that, when encoded, should be separated by commas. -- Since 0.11.0.0, the .= operator is overloaded to create -- either (Text, Value) or Series. You can use Series -- when encoding directly to a bytestring builder as in the following -- example: -- --
-- toEncoding (Person name age) = pairs ("name" .= name <> "age" .= age)
--
data Series
Empty :: Series
Value :: (Encoding' Series) -> Series
-- | Encode a series of key/value pairs, separated by commas.
pairs :: Series -> Encoding
pair :: Text -> Encoding -> Series
pair' :: Encoding' Text -> Encoding -> Series
nullEncoding :: Encoding' a -> Bool
emptyArray_ :: Encoding
emptyObject_ :: Encoding
wrapObject :: Encoding' a -> Encoding
wrapArray :: Encoding' a -> Encoding
null_ :: Encoding
bool :: Bool -> Encoding
text :: Text -> Encoding' a
lazyText :: Text -> Encoding' a
string :: String -> Encoding' a
list :: (a -> Encoding) -> [a] -> Encoding
-- | Encode as JSON object
dict :: (k -> Encoding' Text) -> (v -> Encoding) -> (forall a. (k -> v -> a -> a) -> a -> m -> a) -> m -> Encoding
-- | Encode as a tuple.
--
-- @ toEncoding (X a b c) = tuple $ toEncoding a >*< toEncoding b
-- >*< toEncoding c
tuple :: Encoding' InArray -> Encoding
-- | See tuple.
(>*<) :: Encoding' a -> Encoding' b -> Encoding' InArray
infixr 6 >*<
-- | Type tag for tuples contents, see tuple.
data InArray
empty :: Encoding' a
(><) :: Encoding' a -> Encoding' a -> Encoding' a
infixr 6 ><
econcat :: [Encoding' a] -> Encoding' a
int8 :: Int8 -> Encoding
int16 :: Int16 -> Encoding
int32 :: Int32 -> Encoding
int64 :: Int64 -> Encoding
int :: Int -> Encoding
word8 :: Word8 -> Encoding
word16 :: Word16 -> Encoding
word32 :: Word32 -> Encoding
word64 :: Word64 -> Encoding
word :: Word -> Encoding
integer :: Integer -> Encoding
float :: Float -> Encoding
double :: Double -> Encoding
scientific :: Scientific -> Encoding
int8Text :: Int8 -> Encoding' a
int16Text :: Int16 -> Encoding' a
int32Text :: Int32 -> Encoding' a
int64Text :: Int64 -> Encoding' a
intText :: Int -> Encoding' a
word8Text :: Word8 -> Encoding' a
word16Text :: Word16 -> Encoding' a
word32Text :: Word32 -> Encoding' a
word64Text :: Word64 -> Encoding' a
wordText :: Word -> Encoding' a
integerText :: Integer -> Encoding' a
floatText :: Float -> Encoding' a
doubleText :: Double -> Encoding' a
scientificText :: Scientific -> Encoding' a
day :: Day -> Encoding' a
localTime :: LocalTime -> Encoding' a
utcTime :: UTCTime -> Encoding' a
timeOfDay :: TimeOfDay -> Encoding' a
zonedTime :: ZonedTime -> Encoding' a
value :: Value -> Encoding
comma :: Encoding' a
colon :: Encoding' a
openBracket :: Encoding' a
closeBracket :: Encoding' a
openCurly :: Encoding' a
closeCurly :: Encoding' a
instance GHC.Show.Show (Data.Aeson.Encoding.Internal.Encoding' a)
instance GHC.Classes.Eq (Data.Aeson.Encoding.Internal.Encoding' a)
instance GHC.Classes.Ord (Data.Aeson.Encoding.Internal.Encoding' a)
instance Data.Semigroup.Semigroup Data.Aeson.Encoding.Internal.Series
instance GHC.Base.Monoid Data.Aeson.Encoding.Internal.Series
-- | Functions in this module return well-formed Encoding'.
-- Polymorphic variants, which return Encoding a, return
-- a textual JSON value, so it can be used as both Encoding'
-- Text and Encoding = Encoding'
-- Value.
module Data.Aeson.Encoding
-- | Often used synonnym for Encoding'.
type Encoding = Encoding' Value
-- | An encoding of a JSON value.
--
-- tag represents which kind of JSON the Encoding is encoding
-- to, we reuse Text and Value as tags here.
data Encoding' tag
encodingToLazyByteString :: Encoding' a -> ByteString
-- | Acquire the underlying bytestring builder.
fromEncoding :: Encoding' tag -> Builder
-- | Make Encoding from Builder.
--
-- Use with care! You have to make sure that the passed Builder is a
-- valid JSON Encoding!
unsafeToEncoding :: Builder -> Encoding' a
-- | A series of values that, when encoded, should be separated by commas.
-- Since 0.11.0.0, the .= operator is overloaded to create
-- either (Text, Value) or Series. You can use Series
-- when encoding directly to a bytestring builder as in the following
-- example:
--
--
-- toEncoding (Person name age) = pairs ("name" .= name <> "age" .= age)
--
data Series
-- | Encode a series of key/value pairs, separated by commas.
pairs :: Series -> Encoding
pair :: Text -> Encoding -> Series
pair' :: Encoding' Text -> Encoding -> Series
nullEncoding :: Encoding' a -> Bool
emptyArray_ :: Encoding
emptyObject_ :: Encoding
text :: Text -> Encoding' a
lazyText :: Text -> Encoding' a
string :: String -> Encoding' a
list :: (a -> Encoding) -> [a] -> Encoding
-- | Encode as JSON object
dict :: (k -> Encoding' Text) -> (v -> Encoding) -> (forall a. (k -> v -> a -> a) -> a -> m -> a) -> m -> Encoding
null_ :: Encoding
bool :: Bool -> Encoding
int8 :: Int8 -> Encoding
int16 :: Int16 -> Encoding
int32 :: Int32 -> Encoding
int64 :: Int64 -> Encoding
int :: Int -> Encoding
word8 :: Word8 -> Encoding
word16 :: Word16 -> Encoding
word32 :: Word32 -> Encoding
word64 :: Word64 -> Encoding
word :: Word -> Encoding
integer :: Integer -> Encoding
float :: Float -> Encoding
double :: Double -> Encoding
scientific :: Scientific -> Encoding
int8Text :: Int8 -> Encoding' a
int16Text :: Int16 -> Encoding' a
int32Text :: Int32 -> Encoding' a
int64Text :: Int64 -> Encoding' a
intText :: Int -> Encoding' a
word8Text :: Word8 -> Encoding' a
word16Text :: Word16 -> Encoding' a
word32Text :: Word32 -> Encoding' a
word64Text :: Word64 -> Encoding' a
wordText :: Word -> Encoding' a
integerText :: Integer -> Encoding' a
floatText :: Float -> Encoding' a
doubleText :: Double -> Encoding' a
scientificText :: Scientific -> Encoding' a
day :: Day -> Encoding' a
localTime :: LocalTime -> Encoding' a
utcTime :: UTCTime -> Encoding' a
timeOfDay :: TimeOfDay -> Encoding' a
zonedTime :: ZonedTime -> Encoding' a
value :: Value -> Encoding
-- | Types for working with JSON data.
module Data.Aeson.Types
-- | A JSON value represented as a Haskell value.
data Value
Object :: !Object -> Value
Array :: !Array -> Value
String :: !Text -> Value
Number :: !Scientific -> Value
Bool :: !Bool -> Value
Null :: Value
-- | Often used synonnym for Encoding'.
type Encoding = Encoding' Value
-- | Make Encoding from Builder.
--
-- Use with care! You have to make sure that the passed Builder is a
-- valid JSON Encoding!
unsafeToEncoding :: Builder -> Encoding' a
-- | Acquire the underlying bytestring builder.
fromEncoding :: Encoding' tag -> Builder
-- | A series of values that, when encoded, should be separated by commas.
-- Since 0.11.0.0, the .= operator is overloaded to create
-- either (Text, Value) or Series. You can use Series
-- when encoding directly to a bytestring builder as in the following
-- example:
--
--
-- toEncoding (Person name age) = pairs ("name" .= name <> "age" .= age)
--
data Series
-- | A JSON "array" (sequence).
type Array = Vector Value
-- | The empty array.
emptyArray :: Value
-- | A key/value pair for an Object.
type Pair = (Text, Value)
-- | A JSON "object" (key/value map).
type Object = HashMap Text Value
-- | The empty object.
emptyObject :: Value
-- | A newtype wrapper for UTCTime that uses the same non-standard
-- serialization format as Microsoft .NET, whose System.DateTime
-- type is by default serialized to JSON as in the following example:
--
-- -- /Date(1302547608878)/ ---- -- The number represents milliseconds since the Unix epoch. newtype DotNetTime DotNetTime :: UTCTime -> DotNetTime -- | Acquire the underlying value. [fromDotNetTime] :: DotNetTime -> UTCTime -- | Fail parsing due to a type mismatch, with a descriptive message. -- -- Example usage: -- --
-- instance FromJSON Coord where
-- parseJSON (Object v) = {- type matches, life is good -}
-- parseJSON wat = typeMismatch "Coord" wat
--
typeMismatch :: String -> Value -> Parser a
-- | A JSON parser.
data Parser a
-- | The result of running a Parser.
data Result a
Error :: String -> Result a
Success :: a -> Result a
-- | A type that can be converted from JSON, with the possibility of
-- failure.
--
-- In many cases, you can get the compiler to generate parsing code for
-- you (see below). To begin, let's cover writing an instance by hand.
--
-- There are various reasons a conversion could fail. For example, an
-- Object could be missing a required key, an Array could
-- be of the wrong size, or a value could be of an incompatible type.
--
-- The basic ways to signal a failed conversion are as follows:
--
--
-- -- Allow ourselves to write Text literals.
-- {-# LANGUAGE OverloadedStrings #-}
--
-- data Coord = Coord { x :: Double, y :: Double }
--
-- instance FromJSON Coord where
-- parseJSON (Object v) = Coord
-- <$> v .: "x"
-- <*> v .: "y"
--
-- -- We do not expect a non-Object value here.
-- -- We could use mzero to fail, but typeMismatch
-- -- gives a much more informative error message.
-- parseJSON invalid = typeMismatch "Coord" invalid
--
--
-- For this common case of only being concerned with a single type of
-- JSON value, the functions withObject, withNumber,
-- etc. are provided. Their use is to be preferred when possible, since
-- they are more terse. Using withObject, we can rewrite the
-- above instance (assuming the same language extension and data type)
-- as:
--
-- -- instance FromJSON Coord where -- parseJSON = withObject "Coord" $ v -> Coord -- <$> v .: "x" -- <*> v .: "y" ---- -- Instead of manually writing your FromJSON instance, there are -- two options to do it automatically: -- --
-- {-# LANGUAGE DeriveGeneric #-}
--
-- import GHC.Generics
--
-- data Coord = Coord { x :: Double, y :: Double } deriving Generic
--
-- instance FromJSON Coord
--
--
-- If DefaultSignatures doesn't give exactly the results you
-- want, you can customize the generic decoding with only a tiny amount
-- of effort, using genericParseJSON with your preferred
-- Options:
--
-- -- instance FromJSON Coord where -- parseJSON = genericParseJSON defaultOptions --class FromJSON a where parseJSON = genericParseJSON defaultOptions parseJSONList (Array a) = zipWithM (parseIndexedJSON parseJSON) [0 .. ] . toList $ a parseJSONList v = typeMismatch "[a]" v parseJSON :: FromJSON a => Value -> Parser a parseJSON :: (FromJSON a, Generic a, GFromJSON Zero (Rep a)) => Value -> Parser a parseJSONList :: FromJSON a => Value -> Parser [a] -- | Convert a value from JSON, failing if the types do not match. fromJSON :: (FromJSON a) => Value -> Result a -- | Run a Parser. parse :: (a -> Parser b) -> a -> Result b -- | Run a Parser with an Either result type. If the parse -- fails, the Left payload will contain an error message. parseEither :: (a -> Parser b) -> a -> Either String b -- | Run a Parser with a Maybe result type. parseMaybe :: (a -> Parser b) -> a -> Maybe b -- | A type that can be converted to JSON. -- -- An example type and instance: -- --
-- -- Allow ourselves to write Text literals.
-- {-# LANGUAGE OverloadedStrings #-}
--
-- data Coord = Coord { x :: Double, y :: Double }
--
-- instance ToJSON Coord where
-- toJSON (Coord x y) = object ["x" .= x, "y" .= y]
--
-- toEncoding (Coord x y) = pairs ("x" .= x <> "y" .= y)
--
--
-- Instead of manually writing your ToJSON instance, there are two
-- options to do it automatically:
--
--
-- {-# LANGUAGE DeriveGeneric #-}
--
-- import GHC.Generics
--
-- data Coord = Coord { x :: Double, y :: Double } deriving Generic
--
-- instance ToJSON Coord where
-- toEncoding = genericToEncoding defaultOptions
--
--
-- Why do we provide an implementation for toEncoding here? The
-- toEncoding function is a relatively new addition to this class.
-- To allow users of older versions of this library to upgrade without
-- having to edit all of their instances or encounter surprising
-- incompatibilities, the default implementation of toEncoding
-- uses toJSON. This produces correct results, but since it
-- performs an intermediate conversion to a Value, it will be less
-- efficient than directly emitting an Encoding. Our one-liner
-- definition of toEncoding above bypasses the intermediate
-- Value.
--
-- If DefaultSignatures doesn't give exactly the results you
-- want, you can customize the generic encoding with only a tiny amount
-- of effort, using genericToJSON and genericToEncoding
-- with your preferred Options:
--
-- -- instance ToJSON Coord where -- toJSON = genericToJSON defaultOptions -- toEncoding = genericToEncoding defaultOptions --class ToJSON a where toJSON = genericToJSON defaultOptions toEncoding = value . toJSON toJSONList = listValue toJSON toEncodingList = listEncoding toEncoding -- | Convert a Haskell value to a JSON-friendly intermediate type. toJSON :: ToJSON a => a -> Value -- | Convert a Haskell value to a JSON-friendly intermediate type. toJSON :: (ToJSON a, Generic a, GToJSON Zero (Rep a)) => a -> Value -- | Encode a Haskell value as JSON. -- -- The default implementation of this method creates an intermediate -- Value using toJSON. This provides source-level -- compatibility for people upgrading from older versions of this -- library, but obviously offers no performance advantage. -- -- To benefit from direct encoding, you must provide an -- implementation for this method. The easiest way to do so is by having -- your types implement Generic using the DeriveGeneric -- extension, and then have GHC generate a method body as follows. -- --
-- instance ToJSON Coord where -- toEncoding = genericToEncoding defaultOptions --toEncoding :: ToJSON a => a -> Encoding toJSONList :: ToJSON a => [a] -> Value toEncodingList :: ToJSON a => [a] -> Encoding -- | A key-value pair for encoding a JSON object. class KeyValue kv (.=) :: (KeyValue kv, ToJSON v) => Text -> v -> kv -- | If the inner Parser failed, modify the failure message using -- the provided function. This allows you to create more descriptive -- error messages. For example: -- --
-- parseJSON (Object o) = modifyFailure
-- ("Parsing of the Foo value failed: " ++)
-- (Foo <$> o .: "someField")
--
--
-- Since 0.6.2.0
modifyFailure :: (String -> String) -> Parser a -> Parser a
-- | Typeclass for types that can be used as the key of a map-like
-- container (like Map or HashMap). For example, since
-- Text has a ToJSONKey instance and Char has a
-- ToJSON instance, we can encode a value of type Map
-- Text Char:
--
--
-- >>> LBC8.putStrLn $ encode $ Map.fromList [("foo" :: Text, 'a')]
-- {"foo":"a"}
--
--
-- Since Int also has a ToJSONKey instance, we can
-- similarly write:
--
--
-- >>> LBC8.putStrLn $ encode $ Map.fromList [(5 :: Int, 'a')]
-- {"5":"a"}
--
--
-- JSON documents only accept strings as object keys. For any type from
-- base that has a natural textual representation, it can be
-- expected that its ToJSONKey instance will choose that
-- representation.
--
-- For data types that lack a natural textual representation, an
-- alternative is provided. The map-like container is represented as a
-- JSON array instead of a JSON object. Each value in the array is an
-- array with exactly two values. The first is the key and the second is
-- the value.
--
-- For example, values of type '[Text]' cannot be encoded to a string, so
-- a Map with keys of type '[Text]' is encoded as follows:
--
-- -- >>> LBC8.putStrLn $ encode $ Map.fromList [(["foo","bar","baz" :: Text], 'a')] -- [[["foo","bar","baz"],"a"]] ---- -- The default implementation of ToJSONKey chooses this method of -- encoding a key, using the ToJSON instance of the type. -- -- To use your own data type as the key in a map, all that is needed is -- to write a ToJSONKey (and possibly a FromJSONKey) -- instance for it. If the type cannot be trivially converted to and from -- Text, it is recommended that ToJSONKeyValue is used. -- Since the default implementations of the typeclass methods can build -- this from a ToJSON instance, there is nothing that needs to be -- written: -- --
-- data Foo = Foo { fooAge :: Int, fooName :: Text }
-- deriving (Eq,Ord,Generic)
-- instance ToJSON Foo
-- instance ToJSONKey Foo
--
--
-- That's it. We can now write:
--
--
-- >>> let m = Map.fromList [(Foo 4 "bar",'a'),(Foo 6 "arg",'b')]
--
-- >>> LBC8.putStrLn $ encode m
-- [[{"fooName":"bar","fooAge":4},"a"],[{"fooName":"arg","fooAge":6},"b"]]
--
--
-- The next case to consider is if we have a type that is a newtype
-- wrapper around Text. The recommended approach is to use
-- generalized newtype deriving:
--
--
-- newtype RecordId = RecordId { getRecordId :: Text}
-- deriving (Eq,Ord,ToJSONKey)
--
--
-- Then we may write:
--
--
-- >>> LBC8.putStrLn $ encode $ Map.fromList [(RecordId "abc",'a')]
-- {"abc":"a"}
--
--
-- Simple sum types are a final case worth considering. Suppose we have:
--
-- -- data Color = Red | Green | Blue -- deriving (Show,Read,Eq,Ord) ---- -- It is possible to get the ToJSONKey instance for free as we did -- with Foo. However, in this case, we have a natural way to go -- to and from Text that does not require any escape sequences. -- So, in this example, ToJSONKeyText will be used instead of -- ToJSONKeyValue. The Show instance can be used to help -- write ToJSONKey: -- --
-- instance ToJSONKey Color where -- toJSONKey = ToJSONKeyText f g -- where f = Text.pack . show -- g = text . Text.pack . show -- -- text function is from Data.Aeson.Encoding ---- -- The situation of needing to turning function a -> Text -- into a ToJSONKeyFunction is common enough that a special -- combinator is provided for it. The above instance can be rewritten as: -- --
-- instance ToJSONKey Color where -- toJSONKey = toJSONKeyText (Text.pack . show) ---- -- The performance of the above instance can be improved by not using -- String as an intermediate step when converting to Text. -- One option for improving performance would be to use template haskell -- machinery from the text-show package. However, even with the -- approach, the Encoding (a wrapper around a bytestring builder) -- is generated by encoding the Text to a ByteString, an -- intermediate step that could be avoided. The fastest possible -- implementation would be: -- --
-- -- Assuming that OverloadedStrings is enabled
-- instance ToJSONKey Color where
-- toJSONKey = ToJSONKeyText f g
-- where f x = case x of {Red -> "Red";Green ->"Green";Blue -> "Blue"}
-- g x = case x of {Red -> text "Red";Green -> text "Green";Blue -> text "Blue"}
-- -- text function is from Data.Aeson.Encoding
--
--
-- This works because GHC can lift the encoded values out of the case
-- statements, which means that they are only evaluated once. This
-- approach should only be used when there is a serious need to maximize
-- performance.
class ToJSONKey a where toJSONKey = ToJSONKeyValue toJSON toEncoding toJSONKeyList = ToJSONKeyValue toJSON toEncoding
-- | Strategy for rendering the key for a map-like container.
toJSONKey :: ToJSONKey a => ToJSONKeyFunction a
-- | Strategy for rendering the key for a map-like container.
toJSONKey :: (ToJSONKey a, ToJSON a) => ToJSONKeyFunction a
-- | This is similar in spirit to the showsList method of
-- Show. It makes it possible to give String keys special
-- treatment without using OverlappingInstances. End users
-- should always be able to use the default implementation of this
-- method.
toJSONKeyList :: ToJSONKey a => ToJSONKeyFunction [a]
-- | This is similar in spirit to the showsList method of
-- Show. It makes it possible to give String keys special
-- treatment without using OverlappingInstances. End users
-- should always be able to use the default implementation of this
-- method.
toJSONKeyList :: (ToJSONKey a, ToJSON a) => ToJSONKeyFunction [a]
data ToJSONKeyFunction a
-- | key is encoded to string, produces object
ToJSONKeyText :: !(a -> Text) -> !(a -> Encoding' Text) -> ToJSONKeyFunction a
-- | key is encoded to value, produces array
ToJSONKeyValue :: !(a -> Value) -> !(a -> Encoding) -> ToJSONKeyFunction a
-- | Helper for creating textual keys.
--
-- -- instance ToJSONKey MyKey where -- toJSONKey = toJSONKeyText myKeyToText -- where -- myKeyToText = Text.pack . show -- or showt from text-show --toJSONKeyText :: (a -> Text) -> ToJSONKeyFunction a -- | Contravariant map, as ToJSONKeyFunction is a contravariant -- functor. contramapToJSONKeyFunction :: (b -> a) -> ToJSONKeyFunction a -> ToJSONKeyFunction b -- | Read the docs for ToJSONKey first. This class is a conversion -- in the opposite direction. If you have a newtype wrapper around -- Text, the recommended way to define instances is with -- generalized newtype deriving: -- --
-- newtype SomeId = SomeId { getSomeId :: Text }
-- deriving (Eq,Ord,Hashable,FromJSONKey)
--
class FromJSONKey a where fromJSONKey = FromJSONKeyValue parseJSON fromJSONKeyList = FromJSONKeyValue parseJSON
-- | Strategy for parsing the key of a map-like container.
fromJSONKey :: FromJSONKey a => FromJSONKeyFunction a
-- | Strategy for parsing the key of a map-like container.
fromJSONKey :: (FromJSONKey a, FromJSON a) => FromJSONKeyFunction a
-- | This is similar in spirit to the readList method of
-- Read. It makes it possible to give String keys special
-- treatment without using OverlappingInstances. End users
-- should always be able to use the default implementation of this
-- method.
fromJSONKeyList :: FromJSONKey a => FromJSONKeyFunction [a]
-- | This is similar in spirit to the readList method of
-- Read. It makes it possible to give String keys special
-- treatment without using OverlappingInstances. End users
-- should always be able to use the default implementation of this
-- method.
fromJSONKeyList :: (FromJSONKey a, FromJSON a) => FromJSONKeyFunction [a]
-- | This type is related to ToJSONKeyFunction. If
-- FromJSONKeyValue is used in the FromJSONKey instance,
-- then ToJSONKeyValue should be used in the ToJSONKey
-- instance. The other three data constructors for this type all
-- correspond to ToJSONKeyText. Strictly speaking,
-- FromJSONKeyTextParser is more powerful than
-- FromJSONKeyText, which is in turn more powerful than
-- FromJSONKeyCoerce. For performance reasons, these exist as
-- three options instead of one.
data FromJSONKeyFunction a
-- | uses coerce (unsafeCoerce in older GHCs)
FromJSONKeyCoerce :: !(CoerceText a) -> FromJSONKeyFunction a
-- | conversion from Text that always succeeds
FromJSONKeyText :: !(Text -> a) -> FromJSONKeyFunction a
-- | conversion from Text that may fail
FromJSONKeyTextParser :: !(Text -> Parser a) -> FromJSONKeyFunction a
-- | conversion for non-textual keys
FromJSONKeyValue :: !(Value -> Parser a) -> FromJSONKeyFunction a
-- | Construct FromJSONKeyFunction for types coercible from
-- Text. This conversion is still unsafe, as Hashable and
-- Eq instances of a should be compatible with
-- Text i.e. hash values should be equal for wrapped values as
-- well. This property will always be maintained if the Hashable
-- and Eq instances are derived with generalized newtype deriving.
-- compatible with Text i.e. hash values be equal for wrapped
-- values as well.
--
-- On pre GHC 7.8 this is unconstrainted function.
fromJSONKeyCoerce :: Coercible Text a => FromJSONKeyFunction a
-- | Semantically the same as coerceFromJSONKeyFunction = fmap coerce =
-- coerce.
--
-- See note on fromJSONKeyCoerce.
coerceFromJSONKeyFunction :: Coercible a b => FromJSONKeyFunction a -> FromJSONKeyFunction b
-- | Same as fmap. Provided for the consistency with
-- ToJSONKeyFunction.
mapFromJSONKeyFunction :: (a -> b) -> FromJSONKeyFunction a -> FromJSONKeyFunction b
-- | Lifting of the FromJSON class to unary type constructors.
--
-- Instead of manually writing your FromJSON1 instance, there are
-- two options to do it automatically:
--
--
-- {-# LANGUAGE DeriveGeneric #-}
--
-- import GHC.Generics
--
-- data Pair a b = Pair { pairFst :: a, pairSnd :: b } deriving Generic1
--
-- instance FromJSON a => FromJSON1 (Pair a)
--
--
-- If DefaultSignatures doesn't give exactly the results you
-- want, you can customize the generic decoding with only a tiny amount
-- of effort, using genericLiftParseJSON with your preferred
-- Options:
--
-- -- instance FromJSON a => FromJSON1 (Pair a) where -- liftParseJSON = genericLiftParseJSON defaultOptions --class FromJSON1 f where liftParseJSON = genericLiftParseJSON defaultOptions liftParseJSONList f g v = listParser (liftParseJSON f g) v liftParseJSON :: FromJSON1 f => (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (f a) liftParseJSON :: (FromJSON1 f, Generic1 f, GFromJSON One (Rep1 f)) => (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (f a) liftParseJSONList :: FromJSON1 f => (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [f a] -- | Lift the standard parseJSON function through the type -- constructor. parseJSON1 :: (FromJSON1 f, FromJSON a) => Value -> Parser (f a) -- | Lifting of the FromJSON class to binary type constructors. -- -- Instead of manually writing your FromJSON2 instance, -- Data.Aeson.TH provides Template Haskell functions which will -- derive an instance at compile time. class FromJSON2 f where liftParseJSONList2 fa ga fb gb v = case v of { Array vals -> fmap toList (mapM (liftParseJSON2 fa ga fb gb) vals) _ -> typeMismatch "[a]" v } liftParseJSON2 :: FromJSON2 f => (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (f a b) liftParseJSONList2 :: FromJSON2 f => (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [f a b] -- | Lift the standard parseJSON function through the type -- constructor. parseJSON2 :: (FromJSON2 f, FromJSON a, FromJSON b) => Value -> Parser (f a b) -- | Lifting of the ToJSON class to unary type constructors. -- -- Instead of manually writing your ToJSON1 instance, there are -- two options to do it automatically: -- --
-- {-# LANGUAGE DeriveGeneric #-}
--
-- import GHC.Generics
--
-- data Pair = Pair { pairFst :: a, pairSnd :: b } deriving Generic1
--
-- instance ToJSON a => ToJSON1 (Pair a)
--
--
-- If DefaultSignatures doesn't give exactly the results you
-- want, you can customize the generic encoding with only a tiny amount
-- of effort, using genericLiftToJSON and
-- genericLiftToEncoding with your preferred Options:
--
-- -- instance ToJSON a => ToJSON1 (Pair a) where -- liftToJSON = genericLiftToJSON defaultOptions -- liftToEncoding = genericLiftToEncoding defaultOptions --class ToJSON1 f where liftToJSON = genericLiftToJSON defaultOptions liftToJSONList f g = listValue (liftToJSON f g) liftToEncoding = genericLiftToEncoding defaultOptions liftToEncodingList f g = listEncoding (liftToEncoding f g) liftToJSON :: ToJSON1 f => (a -> Value) -> ([a] -> Value) -> f a -> Value liftToJSON :: (ToJSON1 f, Generic1 f, GToJSON One (Rep1 f)) => (a -> Value) -> ([a] -> Value) -> f a -> Value liftToJSONList :: ToJSON1 f => (a -> Value) -> ([a] -> Value) -> [f a] -> Value liftToEncoding :: ToJSON1 f => (a -> Encoding) -> ([a] -> Encoding) -> f a -> Encoding liftToEncoding :: (ToJSON1 f, Generic1 f, GToEncoding One (Rep1 f)) => (a -> Encoding) -> ([a] -> Encoding) -> f a -> Encoding liftToEncodingList :: ToJSON1 f => (a -> Encoding) -> ([a] -> Encoding) -> [f a] -> Encoding -- | Lift the standard toJSON function through the type constructor. toJSON1 :: (ToJSON1 f, ToJSON a) => f a -> Value -- | Lift the standard toEncoding function through the type -- constructor. toEncoding1 :: (ToJSON1 f, ToJSON a) => f a -> Encoding -- | Lifting of the ToJSON class to binary type constructors. -- -- Instead of manually writing your ToJSON2 instance, -- Data.Aeson.TH provides Template Haskell functions which will -- derive an instance at compile time. -- -- The compiler cannot provide a default generic implementation for -- liftToJSON2, unlike toJSON and liftToJSON. class ToJSON2 f where liftToJSONList2 fa ga fb gb = listValue (liftToJSON2 fa ga fb gb) liftToEncodingList2 fa ga fb gb = listEncoding (liftToEncoding2 fa ga fb gb) liftToJSON2 :: ToJSON2 f => (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> f a b -> Value liftToJSONList2 :: ToJSON2 f => (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [f a b] -> Value liftToEncoding2 :: ToJSON2 f => (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> f a b -> Encoding liftToEncodingList2 :: ToJSON2 f => (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [f a b] -> Encoding -- | Lift the standard toJSON function through the type constructor. toJSON2 :: (ToJSON2 f, ToJSON a, ToJSON b) => f a b -> Value -- | Lift the standard toEncoding function through the type -- constructor. toEncoding2 :: (ToJSON2 f, ToJSON a, ToJSON b) => f a b -> Encoding -- | Class of generic representation types that can be converted from JSON. class GFromJSON arity f -- | This method (applied to defaultOptions) is used as the default -- generic implementation of parseJSON (if the arity is -- Zero) or liftParseJSON (if the arity is -- One). gParseJSON :: GFromJSON arity f => Options -> FromArgs arity a -> Value -> Parser (f a) -- | A FromArgs value either stores nothing (for FromJSON) or -- it stores the two function arguments that decode occurrences of the -- type parameter (for FromJSON1). data FromArgs arity a [NoFromArgs] :: FromArgs Zero a [From1Args] :: (Value -> Parser a) -> (Value -> Parser [a]) -> FromArgs One a -- | Class of generic representation types that can be converted to JSON. class GToJSON arity f -- | This method (applied to defaultOptions) is used as the default -- generic implementation of toJSON (if the arity is -- Zero) or liftToJSON (if the arity is -- One). gToJSON :: GToJSON arity f => Options -> ToArgs Value arity a -> f a -> Value -- | Class of generic representation types that can be converted to a JSON -- Encoding. class GToEncoding arity f -- | This method (applied to defaultOptions) can be used as the -- default generic implementation of toEncoding (if the -- arity is Zero) or liftToEncoding (if the -- arity is One). gToEncoding :: GToEncoding arity f => Options -> ToArgs Encoding arity a -> f a -> Encoding -- | A ToArgs value either stores nothing (for ToJSON) or it -- stores the two function arguments that encode occurrences of the type -- parameter (for ToJSON1). data ToArgs res arity a [NoToArgs] :: ToArgs res Zero a [To1Args] :: (a -> res) -> ([a] -> res) -> ToArgs res One a -- | A type-level indicator that ToJSON or FromJSON is -- being derived generically. data Zero -- | A type-level indicator that ToJSON1 or FromJSON1 is -- being derived generically. data One -- | A configurable generic JSON creator. This function applied to -- defaultOptions is used as the default for toJSON when -- the type is an instance of Generic. genericToJSON :: (Generic a, GToJSON Zero (Rep a)) => Options -> a -> Value -- | A configurable generic JSON creator. This function applied to -- defaultOptions is used as the default for liftToJSON -- when the type is an instance of Generic1. genericLiftToJSON :: (Generic1 f, GToJSON One (Rep1 f)) => Options -> (a -> Value) -> ([a] -> Value) -> f a -> Value -- | A configurable generic JSON encoder. This function applied to -- defaultOptions is used as the default for toEncoding -- when the type is an instance of Generic. genericToEncoding :: (Generic a, GToEncoding Zero (Rep a)) => Options -> a -> Encoding -- | A configurable generic JSON encoder. This function applied to -- defaultOptions is used as the default for liftToEncoding -- when the type is an instance of Generic1. genericLiftToEncoding :: (Generic1 f, GToEncoding One (Rep1 f)) => Options -> (a -> Encoding) -> ([a] -> Encoding) -> f a -> Encoding -- | A configurable generic JSON decoder. This function applied to -- defaultOptions is used as the default for parseJSON when -- the type is an instance of Generic. genericParseJSON :: (Generic a, GFromJSON Zero (Rep a)) => Options -> Value -> Parser a -- | A configurable generic JSON decoder. This function applied to -- defaultOptions is used as the default for liftParseJSON -- when the type is an instance of Generic1. genericLiftParseJSON :: (Generic1 f, GFromJSON One (Rep1 f)) => Options -> (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (f a) -- | withObject expected f value applies f to the -- Object when value is an Object and fails -- using typeMismatch expected otherwise. withObject :: String -> (Object -> Parser a) -> Value -> Parser a -- | withText expected f value applies f to the -- Text when value is a String and fails using -- typeMismatch expected otherwise. withText :: String -> (Text -> Parser a) -> Value -> Parser a -- | withArray expected f value applies f to the -- Array when value is an Array and fails using -- typeMismatch expected otherwise. withArray :: String -> (Array -> Parser a) -> Value -> Parser a -- | withNumber expected f value applies f to the -- Number when value is a Number. and fails using -- typeMismatch expected otherwise. -- | Deprecated: Use withScientific instead withNumber :: String -> (Number -> Parser a) -> Value -> Parser a -- | withScientific expected f value applies f to the -- Scientific number when value is a Number. and -- fails using typeMismatch expected otherwise. withScientific :: String -> (Scientific -> Parser a) -> Value -> Parser a -- | withBool expected f value applies f to the -- Bool when value is a Bool and fails using -- typeMismatch expected otherwise. withBool :: String -> (Bool -> Parser a) -> Value -> Parser a -- | Encode a series of key/value pairs, separated by commas. pairs :: Series -> Encoding -- | Encode a Foldable as a JSON array. foldable :: (Foldable t, ToJSON a) => t a -> Encoding -- | Retrieve the value associated with the given key of an Object. -- The result is empty if the key is not present or the value -- cannot be converted to the desired type. -- -- This accessor is appropriate if the key and value must be -- present in an object for it to be valid. If the key and value are -- optional, use .:? instead. (.:) :: (FromJSON a) => Object -> Text -> Parser a -- | Retrieve the value associated with the given key of an Object. -- The result is Nothing if the key is not present or if its value -- is Null, or empty if the value cannot be converted to -- the desired type. -- -- This accessor is most useful if the key and value can be absent from -- an object without affecting its validity. If the key and value are -- mandatory, use .: instead. (.:?) :: (FromJSON a) => Object -> Text -> Parser (Maybe a) -- | Retrieve the value associated with the given key of an Object. -- The result is Nothing if the key is not present or -- empty if the value cannot be converted to the desired type. -- -- This differs from .:? by attempting to parse Null the -- same as any other JSON value, instead of interpreting it as -- Nothing. (.:!) :: (FromJSON a) => Object -> Text -> Parser (Maybe a) -- | Helper for use in combination with .:? to provide default -- values for optional JSON object fields. -- -- This combinator is most useful if the key and value can be absent from -- an object without affecting its validity and we know a default value -- to assign in that case. If the key and value are mandatory, use -- .: instead. -- -- Example usage: -- --
-- v1 <- o .:? "opt_field_with_dfl" .!= "default_val" -- v2 <- o .: "mandatory_field" -- v3 <- o .:? "opt_field2" --(.!=) :: Parser (Maybe a) -> a -> Parser a -- | Create a Value from a list of name/value Pairs. If -- duplicate keys arise, earlier keys and their associated values win. object :: [Pair] -> Value -- | Function variant of .:. parseField :: (FromJSON a) => Object -> Text -> Parser a -- | Function variant of .:?. parseFieldMaybe :: (FromJSON a) => Object -> Text -> Parser (Maybe a) -- | Function variant of .:!. parseFieldMaybe' :: (FromJSON a) => Object -> Text -> Parser (Maybe a) -- | Variant of .: with explicit parser function. -- -- E.g. explicitParseField parseJSON1 :: -- (FromJSON1 f, FromJSON a) -> Object -> -- Text -> Parser (f a) explicitParseField :: (Value -> Parser a) -> Object -> Text -> Parser a -- | Variant of .:? with explicit parser function. explicitParseFieldMaybe :: (Value -> Parser a) -> Object -> Text -> Parser (Maybe a) -- | Variant of .:! with explicit parser function. explicitParseFieldMaybe' :: (Value -> Parser a) -> Object -> Text -> Parser (Maybe a) -- | Helper function to use with liftToEncoding. Useful when writing -- own ToJSON1 instances. -- --
-- newtype F a = F [a] -- -- -- This instance encodes String as an array of chars -- instance ToJSON1 F where -- liftToJSON tj _ (F xs) = liftToJSON tj (listValue tj) xs -- liftToEncoding te _ (F xs) = liftToEncoding te (listEncoding te) xs -- -- instance FromJSON1 F where -- liftParseJSON p _ v = F <$> liftParseJSON p (listParser p) v --listEncoding :: (a -> Encoding) -> [a] -> Encoding -- | Helper function to use with liftToJSON, see -- listEncoding. listValue :: (a -> Value) -> [a] -> Value -- | Helper function to use with liftParseJSON. See -- listEncoding. listParser :: (Value -> Parser a) -> Value -> Parser [a] -- | Options that specify how to encode/decode your datatype to/from JSON. data Options Options :: (String -> String) -> (String -> String) -> Bool -> Bool -> SumEncoding -> Bool -> Options -- | Function applied to field labels. Handy for removing common record -- prefixes for example. [fieldLabelModifier] :: Options -> String -> String -- | Function applied to constructor tags which could be handy for -- lower-casing them for example. [constructorTagModifier] :: Options -> String -> String -- | If True the constructors of a datatype, with all nullary -- constructors, will be encoded to just a string with the constructor -- tag. If False the encoding will always follow the -- sumEncoding. [allNullaryToStringTag] :: Options -> Bool -- | If True record fields with a Nothing value will be -- omitted from the resulting object. If False the resulting -- object will include those fields mapping to null. [omitNothingFields] :: Options -> Bool -- | Specifies how to encode constructors of a sum datatype. [sumEncoding] :: Options -> SumEncoding -- | Hide the field name when a record constructor has only one field, like -- a newtype. [unwrapUnaryRecords] :: Options -> Bool -- | Specifies how to encode constructors of a sum datatype. data SumEncoding -- | A constructor will be encoded to an object with a field -- tagFieldName which specifies the constructor tag (modified by -- the constructorTagModifier). If the constructor is a record the -- encoded record fields will be unpacked into this object. So make sure -- that your record doesn't have a field with the same label as the -- tagFieldName. Otherwise the tag gets overwritten by the encoded -- value of that field! If the constructor is not a record the encoded -- constructor contents will be stored under the contentsFieldName -- field. TaggedObject :: String -> String -> SumEncoding [tagFieldName] :: SumEncoding -> String [contentsFieldName] :: SumEncoding -> String -- | Constructor names won't be encoded. Instead only the contents of the -- constructor will be encoded as if the type had single constructor. -- JSON encodings have to be disjoint for decoding to work properly. -- -- When decoding, constructors are tried in the order of definition. If -- some encodings overlap, the first one defined will succeed. -- -- Note: Nullary constructors are encoded as the string (using -- constructorTagModifier). Having a nullary constructor alongside -- a single field constructor that encodes to a string leads to -- ambiguity. -- -- Note: Only the last error is kept when decoding, so in the case -- of mailformed JSON, only an error for the last constructor will be -- reported. UntaggedValue :: SumEncoding -- | A constructor will be encoded to an object with a single field named -- after the constructor tag (modified by the -- constructorTagModifier) which maps to the encoded contents of -- the constructor. ObjectWithSingleField :: SumEncoding -- | A constructor will be encoded to a 2-element array where the first -- element is the tag of the constructor (modified by the -- constructorTagModifier) and the second element the encoded -- contents of the constructor. TwoElemArray :: SumEncoding -- | Converts from CamelCase to another lower case, interspersing the -- character between all capital letters and their previous entries, -- except those capital letters that appear together, like API. -- -- For use by Aeson template haskell calls. -- --
-- camelTo '_' 'CamelCaseAPI' == "camel_case_api" ---- | Deprecated: Use camelTo2 for better results camelTo :: Char -> String -> String -- | Better version of camelTo. Example where it works better: -- --
-- camelTo '_' 'CamelAPICase' == "camel_apicase" -- camelTo2 '_' 'CamelAPICase' == "camel_api_case" --camelTo2 :: Char -> String -> String -- | Default encoding Options: -- --
-- Options
-- { fieldLabelModifier = id
-- , constructorTagModifier = id
-- , allNullaryToStringTag = True
-- , omitNothingFields = False
-- , sumEncoding = defaultTaggedObject
-- , unwrapUnaryRecords = False
-- }
--
defaultOptions :: Options
-- | Default TaggedObject SumEncoding options:
--
--
-- defaultTaggedObject = TaggedObject
-- { tagFieldName = "tag"
-- , contentsFieldName = "contents"
-- }
--
defaultTaggedObject :: SumEncoding
-- | Most frequently, you'll probably want to encode straight to UTF-8 (the
-- standard JSON encoding) using encode.
--
-- You can use the conversions to Builders when embedding JSON
-- messages as parts of a protocol.
module Data.Aeson.Text
-- | Encode a JSON Value to a Data.Text.Lazy
--
-- Note: uses toEncoding
encodeToLazyText :: ToJSON a => a -> Text
-- | Encode a JSON Value to a Data.Text Builder, which
-- can be embedded efficiently in a text-based protocol.
--
-- If you are going to immediately encode straight to a
-- ByteString, it is more efficient to use
-- encodeToBuilder instead.
--
-- Note: Uses toJSON
encodeToTextBuilder :: ToJSON a => a -> Builder
-- | Types and functions for working efficiently with JSON data.
--
-- (A note on naming: in Greek mythology, Aeson was the father of Jason.)
module Data.Aeson
-- | Efficiently deserialize a JSON value from a lazy ByteString. If
-- this fails due to incomplete or invalid input, Nothing is
-- returned.
--
-- The input must consist solely of a JSON document, with no trailing
-- data except for whitespace.
--
-- This function parses immediately, but defers conversion. See
-- json for details.
decode :: (FromJSON a) => ByteString -> Maybe a
-- | Efficiently deserialize a JSON value from a lazy ByteString. If
-- this fails due to incomplete or invalid input, Nothing is
-- returned.
--
-- The input must consist solely of a JSON document, with no trailing
-- data except for whitespace.
--
-- This function parses and performs conversion immediately. See
-- json' for details.
decode' :: (FromJSON a) => ByteString -> Maybe a
-- | Like decode but returns an error message when decoding fails.
eitherDecode :: (FromJSON a) => ByteString -> Either String a
-- | Like decode' but returns an error message when decoding fails.
eitherDecode' :: (FromJSON a) => ByteString -> Either String a
-- | Efficiently serialize a JSON value as a lazy ByteString.
--
-- This is implemented in terms of the ToJSON class's
-- toEncoding method.
encode :: (ToJSON a) => a -> ByteString
-- | Efficiently deserialize a JSON value from a strict ByteString.
-- If this fails due to incomplete or invalid input, Nothing is
-- returned.
--
-- The input must consist solely of a JSON document, with no trailing
-- data except for whitespace.
--
-- This function parses immediately, but defers conversion. See
-- json for details.
decodeStrict :: (FromJSON a) => ByteString -> Maybe a
-- | Efficiently deserialize a JSON value from a strict ByteString.
-- If this fails due to incomplete or invalid input, Nothing is
-- returned.
--
-- The input must consist solely of a JSON document, with no trailing
-- data except for whitespace.
--
-- This function parses and performs conversion immediately. See
-- json' for details.
decodeStrict' :: (FromJSON a) => ByteString -> Maybe a
-- | Like decodeStrict but returns an error message when decoding
-- fails.
eitherDecodeStrict :: (FromJSON a) => ByteString -> Either String a
-- | Like decodeStrict' but returns an error message when decoding
-- fails.
eitherDecodeStrict' :: (FromJSON a) => ByteString -> Either String a
-- | A JSON value represented as a Haskell value.
data Value
Object :: !Object -> Value
Array :: !Array -> Value
String :: !Text -> Value
Number :: !Scientific -> Value
Bool :: !Bool -> Value
Null :: Value
-- | Often used synonnym for Encoding'.
type Encoding = Encoding' Value
-- | Acquire the underlying bytestring builder.
fromEncoding :: Encoding' tag -> Builder
-- | A JSON "array" (sequence).
type Array = Vector Value
-- | A JSON "object" (key/value map).
type Object = HashMap Text Value
-- | A newtype wrapper for UTCTime that uses the same non-standard
-- serialization format as Microsoft .NET, whose System.DateTime
-- type is by default serialized to JSON as in the following example:
--
-- -- /Date(1302547608878)/ ---- -- The number represents milliseconds since the Unix epoch. newtype DotNetTime DotNetTime :: UTCTime -> DotNetTime -- | Acquire the underlying value. [fromDotNetTime] :: DotNetTime -> UTCTime -- | A type that can be converted from JSON, with the possibility of -- failure. -- -- In many cases, you can get the compiler to generate parsing code for -- you (see below). To begin, let's cover writing an instance by hand. -- -- There are various reasons a conversion could fail. For example, an -- Object could be missing a required key, an Array could -- be of the wrong size, or a value could be of an incompatible type. -- -- The basic ways to signal a failed conversion are as follows: -- --
-- -- Allow ourselves to write Text literals.
-- {-# LANGUAGE OverloadedStrings #-}
--
-- data Coord = Coord { x :: Double, y :: Double }
--
-- instance FromJSON Coord where
-- parseJSON (Object v) = Coord
-- <$> v .: "x"
-- <*> v .: "y"
--
-- -- We do not expect a non-Object value here.
-- -- We could use mzero to fail, but typeMismatch
-- -- gives a much more informative error message.
-- parseJSON invalid = typeMismatch "Coord" invalid
--
--
-- For this common case of only being concerned with a single type of
-- JSON value, the functions withObject, withNumber,
-- etc. are provided. Their use is to be preferred when possible, since
-- they are more terse. Using withObject, we can rewrite the
-- above instance (assuming the same language extension and data type)
-- as:
--
-- -- instance FromJSON Coord where -- parseJSON = withObject "Coord" $ v -> Coord -- <$> v .: "x" -- <*> v .: "y" ---- -- Instead of manually writing your FromJSON instance, there are -- two options to do it automatically: -- --
-- {-# LANGUAGE DeriveGeneric #-}
--
-- import GHC.Generics
--
-- data Coord = Coord { x :: Double, y :: Double } deriving Generic
--
-- instance FromJSON Coord
--
--
-- If DefaultSignatures doesn't give exactly the results you
-- want, you can customize the generic decoding with only a tiny amount
-- of effort, using genericParseJSON with your preferred
-- Options:
--
-- -- instance FromJSON Coord where -- parseJSON = genericParseJSON defaultOptions --class FromJSON a where parseJSON = genericParseJSON defaultOptions parseJSONList (Array a) = zipWithM (parseIndexedJSON parseJSON) [0 .. ] . toList $ a parseJSONList v = typeMismatch "[a]" v parseJSON :: FromJSON a => Value -> Parser a parseJSON :: (FromJSON a, Generic a, GFromJSON Zero (Rep a)) => Value -> Parser a parseJSONList :: FromJSON a => Value -> Parser [a] -- | The result of running a Parser. data Result a Error :: String -> Result a Success :: a -> Result a -- | Convert a value from JSON, failing if the types do not match. fromJSON :: (FromJSON a) => Value -> Result a -- | A type that can be converted to JSON. -- -- An example type and instance: -- --
-- -- Allow ourselves to write Text literals.
-- {-# LANGUAGE OverloadedStrings #-}
--
-- data Coord = Coord { x :: Double, y :: Double }
--
-- instance ToJSON Coord where
-- toJSON (Coord x y) = object ["x" .= x, "y" .= y]
--
-- toEncoding (Coord x y) = pairs ("x" .= x <> "y" .= y)
--
--
-- Instead of manually writing your ToJSON instance, there are two
-- options to do it automatically:
--
--
-- {-# LANGUAGE DeriveGeneric #-}
--
-- import GHC.Generics
--
-- data Coord = Coord { x :: Double, y :: Double } deriving Generic
--
-- instance ToJSON Coord where
-- toEncoding = genericToEncoding defaultOptions
--
--
-- Why do we provide an implementation for toEncoding here? The
-- toEncoding function is a relatively new addition to this class.
-- To allow users of older versions of this library to upgrade without
-- having to edit all of their instances or encounter surprising
-- incompatibilities, the default implementation of toEncoding
-- uses toJSON. This produces correct results, but since it
-- performs an intermediate conversion to a Value, it will be less
-- efficient than directly emitting an Encoding. Our one-liner
-- definition of toEncoding above bypasses the intermediate
-- Value.
--
-- If DefaultSignatures doesn't give exactly the results you
-- want, you can customize the generic encoding with only a tiny amount
-- of effort, using genericToJSON and genericToEncoding
-- with your preferred Options:
--
-- -- instance ToJSON Coord where -- toJSON = genericToJSON defaultOptions -- toEncoding = genericToEncoding defaultOptions --class ToJSON a where toJSON = genericToJSON defaultOptions toEncoding = value . toJSON toJSONList = listValue toJSON toEncodingList = listEncoding toEncoding -- | Convert a Haskell value to a JSON-friendly intermediate type. toJSON :: ToJSON a => a -> Value -- | Convert a Haskell value to a JSON-friendly intermediate type. toJSON :: (ToJSON a, Generic a, GToJSON Zero (Rep a)) => a -> Value -- | Encode a Haskell value as JSON. -- -- The default implementation of this method creates an intermediate -- Value using toJSON. This provides source-level -- compatibility for people upgrading from older versions of this -- library, but obviously offers no performance advantage. -- -- To benefit from direct encoding, you must provide an -- implementation for this method. The easiest way to do so is by having -- your types implement Generic using the DeriveGeneric -- extension, and then have GHC generate a method body as follows. -- --
-- instance ToJSON Coord where -- toEncoding = genericToEncoding defaultOptions --toEncoding :: ToJSON a => a -> Encoding toJSONList :: ToJSON a => [a] -> Value toEncodingList :: ToJSON a => [a] -> Encoding -- | A key-value pair for encoding a JSON object. class KeyValue kv (.=) :: (KeyValue kv, ToJSON v) => Text -> v -> kv -- | Typeclass for types that can be used as the key of a map-like -- container (like Map or HashMap). For example, since -- Text has a ToJSONKey instance and Char has a -- ToJSON instance, we can encode a value of type Map -- Text Char: -- --
-- >>> LBC8.putStrLn $ encode $ Map.fromList [("foo" :: Text, 'a')]
-- {"foo":"a"}
--
--
-- Since Int also has a ToJSONKey instance, we can
-- similarly write:
--
--
-- >>> LBC8.putStrLn $ encode $ Map.fromList [(5 :: Int, 'a')]
-- {"5":"a"}
--
--
-- JSON documents only accept strings as object keys. For any type from
-- base that has a natural textual representation, it can be
-- expected that its ToJSONKey instance will choose that
-- representation.
--
-- For data types that lack a natural textual representation, an
-- alternative is provided. The map-like container is represented as a
-- JSON array instead of a JSON object. Each value in the array is an
-- array with exactly two values. The first is the key and the second is
-- the value.
--
-- For example, values of type '[Text]' cannot be encoded to a string, so
-- a Map with keys of type '[Text]' is encoded as follows:
--
-- -- >>> LBC8.putStrLn $ encode $ Map.fromList [(["foo","bar","baz" :: Text], 'a')] -- [[["foo","bar","baz"],"a"]] ---- -- The default implementation of ToJSONKey chooses this method of -- encoding a key, using the ToJSON instance of the type. -- -- To use your own data type as the key in a map, all that is needed is -- to write a ToJSONKey (and possibly a FromJSONKey) -- instance for it. If the type cannot be trivially converted to and from -- Text, it is recommended that ToJSONKeyValue is used. -- Since the default implementations of the typeclass methods can build -- this from a ToJSON instance, there is nothing that needs to be -- written: -- --
-- data Foo = Foo { fooAge :: Int, fooName :: Text }
-- deriving (Eq,Ord,Generic)
-- instance ToJSON Foo
-- instance ToJSONKey Foo
--
--
-- That's it. We can now write:
--
--
-- >>> let m = Map.fromList [(Foo 4 "bar",'a'),(Foo 6 "arg",'b')]
--
-- >>> LBC8.putStrLn $ encode m
-- [[{"fooName":"bar","fooAge":4},"a"],[{"fooName":"arg","fooAge":6},"b"]]
--
--
-- The next case to consider is if we have a type that is a newtype
-- wrapper around Text. The recommended approach is to use
-- generalized newtype deriving:
--
--
-- newtype RecordId = RecordId { getRecordId :: Text}
-- deriving (Eq,Ord,ToJSONKey)
--
--
-- Then we may write:
--
--
-- >>> LBC8.putStrLn $ encode $ Map.fromList [(RecordId "abc",'a')]
-- {"abc":"a"}
--
--
-- Simple sum types are a final case worth considering. Suppose we have:
--
-- -- data Color = Red | Green | Blue -- deriving (Show,Read,Eq,Ord) ---- -- It is possible to get the ToJSONKey instance for free as we did -- with Foo. However, in this case, we have a natural way to go -- to and from Text that does not require any escape sequences. -- So, in this example, ToJSONKeyText will be used instead of -- ToJSONKeyValue. The Show instance can be used to help -- write ToJSONKey: -- --
-- instance ToJSONKey Color where -- toJSONKey = ToJSONKeyText f g -- where f = Text.pack . show -- g = text . Text.pack . show -- -- text function is from Data.Aeson.Encoding ---- -- The situation of needing to turning function a -> Text -- into a ToJSONKeyFunction is common enough that a special -- combinator is provided for it. The above instance can be rewritten as: -- --
-- instance ToJSONKey Color where -- toJSONKey = toJSONKeyText (Text.pack . show) ---- -- The performance of the above instance can be improved by not using -- String as an intermediate step when converting to Text. -- One option for improving performance would be to use template haskell -- machinery from the text-show package. However, even with the -- approach, the Encoding (a wrapper around a bytestring builder) -- is generated by encoding the Text to a ByteString, an -- intermediate step that could be avoided. The fastest possible -- implementation would be: -- --
-- -- Assuming that OverloadedStrings is enabled
-- instance ToJSONKey Color where
-- toJSONKey = ToJSONKeyText f g
-- where f x = case x of {Red -> "Red";Green ->"Green";Blue -> "Blue"}
-- g x = case x of {Red -> text "Red";Green -> text "Green";Blue -> text "Blue"}
-- -- text function is from Data.Aeson.Encoding
--
--
-- This works because GHC can lift the encoded values out of the case
-- statements, which means that they are only evaluated once. This
-- approach should only be used when there is a serious need to maximize
-- performance.
class ToJSONKey a where toJSONKey = ToJSONKeyValue toJSON toEncoding toJSONKeyList = ToJSONKeyValue toJSON toEncoding
-- | Strategy for rendering the key for a map-like container.
toJSONKey :: ToJSONKey a => ToJSONKeyFunction a
-- | Strategy for rendering the key for a map-like container.
toJSONKey :: (ToJSONKey a, ToJSON a) => ToJSONKeyFunction a
-- | This is similar in spirit to the showsList method of
-- Show. It makes it possible to give String keys special
-- treatment without using OverlappingInstances. End users
-- should always be able to use the default implementation of this
-- method.
toJSONKeyList :: ToJSONKey a => ToJSONKeyFunction [a]
-- | This is similar in spirit to the showsList method of
-- Show. It makes it possible to give String keys special
-- treatment without using OverlappingInstances. End users
-- should always be able to use the default implementation of this
-- method.
toJSONKeyList :: (ToJSONKey a, ToJSON a) => ToJSONKeyFunction [a]
data ToJSONKeyFunction a
-- | key is encoded to string, produces object
ToJSONKeyText :: !(a -> Text) -> !(a -> Encoding' Text) -> ToJSONKeyFunction a
-- | key is encoded to value, produces array
ToJSONKeyValue :: !(a -> Value) -> !(a -> Encoding) -> ToJSONKeyFunction a
-- | Read the docs for ToJSONKey first. This class is a conversion
-- in the opposite direction. If you have a newtype wrapper around
-- Text, the recommended way to define instances is with
-- generalized newtype deriving:
--
--
-- newtype SomeId = SomeId { getSomeId :: Text }
-- deriving (Eq,Ord,Hashable,FromJSONKey)
--
class FromJSONKey a where fromJSONKey = FromJSONKeyValue parseJSON fromJSONKeyList = FromJSONKeyValue parseJSON
-- | Strategy for parsing the key of a map-like container.
fromJSONKey :: FromJSONKey a => FromJSONKeyFunction a
-- | Strategy for parsing the key of a map-like container.
fromJSONKey :: (FromJSONKey a, FromJSON a) => FromJSONKeyFunction a
-- | This is similar in spirit to the readList method of
-- Read. It makes it possible to give String keys special
-- treatment without using OverlappingInstances. End users
-- should always be able to use the default implementation of this
-- method.
fromJSONKeyList :: FromJSONKey a => FromJSONKeyFunction [a]
-- | This is similar in spirit to the readList method of
-- Read. It makes it possible to give String keys special
-- treatment without using OverlappingInstances. End users
-- should always be able to use the default implementation of this
-- method.
fromJSONKeyList :: (FromJSONKey a, FromJSON a) => FromJSONKeyFunction [a]
-- | This type is related to ToJSONKeyFunction. If
-- FromJSONKeyValue is used in the FromJSONKey instance,
-- then ToJSONKeyValue should be used in the ToJSONKey
-- instance. The other three data constructors for this type all
-- correspond to ToJSONKeyText. Strictly speaking,
-- FromJSONKeyTextParser is more powerful than
-- FromJSONKeyText, which is in turn more powerful than
-- FromJSONKeyCoerce. For performance reasons, these exist as
-- three options instead of one.
data FromJSONKeyFunction a
-- | uses coerce (unsafeCoerce in older GHCs)
FromJSONKeyCoerce :: !(CoerceText a) -> FromJSONKeyFunction a
-- | conversion from Text that always succeeds
FromJSONKeyText :: !(Text -> a) -> FromJSONKeyFunction a
-- | conversion from Text that may fail
FromJSONKeyTextParser :: !(Text -> Parser a) -> FromJSONKeyFunction a
-- | conversion for non-textual keys
FromJSONKeyValue :: !(Value -> Parser a) -> FromJSONKeyFunction a
-- | Lifting of the FromJSON class to unary type constructors.
--
-- Instead of manually writing your FromJSON1 instance, there are
-- two options to do it automatically:
--
--
-- {-# LANGUAGE DeriveGeneric #-}
--
-- import GHC.Generics
--
-- data Pair a b = Pair { pairFst :: a, pairSnd :: b } deriving Generic1
--
-- instance FromJSON a => FromJSON1 (Pair a)
--
--
-- If DefaultSignatures doesn't give exactly the results you
-- want, you can customize the generic decoding with only a tiny amount
-- of effort, using genericLiftParseJSON with your preferred
-- Options:
--
-- -- instance FromJSON a => FromJSON1 (Pair a) where -- liftParseJSON = genericLiftParseJSON defaultOptions --class FromJSON1 f where liftParseJSON = genericLiftParseJSON defaultOptions liftParseJSONList f g v = listParser (liftParseJSON f g) v liftParseJSON :: FromJSON1 f => (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (f a) liftParseJSON :: (FromJSON1 f, Generic1 f, GFromJSON One (Rep1 f)) => (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (f a) liftParseJSONList :: FromJSON1 f => (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [f a] -- | Lift the standard parseJSON function through the type -- constructor. parseJSON1 :: (FromJSON1 f, FromJSON a) => Value -> Parser (f a) -- | Lifting of the FromJSON class to binary type constructors. -- -- Instead of manually writing your FromJSON2 instance, -- Data.Aeson.TH provides Template Haskell functions which will -- derive an instance at compile time. class FromJSON2 f where liftParseJSONList2 fa ga fb gb v = case v of { Array vals -> fmap toList (mapM (liftParseJSON2 fa ga fb gb) vals) _ -> typeMismatch "[a]" v } liftParseJSON2 :: FromJSON2 f => (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (f a b) liftParseJSONList2 :: FromJSON2 f => (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [f a b] -- | Lift the standard parseJSON function through the type -- constructor. parseJSON2 :: (FromJSON2 f, FromJSON a, FromJSON b) => Value -> Parser (f a b) -- | Lifting of the ToJSON class to unary type constructors. -- -- Instead of manually writing your ToJSON1 instance, there are -- two options to do it automatically: -- --
-- {-# LANGUAGE DeriveGeneric #-}
--
-- import GHC.Generics
--
-- data Pair = Pair { pairFst :: a, pairSnd :: b } deriving Generic1
--
-- instance ToJSON a => ToJSON1 (Pair a)
--
--
-- If DefaultSignatures doesn't give exactly the results you
-- want, you can customize the generic encoding with only a tiny amount
-- of effort, using genericLiftToJSON and
-- genericLiftToEncoding with your preferred Options:
--
-- -- instance ToJSON a => ToJSON1 (Pair a) where -- liftToJSON = genericLiftToJSON defaultOptions -- liftToEncoding = genericLiftToEncoding defaultOptions --class ToJSON1 f where liftToJSON = genericLiftToJSON defaultOptions liftToJSONList f g = listValue (liftToJSON f g) liftToEncoding = genericLiftToEncoding defaultOptions liftToEncodingList f g = listEncoding (liftToEncoding f g) liftToJSON :: ToJSON1 f => (a -> Value) -> ([a] -> Value) -> f a -> Value liftToJSON :: (ToJSON1 f, Generic1 f, GToJSON One (Rep1 f)) => (a -> Value) -> ([a] -> Value) -> f a -> Value liftToJSONList :: ToJSON1 f => (a -> Value) -> ([a] -> Value) -> [f a] -> Value liftToEncoding :: ToJSON1 f => (a -> Encoding) -> ([a] -> Encoding) -> f a -> Encoding liftToEncoding :: (ToJSON1 f, Generic1 f, GToEncoding One (Rep1 f)) => (a -> Encoding) -> ([a] -> Encoding) -> f a -> Encoding liftToEncodingList :: ToJSON1 f => (a -> Encoding) -> ([a] -> Encoding) -> [f a] -> Encoding -- | Lift the standard toJSON function through the type constructor. toJSON1 :: (ToJSON1 f, ToJSON a) => f a -> Value -- | Lift the standard toEncoding function through the type -- constructor. toEncoding1 :: (ToJSON1 f, ToJSON a) => f a -> Encoding -- | Lifting of the ToJSON class to binary type constructors. -- -- Instead of manually writing your ToJSON2 instance, -- Data.Aeson.TH provides Template Haskell functions which will -- derive an instance at compile time. -- -- The compiler cannot provide a default generic implementation for -- liftToJSON2, unlike toJSON and liftToJSON. class ToJSON2 f where liftToJSONList2 fa ga fb gb = listValue (liftToJSON2 fa ga fb gb) liftToEncodingList2 fa ga fb gb = listEncoding (liftToEncoding2 fa ga fb gb) liftToJSON2 :: ToJSON2 f => (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> f a b -> Value liftToJSONList2 :: ToJSON2 f => (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [f a b] -> Value liftToEncoding2 :: ToJSON2 f => (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> f a b -> Encoding liftToEncodingList2 :: ToJSON2 f => (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [f a b] -> Encoding -- | Lift the standard toJSON function through the type constructor. toJSON2 :: (ToJSON2 f, ToJSON a, ToJSON b) => f a b -> Value -- | Lift the standard toEncoding function through the type -- constructor. toEncoding2 :: (ToJSON2 f, ToJSON a, ToJSON b) => f a b -> Encoding -- | Class of generic representation types that can be converted from JSON. class GFromJSON arity f -- | This method (applied to defaultOptions) is used as the default -- generic implementation of parseJSON (if the arity is -- Zero) or liftParseJSON (if the arity is -- One). gParseJSON :: GFromJSON arity f => Options -> FromArgs arity a -> Value -> Parser (f a) -- | A FromArgs value either stores nothing (for FromJSON) or -- it stores the two function arguments that decode occurrences of the -- type parameter (for FromJSON1). data FromArgs arity a [NoFromArgs] :: FromArgs Zero a [From1Args] :: (Value -> Parser a) -> (Value -> Parser [a]) -> FromArgs One a -- | Class of generic representation types that can be converted to JSON. class GToJSON arity f -- | This method (applied to defaultOptions) is used as the default -- generic implementation of toJSON (if the arity is -- Zero) or liftToJSON (if the arity is -- One). gToJSON :: GToJSON arity f => Options -> ToArgs Value arity a -> f a -> Value -- | Class of generic representation types that can be converted to a JSON -- Encoding. class GToEncoding arity f -- | This method (applied to defaultOptions) can be used as the -- default generic implementation of toEncoding (if the -- arity is Zero) or liftToEncoding (if the -- arity is One). gToEncoding :: GToEncoding arity f => Options -> ToArgs Encoding arity a -> f a -> Encoding -- | A ToArgs value either stores nothing (for ToJSON) or it -- stores the two function arguments that encode occurrences of the type -- parameter (for ToJSON1). data ToArgs res arity a [NoToArgs] :: ToArgs res Zero a [To1Args] :: (a -> res) -> ([a] -> res) -> ToArgs res One a -- | A type-level indicator that ToJSON or FromJSON is -- being derived generically. data Zero -- | A type-level indicator that ToJSON1 or FromJSON1 is -- being derived generically. data One -- | A configurable generic JSON creator. This function applied to -- defaultOptions is used as the default for toJSON when -- the type is an instance of Generic. genericToJSON :: (Generic a, GToJSON Zero (Rep a)) => Options -> a -> Value -- | A configurable generic JSON creator. This function applied to -- defaultOptions is used as the default for liftToJSON -- when the type is an instance of Generic1. genericLiftToJSON :: (Generic1 f, GToJSON One (Rep1 f)) => Options -> (a -> Value) -> ([a] -> Value) -> f a -> Value -- | A configurable generic JSON encoder. This function applied to -- defaultOptions is used as the default for toEncoding -- when the type is an instance of Generic. genericToEncoding :: (Generic a, GToEncoding Zero (Rep a)) => Options -> a -> Encoding -- | A configurable generic JSON encoder. This function applied to -- defaultOptions is used as the default for liftToEncoding -- when the type is an instance of Generic1. genericLiftToEncoding :: (Generic1 f, GToEncoding One (Rep1 f)) => Options -> (a -> Encoding) -> ([a] -> Encoding) -> f a -> Encoding -- | A configurable generic JSON decoder. This function applied to -- defaultOptions is used as the default for parseJSON when -- the type is an instance of Generic. genericParseJSON :: (Generic a, GFromJSON Zero (Rep a)) => Options -> Value -> Parser a -- | A configurable generic JSON decoder. This function applied to -- defaultOptions is used as the default for liftParseJSON -- when the type is an instance of Generic1. genericLiftParseJSON :: (Generic1 f, GFromJSON One (Rep1 f)) => Options -> (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (f a) -- | Default encoding Options: -- --
-- Options
-- { fieldLabelModifier = id
-- , constructorTagModifier = id
-- , allNullaryToStringTag = True
-- , omitNothingFields = False
-- , sumEncoding = defaultTaggedObject
-- , unwrapUnaryRecords = False
-- }
--
defaultOptions :: Options
-- | withObject expected f value applies f to the
-- Object when value is an Object and fails
-- using typeMismatch expected otherwise.
withObject :: String -> (Object -> Parser a) -> Value -> Parser a
-- | withText expected f value applies f to the
-- Text when value is a String and fails using
-- typeMismatch expected otherwise.
withText :: String -> (Text -> Parser a) -> Value -> Parser a
-- | withArray expected f value applies f to the
-- Array when value is an Array and fails using
-- typeMismatch expected otherwise.
withArray :: String -> (Array -> Parser a) -> Value -> Parser a
-- | withNumber expected f value applies f to the
-- Number when value is a Number. and fails using
-- typeMismatch expected otherwise.
-- | Deprecated: Use withScientific instead
withNumber :: String -> (Number -> Parser a) -> Value -> Parser a
-- | withScientific expected f value applies f to the
-- Scientific number when value is a Number. and
-- fails using typeMismatch expected otherwise.
withScientific :: String -> (Scientific -> Parser a) -> Value -> Parser a
-- | withBool expected f value applies f to the
-- Bool when value is a Bool and fails using
-- typeMismatch expected otherwise.
withBool :: String -> (Bool -> Parser a) -> Value -> Parser a
-- | A series of values that, when encoded, should be separated by commas.
-- Since 0.11.0.0, the .= operator is overloaded to create
-- either (Text, Value) or Series. You can use Series
-- when encoding directly to a bytestring builder as in the following
-- example:
--
--
-- toEncoding (Person name age) = pairs ("name" .= name <> "age" .= age)
--
data Series
-- | Encode a series of key/value pairs, separated by commas.
pairs :: Series -> Encoding
-- | Encode a Foldable as a JSON array.
foldable :: (Foldable t, ToJSON a) => t a -> Encoding
-- | Retrieve the value associated with the given key of an Object.
-- The result is empty if the key is not present or the value
-- cannot be converted to the desired type.
--
-- This accessor is appropriate if the key and value must be
-- present in an object for it to be valid. If the key and value are
-- optional, use .:? instead.
(.:) :: (FromJSON a) => Object -> Text -> Parser a
-- | Retrieve the value associated with the given key of an Object.
-- The result is Nothing if the key is not present or if its value
-- is Null, or empty if the value cannot be converted to
-- the desired type.
--
-- This accessor is most useful if the key and value can be absent from
-- an object without affecting its validity. If the key and value are
-- mandatory, use .: instead.
(.:?) :: (FromJSON a) => Object -> Text -> Parser (Maybe a)
-- | Retrieve the value associated with the given key of an Object.
-- The result is Nothing if the key is not present or
-- empty if the value cannot be converted to the desired type.
--
-- This differs from .:? by attempting to parse Null the
-- same as any other JSON value, instead of interpreting it as
-- Nothing.
(.:!) :: (FromJSON a) => Object -> Text -> Parser (Maybe a)
-- | Helper for use in combination with .:? to provide default
-- values for optional JSON object fields.
--
-- This combinator is most useful if the key and value can be absent from
-- an object without affecting its validity and we know a default value
-- to assign in that case. If the key and value are mandatory, use
-- .: instead.
--
-- Example usage:
--
-- -- v1 <- o .:? "opt_field_with_dfl" .!= "default_val" -- v2 <- o .: "mandatory_field" -- v3 <- o .:? "opt_field2" --(.!=) :: Parser (Maybe a) -> a -> Parser a -- | Create a Value from a list of name/value Pairs. If -- duplicate keys arise, earlier keys and their associated values win. object :: [Pair] -> Value -- | Parse a top-level JSON value. -- -- The conversion of a parsed value to a Haskell value is deferred until -- the Haskell value is needed. This may improve performance if only a -- subset of the results of conversions are needed, but at a cost in -- thunk allocation. -- -- This function is an alias for value. In aeson 0.8 and earlier, -- it parsed only object or array types, in conformance with the -- now-obsolete RFC 4627. json :: Parser Value -- | Parse a top-level JSON value. -- -- This is a strict version of json which avoids building up -- thunks during parsing; it performs all conversions immediately. Prefer -- this version if most of the JSON data needs to be accessed. -- -- This function is an alias for value'. In aeson 0.8 and earlier, -- it parsed only object or array types, in conformance with the -- now-obsolete RFC 4627. json' :: Parser Value -- | This module is left to supply limited backwards-compatibility. -- | Deprecated: Use Data.Aeson or Data.Aeson.Text instead module Data.Aeson.Encode encode :: ToJSON a => a -> ByteString encodeToTextBuilder :: Value -> Builder -- | Functions to mechanically derive ToJSON and FromJSON -- instances. Note that you need to enable the TemplateHaskell -- language extension in order to use this module. -- -- An example shows how instances are generated for arbitrary data types. -- First we define a data type: -- --
-- data D a = Nullary
-- | Unary Int
-- | Product String Char a
-- | Record { testOne :: Double
-- , testTwo :: Bool
-- , testThree :: D a
-- } deriving Eq
--
--
-- Next we derive the necessary instances. Note that we make use of the
-- feature to change record field names. In this case we drop the first 4
-- characters of every field name. We also modify constructor names by
-- lower-casing them:
--
--
-- $(deriveJSON defaultOptions{fieldLabelModifier = drop 4, constructorTagModifier = map toLower} ''D)
--
--
-- Now we can use the newly created instances.
--
--
-- d :: D Int
-- d = Record { testOne = 3.14159
-- , testTwo = True
-- , testThree = Product "test" 'A' 123
-- }
--
--
-- -- >>> fromJSON (toJSON d) == Success d -- > True ---- -- This also works for data family instances, but instead of passing in -- the data family name (with double quotes), we pass in a data family -- instance constructor (with a single quote): -- --
-- data family DF a -- data instance DF Int = DF1 Int -- | DF2 Int Int -- deriving Eq -- -- $(deriveJSON defaultOptions 'DF1) -- -- Alternatively, one could pass 'DF2 instead ---- -- Please note that you can derive instances for tuples using the -- following syntax: -- --
-- -- FromJSON and ToJSON instances for 4-tuples. -- $(deriveJSON defaultOptions ''(,,,)) --module Data.Aeson.TH -- | Options that specify how to encode/decode your datatype to/from JSON. data Options Options :: (String -> String) -> (String -> String) -> Bool -> Bool -> SumEncoding -> Bool -> Options -- | Function applied to field labels. Handy for removing common record -- prefixes for example. [fieldLabelModifier] :: Options -> String -> String -- | Function applied to constructor tags which could be handy for -- lower-casing them for example. [constructorTagModifier] :: Options -> String -> String -- | If True the constructors of a datatype, with all nullary -- constructors, will be encoded to just a string with the constructor -- tag. If False the encoding will always follow the -- sumEncoding. [allNullaryToStringTag] :: Options -> Bool -- | If True record fields with a Nothing value will be -- omitted from the resulting object. If False the resulting -- object will include those fields mapping to null. [omitNothingFields] :: Options -> Bool -- | Specifies how to encode constructors of a sum datatype. [sumEncoding] :: Options -> SumEncoding -- | Hide the field name when a record constructor has only one field, like -- a newtype. [unwrapUnaryRecords] :: Options -> Bool -- | Specifies how to encode constructors of a sum datatype. data SumEncoding -- | A constructor will be encoded to an object with a field -- tagFieldName which specifies the constructor tag (modified by -- the constructorTagModifier). If the constructor is a record the -- encoded record fields will be unpacked into this object. So make sure -- that your record doesn't have a field with the same label as the -- tagFieldName. Otherwise the tag gets overwritten by the encoded -- value of that field! If the constructor is not a record the encoded -- constructor contents will be stored under the contentsFieldName -- field. TaggedObject :: String -> String -> SumEncoding [tagFieldName] :: SumEncoding -> String [contentsFieldName] :: SumEncoding -> String -- | Constructor names won't be encoded. Instead only the contents of the -- constructor will be encoded as if the type had single constructor. -- JSON encodings have to be disjoint for decoding to work properly. -- -- When decoding, constructors are tried in the order of definition. If -- some encodings overlap, the first one defined will succeed. -- -- Note: Nullary constructors are encoded as the string (using -- constructorTagModifier). Having a nullary constructor alongside -- a single field constructor that encodes to a string leads to -- ambiguity. -- -- Note: Only the last error is kept when decoding, so in the case -- of mailformed JSON, only an error for the last constructor will be -- reported. UntaggedValue :: SumEncoding -- | A constructor will be encoded to an object with a single field named -- after the constructor tag (modified by the -- constructorTagModifier) which maps to the encoded contents of -- the constructor. ObjectWithSingleField :: SumEncoding -- | A constructor will be encoded to a 2-element array where the first -- element is the tag of the constructor (modified by the -- constructorTagModifier) and the second element the encoded -- contents of the constructor. TwoElemArray :: SumEncoding -- | Default encoding Options: -- --
-- Options
-- { fieldLabelModifier = id
-- , constructorTagModifier = id
-- , allNullaryToStringTag = True
-- , omitNothingFields = False
-- , sumEncoding = defaultTaggedObject
-- , unwrapUnaryRecords = False
-- }
--
defaultOptions :: Options
-- | Default TaggedObject SumEncoding options:
--
--
-- defaultTaggedObject = TaggedObject
-- { tagFieldName = "tag"
-- , contentsFieldName = "contents"
-- }
--
defaultTaggedObject :: SumEncoding
-- | Generates both ToJSON and FromJSON instance declarations
-- for the given data type or data family instance constructor.
--
-- This is a convienience function which is equivalent to calling both
-- deriveToJSON and deriveFromJSON.
deriveJSON :: Options -> Name -> Q [Dec]
-- | Generates both ToJSON1 and FromJSON1 instance
-- declarations for the given data type or data family instance
-- constructor.
--
-- This is a convienience function which is equivalent to calling both
-- deriveToJSON1 and deriveFromJSON1.
deriveJSON1 :: Options -> Name -> Q [Dec]
-- | Generates both ToJSON2 and FromJSON2 instance
-- declarations for the given data type or data family instance
-- constructor.
--
-- This is a convienience function which is equivalent to calling both
-- deriveToJSON2 and deriveFromJSON2.
deriveJSON2 :: Options -> Name -> Q [Dec]
-- | Generates a ToJSON instance declaration for the given data type
-- or data family instance constructor.
deriveToJSON :: Options -> Name -> Q [Dec]
-- | Generates a ToJSON1 instance declaration for the given data
-- type or data family instance constructor.
deriveToJSON1 :: Options -> Name -> Q [Dec]
-- | Generates a ToJSON2 instance declaration for the given data
-- type or data family instance constructor.
deriveToJSON2 :: Options -> Name -> Q [Dec]
-- | Generates a FromJSON instance declaration for the given data
-- type or data family instance constructor.
deriveFromJSON :: Options -> Name -> Q [Dec]
-- | Generates a FromJSON1 instance declaration for the given data
-- type or data family instance constructor.
deriveFromJSON1 :: Options -> Name -> Q [Dec]
-- | Generates a FromJSON2 instance declaration for the given data
-- type or data family instance constructor.
deriveFromJSON2 :: Options -> Name -> Q [Dec]
-- | Generates a lambda expression which encodes the given data type or
-- data family instance constructor as a Value.
mkToJSON :: Options -> Name -> Q Exp
-- | Generates a lambda expression which encodes the given data type or
-- data family instance constructor as a Value by using the given
-- encoding function on occurrences of the last type parameter.
mkLiftToJSON :: Options -> Name -> Q Exp
-- | Generates a lambda expression which encodes the given data type or
-- data family instance constructor as a Value by using the given
-- encoding functions on occurrences of the last two type parameters.
mkLiftToJSON2 :: Options -> Name -> Q Exp
-- | Generates a lambda expression which encodes the given data type or
-- data family instance constructor as a JSON string.
mkToEncoding :: Options -> Name -> Q Exp
-- | Generates a lambda expression which encodes the given data type or
-- data family instance constructor as a JSON string by using the given
-- encoding function on occurrences of the last type parameter.
mkLiftToEncoding :: Options -> Name -> Q Exp
-- | Generates a lambda expression which encodes the given data type or
-- data family instance constructor as a JSON string by using the given
-- encoding functions on occurrences of the last two type parameters.
mkLiftToEncoding2 :: Options -> Name -> Q Exp
-- | Generates a lambda expression which parses the JSON encoding of the
-- given data type or data family instance constructor.
mkParseJSON :: Options -> Name -> Q Exp
-- | Generates a lambda expression which parses the JSON encoding of the
-- given data type or data family instance constructor by using the given
-- parsing function on occurrences of the last type parameter.
mkLiftParseJSON :: Options -> Name -> Q Exp
-- | Generates a lambda expression which parses the JSON encoding of the
-- given data type or data family instance constructor by using the given
-- parsing functions on occurrences of the last two type parameters.
mkLiftParseJSON2 :: Options -> Name -> Q Exp
instance GHC.Classes.Eq Data.Aeson.TH.StarKindStatus
instance GHC.Classes.Ord Data.Aeson.TH.Arity
instance GHC.Classes.Eq Data.Aeson.TH.Arity
instance GHC.Enum.Enum Data.Aeson.TH.Arity
instance Data.Aeson.TH.LookupField a
instance Data.Aeson.TH.LookupField (GHC.Base.Maybe a)