Skip to content

Commit

Permalink
Merge pull request #1041 from haskell/issue-571
Browse files Browse the repository at this point in the history
Add a regression test for issue #571
  • Loading branch information
phadej committed Jun 13, 2023
2 parents e0737db + a88f701 commit 0b33f6f
Show file tree
Hide file tree
Showing 3 changed files with 26 additions and 0 deletions.
1 change: 1 addition & 0 deletions aeson.cabal
Expand Up @@ -163,6 +163,7 @@ test-suite aeson-tests
PropertyRTFunctors
PropertyTH
PropUtils
Regression.Issue571
Regression.Issue967
SerializationFormatSpec
Types
Expand Down
23 changes: 23 additions & 0 deletions tests/Regression/Issue571.hs
@@ -0,0 +1,23 @@
{-# LANGUAGE OverloadedStrings, DeriveGeneric #-}
module Regression.Issue571 (issue571) where

import Test.Tasty (TestTree)
import Test.Tasty.HUnit (testCase, (@?=))
import GHC.Generics (Generic)

import Data.Aeson

data F = F
{ a :: Maybe Int
, b :: Maybe Int
}
deriving (Eq, Show, Generic)

instance FromJSON F where
parseJSON = genericParseJSON defaultOptions { omitNothingFields = False } -- default

issue571 :: TestTree
issue571 = testCase "issue571" $ do
-- the Maybe fields can be omitted.
let actual = decode "{}" :: Maybe F
actual @?= Just F { a = Nothing, b = Nothing }
2 changes: 2 additions & 0 deletions tests/UnitTests.hs
Expand Up @@ -72,6 +72,7 @@ import qualified Data.Text.Lazy.Encoding as TLE
import qualified ErrorMessages
import qualified SerializationFormatSpec
import qualified Data.Map as Map -- Lazy!
import Regression.Issue571
import Regression.Issue967

roundTripCamel :: String -> Assertion
Expand Down Expand Up @@ -826,6 +827,7 @@ tests = testGroup "unit" [
assertEqual "" (object ["foo" .= True]) [aesonQQ| {"foo": true } |]
]
, monadFixTests
, issue571
, issue967
, testCase "KeyMap.insertWith" $ do
KM.insertWith (-) "a" 2 (KM.fromList [("a", 1)]) @?= KM.fromList [("a",1 :: Int)]
Expand Down

0 comments on commit 0b33f6f

Please sign in to comment.