-- 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: -- -- -- -- Encoding performance on the same machine and data: -- -- -- -- (A note on naming: in Greek mythology, Aeson was the father of Jason.) @package aeson @version 0.11.2.0 module Data.Aeson.Internal.Time -- | Like TimeOfDay, but using a fixed-width integer for seconds. data TimeOfDay64 TOD :: {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int64 -> TimeOfDay64 fromPico :: Pico -> Integer toPico :: Integer -> Pico diffTimeOfDay64 :: DiffTime -> TimeOfDay64 toTimeOfDay64 :: TimeOfDay -> TimeOfDay64 -- | Internal types and functions. -- -- Note: all declarations in this module are unstable, and prone -- to being changed at any time. module Data.Aeson.Internal -- | The internal result of running a Parser. data IResult a IError :: JSONPath -> String -> IResult a ISuccess :: a -> IResult a -- | Elements of a JSON path used to describe the location of an error. data JSONPathElement -- | JSON path element of a key into an object, "object.key". Key :: Text -> JSONPathElement -- | JSON path element of an index into an array, "array[index]". Index :: {-# UNPACK #-} !Int -> JSONPathElement type JSONPath = [JSONPathElement] -- | Add JSON Path context to a parser -- -- When parsing a complex structure, it helps to annotate (sub)parsers -- with context, so that if an error occurs, you can find its location. -- --
--   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 -- | 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 -- | An encoding of a JSON value. data Encoding -- | Make Encoding from Builder. -- -- Use with care! You have to make sure that the passed Builder is a -- valid JSON Encoding! unsafeToEncoding :: Builder -> Encoding -- | Acquire the underlying bytestring builder. fromEncoding :: Encoding -> 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: -- -- -- -- An example type and instance: -- --
--   -- 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
--   
-- -- Instead of manually writing your FromJSON instance, there are -- two options to do it automatically: -- -- -- -- To use the second, simply add a deriving Generic -- clause to your datatype and declare a FromJSON instance for -- your datatype without giving a definition for parseJSON. -- -- For example, the previous example can be simplified to just: -- --
--   {-# 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 parseJSON :: FromJSON a => Value -> Parser a parseJSON :: (FromJSON a, Generic a, GFromJSON (Rep 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: -- -- -- -- To use the second, simply add a deriving Generic -- clause to your datatype and declare a ToJSON instance for your -- datatype without giving definitions for toJSON or -- toEncoding. -- -- For example, the previous example can be simplified to a more minimal -- instance: -- --
--   {-# 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 = Encoding . encodeToBuilder . toJSON -- | 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 (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 -- | 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 -- | Class of generic representation types (Rep) that can be -- converted from JSON. class GFromJSON f -- | This method (applied to defaultOptions) is used as the default -- generic implementation of parseJSON. gParseJSON :: GFromJSON f => Options -> Value -> Parser (f a) -- | Class of generic representation types (Rep) that can be -- converted to JSON. class GToJSON f -- | This method (applied to defaultOptions) is used as the default -- generic implementation of toJSON. gToJSON :: GToJSON f => Options -> f a -> Value -- | Class of generic representation types (Rep) that can be -- converted to a JSON Encoding. class GToEncoding f -- | This method (applied to defaultOptions) can be used as the -- default generic implementation of toEncoding. gToEncoding :: GToEncoding f => Options -> f a -> Encoding -- | 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 (Rep a)) => Options -> 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 (Rep a)) => Options -> 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 (Rep a)) => Options -> Value -> Parser 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 -- 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) -- | Like .:?, but the resulting parser will fail, if the key is -- present but is Null. (.:!) :: (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 -- | 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 -- | 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 -- | Efficiently and correctly parse a JSON string. The string must be -- encoded as UTF-8. -- -- It can be useful to think of parsing as occurring in two phases: -- -- -- -- The question of whether to choose a lazy or strict parser is subtle, -- but it can have significant performance implications, resulting in -- changes in CPU use and memory footprint of 30% to 50%, or occasionally -- more. Measure the performance of your application with each! module Data.Aeson.Parser -- | 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 any JSON value. You should usually json in preference to -- this function, as this function relaxes the object-or-array -- requirement of RFC 4627. -- -- In particular, be careful in using this function if you think your -- code might interoperate with Javascript. A naïve Javascript library -- that parses JSON data using eval is vulnerable to attack -- unless the encoded data represents an object or an array. JSON -- implementations in other languages conform to that same restriction to -- preserve interoperability and security. value :: Parser Value -- | Parse a quoted JSON string. jstring :: Parser Text -- | 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 -- | Strict version of value. See also json'. value' :: Parser Value -- | Efficiently serialize a JSON value. -- -- 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.Encode -- | 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 -- | Encode a JSON value to a Data.ByteString Builder. -- -- Use this function if you are encoding over the wire, or need to -- prepend or append further bytes to the encoded JSON value. encodeToBuilder :: Value -> Builder -- | 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. encodeToTextBuilder :: Value -> Builder -- | Deprecated: Use encodeToTextBuilder instead fromValue :: Value -> 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 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. 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 -- | An encoding of a JSON value. data Encoding -- | Acquire the underlying bytestring builder. fromEncoding :: Encoding -> 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: -- -- -- -- An example type and instance: -- --
--   -- 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
--   
-- -- Instead of manually writing your FromJSON instance, there are -- two options to do it automatically: -- -- -- -- To use the second, simply add a deriving Generic -- clause to your datatype and declare a FromJSON instance for -- your datatype without giving a definition for parseJSON. -- -- For example, the previous example can be simplified to just: -- --
--   {-# 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 parseJSON :: FromJSON a => Value -> Parser a parseJSON :: (FromJSON a, Generic a, GFromJSON (Rep 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: -- -- -- -- To use the second, simply add a deriving Generic -- clause to your datatype and declare a ToJSON instance for your -- datatype without giving definitions for toJSON or -- toEncoding. -- -- For example, the previous example can be simplified to a more minimal -- instance: -- --
--   {-# 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 = Encoding . encodeToBuilder . toJSON -- | 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 (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 -- | A key-value pair for encoding a JSON object. class KeyValue kv (.=) :: (KeyValue kv, ToJSON v) => Text -> v -> kv -- | Class of generic representation types (Rep) that can be -- converted from JSON. class GFromJSON f -- | This method (applied to defaultOptions) is used as the default -- generic implementation of parseJSON. gParseJSON :: GFromJSON f => Options -> Value -> Parser (f a) -- | Class of generic representation types (Rep) that can be -- converted to JSON. class GToJSON f -- | This method (applied to defaultOptions) is used as the default -- generic implementation of toJSON. gToJSON :: GToJSON f => Options -> f a -> Value -- | Class of generic representation types (Rep) that can be -- converted to a JSON Encoding. class GToEncoding f -- | This method (applied to defaultOptions) can be used as the -- default generic implementation of toEncoding. gToEncoding :: GToEncoding f => Options -> f a -> Encoding -- | 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 (Rep a)) => Options -> 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 (Rep a)) => Options -> 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 (Rep a)) => Options -> Value -> Parser 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 -- 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) -- | Like .:?, but the resulting parser will fail, if the key is -- present but is Null. (.:!) :: (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 -- | 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 -- | 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 a ToJSON instance declaration for the given data type -- or data family instance constructor. deriveToJSON :: 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 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 JSON string. mkToEncoding :: 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 instance Data.Aeson.Types.Class.FromJSON a => Data.Aeson.TH.LookupField a instance Data.Aeson.Types.Class.FromJSON a => Data.Aeson.TH.LookupField (GHC.Base.Maybe a)