Home > Net >  Haskell: How do I model a nested JSON with fixed outer keys and an enumerated inner key?
Haskell: How do I model a nested JSON with fixed outer keys and an enumerated inner key?

Time:07-23

Consider an external API that takes as input either usd or eur, and accordingly returns a json, something like this:

api currency = case currency of
  "usd" -> "{\"bitcoin\": {\"usd\": 20403}, \"ethereum\": {\"usd\": 1138.75}}"
  "eur" -> "{\"bitcoin\": {\"eur\": 20245}, \"ethereum\": {\"eur\": 1129.34}}"

If I just needed api "usd", I would use Aeson's (?) generic decoding feature:

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric #-}

import Data.Aeson
import GHC.Generics
  
data Usd = Usd 
  { usd :: Double
  } deriving (Show, Generic)
instance FromJSON Usd

data Coin = Coin
  { bitcoin :: Usd
  , ethereum :: Usd
  } deriving (Show,Generic)
instance FromJSON Coin

processUsd = decode (api "usd") :: Maybe CoinUsd

But if both api "usd" and api "eur" are to be used, what is the best way to abstract currency out?

(In case you ask what I really want to do with it, well, the answer is nothing! This example is admittedly contrived. I want to understand ways to use data and class in modeling a json format whose keys are constrained in some ways. I would also like to maximally use Aeson's automatic decoding feature, avoiding custom fromJSON code to the extent possible.)

One option is to use nested Data.Map:

processAny :: String -> Maybe (M.Map String (M.Map String Double)) 
processAny currency = decode (api currency)  

But this is too general. I still want the outer keys ("bitcoin" etc) hardcoded/fixed. What are the options at this degree of pickiness? My immediate thought is to have a generalized Currency type and use it as a parameter for Coin. But I can't figure how to work it out?! Below are some vague statements that I hope convey my intent:

data (Currency a) => Coin a
  { bitcoin :: a
  , ethereum :: a
  } deriving (Show,Generic)
instance FromJSON (Coin a) where
  -- parseJSON x = codeIfNeeded

class (FromJSON a) => Currency a where
  -- somehow abstract out {currencyName :: Double} ?!

I am not even sure if it makes any sense at all, but if it does, how do I formalize it? Also, what is the best way to model it otherwise (while, as mentioned before, not resorting to the extremes of Data.Map and fully hand written parseJSON)?

CodePudding user response:

Let's begin by modeling elements like {"usd": 20403} in isolation. We can define a type like

{-# LANGUAGE DerivingStrategies #-}
newtype CurrencyAmount currency = CurrencyAmount {getCurrencyAmount :: Double}
  deriving stock (Show)

parameterized with "phantom types" like:

data Euro  -- no constructors required, used only as type-level info

data USD

This approach lets us (and forces us) to reuse the same "implementation" and operations for different currencies.

One operation we want to do is to parse "tagged" currency amounts. But the key in the JSON varies for each currency, that is, it depends on the phantom type. How to tackle that?

Typeclasses in Haskell let us obtain values from types. So let's write a typeclass that gives us the JSON Key to use for each currency:

import Data.Aeson
import Data.Aeson.Key
import Data.Proxy

class Currency currency where
  currencyKey :: Proxy currency -> Key -- Proxy optional with AllowAmbiguousTypes

With instances

{-# LANGUAGE OverloadedStrings #-}
instance Currency Euro where
  currencyKey _ = "eur"

instance Currency USD where
  currencyKey _ = "usd"

Now we can write an explicit FromJSON instance for CurrencyAmount:

instance Currency currency => FromJSON (CurrencyAmount currency) where
  parseJSON = withObject "amount" $ \o ->
    CurrencyAmount <$> o .: currencyKey (Proxy @currency)

And we can define Coin like this:

{-# LANGUAGE DeriveAnyClass #-}
data Coin currency = Coin
  { bitcoin :: CurrencyAmount currency,
    ethereum :: CurrencyAmount currency
  }
  deriving stock (Show, Generic)
  deriving anyclass (FromJSON)
  • Related