| Copyright | (c) 2011, 2012 Bryan O'Sullivan (c) 2011 MailRank, Inc. | 
|---|---|
| License | Apache | 
| Maintainer | Bryan O'Sullivan <bos@serpentine.com> | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Data.Aeson
Contents
Description
Types and functions for working efficiently with JSON data.
(A note on naming: in Greek mythology, Aeson was the father of Jason.)
- decode :: FromJSON a => ByteString -> Maybe a
- decode' :: FromJSON a => ByteString -> Maybe a
- eitherDecode :: FromJSON a => ByteString -> Either String a
- eitherDecode' :: FromJSON a => ByteString -> Either String a
- encode :: ToJSON a => a -> ByteString
- decodeStrict :: FromJSON a => ByteString -> Maybe a
- decodeStrict' :: FromJSON a => ByteString -> Maybe a
- eitherDecodeStrict :: FromJSON a => ByteString -> Either String a
- eitherDecodeStrict' :: FromJSON a => ByteString -> Either String a
- data Value
- type Array = Vector Value
- type Object = HashMap Text Value
- newtype DotNetTime = DotNetTime {}
- class FromJSON a where
- data Result a
- fromJSON :: FromJSON a => Value -> Result a
- class ToJSON a where
- class GFromJSON f where- gParseJSON :: Options -> Value -> Parser (f a)
 
- class GToJSON f where
- genericToJSON :: (Generic a, GToJSON (Rep a)) => Options -> a -> Value
- genericParseJSON :: (Generic a, GFromJSON (Rep a)) => Options -> Value -> Parser a
- withObject :: String -> (Object -> Parser a) -> Value -> Parser a
- withText :: String -> (Text -> Parser a) -> Value -> Parser a
- withArray :: String -> (Array -> Parser a) -> Value -> Parser a
- withNumber :: String -> (Number -> Parser a) -> Value -> Parser a
- withScientific :: String -> (Scientific -> Parser a) -> Value -> Parser a
- withBool :: String -> (Bool -> Parser a) -> Value -> Parser a
- (.=) :: ToJSON a => Text -> a -> Pair
- (.:) :: FromJSON a => Object -> Text -> Parser a
- (.:?) :: FromJSON a => Object -> Text -> Parser (Maybe a)
- (.!=) :: Parser (Maybe a) -> a -> Parser a
- object :: [Pair] -> Value
- json :: Parser Value
- json' :: Parser Value
How to use this library
This section contains basic information on the different ways to decode data using this library. These range from simple but inflexible, to complex but flexible.
The most common way to use the library is to define a data type,
 corresponding to some JSON data you want to work with, and then
 write either a FromJSON instance, a to ToJSON instance, or both
 for that type. For example, given this JSON data:
{ "name": "Joe", "age": 12 }we create a matching data type:
data Person = Person
    { name :: Text
    , age  :: Int
    } deriving ShowTo decode data, we need to define a FromJSON instance:
{-# LANGUAGE OverloadedStrings #-}
instance FromJSON Person where
    parseJSON (Object v) = Person <$>
                           v .: "name" <*>
                           v .: "age"
    -- A non-Object value is of the wrong type, so fail.
    parseJSON _          = mzeroWe can now parse the JSON data like so:
>>> decode "{\"name\":\"Joe\",\"age\":12}" :: Maybe Person
Just (Person {name = "Joe", age = 12})To encode data, we need to define a ToJSON instance:
instance ToJSON Person where
    toJSON (Person name age) = object ["name" .= name, "age" .= age]We can now encode a value like so:
>>> encode (Person {name = "Joe", age = 12})
"{\"name\":\"Joe\",\"age\":12}"There are predefined FromJSON and ToJSON instances for many
 types. Here's an example using lists and Ints:
>>> decode "[1,2,3]" :: Maybe [Int] Just [1,2,3]
And here's an example using the Map type to get a map of
 Ints.
>>> decode "{\"foo\":1,\"bar\":2}" :: Maybe (Map String Int)
Just (fromList [("bar",2),("foo",1)])Working with the AST
Sometimes you want to work with JSON data directly, without first
 converting it to a custom data type. This can be useful if you want
 to e.g. convert JSON data to YAML data, without knowing what the
 contents of the original JSON data was. The Value type, which is
 an instance of FromJSON, is used to represent an arbitrary JSON
 AST (abstract syntax tree). Example usage:
>>> decode "{\"foo\": 123}" :: Maybe Value
Just (Object (fromList [("foo",Number 123)]))>>> decode "{\"foo\": [\"abc\",\"def\"]}" :: Maybe Value
Just (Object (fromList [("foo",Array (fromList [String "abc",String "def"]))]))Once you have a Value you can write functions to traverse it and
 make arbitrary transformations.
Decoding to a Haskell value
Any instance of FromJSON can be specified (but see the
 "Pitfalls" section here—Data.Aeson):
λ> decode "[1,2,3]" :: Maybe [Int] Just [1,2,3]
Alternatively, there are instances for standard data types, so you
 can use them directly. For example, use the Map type to
 get a map of Ints.
λ> :m + Data.Map
λ> decode "{\"foo\":1,\"bar\":2}" :: Maybe (Map String Int)
Just (fromList [("bar",2),("foo",1)])Decoding a mixed-type object
The above approach with maps of course will not work for mixed-type objects that don't follow a strict schema, but there are a couple of approaches available for these.
The Object type contains JSON objects:
λ> decode "{\"name\":\"Dave\",\"age\":2}" :: Maybe Object
Just (fromList) [("name",String "Dave"),("age",Number 2)]You can extract values from it with a parser using parse,
 parseEither or, in this example, parseMaybe:
λ> do result <- decode "{\"name\":\"Dave\",\"age\":2}"
      flip parseMaybe result $ \obj -> do
        age <- obj .: "age"
        name <- obj .: "name"
        return (name ++ ": " ++ show (age*2))
Just "Dave: 4"Considering that any type that implements FromJSON can be used
 here, this is quite a powerful way to parse JSON. See the
 documentation in FromJSON for how to implement this class for
 your own data types.
The downside is that you have to write the parser yourself; the upside is that you have complete control over the way the JSON is parsed.
Automatically decoding data types
If you don't want fine control and would prefer the JSON be parsed
 to your own data types automatically according to some reasonably
 sensible isomorphic implementation, you can use the generic parser
 based on Typeable and Data. Switch to
 the Generic module, and you can do the following:
λ> decode "[1]" :: Maybe [Int]
Just [1]
λ> :m + Data.Typeable Data.Data
λ> :set -XDeriveDataTypeable
λ> data Person = Person { personName :: String, personAge :: Int } deriving (Data,Typeable,Show)
λ> encode Person { personName = "Chris", personAge = 123 }
"{\"personAge\":123,\"personName\":\"Chris\"}"
λ> decode "{\"personAge\":123,\"personName\":\"Chris\"}" :: Maybe Person
Just (Person {
personName = "Chris", personAge = 123
})Be aware that the encoding may not always be what you'd naively expect:
λ> data Foo = Foo Int Int deriving (Data,Typeable,Show) λ> encode (Foo 1 2) "[1,2]"
With this approach, it's best to treat the
 decode and encode
 functions as an isomorphism, and not to rely upon (or care about)
 the specific intermediate representation.
Pitfalls
Note that the JSON standard requires that the top-level value be
 either an array or an object. If you try to use decode with a
 result type that is not represented in JSON as an array or
 object, your code will typecheck, but it will always "fail" at
 runtime:
>>> decode "1" :: Maybe Int Nothing >>> decode "1" :: Maybe String Nothing
So stick to objects (e.g. maps in Haskell) or arrays (lists or vectors in Haskell):
>>> decode "[1,2,3]" :: Maybe [Int] Just [1,2,3]
When encoding to JSON you can encode anything that's an instance of
 ToJSON, and this may include simple types. So beware that this
 aspect of the API is not isomorphic. You can round-trip arrays and
 maps, but not simple values:
>>> encode [1,2,3] "[1,2,3]" >>> decode (encode [1]) :: Maybe [Int] Just [1] >>> encode 1 "1" >>> decode (encode (1 :: Int)) :: Maybe Int Nothing
Alternatively, see value to parse non-top-level
 JSON values.
Encoding and decoding
Encoding and decoding are each two-step processes.
- To encode a value, it is first converted to an abstract syntax
   tree (AST), using ToJSON. This generic representation is then encoded as bytes.
- When decoding a value, the process is reversed: the bytes are
   converted to an AST, then the FromJSONclass is used to convert to the desired type.
For convenience, the encode and decode functions combine both
 steps.
decode :: FromJSON a => ByteString -> Maybe a Source
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 Source
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 restriction is necessary to ensure that if data is being lazily read from a file handle, the file handle will be closed in a timely fashion once the document has been parsed.
This function parses and performs conversion immediately.  See
 json' for details.
eitherDecode :: FromJSON a => ByteString -> Either String a Source
Like decode but returns an error message when decoding fails.
eitherDecode' :: FromJSON a => ByteString -> Either String a Source
Like decode' but returns an error message when decoding fails.
encode :: ToJSON a => a -> ByteString Source
Efficiently serialize a JSON value as a lazy ByteString.
Variants for strict bytestrings
decodeStrict :: FromJSON a => ByteString -> Maybe a Source
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 Source
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.
eitherDecodeStrict :: FromJSON a => ByteString -> Either String a Source
Like decodeStrict but returns an error message when decoding fails.
eitherDecodeStrict' :: FromJSON a => ByteString -> Either String a Source
Like decodeStrict' but returns an error message when decoding fails.
Core JSON types
A JSON value represented as a Haskell value.
Convenience types
newtype DotNetTime Source
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.
Constructors
| DotNetTime | |
| Fields | |
Type conversion
A type that can be converted from JSON, with the possibility of failure.
When writing an instance, use empty, mzero, or fail to make a
 conversion fail, e.g. if an Object is missing a required key, or
 the value is of the wrong type.
An example type and instance:
{-# LANGUAGE OverloadedStrings #-}
data Coord = Coord { x :: Double, y :: Double }
instance FromJSON Coord where
  parseJSON (Object v) = Coord    <$>
                         v .: "x" <*>
                         v .: "y"
  -- A non-Object value is of the wrong type, so use mzero to fail.
  parseJSON _          = mzero
Note the use of the OverloadedStrings language extension which enables
 Text values to be written as string literals.
Instead of manually writing your FromJSON instance, there are three options
 to do it automatically:
- Data.Aeson.TH provides template-haskell functions which will derive an instance at compile-time. The generated instance is optimized for your type so will probably be more efficient than the following two options:
- Data.Aeson.Generic provides a generic fromJSONfunction that parses to any type which is an instance ofData.
- If your compiler has support for the DeriveGenericandDefaultSignatureslanguage extensions,parseJSONwill have a default generic implementation.
To use this, simply add a deriving  clause to your datatype and
 declare a GenericFromJSON 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
Note that, instead of using DefaultSignatures, it's also possible
 to parameterize the generic decoding using genericParseJSON applied
 to your encoding/decoding Options:
instance FromJSON Coord where
    parseJSON = genericParseJSON defaultOptions
Minimal complete definition
Nothing
Instances
The result of running a Parser.
fromJSON :: FromJSON a => Value -> Result a Source
Convert a value from JSON, failing if the types do not match.
A type that can be converted to JSON.
An example type and instance:
@{-# LANGUAGE OverloadedStrings #-}
data Coord = Coord { x :: Double, y :: Double }
instance ToJSON Coord where
   toJSON (Coord x y) = object ["x" .= x, "y" .= y]
 @
Note the use of the OverloadedStrings language extension which enables
 Text values to be written as string literals.
Instead of manually writing your ToJSON instance, there are three options
 to do it automatically:
- Data.Aeson.TH provides template-haskell functions which will derive an instance at compile-time. The generated instance is optimized for your type so will probably be more efficient than the following two options:
- Data.Aeson.Generic provides a generic toJSONfunction that accepts any type which is an instance ofData.
- If your compiler has support for the DeriveGenericandDefaultSignatureslanguage extensions (GHC 7.2 and newer),toJSONwill have a default generic implementation.
To use the latter option, simply add a deriving  clause to your
 datatype and declare a GenericToJSON instance for your datatype without giving a
 definition for toJSON.
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 ToJSON Coord @
Note that, instead of using DefaultSignatures, it's also possible
 to parameterize the generic encoding using genericToJSON applied
 to your encoding/decoding Options:
instance ToJSON Coord where
    toJSON = genericToJSON defaultOptions
Minimal complete definition
Nothing
Instances
Generic JSON classes
class GFromJSON f where Source
Class of generic representation types (Rep) that can be converted from JSON.
Methods
gParseJSON :: Options -> Value -> Parser (f a) Source
This method (applied to defaultOptions) is used as the
 default generic implementation of parseJSON.
Instances
Class of generic representation types (Rep) that can be converted to JSON.
genericToJSON :: (Generic a, GToJSON (Rep a)) => Options -> a -> Value Source
A configurable generic JSON encoder. This function applied to
 defaultOptions is used as the default for toJSON when the type
 is an instance of Generic.
genericParseJSON :: (Generic a, GFromJSON (Rep a)) => Options -> Value -> Parser a Source
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.
Inspecting Values
ValueswithObject :: String -> (Object -> Parser a) -> Value -> Parser a Source
withObject expected f value applies f to the Object when value is an Object
   and fails using typeMismatch expected
withText :: String -> (Text -> Parser a) -> Value -> Parser a Source
withText expected f value applies f to the Text when value is a String
   and fails using typeMismatch expected
withArray :: String -> (Array -> Parser a) -> Value -> Parser a Source
withArray expected f value applies f to the Array when value is an Array
   and fails using typeMismatch expected
withNumber :: String -> (Number -> Parser a) -> Value -> Parser a Source
Deprecated: Use withScientific instead
withNumber expected f value applies f to the Number when value is a Number.
   and fails using typeMismatch expected
withScientific :: String -> (Scientific -> Parser a) -> Value -> Parser a Source
withScientific expected f value applies f to the Scientific number when value is a Number.
   and fails using typeMismatch expected
withBool :: String -> (Bool -> Parser a) -> Value -> Parser a Source
withBool expected f value applies f to the Bool when value is a Bool
   and fails using typeMismatch expected
Constructors and accessors
(.:) :: FromJSON a => Object -> Text -> Parser a Source
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 (Maybe a) Source
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.
(.!=) :: Parser (Maybe a) -> a -> Parser a Source
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"
Parsing
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.
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.