| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Data.ByteString.Streaming.Aeson
Description
The encode, decode and decoded functions replicate
     the similar functions in Renzo Carbonara's
     pipes-aeson .
     Note that aeson accumulates a whole top level json array or object before coming to any conclusion.
     This is the only default that could cover all cases.
The streamParse function accepts parsers from the
     json-streams library.
     The 'json-streams' parsers use aeson types, but will stream suitable elements
     as they arise.  For this reason, of course, it cannot validate the entire json
     entity before acting, but carries on validation as it moves along, reporting
     failure when it comes. Though it is generally faster and accumulates less memory than
     the usual aeson parsers, it is by no means a universal replacement for
     aeson's behavior.  It will certainly be sensible, for example, wherever
     you are executing a left fold over the subordinate elements, e.g. gathering certain
     statistics about them.
Here we use a long top level array of objects from
     a file
     json-streams benchmarking directory. Each object in the top level array
     has a "friends" field with an assocated array of friends; each of these has a "name".
     Here, we extract the name of each friend of each person recorded in the level array, and
     enumerate them all:
{-#LANGUAGE OverloadedStrings #-}
import Streaming
import qualified Streaming.Prelude as S
import Data.ByteString.Streaming.HTTP
import Data.ByteString.Streaming.Aeson (streamParse)
import Data.JsonStream.Parser (string, arrayOf, (.:), Parser)
import Data.Text (Text)
import Data.Function ((&))
main = do
   req <- parseRequest "https://raw.githubusercontent.com/ondrap/json-stream/master/benchmarks/json-data/buffer-builder.json"
   m <- newManager tlsManagerSettings
   withHTTP req m $ \resp -> do
     let names, friend_names :: Parser Text
         names = arrayOf ("name" .: string)
         friend_names = arrayOf ("friends" .: names)
     responseBody resp                           -- raw bytestream from http-client
      & streamParse friend_names                 -- find name fields in each sub-array of friends
      & void                                     -- drop material after any bad parse
      & S.zip (S.each [1..])                     -- number the friends' names
      & S.print                                  -- successively print to stdout
-- (1,"Joyce Jordan")
-- (2,"Ophelia Rosales")
-- (3,"Florine Stark")
-- ...
-- (287,"Hilda Craig")
-- (288,"Leola Higgins")This program does not accumulate the whole byte stream, as an aeson parser for a top-level json entity would. Rather it streams and enumerates friends' names as soon as they come. With appropriate instances, we could of course just stream the objects in the top-level array instead.
Synopsis
- data DecodingError
- = AttoparsecError ParsingError
 - | FromJSONError String
 
 - encode :: (Monad m, ToJSON a) => a -> ByteString m ()
 - decode :: (Monad m, FromJSON a) => StateT (ByteString m x) m (Either DecodingError a)
 - decoded :: (Monad m, FromJSON a) => ByteString m r -> Stream (Of a) m (Either (DecodingError, ByteString m r) r)
 - streamParse :: Monad m => Parser a -> ByteString m r -> Stream (Of a) m (Maybe String, ByteString m r)
 
Documentation
data DecodingError Source #
Constructors
| AttoparsecError ParsingError | An   | 
| FromJSONError String | An   | 
Instances
encode :: (Monad m, ToJSON a) => a -> ByteString m () Source #
This instance allows using errorP with decoded
 and decodedL
 instance Error (DecodingError, Producer a m r)
Consecutively parse a elements from the given Producer using the given
 parser (such as decode or parseValue), skipping
 any leading whitespace each time.
This Producer runs until it either runs out of input or until a decoding
 failure occurs, in which case it returns Left with a DecodingError and
 a Producer with any leftovers. You can use errorP to turn the
 Either return value into an ErrorT
 monad transformer.
Like encode, except it accepts any ToJSON instance,
 not just Array or Object.
decode :: (Monad m, FromJSON a) => StateT (ByteString m x) m (Either DecodingError a) Source #
Given a bytestring, parse a top level json entity - returning any leftover bytes.
decoded :: (Monad m, FromJSON a) => ByteString m r -> Stream (Of a) m (Either (DecodingError, ByteString m r) r) Source #
Resolve a succession of top-level json items into a corresponding stream of Haskell values.
streamParse :: Monad m => Parser a -> ByteString m r -> Stream (Of a) m (Maybe String, ByteString m r) Source #
Experimental. Parse a bytestring with a json-streams parser.
     The function will read through
     the whole of a single top level json entity, streaming the valid parses as they
     arise. (It will thus for example parse an infinite json bytestring, though these
     are rare in practice ...)
If the parser is fitted to recognize only one thing,
     then zero or one item will be yielded; if it uses combinators like arrayOf,
     it will stream many values as they arise. See the example at the top of this module,
     in which values inside a top level array are emitted as they are parsed. Aeson would
     accumulate the whole bytestring before declaring on the contents of the array.
     This of course makes sense, since attempt to parse a json array may end with
     a bad parse, invalidating the json as a whole.  With json-streams, a bad
     parse will also of course emerge in the end, but only after the initial good parses
     are streamed. This too makes sense though, but in a smaller range of contexts
     -- for example, where one is folding over the parsed material.
This function is closely modelled on
     parseByteString and
     parseLazyByteString from Data.JsonStream.Parser.