Question

I've been banging my head trying to use Aeson to parse Bitly responses. Could someone give me a hint as to what Haskell types should be defined and how to use Aeson to then parse the following into those types?:

// BITLY EXPAND RESPONSE
{
  "data": {
    "expand": [
      {
        "global_hash": "900913",
        "long_url": "http://google.com/",
        "short_url": "http://bit.ly/ze6poY",
        "user_hash": "ze6poY"
      }
    ]
  },
  "status_code": 200,
  "status_txt": "OK"
}

// BITLY SHORTEN RESPONSE
{
  "data": {
    "global_hash": "900913",
    "hash": "ze6poY",
    "long_url": "http://google.com/",
    "new_hash": 0,
    "url": "http://bit.ly/ze6poY"
  },
  "status_code": 200,
  "status_txt": "OK"
}

Here is what I have tried so far:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}

module BitlyClientResponses where

import           Control.Applicative
import           Data.Aeson
import qualified Data.ByteString.Lazy.Char8 as L (pack)
import qualified Data.HashMap.Strict        as M

data DataStatusCodeStatusTxt =
    DSCST { ddata       :: ResponseData
          , status_code :: Integer
          , status_txt  :: String
          }
    deriving (Eq, Show)

data ResponseData
  = ExpandResponseData { expand :: [Response]
                       }
    deriving (Eq, Show)

data Response = ExpandResponse { long_url    :: String -- URI
                               , global_hash :: String
                               , short_url   :: String -- URI
                               , user_hash   :: String
                               -- , hash        :: [String]
                               -- , error       :: String
                               }
              | J String
              | N String
    deriving (Eq, Show)

instance FromJSON DataStatusCodeStatusTxt where
    parseJSON (Object o) = DSCST <$>
                               o .: "data" <*>
                               o .: "status_code" <*>
                               o .: "status_txt"
    parseJSON x = fail $ "FAIL: DataStatusCodeStatusTxt: " ++ (show x)

instance FromJSON ResponseData where
    parseJSON (Object o) =
        case M.lookup "expand" o of
            -- LOST RIGHT HERE
            Just v  -> return $ ExpandResponseData [J ((show o) ++ " $$$ " ++ (show v))]
            Nothing -> return $ ExpandResponseData [N "N"]
    parseJSON x =  fail $ "FAIL: ResponseData: " ++ (show x)

instance FromJSON Response where
    parseJSON (Object o) = ExpandResponse         <$>
                               o .: "long_url"    <*>
                               o .: "global_hash" <*>
                               o .: "short_url"   <*>
                               o .: "user_hash"
                               -- o .: "hash"        <*>
                               -- o .: "error"       <*>
    parseJSON x =  fail $ "FAIL: Response: " ++ (show x)

parseResponse :: String -> Either String DataStatusCodeStatusTxt
parseResponse x = eitherDecode $ L.pack x

When I input (hand edited for readability):

"{ \"status_code\": 200,
   \"status_txt\": \"OK\",
   \"data\": { \"expand\": [
                            { \"short_url\": \"http:\\/\\/bit.ly\\/LCJq0b\",
                              \"long_url\": \"http:\\/\\/blog.swisstech.net\\/2012\\/06\\/local-postfix-as-relay-to-amazon-ses.html\",
                              \"user_hash\": \"LCJq0b\",
                              \"global_hash\": \"LCJsVy\" }, ...

I get back (hand edited too):

Right
  (Right
    (DSCST
      {ddata = ExpandResponseData {expand = [J "fromList [(\"expand\",Array (fromList [Object fromList [(\"long_url\",String \"http://blog.swisstech.net/2012/06/local-postfix-as-relay-to-amazon-ses.html\"),(\"global_hash\",String \"LCJsVy\"),(\"short_url\",String \"http://bit.ly/LCJq0b\"),(\"user_hash\",String \"LCJq0b\")], ...
$$$
Array (fromList [Object fromList [(\"long_url\",String \"http://blog.swisstech.net/2012/06/local-postfix-as-relay-to-amazon-ses.html\"),(\"global_hash\",String \"LCJsVy\"),(\"short_url\",String \"http://bit.ly/LCJq0b\"),(\"user_hash\",String \"LCJq0b\")], ...

In the code, look for -- LOST RIGHT HERE. I can't figure out how to parse the array of "expand".

It would be great to see how to make progress. And perhaps I am on the wrong path and someone can set me straight (e.g., maybe the data type I have defined so far is off).

Était-ce utile?

La solution

The trick with using Aeson effectively is to call down to parseJSON recursively. This is done implicitly when you use the (.:) operator, so seeing something like M.lookup is usually a bad sign. I'll provide a simplified example: a path of (latitude, longitude) pairs, represented by a JSON array of JSON objects.

data Path  = Path  { points :: [Point] }
data Point = Point { lat :: Double, lon :: Double }

-- JSON format looks a bit like this
--
-- { "points": [ {"latitude": 86, "longitude": 23} ,
--               {"latitude": 0,  "longitude": 16} ,
--               {"latitude": 43, "longitude": 87} ] }

instance FromJSON Path where
  parseJSON = withObject "path" $ \o -> 
    Path <$> o .: "points"

instance FromJSON Point where
  parseJSON = withObject "point" $ \o ->
    Point <$> o .: "latitude"
          <*> o .: "longitude"

There are two major points to take away from this snippet. Firstly, note the use of withObject to quickly constrain that the Value passed to parseJSON is tagged as an Object—it's not significantly different than using pattern matching, but it produces automatic, uniform error messages so it's worth considering.

Secondly, and more importantly, note that I only define FromJSON instance which describe the high-level outline of each object. In particular, examine the body of FromJSON Path

Path <$> o .: "points"

All this says is that I need to look into the entry named "points" and try to parse it as whatever type is necessary to build a Path—in this case, a list of Points, [Point]. This use depends upon recursively defined FromJSON instances. We need to parse an array, but fortunately there already exists the FromJSON instance

instance FromJSON a => FromJSON [a] where ...

which is interpreted as a JSON array of whatever JSON types a can parse as. In our case a ~ Point, so we just define that instance

instance FromJSON Point where ...

and then recursively depend upon the

instance FromJSON Double where ...

which is quite standard.


Another important trick you can use is adjoining multiple parses with (<|>). I'll simplify the Response data type a bit where it either parses as a particular Object or fails and produces a plain, dynamically typed Value as default. First we'll write each parser independently.

data Obj = Obj { foo :: String, bar :: String }
         | Dyn Value

okParse :: Value -> Parser Obj
okParse = withObject "obj" (\o -> Obj <$> o .: "foo" <*> o .: "bar")

elseParse :: Value -> Parser Obj
elseParse v = pure (Dyn v)

And now we combine them in the actual FromJSON instance

instance FromJSON Obj where
  parseJSON v = okParse v <|> elseParse v

In this case, aeson will try to use okParse first and, if it fails, fall back on elseParse. Since elseParse is simply a pure value it will never fail and thus provides a "default" fallback.

Licencié sous: CC-BY-SA avec attribution
Non affilié à StackOverflow
scroll top