pipes-aeson-0.1.0.0: Encode and decode JSON streams using aeson and pipes.

Safe HaskellNone

Control.Proxy.Aeson

Contents

Description

This module allows you to encode and decode JSON values flowing downstream through Pipes streams, possibly interleaving other stream effects.

This module builds on top of the pipes-parse and pipes-attoparsec packages and assumes you have read Control.Proxy.Parse.Tutorial.

Synopsis

Top level JSON values

The JSON RFC-4627 standard only allows Array or Object values as top-level. The TopLevelValue type used throughout this module in replacement of Aesons's Value enforces that restricion in a type-safe manner.

If you want to ignore the standard and encode or decode any Value, then use the facilities exported by the Control.Proxy.Aeson.Unsafe module.

data TopLevelValue Source

A JSON top-level value must be an Object or an Array, according to RFC-4627.

Constructors

Object !Object 
Array !Array 

toTopLevelValue :: ToJSON a => a -> Maybe TopLevelValueSource

Converts the given ToJSON instance to a TopLevelValue as long as its Value representation is one of Object or Array, otherwise Nothing. Remember that Value itself is a ToJSON instance.

Encoding

There are two different JSON encoding facilities exported by this module, and choosing between them is easy: If you need to interleave JSON encoding with other stream effects you must use encode, otherwise you may use the simpler encodeD.

Both encoding proxies enforce the JSON RFC-4627 requirement that top-level values are either Arrays or Objects, as witnessed by the TopLevelValue type. However, if you need to ignore this requirement you may use the similar encoding proxies exported by the Control.Proxy.Aeson.Unsafe module.

encode :: (Proxy p, Monad m) => TopLevelValue -> p x' x () ByteString m ()Source

Encodes the given TopLevelValue as JSON and sends it downstream, possibly in more than one ByteString chunk.

encodeD :: (Proxy p, Monad m) => () -> Pipe p TopLevelValue ByteString m rSource

Encodes TopLevelValues flowing downstream as JSON, each in possibly more than one ByteString chunk, and sends each chunk downstream.

Decoding

Decoding a JSON value as a Haskell type in involves two different steps:

Any of those steps can fail, and in case of errors, the DecodingError type explicitly states at which the step the error happened.

There are two different JSON decoding facilities exported by this module, both perform those steps at once. Choosing between them is easy: If you need to interleave JSON decoding with other stream effects you must use decode, otherwise you may use the simpler decodeD.

These proxies use the EitherP proxy transformer to report decoding errors, you might use any of the facilities exported by Control.Proxy.Trans.Either to recover from them.

If you prefer to perform each of the decoding steps separately, you could use instead the parseValue, parseValueD, fromValue or fromValueD proxies.

decode :: (Monad m, Proxy p, FromJSON r) => EitherP DecodingError (StateP [ByteString] p) () (Maybe ByteString) y' y m rSource

Decodes one JSON value flowing downstream.

  • In case of decoding errors, a DecodingError exception is thrown in the EitherP proxy transformer.
  • Requests more input from upstream using draw when needed.
  • Do not use this proxy if your stream has leading empty chunks or whitespace, otherwise you may get unexpected parsing errors.

Here is an example parsing loop that allows interleaving stream effects together with decode:

   loop = do
       -- Skip any leading whitespace and check that we haven't reached EOF.
       eof <- liftP $ dropWhile isSpace >> isEndOfParserInput
       unless eof $ do
           -- 1. Possibly perform some stream effects here.
           -- 2. Decode one JSON element from the stream.
           exampleElement <- decode
           -- 3. Do something with exampleElement and possibly perform
           --    some more stream effects.
           -- 4. Start all over again.
           loop

decodeD :: (Monad m, Proxy p, FromJSON b) => () -> Pipe (EitherP DecodingError (StateP [ByteString] p)) (Maybe ByteString) b m ()Source

Decodes consecutive JSON values flowing downstream until end of input.

  • In case of decoding errors, a DecodingError exception is thrown in the EitherP proxy transformer.
  • Requests more input from upstream using draw when needed.
  • Empty input chunks flowing downstream and whitespace in between JSON values will be discarded.

Lower level parsing

parseValue :: (Monad m, Proxy p) => EitherP ParsingError (StateP [ByteString] p) () (Maybe ByteString) y' y m TopLevelValueSource

Parses a JSON value flowing downstream into a TopLevelValue.

  • In case of parsing errors, a ParsingError exception is thrown in the EitherP proxy transformer.
  • Requests more input from upstream using draw when needed.
  • Do not use this proxy if your stream has leading empty chunks or whitespace, otherwise you may get unexpected parsing errors.

See the documentation of decode for an example of how to interleave other stream effects together with this proxy.

parseValueD :: (Monad m, Proxy p) => () -> Pipe (EitherP ParsingError (StateP [ByteString] p)) (Maybe ByteString) TopLevelValue m ()Source

Parses consecutive JSON values flowing downstream as TopLevelValues, until end of input.

  • In case of parsing errors, a DecodingError exception is thrown in the EitherP proxy transformer.
  • Requests more input from upstream using draw when needed.
  • Empty input chunks flowing downstream and whitespace in between JSON values will be discarded.

fromValue :: (Monad m, Proxy p, FromJSON r) => x -> EitherP String p x Value y' y m rSource

Converts any Value flowing downstream to a FromJSON instance.

  • In case of parsing errors, a String exception holding the value provided by Aeson's Error is thrown in the EitherP proxy transformer.

See the documentation of decode for an example of how to interleave other stream effects together with this proxy.

fromValueD :: (Monad m, Proxy p, FromJSON b) => x -> EitherP String p x Value x b m rSource

Converts any Values flowing downstream to FromJSON instances and forwards them downstream.

  • In case of parsing errors, a String exception holding the value provided by Aeson's Error is thrown in the EitherP proxy transformer.

Types

data DecodingError Source

An error while decoding a JSON value.

Constructors

ParserError ParsingError

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

ValueError String

An Aeson error that happened while trying to convert a Value to an FromJSON instance, as reported by Error.