0

I have JSON data that may either look like this

{
"items": [Day],
"pageCount": Int,
"totalCount": Int
}

or this

{
"items": [Order],
"pageCount": Int,
"totalCount": Int
}

I've been trying to create a data type for the unvaried fields for use with FromJSON, but I haven't been able to find the proper way to do it, while going through a variety of errors. This is my code in its current state

--{-# LANGUAGE FlexibleInstances #-}
--{-# LANGUAGE MultiParamTypeClasses #-}
--{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE OverloadedStrings #-}
import           Data.Aeson

data Typed = Typed {typeID::Int,name::String} deriving (Show,Eq)
data Day =  Day {orderCount::Int,lowPrice::Float,highPrice::Float, avgPrice:: Float,volume::Int,date::String}
data Order = Order {price::Float,isBuy::Bool,location::Typed} deriving (Show,Eq)
data Market a = Market {items::a,pageCount::Int,totalCount::Int} deriving (Show,Eq)
-- Can be either Market [Order] or Market [Day]
instance FromJSON (Market a) where
  parseJSON (Object x) = Market <$> x .: "items" <*> x .: "pageCount" <*> x .: "totalCount"
instance FromJSON Order where
  parseJSON (Object x) = Order <$> x .: "price" <*> x .: "buy" <*> x .: "location"
instance FromJSON Typed where
  parseJSON (Object x) = Typed <$> x .: "id" <*> x .: "name"
instance FromJSON Day where
  parseJSON (Object x) = Day <$> x .: "orderCount" <*> x .: "lowPrice" <*> x .: "highPrice"
    <*> x .: "avgPrice" <*> x .: "volume" <*> x .: "date"

And this is the current error I get

No instance for (FromJSON a) arising from a use of ‘.:’
    Possible fix:
      add (FromJSON a) to the context of the instance declaration
    In the second argument of ‘(<$>)’, namely ‘x .: "items"’
    In the first argument of ‘(<*>)’, namely ‘Market <$> x .: "items"’
    In the first argument of ‘(<*>)’, namely
      ‘Market <$> x .: "items" <*> x .: "pageCount"’
  • 1
    Do what it tells you, add `FromJSON a` to the context: `instance FromJSON a => FromJSON (Market a) where ...` – user2407038 Mar 19 '16 at 19:39
  • Thank you. I didn't know what it meant, nor did I think it would be that simple. This is my first attempt at using instances, and I just got rid of several "Couldn't match type" errors relating to that instance, so I thought it would be more complicated than that. – IDon'tUnderstandOOP Mar 19 '16 at 19:51

1 Answers1

1

So there are two issues here. The first is the compilation error: you claim that you have an instance for Market a which should mean you know how to parse the JSON serialization of a market for any choice of a, but this isn't really possible because you want to parse something of type a in order to price the contents of the price field.

We restrict our attention to only consider possible a's that we know how to parse by adding a constraint to our instance declaration:

instance FromJSON a => FromJSON (Market a) where
  ...

and now all is well. There's another problem though, the way that we've implemented FromJSON we see that it's riddled with nonexhaustive matches! Try running this with -Wall to see GHC complain at us for it. Now the problem is that each parseJSON will actually fail with an exception (not a parsing failure, like a "blow up the whole program" failure) if fed something other than an Object. This means that we get poor behaviour like

λ> decode "1.0" :: Maybe Typed
*** Exception: /home/jozefg/scratch/Aeson.hs:(24,3)-(25,39): Non-exhaustive patterns in function parseJSON

In order to fix this we can just add another clause explicitly failing in all the other cases. The more production-y solution might be to not handwrite these instances since they're all pretty straightforward and instead use aeson's support for generics for example. Here's the fixed instance for Order for example where I've just added an extra clause

instance FromJSON Order where
  parseJSON (Object x) =
    Order <$> x .: "price" <*> x .: "buy" <*> x .: "location"
  parseJSON _ = mempty
daniel gratzer
  • 52,833
  • 11
  • 94
  • 134