Parse Json tweets using Aeson

{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE DeriveGeneric #-} import Data.Aeson import GHC.Generics import qualified Data.ByteString.Lazy as B data Tweet = Tweet { id_str :: String, text :: String }deriving Generic instance FromJSON Tweet main = do input <- B.readFile "1.json" let mm = decode input :: Maybe Tweet case mm of Nothing -> print "error parsing JSON" Just m -> (putStrLn.greet) m greet m = (show.id_str) m This program is fine if 1.json file has 1 tweet if 1.json file has multiple tweets then it fails so how we can parse multiple tweets

Tushar Jarhad
let mm = decode input :: Maybe Tweet
You have told the program you expect one tweet---anything else is, by definition, an error. The program takes you at your word. So if you want it to parse multiple tweets, tell it that you expect a *list* of tweets.
let mm = decode input :: Maybe [Tweet]
Or are you saying that your file simply has multiple tweets appended one after another? If so, that file does not represent a valid JSON structure. I feel sure there's a way to run the parse incrementally---taking a complete data structure at a time---but I don't know it offhand. Mike.

Michael Alan Dorman
I feel sure there's a way to run the parse incrementally---taking a complete data structure at a time---but I don't know it offhand.
Since I felt like I *should* know this offhand, I decided to figure it out. It's very easy---Aeson provides an Attoparsec parser, so you can, in fact, do parsing-with-leftovers with virtually zero effort: import Data.Aeson import Data.Attoparsec.ByteString import Data.ByteString var :: ByteString var = "{\"Some\" : \"Text\"}Leftover" main = print $ parse json var This produces a value representing the simple Object, as well as leftovers---so you could, presumably, do a fold to pull out as many JSON items as can be parsed, even if the overall file isn't a valid JSON structure in itself. Mike.
participants (2)
-
Michael Alan Dorman
-
Tushar Jarhad