{-# LANGUAGE BlockArguments #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications, QuasiQuotes #-} module Read where import Data.Aeson import Data.Aeson.Lens import qualified Data.Text as T import Generics.SOP import Data.JSOP import Protolude hiding (All, optional, (:*:)) import Test.Tasty.Hspec (Spec, describe, it, shouldBe) import Data.Maybe (fromJust) import Data.String.Interpolate decodeU :: Text -> Value decodeU = fromJust . decode . toUtf8Lazy spec_generic :: Spec spec_generic = do describe "jsop" do it "can read an Int in an object" $ shouldBe do jread do T.splitOn " / " do required "a number" _Integral :* Nil do object ["a number" .= Number 2] do Right (Identity (2 :: Int)) it "can read an Int in an nested object" $ shouldBe do jread do T.splitOn " / " do required "object / a number" _Integral :* Nil do object [ "object" .= object ["a number" .= Number 2] ] do Right (Identity (2 :: Int)) it "can read String and Integer" $ shouldBe do jread do T.splitOn " / " do required "a string" _String :* required "a number" _Integral :* Nil do object [ "a number" .= Number 2 , "a string" .= ("ciao" :: Text) ] do Right ("ciao", 2 :: Int) it "can read String and Int down different paths" $ shouldBe do jread do T.splitOn " / " do required "object 1 / a string" _String :* required "object 2 / a number" _Integral :* Nil do decodeU [i| { "object 1": { "a string": "ciao" , "ignore me" : 34 } , "object 2": { "a number": 2 , "object 3": {} } } |] do Right ("ciao", 2 :: Int) it "can read String and Int and Optional Int down different paths" $ shouldBe do jread do T.splitOn " / " do required "object 1 / a string" _String :* required "object 2 / a number" _Integral :* optional "object 4 / a number" 42 _Integral :* Nil do decodeU [i| { "object 1": { "a string": "ciao" , "ignore me" : 34 } , "object 2": { "a number": 2 , "object 3": {} } , "object 4": { "a plumber" :43 } } |] do Right ("ciao", 2 :: Int, 42 :: Int )