Copyright | (c) Marek Fajkus |
---|---|
License | BSD3 |
Maintainer | marek.faj@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
Aeson decoding API is closed over the type class FromJSON
.
Because of this there is one to one mapping between JSON
format and data decoded from it.
While this is handy in many situations it forces
users of Aeson library to define proxy types and
data wrappers just for sake of implementing instance
of FromJSON
.
This module provides value level Decoder
which can be used
instead of instance implementation.
Synopsis
- newtype Decoder a = Decoder (Value -> Parser a)
- auto :: FromJSON a => Decoder a
- void :: Decoder Void
- unit :: Decoder ()
- bool :: Decoder Bool
- int :: Decoder Int
- integer :: Decoder Integer
- int8 :: Decoder Int8
- int16 :: Decoder Int16
- int32 :: Decoder Int32
- int64 :: Decoder Int64
- word :: Decoder Word
- word8 :: Decoder Word8
- word16 :: Decoder Word16
- word32 :: Decoder Word32
- word64 :: Decoder Word64
- natural :: Decoder Natural
- float :: Decoder Float
- double :: Decoder Double
- scientific :: Decoder Scientific
- char :: Decoder Char
- text :: Decoder Text
- string :: Decoder String
- uuid :: Decoder UUID
- version :: Decoder Version
- zonedTime :: Decoder ZonedTime
- localTime :: Decoder LocalTime
- timeOfDay :: Decoder TimeOfDay
- utcTime :: Decoder UTCTime
- day :: Decoder Day
- dayOfWeek :: Decoder DayOfWeek
- nullable :: Decoder a -> Decoder (Maybe a)
- list :: Decoder a -> Decoder [a]
- vector :: Decoder a -> Decoder (Vector a)
- hashMapLazy :: Decoder a -> Decoder (HashMap Text a)
- hashMapStrict :: Decoder a -> Decoder (HashMap Text a)
- mapLazy :: Decoder a -> Decoder (Map Text a)
- mapStrict :: Decoder a -> Decoder (Map Text a)
- jsonNull :: a -> Decoder a
- key :: Text -> Decoder a -> Decoder a
- at :: [Text] -> Decoder a -> Decoder a
- index :: Int -> Decoder a -> Decoder a
- indexes :: [Int] -> Decoder a -> Decoder a
- element :: JSONPathElement -> Decoder a -> Decoder a
- path :: JSONPath -> Decoder a -> Decoder a
- decode :: Decoder a -> ByteString -> Maybe a
- decode' :: Decoder a -> ByteString -> Maybe a
- eitherDecode :: Decoder a -> ByteString -> Either String a
- eitherDecode' :: Decoder a -> ByteString -> Either String a
- decodeStrict :: Decoder a -> ByteString -> Maybe a
- decodeStrict' :: Decoder a -> ByteString -> Maybe a
- eitherDecodeStrict :: Decoder a -> ByteString -> Either String a
- eitherDecodeStrict' :: Decoder a -> ByteString -> Either String a
- decodeFileStrict :: Decoder a -> FilePath -> IO (Maybe a)
- decodeFileStrict' :: Decoder a -> FilePath -> IO (Maybe a)
- eitherDecodeFileStrict :: Decoder a -> FilePath -> IO (Either String a)
- eitherDecodeFileStrict' :: Decoder a -> FilePath -> IO (Either String a)
Example Usage
As mentioned above, combinators and type classes can be used together.
Decode type nested in json
{-# LANGUAGE DeriveGeneric #-} import Data.Text import Data.ByteString.Lazy (ByteString) import Data.Aeson.Types import qualified Data.Aeson.Combinators.Decode as ACD import GHC.Generics data Person = Person { name :: Text , age :: Int } deriving (Generic, Show) instance FromJSON Person decodeEmbededPerson :: [Text] -> ByteString -> Maybe Person decodeEmbededPerson path json = ACD.decode (ACD.at path ACD.auto) json
Now we can extract Person from any key within the json.
>>> decodeEmbededPerson ["data", "person"] "{\"data\": {\"person\":{\"name\":\"Joe\",\"age\":12}}}" Just (Person {name = "Joe", age = 12})
Easily decode multiple data from single json:
-- data Person defined above ^ type Token = Text decodePersonWithToken :: ByteString -> Maybe (Token, Person) decodePersonWithToken json = ACD.decode decoder json where decoder = (,) <$> ACD.key "token" ACD.text <*> ACD.key "person" ACD.auto
Which can be used as following
>>> decodePersonWithToken "{\"person\":{\"name\":\"Joe\",\"age\":12}, \"token\": \"foo\"}" Just ("foo",Person {name = "Joe", age = 12})
Applicative "Elm Style" Decoders
If you like elm style decoding you can avoid using FromJSON
type class all togher.
import Data.Text import qualified Data.Aeson.Combinators.Decode as ACD data Person = Person { name :: Text , age :: Int } deriving (Show) personDecoder :: ACD.Decoder Person personDecoder = Person <$> ACD.key "name" ACD.text <*> ACD.key "age" ACD.int
And use it directly as:
>>> decode personDecoder "{\"name\":\"Joe\",\"age\":12}" Just (Person {name = "Joe", age = 12})
JSON Decoder
A value that describes how values are decoded from JSON.
This type is an alternative to Aeson's FromJSON
instance implementation.
Use decode
, decode
, eitherDecode
, eitherDecode'
decodeStrict
, decodeStrict'
, eitherDecodeStrict
or eitherDecodeStrict'
alternatives provided by this module for decoding from BytString
.
For decoding files use
decodeFileStrict
, decodeFileStrict'
eitherDecodeFileStrict
, eitherDecodeFileStrict'
also provided by this module.
Using Instances of Decoder
Functor to map function over Decoder
intToString :: Decoder String intToString = show <$> Decode.int
>>> decode intToString "2" Just "2"
Applicateve to construct products
stringIntPair :: Decoder (String, Int) stringIntPair = (,) <$> index 0 string <*> index 1 int
>>> decode stringIntPair "[\"hello\", 42]" Just ("hello", 42)
Alternative to construct sums
eitherTextOrInt :: Decoder (Either Text Int) eitherTextOrInt = Left <$> Decode.text <|> Right <$> Decode.int
>>> decode eitherTextOrInt "\"Lorem Ipsum\"" Just (Left "Lorem Ipsum") >>> decode eitherTextOrInt "42" Just (Right 42)
Monad for Decoder
chaining
odd :: Decoder Int odd = do val <- int if val `mod` 2 == 1 then $ return val else fail $ "Expected odd value, got " <> show val
>>> eitherDecode odd "3" Left 3 >>> eitherDecode odd "4" Right "Error in $: Expected odd value, got 4"
auto :: FromJSON a => Decoder a Source #
Decoder
is compatible with Aeson's FromJSON
class.
auto
decoder acts like a proxy to instance implementation.
Any type that is an instance of this class is automatically compatible.
While auto
is universally usable for all primitive values,
this library provides individual type constraint functions
for decoding those values.
Decoding Primitive Values
Void, Unit, Bool
Decode any JSON value to Void
value
which is impossible to construct.
This Decoder is guarenteed to fail.
Integers (and Natural)
natural :: Decoder Natural Source #
Decode JSON number to GHC's Natural
(non negative)
This function requires base
>= 4.8.0
Floating Points
scientific :: Decoder Scientific Source #
Decode JSON number to arbitrary precision Scientific
Strings
Decoding Time
zonedTime :: Decoder ZonedTime Source #
Decode JSON string to ZonedTime
using Aeson's instance implementation.
Supported string formats:
YYYY-MM-DD HH:MM Z YYYY-MM-DD HH:MM:SS Z YYYY-MM-DD HH:MM:SS.SSS Z
The first space may instead be a T, and the second space is optional. The Z represents UTC. The Z may be replaced with a time zone offset of the form +0000 or -08:00, where the first two digits are hours, the : is optional and the second two digits (also optional) are minutes.
localTime :: Decoder LocalTime Source #
Decode JSON string to LocalTime
using Aeson's instance implementation.
timeOfDay :: Decoder TimeOfDay Source #
Decode JSON string to TimeOfDay
using Aeson's instance implementation.
utcTime :: Decoder UTCTime Source #
Decode JSON string to UTCTime
using Aesons's instance implementation
dayOfWeek :: Decoder DayOfWeek Source #
Decode JSON string to DayOfWeek
using Aesons's instance implementation
Decodeing Containers
Maybe
Sequences
list :: Decoder a -> Decoder [a] Source #
Decode JSON array of values to '[a]' of values
using provided Decoder
.
Hasmap
Map
Combinators
jsonNull :: a -> Decoder a Source #
Decode JSON null to any value. This function is usefull if you have custom constructor which represented by null in JSONs.
data Codomain = NotSet | Foo | Bar myDomainDecoder :: Decoder Codomain myDomainDecoder = jsonNull NotSet <|> (text >>= fooBar) where fooBar "foo" = return Foo fooBar "bar" = return Bar fooBar unknown = fail $ "Unknown value " <> show unknown
Objects:
key :: Text -> Decoder a -> Decoder a Source #
Extract JSON value from JSON object key
>>> decode (key "data" int) "{\"data\": 42}" Just 42
at :: [Text] -> Decoder a -> Decoder a Source #
Extract JSON value from JSON object keys
>>> decode (at ["data", "value"] int) "{\"data\": {\"value\": 42}}" Just 42
Arrays
index :: Int -> Decoder a -> Decoder a Source #
Extract JSON value from JSON array index
>>> decode (index 2 int) "[0,1,2,3,4]" Just 2
indexes :: [Int] -> Decoder a -> Decoder a Source #
Extract JSON value from JSON array indexes
>>> decode (indexes [0,1,0] int) "[[true, [42]]]" Just 42
Path
Combinators using Aeson's JSONPathElement
and JSONPath
types.
This makes it possible to mix object keys and array index accessors.
element :: JSONPathElement -> Decoder a -> Decoder a Source #
Decode value from JSON structure.
From object key:
>>> decode (element (Key "data") text) "{\"data\": \"foo\"}" Just "foo"
From array index:
>>> decode (element (Index 1) int) "[0,1,2]" Just 1
path :: JSONPath -> Decoder a -> Decoder a Source #
Decode value from deep JSON structure.
>>> decode (path [Key "data", Index 0] bool) "{\"data\":[true, false, false]}" Just True
Running Decoders
Following functions are evivalent to the one provided by Aeson.
The only difference is versions provided by Aeson
for with FromJSON
instances while these use Decoder
type
instead.
decode :: Decoder 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' :: Decoder 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.
eitherDecode :: Decoder a -> ByteString -> Either String a Source #
Like decode
but returns an error message when decoding fails.
eitherDecode' :: Decoder a -> ByteString -> Either String a Source #
Like decode'
but returns an error message when decoding fails.
decodeStrict :: Decoder 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' :: Decoder 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 and performs conversion immediately. See
json'
for details.
eitherDecodeStrict :: Decoder a -> ByteString -> Either String a Source #
Like decodeStrict
but returns an error message when decoding fails.
eitherDecodeStrict' :: Decoder a -> ByteString -> Either String a Source #
Like decodeStrict'
but returns an error message when decoding fails.
Decoding Files
decodeFileStrict :: Decoder a -> FilePath -> IO (Maybe a) Source #
Efficiently deserialize a JSON value from a file.
If this fails due to incomplete or invalid input, Nothing
is
returned.
The input file's content 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.
decodeFileStrict' :: Decoder a -> FilePath -> IO (Maybe a) Source #
Efficiently deserialize a JSON value from a file.
If this fails due to incomplete or invalid input, Nothing
is
returned.
The input file's content 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.
eitherDecodeFileStrict :: Decoder a -> FilePath -> IO (Either String a) Source #
Like decodeFileStrict
but returns an error message when decoding fails.
eitherDecodeFileStrict' :: Decoder a -> FilePath -> IO (Either String a) Source #
Like decodeFileStrict'
but returns an error message when decoding fails.