Skip to content

Instantly share code, notes, and snippets.

@srhb
Created September 14, 2018 09:25
Show Gist options
  • Save srhb/3c57f3298f655afd1743ae6e4e7b3548 to your computer and use it in GitHub Desktop.
Save srhb/3c57f3298f655afd1743ae6e4e7b3548 to your computer and use it in GitHub Desktop.
lens-aeson-lossy.hs:30:27: error:
• No instance for (Data.String.IsString
(Getting
(base-4.11.1.0:Data.Semigroup.Internal.Endo [a0]) Value a0))
arising from the literal ‘"mapset"’
(maybe you haven't applied a function to enough arguments?)
• In the second argument of ‘(^..)’, namely ‘"mapset"’
In the first argument of ‘(^@..)’, namely ‘o ^.. "mapset"’
In the second argument of ‘($)’, namely
‘o ^.. "mapset" ^@.. members . _JSON’
|
30 | $ M.fromList $ o ^.. "mapset" ^@.. members . _JSON
| ^^^^^^^^
lens-aeson-lossy.hs:30:41: error:
• Ambiguous type variable ‘a0’ arising from a use of ‘members’
prevents the constraint ‘(AsValue [a0])’ from being solved.
Probable fix: use a type annotation to specify what ‘a0’ should be.
These potential instance exist:
instance AsValue String -- Defined in ‘Data.Aeson.Lens’
• In the first argument of ‘(.)’, namely ‘members’
In the second argument of ‘(^@..)’, namely ‘members . _JSON’
In the second argument of ‘($)’, namely
‘o ^.. "mapset" ^@.. members . _JSON’
|
30 | $ M.fromList $ o ^.. "mapset" ^@.. members . _JSON
| ^^^^^^^
lens-aeson-lossy.hs:30:51: error:
• No instance for (ToJSON Val) arising from a use of ‘_JSON’
• In the second argument of ‘(.)’, namely ‘_JSON’
In the second argument of ‘(^@..)’, namely ‘members . _JSON’
In the second argument of ‘($)’, namely
‘o ^.. "mapset" ^@.. members . _JSON’
|
30 | $ M.fromList $ o ^.. "mapset" ^@.. members . _JSON
| ^^^^^
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
import Data.Aeson
import Data.Aeson.Lens
import qualified Data.Set as S
import qualified Data.Map as M
import Control.Lens hiding ((.=))
import GHC.Generics
import Test.Hspec
import Data.Text
data Key = Key1
deriving (Generic, Show, Eq, Ord)
instance FromJSON Key
instance FromJSONKey Key
data Val = Val1
deriving (Generic, Show, Eq, Ord)
instance FromJSON Val
data MapSet = MapSet { unMapSet :: M.Map Key (S.Set Val) }
deriving (Show, Eq)
instance FromJSON MapSet where
parseJSON o = pure $ MapSet
$ (undefined :: M.Map Text (S.Set Val) -> M.Map Key (S.Set Val))
$ M.fromList $ o ^.. "mapset" ^@.. members . _JSON
emptyOuter = "{}"
emptyInner = "{ \"mapset\": {} }"
wrongKey = "{ \"mapset\": { \"Key2\": [] } }"
emptyList = "{ \"mapset\": { \"Key1\": [] } }"
wrongVal = "{ \"mapset\": { \"Key1\": [ \"Val2\" ] } }"
rightVal = "{ \"mapset\": { \"Key1\": [ \"Val1\" ] } }"
shouldBe' a b = decode a `shouldBe` Just (MapSet b :: MapSet)
main = hspec $ do
describe "FromJSON MapSet" $ do
it "maps the empty outer object to the empty Map"
$ emptyOuter `shouldBe'` M.empty
it "maps the empty inner object to the empty Map"
$ emptyInner `shouldBe'` M.empty
it "discards non-existant Keys"
$ wrongKey `shouldBe'` M.empty
it "maps empty arrays to the empty Set"
$ emptyList `shouldBe'` M.fromList [(Key1, S.empty)]
it "discards non-existant Vals"
$ wrongVal `shouldBe'` M.fromList [(Key1, S.empty)]
it ("maps objects containing the key mapset containing objects "
++ "of Keys containing arrays of Vals to Map Key (Set Val)")
$ rightVal `shouldBe'` M.fromList [(Key1, S.fromList [Val1])]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment