{-# LANGUAGE BlockArguments #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications, QuasiQuotes #-} module Write 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, it, shouldBe, describe) import Data.String.Interpolate import Protolude.Partial (fromJust) decodeU :: Text -> Value decodeU = fromJust . decode . toUtf8Lazy spec_write :: Spec spec_write = do describe "jsop" do it "can write an Int in an object" $ shouldBe do jwrite do T.splitOn " / " do required "a number" _Integral :* Nil do object ["a number" .= Number 0] do Identity (2 :: Int) do object ["a number" .= Number 2] it "can write an Int in an nested object" $ shouldBe do jwrite do T.splitOn " / " do required "object / a number" _Integral :* Nil do object [ "object" .= object ["a number" .= Number 0] ] do Identity (2 :: Int) do object [ "object" .= object ["a number" .= Number 2] ] it "can write String and Integer" $ shouldBe do jwrite do T.splitOn " / " do required "a string" _String :* required "a number" _Integral :* Nil do object [ "a number" .= Number 0 , "a string" .= ("mamma" :: Text) ] do ("ciao", 2 :: Int) do object [ "a number" .= Number 2 , "a string" .= ("ciao" :: Text) ] it "can write String and Int and Optional Int down different paths" $ shouldBe do jwrite 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": "mamma" , "ignore me" : 34 } , "object 2": { "a number": 0 , "object 3": {} } , "object 4": { "a plumber" :43 } } |] do ("ciao", 2 :: Int, 42 :: Int ) do decodeU [i| { "object 1": { "a string": "ciao" , "ignore me" : 34 } , "object 2": { "a number": 2 , "object 3": {} } , "object 4": { "a plumber" :43 , "a number" :42 } } |] it "can write String and Int and Optional Int down different paths in emptyness" $ shouldBe do jwrite 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| { } |] do ("ciao", 2 :: Int, 42 :: Int ) do decodeU [i| { "object 1": { "a string": null } , "object 2": { "a number": null } , "object 4": { "a number" :42 } } |]