0

I have a JSON structure like this

{
  "tag1": 1,
  "tag2": 7,
  ...
}

And I have a type like this

data TagResult { name :: String, numberOfDevicesTagged :: Int } deriving (Show, Eq)
newtype TagResultList = TagResultList { tags :: [TagResult] }

The tag names are of course fully dynamic and I don't know them at compile time. I'd like to create an instance FromJSON to parse the JSON data but I just cannot make it compile.

How can I define parseJSON to make this happen?

Batou99
  • 869
  • 10
  • 19
  • You could just use the existing `FromJSON` and `ToJSON` types for `Map`. Your tags would then be the keys. – Shaun the Sheep Jul 03 '17 at 10:09
  • 1
    Possible duplicate of [FromJSON make a list from multiple fields](https://stackoverflow.com/questions/44514645/fromjson-make-a-list-from-multiple-fields) – Mark Seemann Jul 03 '17 at 10:31
  • It's a different case from the [FromJSON make a list from multiple fields](https://stackoverflow.com/questions/44514645/fromjson-make-a-list-from-multiple-fields). The aforementioned link is for a case where the list of possible tags is known at compile time, in this case they are unknown. – Batou99 Jul 04 '17 at 09:17

1 Answers1

1

You can use the fact that Object is an HasMap and extract the key at runtime. You can then write the FromJSON instance as follows -

{-# LANGUAGE OverloadedStrings #-}
module Main where

import Data.Aeson
import qualified Data.Text as T
import qualified Data.HashMap.Lazy as HashMap

data TagResult = TagResult { name :: String
                           , numberOfDevicesTagged :: Int
                           } deriving (Show, Eq)


newtype TagResultList = TagResultList { tags :: [TagResult] } deriving Show


instance ToJSON TagResult where

  toJSON (TagResult tag ntag) =
    object [ T.pack tag .= ntag ]

instance ToJSON TagResultList where

  toJSON (TagResultList tags) =
    object [ "tagresults" .= toJSON tags ]


instance FromJSON TagResult where

  parseJSON (Object v) =
    let (k, _) = head (HashMap.toList v)
    in TagResult (T.unpack k) <$> v .: k

  parseJSON _ = fail "Invalid JSON type"

instance FromJSON TagResultList where

  parseJSON (Object v) =
    TagResultList <$> v .: "tagresults"


main :: IO ()
main = do

  let tag1 = TagResult "tag1" 1
      tag2 = TagResult "tag2" 7
      taglist = TagResultList [tag1, tag2]

  let encoded = encode taglist
      decoded = decode encoded :: Maybe TagResultList

  print decoded

The above program should print the tag result list.

Just (TagResultList {tags = [TagResult {name = "tag1", numberOfDevicesTagged = 1},TagResult {name = "tag2", numberOfDevicesTagged = 7}]})
Yogesh Sajanikar
  • 1,086
  • 7
  • 19