jsop, JSON record cherry picker
JSOP is good for picking out a product type value from nested json objects
The jread
memoize the keys path structure so jread f g
should be curried to repeat on multiple values. The Value
will be scanned only one time, despite the paths are always expressed from the root. Order is restored by a final lookup.
Example
Preamble
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
import Data.Aeson
import Data.Aeson.Lens
import Data.String.Interpolate
import qualified Data.Text as T
import Generics.SOP
import Generics.SOP.TH
import JSOP.Parse
import Protolude hiding (All, optional, (:*:))
import Data.Maybe (fromJust)
Given we have a SOP encoding of the record (tuples are good).
data ABC = ABC Text Int Int deriving (Show, Eq)
deriveGeneric ''ABC
Then we need a product of pickers with the same shape as our product type.
In this case I choose to encode paths joining json keys with /
cherryPickABC :: NP (Parser Text) '[Text, Int, Int]
cherryPickABC =
required "object 1 / a string" _String
:* required "object 2 / a number" _Integral
:* optional "object 4 / a number" 42 _Integral
:* Nil
Given the next json structure
jsonWithABC :: Value
jsonWithABC = fromJust . decode $ [i|
{
"object 1":
{ "a string": "ciao"
, "ignore me" : 34
}
, "object 2":
{ "a number": 2
, "object 3": {}
}
, "object 4": {
"a plumber" :43
}
}
|]
We can cherry pick the scattered ABC
with
abc :: ABC
Right abc = jread (T.splitOn " / ") cherryPickABC jsonWithAB
We can also rewrite an ABC value in the json
Writing optionals has an ad-hoc defined behaviour, in general writing is still to be thought in case of missing keys
jsonABC :: Value
jsonABC = jwrite (T.splitOn " / ") cherryPickABC jsonWithABC (ABC "mamma" 44 103)