pipes-aeson-0.4.2: Encode and decode JSON streams using Aeson and Pipes.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Pipes.Aeson

Description

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

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 #

Encode an Array as JSON and send it downstream,

Hint: You can easily turn this Producer' into a Pipe that encodes Array values as JSON as they flow downstream using:

for cat encodeArray :: Monad m => Pipe Array ByteString m r

encodeObject :: Monad m => Object -> Proxy x' x () ByteString m () Source #

Encode an Object as JSON and send it downstream,

Hint: You can easily turn this Producer' into a Pipe that encodes Object values as JSON as they flow downstream using:

for cat encodeObject :: Monad m => Pipe Object ByteString m r

Decoding

Decoding JSON as a Haskell value involves two different steps:

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.

decoded Source #

Arguments

:: (Monad m, FromJSON a, ToJSON a) 
=> (Value -> Either Object Array)

A witness that a can be represented either as an Object or as an Array. The passed in Value is toJSON a

-> 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 r
zoom 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.

loop Source #

Arguments

:: (Monad m, FromJSON a) 
=> (Producer ByteString m r -> Producer ByteString m r)

In case of AttoparsecError, this function will be called to modify the leftovers Producer before using it.

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., drop 1 . dropWhile (/= 0xA)). However, it can be hard to do correctly is there is no such delimiter. Skipping the first character (i.e., drop 1) should be sufficient in most cases, but not when parsing recursive data structures because you can accidentally parse a child in its parent's stead.

Notice that unless you advance the Producer somehow, loop will never terminate.

-> 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 DecodingErrors 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.

decodedL Source #

Arguments

:: (Monad m, FromJSON a, ToJSON a) 
=> (Value -> Either Object Array)

A witness that a can be represented either as an Object or as an Array. The passed in Value is toJSON a

-> 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.

loopL Source #

Arguments

:: (Monad m, FromJSON a) 
=> (Producer ByteString m r -> Producer ByteString m r)

In case of AttoparsecError, this function will be called to modify the leftovers Producer before using it.

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., drop 1 . dropWhile (/= 0xA)). However, it can be hard to do correctly is there is no such delimiter. Skipping the first character (i.e., drop 1) should be sufficient in most cases, but not when parsing recursive data structures because you can accidentally parse a child in its parent's stead.

Notice that unless you advance the Producer somehow, loopL will never terminate.

-> 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.

Constructors

AttoparsecError ParsingError

An attoparsec error that happened while parsing the raw JSON string.

FromJSONError Value String

An aeson error that happened while trying to convert the given Value to an FromJSON instance, as reported by Error.

Instances

Instances details
Data DecodingError Source # 
Instance details

Defined in Pipes.Aeson.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DecodingError -> c DecodingError #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DecodingError #

toConstr :: DecodingError -> Constr #

dataTypeOf :: DecodingError -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DecodingError) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DecodingError) #

gmapT :: (forall b. Data b => b -> b) -> DecodingError -> DecodingError #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DecodingError -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DecodingError -> r #

gmapQ :: (forall d. Data d => d -> u) -> DecodingError -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DecodingError -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DecodingError -> m DecodingError #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DecodingError -> m DecodingError #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DecodingError -> m DecodingError #

Exception DecodingError Source # 
Instance details

Defined in Pipes.Aeson.Internal

Show DecodingError Source # 
Instance details

Defined in Pipes.Aeson.Internal

Eq DecodingError Source # 
Instance details

Defined in Pipes.Aeson.Internal