FallingSkies
FallingSkies

Reputation: 121

Transformations with Data.Aeson.Lens

Using aeson-lens, I wrote this program that takes me very close to what I want to achieve:

{-# LANGUAGE OverloadedStrings #-}

import Network.HTTP.Conduit ( simpleHttp )
import Data.Aeson           ( decode
                            , Value
                            )
import Data.Maybe           ( fromJust )
import Control.Lens         ( (^.) )
import Data.Aeson.Lens      ( key, nth )

main :: IO ()
main = do
  pageContents <- simpleHttp "http://127.0.0.1:28017/baseball/team/"
  let v = decode pageContents :: Maybe Value
  let totalRowsVal = v ^. key "total_rows" :: Maybe Int
      oidVal       = v ^. key "rows" . nth 0 ^. key "_id" ^. key "$oid" :: Maybe String
  print totalRowsVal
  print oidVal
  return ()

The JSON content is:

{
  "total_rows": 2,
  "rows": [
    {
      "_id": { "$oid": "5548ed2671eab385baadf0a7" },
      "abc": 123
    },
    {
      "_id": { "$oid": "5548ed5171eab385baadf0a8" },
      "def": 456
    }
  ],
  "query": {},
  "offset": 0,
  "millis": 0
}

The output is:

Just 2
Just "5548ed2671eab385baadf0a7"

I would like to get to a point where the output is:

Just 2
Just [("abc",123),("def",456)]

In other words, I would like to extract the useful contents from the value under the rows key without knowing in advance what the keys are in the elements of that JSON array. I would also like the program to signal to the user that the value under the query key is an empty JSON object.

Upvotes: 1

Views: 955

Answers (1)

cchalmers
cchalmers

Reputation: 2986

First of all use lens-aeson not aeson-lens. aeson-lens hasn't been updated in a while and I don't think all its lenses are law-abiding. Since they both share Data.Aeson.Lens you'll have to run ghc-pkg unregister aeson-lens (or cabal sandbox hc-pkg unregister aeson-lens if you're using a sandbox).

You haven't described exactly how you know what the "useful contents" are so I'm assuming it's anything not called "_id" and points to an integer. In aeson-lens each object of an array is a HashMap so first we'll make a traversal over those:

rows :: Traversal' Value (HM.HashMap Text Value)
rows = key "rows" . _Array . each . _Object
-- or  key "rows" . values

For the row values we can use indexed traversals, where the index is the Text of the HashMap. We can then filter the contents using ifiltered by checking the index isn't "_id". We also use _Integer to only get things pointing to an Integer.

nonIds :: IndexedTraversal' Text (HM.HashMap Text Value)  Integer
nonIds = itraversed . ifiltered (\i _ -> i /= "_id") . _Integer
-- or    members . ifiltered (\i _ -> i /= "_id") . _Integer

From here it's easy to get a list of what you want:

> v ^@.. rows . nonIds
[("abc",123),("def",456)]

(^@..) returns a list of an indexed traversal, along with it's index.

To check "query" is an empty object you can use nullOf:

emptyQuery = nullOf (key "query" . _Object . each) v

Here's a working example (I saved the json file to "json.json":

{-# LANGUAGE OverloadedStrings #-}

import Data.Aeson
import Data.Aeson.Lens
import qualified Data.ByteString.Lazy as LB
import Control.Lens

main :: IO ()
main = do
  contents <- LB.readFile "json.json"
  let Just v = decode contents :: Maybe Value
  let totalRows  = v ^? key "total_rows" . _Integer
      rows       = key "rows" . values
      nonIds     = members . ifiltered (\i _ -> i /= "_id") . _Integer
      vals       = v ^@.. rows . nonIds
      emptyQuery = nullOf (key "query" . members) v
  print totalRows
  print vals
  print emptyQuery

which gives the output

Just 2
[("abc",123),("def",456)]
True

(You could equivalently use traverse or traversed instead of each here, they all traverse over the Vector; I just think each reads nicer.)

Upvotes: 6

Related Questions