# jsop, JSON record cherry picker JSOP is good for picking out a product type value from nested json objects ## Example Preamble ```haskell {-# 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). The `jSOP` memoize the keys path structure so `jSOP 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. ```haskell 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 ` / ` ```haskell 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 ```haskell 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 ```haskell abc :: ABC Right abc = jSOP (T.splitOn " / ") cherryPickABC jsonWithAB ```