Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class FromJSON a where
- gparseJson :: (Generic a, GfromJson (Rep a), ConNames (Rep a), GIsEnum (Rep a)) => Value -> Parser a
- class FromJSONKey a where
- data FromJSONKeyFunction a
- = FromJSONKeyCoerce !(CoerceText a)
- | FromJSONKeyText !(Text -> a)
- | FromJSONKeyTextParser !(Text -> Parser a)
- | FromJSONKeyValue !(Value -> Parser a)
- fromJSON :: FromJSON a => Value -> Result a
- decode :: FromJSON a => ByteString -> Maybe a
- decode' :: FromJSON a => ByteString -> Maybe a
- decodeStrict :: FromJSON a => ByteString -> Maybe a
- decodeStrict' :: FromJSON a => ByteString -> Maybe a
- eitherDecode :: FromJSON a => ByteString -> Either String a
- eitherDecode' :: FromJSON a => ByteString -> Either String a
- eitherDecodeStrict :: FromJSON a => ByteString -> Either String a
- eitherDecodeStrict' :: FromJSON a => ByteString -> Either String a
- decodeWith :: Parser Value -> (Value -> Result a) -> ByteString -> Maybe a
- decodeStrictWith :: Parser Value -> (Value -> Result a) -> ByteString -> Maybe a
- eitherDecodeWith :: Parser Value -> (Value -> IResult a) -> ByteString -> Either (JSONPath, String) a
- eitherDecodeStrictWith :: Parser Value -> (Value -> IResult a) -> ByteString -> Either (JSONPath, String) 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
- withScientific :: String -> (Scientific -> Parser a) -> Value -> Parser a
- withBool :: String -> (Bool -> Parser a) -> Value -> Parser a
- withEmbeddedJSON :: String -> (Value -> Parser a) -> Value -> Parser a
- (.:) :: FromJSON a => Object -> Text -> Parser a
- (.:?) :: FromJSON a => Object -> Text -> Parser (Maybe a)
- (.:!) :: FromJSON a => Object -> Text -> Parser (Maybe a)
- (.!=) :: Parser (Maybe a) -> a -> Parser a
- parseField :: FromJSON a => Object -> Text -> Parser a
- parseFieldMaybe :: FromJSON a => Object -> Text -> Parser (Maybe a)
- parseFieldMaybe' :: FromJSON a => Object -> Text -> Parser (Maybe a)
- explicitParseField :: (Value -> Parser a) -> Object -> Text -> Parser a
- explicitParseFieldMaybe :: (Value -> Parser a) -> Object -> Text -> Parser (Maybe a)
- explicitParseFieldMaybe' :: (Value -> Parser a) -> Object -> Text -> Parser (Maybe a)
- data Parser a
- data Result a
- parse :: (a -> Parser b) -> a -> Result b
- parseMaybe :: (a -> Parser b) -> a -> Maybe b
- parseEither :: (a -> Parser b) -> a -> Either String b
- iparse :: (a -> Parser b) -> a -> IResult b
- json :: Parser Value
- json' :: Parser Value
- value :: Parser Value
- value' :: Parser Value
- jstring :: Parser Text
- scientific :: Parser Scientific
- module Json
Decoding
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:
empty
andmzero
work, but are terse and uninformative;fail
yields a custom error message;typeMismatch
produces an informative message for cases when the value encountered is not of the expected type.
An example type and instance using typeMismatch
:
-- Allow ourselves to writeText
literals. {-# LANGUAGE OverloadedStrings #-} data Coord = Coord { x :: Double, y :: Double } instanceFromJSON
Coord whereparseJSON
(Object
v) = Coord<$>
v.:
"x"<*>
v.:
"y" -- We do not expect a non-Object
value here. -- We could usemzero
to fail, buttypeMismatch
-- 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:
instanceFromJSON
Coord whereparseJSON
=withObject
"Coord" $ \v -> Coord<$>
v.:
"x"<*>
v.:
"y"
Instead of manually writing your FromJSON
instance, there are two 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 it will probably be more efficient than the following option.
- The compiler can provide a default generic implementation for
parseJSON
.
To use the second, simply add a deriving
clause to your
datatype and declare a Generic
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 } derivingGeneric
instanceFromJSON
Coord
The default implementation will be equivalent to
parseJSON =
; If you need different
options, you can customize the generic decoding by defining:genericParseJSON
defaultOptions
customOptions =defaultOptions
{fieldLabelModifier
=map
toUpper
} instanceFromJSON
Coord whereparseJSON
=genericParseJSON
customOptions
Instances
gparseJson :: (Generic a, GfromJson (Rep a), ConNames (Rep a), GIsEnum (Rep a)) => Value -> Parser a #
class FromJSONKey a where #
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)
fromJSONKey :: FromJSONKeyFunction a #
Strategy for parsing the key of a map-like container.
fromJSONKeyList :: FromJSONKeyFunction [a] #
Instances
data 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.
FromJSONKeyCoerce !(CoerceText a) | uses |
FromJSONKeyText !(Text -> a) | conversion from |
FromJSONKeyTextParser !(Text -> Parser a) | conversion from |
FromJSONKeyValue !(Value -> Parser a) | conversion for non-textual keys |
Instances
Functor FromJSONKeyFunction | Only law abiding up to interpretation |
Defined in Data.Aeson.Types.FromJSON fmap :: (a -> b) -> FromJSONKeyFunction a -> FromJSONKeyFunction b # (<$) :: a -> FromJSONKeyFunction b -> FromJSONKeyFunction a # |
fromJSON :: FromJSON a => Value -> Result a #
Convert a value from JSON, failing if the types do not match.
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 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.
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 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.
eitherDecode :: FromJSON a => ByteString -> Either String 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.
eitherDecodeStrict :: FromJSON a => ByteString -> Either String 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.
decodeWith :: Parser Value -> (Value -> Result a) -> ByteString -> Maybe a #
decodeStrictWith :: Parser Value -> (Value -> Result a) -> ByteString -> Maybe a #
eitherDecodeWith :: Parser Value -> (Value -> IResult a) -> ByteString -> Either (JSONPath, String) a #
eitherDecodeStrictWith :: Parser Value -> (Value -> IResult a) -> ByteString -> Either (JSONPath, String) a #
withObject :: String -> (Object -> Parser a) -> Value -> Parser a #
applies withObject
expected f valuef
to the Object
when value
is an Object
and fails using
otherwise.typeMismatch
expected
withText :: String -> (Text -> Parser a) -> Value -> Parser a #
applies withText
expected f valuef
to the Text
when value
is a
String
and fails using
otherwise.typeMismatch
expected
withArray :: String -> (Array -> Parser a) -> Value -> Parser a #
applies withArray
expected f valuef
to the Array
when value
is
an Array
and fails using
otherwise.typeMismatch
expected
withScientific :: String -> (Scientific -> Parser a) -> Value -> Parser a #
applies withScientific
expected f valuef
to the Scientific
number
when value
is a Number
and fails using
otherwise.
.
Warning: If you are converting from a scientific to an unbounded
type such as typeMismatch
expectedInteger
you may want to add a restriction on the
size of the exponent (see withBoundedScientific
) to prevent
malicious input from filling up the memory of the target system.
withBool :: String -> (Bool -> Parser a) -> Value -> Parser a #
applies withBool
expected f valuef
to the Bool
when value
is a
Bool
and fails using
otherwise.typeMismatch
expected
withEmbeddedJSON :: String -> (Value -> Parser a) -> Value -> Parser a #
Decode a nested JSON-encoded string.
(.:) :: FromJSON a => Object -> Text -> Parser a #
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) #
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.
(.!=) :: Parser (Maybe a) -> a -> Parser 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"
explicitParseField :: (Value -> Parser a) -> Object -> Text -> Parser a #
Variant of .:
with explicit parser function.
E.g. explicitParseField
parseJSON1
:: (FromJSON1
f, FromJSON
a) -> Object
-> Text
-> Parser
(f a)
explicitParseFieldMaybe :: (Value -> Parser a) -> Object -> Text -> Parser (Maybe a) #
Variant of .:?
with explicit parser function.
explicitParseFieldMaybe' :: (Value -> Parser a) -> Object -> Text -> Parser (Maybe a) #
Variant of .:!
with explicit parser function.
A JSON parser. N.B. This might not fit your usual understanding of
"parser". Instead you might like to think of Parser
as a "parse result",
i.e. a parser to which the input has already been applied.
The result of running a Parser
.
Instances
Monad Result | |
Functor Result | |
MonadFail Result | |
Defined in Data.Aeson.Types.Internal | |
Applicative Result | |
Foldable Result | |
Defined in Data.Aeson.Types.Internal fold :: Monoid m => Result m -> m # foldMap :: Monoid m => (a -> m) -> Result a -> m # foldr :: (a -> b -> b) -> b -> Result a -> b # foldr' :: (a -> b -> b) -> b -> Result a -> b # foldl :: (b -> a -> b) -> b -> Result a -> b # foldl' :: (b -> a -> b) -> b -> Result a -> b # foldr1 :: (a -> a -> a) -> Result a -> a # foldl1 :: (a -> a -> a) -> Result a -> a # elem :: Eq a => a -> Result a -> Bool # maximum :: Ord a => Result a -> a # minimum :: Ord a => Result a -> a # | |
Traversable Result | |
Alternative Result | |
MonadPlus Result | |
Eq a => Eq (Result a) | |
Show a => Show (Result a) | |
Semigroup (Result a) | |
Monoid (Result a) | |
NFData a => NFData (Result a) | |
Defined in Data.Aeson.Types.Internal |
parseEither :: (a -> Parser b) -> a -> Either String b #
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.
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.
scientific :: Parser Scientific #
Parse a JSON number.
Re-exports
module Json