Skip to content

Commit

Permalink
make tests compatible with hashable 1.3.1.0 (turboMaCk#26)
Browse files Browse the repository at this point in the history
* make tests compatible with hashable 1.3.1.0

see: commercialhaskell/stackage#5878

* update release info
  • Loading branch information
turboMaCk authored and fendor committed Mar 19, 2022
1 parent 8ba3814 commit b5a3965
Show file tree
Hide file tree
Showing 7 changed files with 70 additions and 14 deletions.
3 changes: 3 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,8 @@
# Revision history for aeson-combinators

## 0.0.5.0 -- 2021-03-13
* make test suite compatible with hashable 1.3.1.0

## 0.0.4.1 -- 2021-02-14
* Cleanup README
* CI maintanance & GHC compatibility update
Expand Down
4 changes: 2 additions & 2 deletions aeson-combinators.cabal
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
cabal-version: >=1.10
name: aeson-combinators
version: 0.0.4.1
version: 0.0.5.0
synopsis: Aeson combinators for dead simple JSON decoding
description:
Low overhead value space `Decoder`
Expand Down Expand Up @@ -33,7 +33,7 @@ Flag doctest
library
exposed-modules: Data.Aeson.Combinators.Decode
, Data.Aeson.Combinators.Encode
-- other-modules:
other-modules: Data.Aeson.Combinators.Compat
-- other-extensions:
build-depends: base >= 4 && < 5
, bytestring
Expand Down
36 changes: 36 additions & 0 deletions lib/Data/Aeson/Combinators/Compat.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,36 @@
{-# LANGUAGE CPP #-}

module Data.Aeson.Combinators.Compat (
-- * Re-exposes compatibility functions for aeson-2

-- * Backwards compatibility with KeyMap
KeyMap
, toHashMapText
-- * Backwards compatibility with KeyMap
, Key
, toText, fromText
) where

#if (MIN_VERSION_aeson(2,0,0))
import Data.Aeson.Key (Key, toText, fromText)
import Data.Aeson.KeyMap (KeyMap)
import Data.Aeson.KeyMap (toHashMapText)
#else
import qualified Data.HashMap as HM
import Data.Text (Text)


type KeyMap a = HM.HashMap Text a
type Key = Text

-- | Aeson 2.0 compatibility function for the 'Key' type.
fromText :: Text -> Text
fromText = id

-- | Aeson 2.0 compatibility function for the 'Key' type.
toText :: Text -> Text
toText = id

toHashMapText :: HL.HashMap Text a -> HL.HashMap Text a
toHashMapText = id
#endif
22 changes: 16 additions & 6 deletions lib/Data/Aeson/Combinators/Decode.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,8 +32,8 @@ module Data.Aeson.Combinators.Decode (
, nullable
-- *** Sequences
, list, vector
-- *** Hashmap
, hashMapLazy, hashMapStrict
-- *** Hashmap and Map
, hashMapLazy, hashMapStrict, keyMap
-- *** Map
, mapLazy, mapStrict
-- * Combinators
Expand Down Expand Up @@ -88,6 +88,8 @@ module Data.Aeson.Combinators.Decode (
-- * Parsing (Running Decoders)
, parseMaybe
, parseEither
-- * Re-expose aeson internals we depend on
, module Data.Aeson.Combinators.Compat
) where

import Prelude hiding (either, fail, maybe)
Expand All @@ -98,6 +100,7 @@ import Control.Monad hiding (void)
import Control.Monad.Fail (MonadFail (..))
import qualified Control.Monad.Fail as Fail

import Data.Aeson.Combinators.Compat
import Data.Aeson.Internal (JSONPath, JSONPathElement (..))
import qualified Data.Aeson.Internal as AI
import qualified Data.Aeson.Parser as Parser
Expand Down Expand Up @@ -346,7 +349,7 @@ vector (Decoder d) = Decoder $ \case
-- using provided 'Decoder'.
hashMapLazy :: Decoder a -> Decoder (HL.HashMap Text a)
hashMapLazy (Decoder d) = Decoder $ \case
Object xs -> traverse d xs
Object xs -> toHashMapText <$> traverse d xs
val -> typeMismatch "Array" val
{-# INLINE hashMapLazy #-}

Expand All @@ -355,10 +358,17 @@ hashMapLazy (Decoder d) = Decoder $ \case
-- using provided 'Decoder'.
hashMapStrict :: Decoder a -> Decoder (HS.HashMap Text a)
hashMapStrict (Decoder d) = Decoder $ \case
Object xs -> traverse d xs
Object xs -> toHashMapText <$> traverse d xs
val -> typeMismatch "Array" val
{-# INLINE hashMapStrict #-}

-- | Decode JSON object to 'KeyMap' with 'Key' key
-- using provided 'Decoder'.
keyMap :: Decoder a -> Decoder (KeyMap a)
keyMap (Decoder d) = Decoder $ \case
Object xs -> traverse d xs
val -> typeMismatch "Array" val
{-# INLINE keyMap #-}

-- | Decode JSON object to 'ML.Map' with 'Data.Text' key
-- using provided 'Decoder'.
Expand Down Expand Up @@ -399,7 +409,7 @@ jsonNull a = Decoder $ \case
--
-- >>> decode (key "data" int) "{\"data\": 42}"
-- Just 42
key :: Text -> Decoder a -> Decoder a
key :: Key -> Decoder a -> Decoder a
key t (Decoder d) = Decoder $ \case
Object v -> d =<< v .: t
val -> typeMismatch "Object" val
Expand All @@ -410,7 +420,7 @@ key t (Decoder d) = Decoder $ \case
--
-- >>> decode (at ["data", "value"] int) "{\"data\": {\"value\": 42}}"
-- Just 42
at :: [Text] -> Decoder a -> Decoder a
at :: [Key] -> Decoder a -> Decoder a
at pth d = foldr key d pth
{-# INLINE at #-}

Expand Down
7 changes: 5 additions & 2 deletions lib/Data/Aeson/Combinators/Encode.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,6 +71,8 @@ module Data.Aeson.Combinators.Encode (
-- * Evaluating Encoders
, encode
, toEncoding
-- * Re-expose aeson internals we depend on
, module Data.Aeson.Combinators.Compat
) where

import Control.Applicative
Expand All @@ -79,6 +81,7 @@ import Data.Functor.Contravariant

import Data.Aeson (ToJSON, Value (..))
import qualified Data.Aeson as Aeson
import Data.Aeson.Combinators.Compat
import qualified Data.Aeson.Encoding as E
import Data.Aeson.Types (Pair)
import qualified Data.ByteString.Lazy as BS
Expand Down Expand Up @@ -285,7 +288,7 @@ object xs = Encoder $ \val -> Aeson.object $ fmap (\f -> f val) xs


{-| Define object field -}
field :: Text -> Encoder b -> (a -> b) -> KeyValueEncoder a
field :: Key -> Encoder b -> (a -> b) -> KeyValueEncoder a
field name (Encoder enc) get v = (name, enc $ get v)
{-# INLINE field #-}

Expand Down Expand Up @@ -322,7 +325,7 @@ object' f = Encoder $ \val -> Aeson.object $ f val


{-| Define object field (alternative) -}
field' :: Text -> Encoder a -> a -> (Text, Value)
field' :: Key -> Encoder a -> a -> (Key, Value)
field' name (Encoder enc) val = (name, enc val)
{-# INLINE field' #-}

Expand Down
1 change: 0 additions & 1 deletion test/JSONDecodeSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,6 @@ import qualified Data.Aeson.Combinators.Decode as JD
import Data.Aeson.Types (FromJSON (..))
import Data.ByteString.Lazy
import Data.ByteString.Lazy.UTF8 (fromString)
import Data.Monoid ((<>))
import Data.Text
import GHC.Generics
import Test.Hspec
Expand Down
11 changes: 8 additions & 3 deletions test/JSONEncodeSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,14 +37,19 @@ encodePrimitives = describe "primitives" $ do
objectEncoding :: Spec
objectEncoding = do
let object = Object "Joe" 30
let json = "{\"age\":30,\"name\":\"Joe\"}"

-- poor man's workaround for key ordering
-- see: https://github.com/haskell/aeson/issues/837
let json res =
res == "{\"age\":30,\"name\":\"Joe\"}"
|| res == "{\"name\":\"Joe\",\"age\":30}"

describe "object encoding" $ do
it "should encode using getter style encoding" $ do
JE.encode objectEncoder object `shouldBe` json
JE.encode objectEncoder object `shouldSatisfy` json

it "should encode using explicit style encoding" $ do
JE.encode objectEncoder' object `shouldBe` json
JE.encode objectEncoder' object `shouldSatisfy` json


listSpec :: Spec
Expand Down

0 comments on commit b5a3965

Please sign in to comment.