Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module allows you to encode and decode JSON values flowing downstream through Pipes streams.
This module builds on top of the aeson
, pipes
and pipes-parse
libraries, and assumes you know how to use them. Please read the examples
in Pipes.Parse.Tutorial to understand how to use these functions.
In this module, the following type synonym compatible with the lens
,
lens-family
and lens-family-core
libraries is used but not exported:
type Lens' s a = forall f . Functor
f => (a -> f a) -> (s -> f s)
Synopsis
- encodeArray :: Monad m => Array -> Proxy x' x () ByteString m ()
- encodeObject :: Monad m => Object -> Proxy x' x () ByteString m ()
- decode :: (Monad m, FromJSON a) => Parser ByteString m (Maybe (Either DecodingError a))
- decoded :: (Monad m, FromJSON a, ToJSON a) => (Value -> Either Object Array) -> Lens' (Producer ByteString m r) (Producer a m (Either (DecodingError, Producer ByteString m r) r))
- loop :: (Monad m, FromJSON a) => (Producer ByteString m r -> Producer ByteString m r) -> Producer ByteString m r -> Producer' (Either DecodingError a) m r
- decodeL :: (Monad m, FromJSON a) => Parser ByteString m (Maybe (Either DecodingError (Int, a)))
- decodedL :: (Monad m, FromJSON a, ToJSON a) => (Value -> Either Object Array) -> Lens' (Producer ByteString m r) (Producer (Int, a) m (Either (DecodingError, Producer ByteString m r) r))
- loopL :: (Monad m, FromJSON a) => (Producer ByteString m r -> Producer ByteString m r) -> Producer ByteString m r -> Proxy x' x () (Either DecodingError (Int, a)) m r
- data DecodingError
Encoding
Encode Array
or Object
values as JSON and send them downstream,
possibly in more than one ByteString
chunk.
Note: The JSON RFC-4627 standard only allows arrays or objects as top-level
entities, which is why these functions restrict their input to them. If you
prefer to ignore the standard and encode any Value
, then use encode
from the Pipes.Aeson.Unchecked module.
encodeArray :: Monad m => Array -> Proxy x' x () ByteString m () Source #
encodeObject :: Monad m => Object -> Proxy x' x () ByteString m () Source #
Decoding
Decoding JSON as a Haskell value involves two different steps:
- Parsing a raw JSON
ByteString
into anObject
or anArray
. - Converting the obtained
Object
orArray
to the desiredFromJSON
instance.
Any of those steps can fail, in which case a DecodingError
will report
the precise error and at which step it happened.
decode :: (Monad m, FromJSON a) => Parser ByteString m (Maybe (Either DecodingError a)) Source #
Decodes an Object
or Array
JSON value from the underlying state.
It returns Nothing
if the underlying Producer
is exhausted, otherwise
it returns either the decoded entity or a DecodingError
in case of error.
Note: The JSON RFC-4627 standard only allows arrays or objects as top-level
entities, which is why this Parser
restricts its output to them. If
you prefer to ignore the standard and decode any Value
, then use
decode
from the Pipes.Aeson.Unchecked module.
:: (Monad m, FromJSON a, ToJSON a) | |
=> (Value -> Either Object Array) | A witness that |
-> Lens' (Producer ByteString m r) (Producer a m (Either (DecodingError, Producer ByteString m r) r)) |
Improper lens that turns a stream of raw JSON input into a stream of
FromJSON
and back.
By improper lens we mean that in practice you can't expect the
Monad Morphism Laws to be true when using decoded
with
zoom
.
zoom
decoded
(return
r) /=return
rzoom
decoded
(m >>= k) /=zoom
m >>=zoom
. f
Note: The JSON RFC-4627 standard only allows arrays or objects as top-level
entities, which is why this function restricts its stream values to them. If
you prefer to ignore the standard and encode or decode any Value
, then
use decoded
from the Pipes.Aeson.Unchecked module.
:: (Monad m, FromJSON a) | |
=> (Producer ByteString m r -> Producer ByteString m r) | In case of Ideally you will want to drop everything until the beginning of the next
JSON element. This is easy to accomplish if there is a clear whitespace
delimiter between the JSON elements, such as a newline (i.e.,
Notice that unless you advance the |
-> Producer ByteString m r | Raw JSON input. |
-> Producer' (Either DecodingError a) m r |
Repeteadly try to parse raw JSON bytes into a
values, reporting any
DecodingError
s downstream as they happen.
Note: The JSON RFC-4627 standard only allows arrays or objects as top-level
entities, which is why these functions restrict their input to them. If you
prefer to ignore the standard and encode any Value
, then use encode
from the Pipes.Aeson.Unchecked module.
Including lengths
decodeL :: (Monad m, FromJSON a) => Parser ByteString m (Maybe (Either DecodingError (Int, a))) Source #
Like decode
, except it also returns the length of JSON input that was
consumed in order to obtain the value, not including the length of whitespace
before nor after the parsed JSON input.
:: (Monad m, FromJSON a, ToJSON a) | |
=> (Value -> Either Object Array) | A witness that |
-> Lens' (Producer ByteString m r) (Producer (Int, a) m (Either (DecodingError, Producer ByteString m r) r)) |
Like decoded
, except it also tags each decoded entity with the length of
JSON input that was consumed in order to obtain the value, not including the
length of whitespace between each parsed JSON input.
:: (Monad m, FromJSON a) | |
=> (Producer ByteString m r -> Producer ByteString m r) | In case of Ideally you will want to drop everything until the beginning of the next
JSON element. This is easy to accomplish if there is a clear whitespace
delimiter between the JSON elements, such as a newline (i.e.,
Notice that unless you advance the |
-> Producer ByteString m r | Raw JSON input. |
-> Proxy x' x () (Either DecodingError (Int, a)) m r |
Like loop
, except it also outputs the length of JSON input that was
consumed in order to obtain the value, not including the length of whitespace
before nor after the parsed JSON input.
Types
data DecodingError Source #
An error while decoding a JSON value.
AttoparsecError ParsingError | An |
FromJSONError Value String | An |