Skip to content

Commit 0b33f6f

Browse files
authored
Merge pull request #1041 from haskell/issue-571
Add a regression test for issue #571
2 parents e0737db + a88f701 commit 0b33f6f

File tree

3 files changed

+26
-0
lines changed

3 files changed

+26
-0
lines changed

aeson.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -163,6 +163,7 @@ test-suite aeson-tests
163163
PropertyRTFunctors
164164
PropertyTH
165165
PropUtils
166+
Regression.Issue571
166167
Regression.Issue967
167168
SerializationFormatSpec
168169
Types

tests/Regression/Issue571.hs

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,23 @@
1+
{-# LANGUAGE OverloadedStrings, DeriveGeneric #-}
2+
module Regression.Issue571 (issue571) where
3+
4+
import Test.Tasty (TestTree)
5+
import Test.Tasty.HUnit (testCase, (@?=))
6+
import GHC.Generics (Generic)
7+
8+
import Data.Aeson
9+
10+
data F = F
11+
{ a :: Maybe Int
12+
, b :: Maybe Int
13+
}
14+
deriving (Eq, Show, Generic)
15+
16+
instance FromJSON F where
17+
parseJSON = genericParseJSON defaultOptions { omitNothingFields = False } -- default
18+
19+
issue571 :: TestTree
20+
issue571 = testCase "issue571" $ do
21+
-- the Maybe fields can be omitted.
22+
let actual = decode "{}" :: Maybe F
23+
actual @?= Just F { a = Nothing, b = Nothing }

tests/UnitTests.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -72,6 +72,7 @@ import qualified Data.Text.Lazy.Encoding as TLE
7272
import qualified ErrorMessages
7373
import qualified SerializationFormatSpec
7474
import qualified Data.Map as Map -- Lazy!
75+
import Regression.Issue571
7576
import Regression.Issue967
7677

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

0 commit comments

Comments
 (0)