-- 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. -- -- For release notes, see -- https://github.com/bos/aeson/blob/master/release-notes.markdown -- -- Note: if you use GHCi or Template Haskell, please see the -- README file for important details about building this -- package, and other packages that depend on it: -- https://github.com/bos/aeson#readme -- -- Parsing performance on a late 2010 MacBook Pro (2.66GHz Core i7), for -- mostly-English tweets from Twitter's JSON search API: -- -- -- -- Handling heavily-escaped text is a little more work. Here is parsing -- performance with Japanese tweets, where much of the text is entirely -- Unicode-escaped. -- -- -- -- 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.6.0.2 -- | 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 :: !Number -> Value Bool :: !Bool -> Value Null :: Value -- | 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 fromDotNetTime :: DotNetTime -> UTCTime -- | Fail parsing due to a type mismatch, with a descriptive message. typeMismatch :: String -> Value -> Parser a -- | A continuation-based parser type. 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. -- -- 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 { 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: -- -- -- -- To use this, 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 { x :: Double, y :: Double } deriving Generic
--   
--   instance FromJSON Coord
--   
class FromJSON a where parseJSON = fmap to . gParseJSON parseJSON :: 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. 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: -- --
--   {-# LANGUAGE OverloadedStrings #-}
--   
--   data 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: -- -- -- -- To use the latter option, simply add a deriving -- Generic clause to your datatype and declare a -- ToJSON 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 { x :: Double, y :: Double } deriving Generic
--   
--   instance ToJSON Coord
--   
class ToJSON a where toJSON = gToJSON . from toJSON :: ToJSON a => a -> Value -- | Construct a Pair from a key and a value. (.=) :: ToJSON a => Text -> a -> Pair -- | 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) -- | 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 -- | 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. This must be either an object or an -- array, per RFC 4627. -- -- 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. 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 must be either an object or an -- array, per RFC 4627. -- -- 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. 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 convert a Builder (as returned by fromValue) to -- a string using e.g. toLazyText. module Data.Aeson.Encode -- | Encode a JSON value to a Builder. You can convert this to a -- string using e.g. toLazyText, or encode straight to UTF-8 (the -- standard JSON encoding) using encode. fromValue :: Value -> Builder -- | Efficiently serialize a JSON value as a lazy ByteString. encode :: ToJSON a => a -> ByteString -- | JSON handling using Generics. -- -- This is based on the Generic package originally written by -- Lennart Augustsson. module Data.Aeson.Generic -- | Efficiently deserialize a JSON value from a lazy ByteString. If -- this fails due to incomplete or invalid input, Nothing is -- returned. -- -- This function parses immediately, but defers conversion. See -- json for details. decode :: Data 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. -- -- This function parses and performs conversion immediately. See -- json' for details. decode' :: Data a => ByteString -> Maybe a -- | Efficiently serialize a JSON value as a lazy ByteString. encode :: Data a => a -> ByteString fromJSON :: Data a => Value -> Result a toJSON :: Data a => a -> Value -- | 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. -- -- 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. -- -- This function parses and performs conversion immediately. See -- json' for details. decode' :: FromJSON a => ByteString -> Maybe a -- | Efficiently serialize a JSON value as a lazy ByteString. encode :: ToJSON a => a -> ByteString -- | A JSON value represented as a Haskell value. data Value Object :: !Object -> Value Array :: !Array -> Value String :: !Text -> Value Number :: !Number -> Value Bool :: !Bool -> Value Null :: Value -- | 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 fromDotNetTime :: DotNetTime -> UTCTime -- | 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 { 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: -- -- -- -- To use this, 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 { x :: Double, y :: Double } deriving Generic
--   
--   instance FromJSON Coord
--   
class FromJSON a where parseJSON = fmap to . gParseJSON parseJSON :: 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: -- --
--   {-# LANGUAGE OverloadedStrings #-}
--   
--   data 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: -- -- -- -- To use the latter option, simply add a deriving -- Generic clause to your datatype and declare a -- ToJSON 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 { x :: Double, y :: Double } deriving Generic
--   
--   instance ToJSON Coord
--   
class ToJSON a where toJSON = gToJSON . from toJSON :: ToJSON a => a -> Value -- | Construct a Pair from a key and a value. (.=) :: ToJSON a => Text -> a -> Pair -- | 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) -- | 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. This must be either an object or an -- array, per RFC 4627. -- -- 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. json :: Parser Value -- | Parse a top-level JSON value. This must be either an object or an -- array, per RFC 4627. -- -- 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. 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. -- --
--   $(deriveJSON (drop 4) ''D)
--   
-- -- This will result in the following (simplified) code to be spliced in -- your program: -- --
--   import Control.Applicative
--   import Control.Monad
--   import Data.Aeson
--   import Data.Aeson.TH
--   import qualified Data.HashMap.Strict as H
--   import qualified Data.Text as T
--   import qualified Data.Vector as V
--   
--   instance ToJSON a => ToJSON (D a) where
--       toJSON =
--         value ->
--           case value of
--             Nullary ->
--                 object [T.pack "Nullary" .= toJSON ([] :: [()])]
--             Unary arg1 ->
--                 object [T.pack "Unary" .= toJSON arg1]
--             Product arg1 arg2 arg3 ->
--                 object [ T.pack "Product"
--                          .= (Array $ create $ do
--                                mv <- unsafeNew 3
--                                unsafeWrite mv 0 (toJSON arg1)
--                                unsafeWrite mv 1 (toJSON arg2)
--                                unsafeWrite mv 2 (toJSON arg3)
--                                return mv)
--                        ]
--             Record arg1 arg2 arg3 ->
--                 object [ T.pack "Record"
--                          .= object [ T.pack "One"   .= arg1
--                                    , T.pack "Two"   .= arg2
--                                    , T.pack "Three" .= arg3
--                                    ]
--                        ]
--   
-- --
--   instance FromJSON a => FromJSON (D a) where
--       parseJSON =
--         value ->
--           case value of
--             Object obj ->
--               case H.toList obj of
--                 [(conKey, conVal)] ->
--                   case conKey of
--                     _ | conKey == T.pack "Nullary" ->
--                           case conVal of
--                             Array arr ->
--                               if V.null arr
--                               then pure Nullary
--                               else fail "<error message>"
--                             _ -> fail "<error message>"
--                       | conKey == T.pack "Unary" ->
--                           case conVal of
--                             arg -> Unary <$> parseJSON arg
--                       | conKey == T.pack "Product" ->
--                           case conVal of
--                             Array arr ->
--                               if V.length arr == 3
--                               then Product <$> parseJSON (arr unsafeIndex 0)
--                                            <*> parseJSON (arr unsafeIndex 1)
--                                            <*> parseJSON (arr unsafeIndex 2)
--                               else fail "<error message>"
--                             _ -> fail "<error message>"
--                       | conKey == T.pack "Record" ->
--                           case conVal of
--                             Object recObj ->
--                               if H.size recObj == 3
--                               then Record <$> recObj .: T.pack "One"
--                                           <*> recObj .: T.pack "Two"
--                                           <*> recObj .: T.pack "Three"
--                               else fail "<error message>"
--                             _ -> fail "<error message>"
--                       | otherwise -> fail "<error message>"
--                 _ -> fail "<error message>"
--             _ -> fail "<error message>"
--   
-- -- Note that every "<error message>" is in fact a descriptive -- message which provides as much information as is reasonable about the -- failed parse. -- -- 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
--   
-- -- Please note that you can derive instances for tuples using the -- following syntax: -- --
--   -- FromJSON and ToJSON instances for 4-tuples.
--   $(deriveJSON id ''(,,,))
--   
module Data.Aeson.TH -- | Generates both ToJSON and FromJSON instance declarations -- for the given data type. -- -- This is a convienience function which is equivalent to calling both -- deriveToJSON and deriveFromJSON. deriveJSON :: (String -> String) -> Name -> Q [Dec] -- | Generates a ToJSON instance declaration for the given data -- type. -- -- Example: -- --
--   data Foo = Foo Char Int
--   $(deriveToJSON id ''Foo)
--   
-- -- This will splice in the following code: -- --
--   instance ToJSON Foo where
--        toJSON =
--            value -> case value of
--                        Foo arg1 arg2 -> Array $ create $ do
--                          mv <- unsafeNew 2
--                          unsafeWrite mv 0 (toJSON arg1)
--                          unsafeWrite mv 1 (toJSON arg2)
--                          return mv
--   
deriveToJSON :: (String -> String) -> Name -> Q [Dec] -- | Generates a FromJSON instance declaration for the given data -- type. -- -- Example: -- --
--   data Foo = Foo Char Int
--   $(deriveFromJSON id ''Foo)
--   
-- -- This will splice in the following code: -- --
--   instance FromJSON Foo where
--       parseJSON =
--           value -> case value of
--                       Array arr ->
--                         if (V.length arr == 2)
--                         then Foo <$> parseJSON (arr unsafeIndex 0)
--                                  <*> parseJSON (arr unsafeIndex 1)
--                         else fail "<error message>"
--                       other -> fail "<error message>"
--   
deriveFromJSON :: (String -> String) -> Name -> Q [Dec] -- | Generates a lambda expression which encodes the given data type as -- JSON. -- -- Example: -- --
--   data Foo = Foo Int
--   
-- --
--   encodeFoo :: Foo -> Value
--   encodeFoo = $(mkToJSON id ''Foo)
--   
-- -- This will splice in the following code: -- --
--   value -> case value of Foo arg1 -> toJSON arg1
--   
mkToJSON :: (String -> String) -> Name -> Q Exp -- | Generates a lambda expression which parses the JSON encoding of the -- given data type. -- -- Example: -- --
--   data Foo = Foo Int
--   
-- --
--   parseFoo :: Value -> Parser Foo
--   parseFoo = $(mkParseJSON id ''Foo)
--   
-- -- This will splice in the following code: -- --
--   \value -> case value of arg -> Foo <$> parseJSON arg
--   
mkParseJSON :: (String -> String) -> Name -> Q Exp