Skip to content

Commit 2f8ed86

Browse files
friedbricephadej
authored andcommitted
Type-directed optional fields
* Adds 'omitField' to 'ToJSON' * Adds 'omittedField' to 'FromJSON'
1 parent 5a7767c commit 2f8ed86

File tree

12 files changed

+419
-175
lines changed

12 files changed

+419
-175
lines changed

aeson.cabal

+4
Original file line numberDiff line numberDiff line change
@@ -174,6 +174,10 @@ test-suite aeson-tests
174174
UnitTests.KeyMapInsertWith
175175
UnitTests.MonadFix
176176
UnitTests.NullaryConstructors
177+
UnitTests.OptionalFields
178+
UnitTests.OptionalFields.Common
179+
UnitTests.OptionalFields.Generics
180+
UnitTests.OptionalFields.TH
177181
UnitTests.UTCTime
178182

179183
build-depends:

src/Data/Aeson/TH.hs

+28-70
Original file line numberDiff line numberDiff line change
@@ -114,11 +114,11 @@ module Data.Aeson.TH
114114

115115
import Data.Aeson.Internal.Prelude
116116

117+
import Data.Bool (bool)
117118
import Data.Char (ord)
118119
import Data.Aeson (Object, (.:), FromJSON(..), FromJSON1(..), FromJSON2(..), ToJSON(..), ToJSON1(..), ToJSON2(..))
119120
import Data.Aeson.Types (Options(..), Parser, SumEncoding(..), Value(..), defaultOptions, defaultTaggedObject)
120121
import Data.Aeson.Types.Internal ((<?>), JSONPathElement(Key))
121-
import Data.Aeson.Types.FromJSON (parseOptionalFieldWith)
122122
import Data.Aeson.Types.ToJSON (fromPairs, pair)
123123
import Data.Aeson.Key (Key)
124124
import qualified Data.Aeson.Key as Key
@@ -135,9 +135,6 @@ import Text.Printf (printf)
135135
import qualified Data.Aeson.Encoding.Internal as E
136136
import qualified Data.List.NonEmpty as NE (length, reverse)
137137
import qualified Data.Map as M (fromList, keys, lookup , singleton, size)
138-
#if !MIN_VERSION_base(4,16,0)
139-
import qualified Data.Semigroup as Semigroup (Option(..))
140-
#endif
141138
import qualified Data.Set as Set (empty, insert, member)
142139
import qualified Data.Text as T (pack, unpack)
143140
import qualified Data.Vector as V (unsafeIndex, null, length, create, empty)
@@ -456,40 +453,24 @@ argsToValue letInsert target jc tvMap opts multiCons
456453
(True,True,[_]) -> argsToValue letInsert target jc tvMap opts multiCons
457454
(info{constructorVariant = NormalConstructor})
458455
_ -> do
456+
459457
argTys' <- mapM resolveTypeSynonyms argTys
460458
args <- newNameList "arg" $ length argTys'
461-
let pairs | omitNothingFields opts = infixApp maybeFields
462-
[|(Monoid.<>)|]
463-
restFields
464-
| otherwise = mconcatE (map pureToPair argCons)
465-
466-
argCons = zip3 (map varE args) argTys' fields
467-
468-
maybeFields = mconcatE (map maybeToPair maybes)
469-
470-
restFields = mconcatE (map pureToPair rest)
471-
472-
(maybes0, rest0) = partition isMaybe argCons
473-
#if MIN_VERSION_base(4,16,0)
474-
maybes = maybes0
475-
rest = rest0
476-
#else
477-
(options, rest) = partition isOption rest0
478-
maybes = maybes0 ++ map optionToMaybe options
479-
#endif
480-
481-
maybeToPair = toPairLifted True
482-
pureToPair = toPairLifted False
483-
484-
toPairLifted lifted (arg, argTy, field) =
485-
let toValue = dispatchToJSON target jc conName tvMap argTy
486-
fieldName = fieldLabel opts field
487-
e arg' = pairE letInsert target fieldName (toValue `appE` arg')
488-
in if lifted
489-
then do
490-
x <- newName "x"
491-
[|maybe mempty|] `appE` lam1E (varP x) (e (varE x)) `appE` arg
492-
else e arg
459+
let argCons = zip3 (map varE args) argTys' fields
460+
461+
toPair (arg, argTy, fld) =
462+
let fieldName = fieldLabel opts fld
463+
toValue = dispatchToJSON target jc conName tvMap argTy
464+
omitFn
465+
| omitNothingFields opts = [| omitField |]
466+
| otherwise = [| const False |]
467+
in
468+
[| \f x arg' -> bool x mempty (f arg') |]
469+
`appE` omitFn
470+
`appE` pairE letInsert target fieldName (toValue `appE` arg)
471+
`appE` arg
472+
473+
pairs = mconcatE (map toPair argCons)
493474

494475
match (conP conName $ map varP args)
495476
(normalB $ recordSumToValue letInsert target opts multiCons (null argTys) conName pairs)
@@ -514,19 +495,6 @@ argsToValue letInsert target jc tvMap opts multiCons
514495
)
515496
[]
516497

517-
isMaybe :: (a, Type, b) -> Bool
518-
isMaybe (_, AppT (ConT t) _, _) = t == ''Maybe
519-
isMaybe _ = False
520-
521-
#if !MIN_VERSION_base(4,16,0)
522-
isOption :: (a, Type, b) -> Bool
523-
isOption (_, AppT (ConT t) _, _) = t == ''Semigroup.Option
524-
isOption _ = False
525-
526-
optionToMaybe :: (ExpQ, b, c) -> (ExpQ, b, c)
527-
optionToMaybe (a, b, c) = ([|Semigroup.getOption|] `appE` a, b, c)
528-
#endif
529-
530498
(<^>) :: ExpQ -> ExpQ -> ExpQ
531499
(<^>) a b = infixApp a [|(E.><)|] b
532500
infixr 6 <^>
@@ -953,6 +921,9 @@ parseRecord jc tvMap argTys opts tName conName fields obj inTaggedObject =
953921
(infixApp (conE conName) [|(<$>)|] x)
954922
xs
955923
where
924+
defVal = case jc of
925+
JSONClass From Arity0 -> [|omittedField|]
926+
_ -> [|Nothing|]
956927
tagFieldNameAppender =
957928
if inTaggedObject then (tagFieldName (sumEncoding opts) :) else id
958929
knownFields = appE [|KM.fromList|] $ listE $
@@ -970,6 +941,7 @@ parseRecord jc tvMap argTys opts tName conName fields obj inTaggedObject =
970941
[]
971942
]
972943
x:xs = [ [|lookupField|]
944+
`appE` defVal
973945
`appE` dispatchParseJSON jc conName tvMap argTy
974946
`appE` litE (stringL $ show tName)
975947
`appE` litE (stringL $ constructorTagModifier opts $ nameBase conName)
@@ -1137,28 +1109,14 @@ parseTypeMismatch tName conName expected actual =
11371109
, actual
11381110
]
11391111

1140-
class LookupField a where
1141-
lookupField :: (Value -> Parser a) -> String -> String
1142-
-> Object -> Key -> Parser a
1143-
1144-
instance {-# OVERLAPPABLE #-} LookupField a where
1145-
lookupField = lookupFieldWith
1146-
1147-
instance {-# INCOHERENT #-} LookupField (Maybe a) where
1148-
lookupField pj _ _ = parseOptionalFieldWith pj
1149-
1150-
#if !MIN_VERSION_base(4,16,0)
1151-
instance {-# INCOHERENT #-} LookupField (Semigroup.Option a) where
1152-
lookupField pj tName rec obj key =
1153-
fmap Semigroup.Option
1154-
(lookupField (fmap Semigroup.getOption . pj) tName rec obj key)
1155-
#endif
1156-
1157-
lookupFieldWith :: (Value -> Parser a) -> String -> String
1158-
-> Object -> Key -> Parser a
1159-
lookupFieldWith pj tName rec obj key =
1112+
lookupField :: Maybe a -> (Value -> Parser a) -> String -> String
1113+
-> Object -> Key -> Parser a
1114+
lookupField maybeDefault pj tName rec obj key =
11601115
case KM.lookup key obj of
1161-
Nothing -> unknownFieldFail tName rec (Key.toString key)
1116+
Nothing ->
1117+
case maybeDefault of
1118+
Nothing -> unknownFieldFail tName rec (Key.toString key)
1119+
Just x -> pure x
11621120
Just v -> pj v <?> Key key
11631121

11641122
unknownFieldFail :: String -> String -> String -> Parser fail

src/Data/Aeson/Types/FromJSON.hs

+64-25
Original file line numberDiff line numberDiff line change
@@ -70,7 +70,6 @@ module Data.Aeson.Types.FromJSON
7070
, (.:?)
7171
, (.:!)
7272
, (.!=)
73-
7473
-- * Internal
7574
, parseOptionalFieldWith
7675
) where
@@ -379,6 +378,33 @@ class FromJSON a where
379378
. V.toList
380379
$ a
381380

381+
-- | Default value for optional fields.
382+
--
383+
-- Defining @omittedField = 'Just' x@ makes object fields of this type optional.
384+
-- When the field is omitted, the default value @x@ will be used.
385+
--
386+
-- @
387+
-- newtype A = A Int deriving (Generic)
388+
-- instance FromJSON A where omittedField = Just (A 0)
389+
--
390+
-- data R = R { a :: A, b :: Int } deriving ('Generic', 'FromJSON')
391+
--
392+
-- decode "{\"b\":1}" -- Just (R (A 0) 1)
393+
-- @
394+
--
395+
-- Defining @omittedField = 'Nothing'@ makes object fields of this type required.
396+
--
397+
-- @
398+
-- omittedField :: Maybe Int -- Nothing
399+
-- decode "{\"a\":1}" -- Nothing
400+
-- @
401+
--
402+
-- The default implementation is @omittedField = Nothing@.
403+
--
404+
-- @since x.x.x.x
405+
omittedField :: Maybe a
406+
omittedField = Nothing
407+
382408
-- | @since 2.1.0.0
383409
instance (Generic a, GFromJSON Zero (Rep a)) => FromJSON (Generically a) where
384410
parseJSON = coerce (genericParseJSON defaultOptions :: Value -> Parser a)
@@ -1336,34 +1362,46 @@ instance ( RecordFromJSON' arity a
13361362
<*> recordParseJSON' p obj
13371363
{-# INLINE recordParseJSON' #-}
13381364

1339-
instance {-# OVERLAPPABLE #-} (Selector s, GFromJSON arity a) =>
1340-
RecordFromJSON' arity (S1 s a) where
1341-
recordParseJSON' (cname :* tname :* opts :* fargs) obj = do
1342-
fv <- contextCons cname tname (obj .: label)
1343-
M1 <$> gParseJSON opts fargs fv <?> Key label
1344-
where
1345-
label = Key.fromString $ fieldLabelModifier opts sname
1346-
sname = selName (undefined :: M1 _i s _f _p)
1365+
instance {-# OVERLAPPABLE #-}
1366+
RecordFromJSON' arity f => RecordFromJSON' arity (M1 i s f) where
1367+
recordParseJSON' args obj = M1 <$> recordParseJSON' args obj
13471368
{-# INLINE recordParseJSON' #-}
13481369

1349-
instance {-# INCOHERENT #-} (Selector s, FromJSON a) =>
1350-
RecordFromJSON' arity (S1 s (K1 i (Maybe a))) where
1351-
recordParseJSON' (_ :* _ :* opts :* _) obj = M1 . K1 <$> obj .:? label
1352-
where
1353-
label = Key.fromString $ fieldLabelModifier opts sname
1354-
sname = selName (undefined :: M1 _i s _f _p)
1370+
instance (Selector s, FromJSON a, Generic a, K1 i a ~ Rep a) =>
1371+
RecordFromJSON' arity (S1 s (K1 i a)) where
1372+
recordParseJSON' args obj =
1373+
recordParseJSONImpl (fmap K1 omittedField) gParseJSON args obj
13551374
{-# INLINE recordParseJSON' #-}
13561375

1357-
#if !MIN_VERSION_base(4,16,0)
1358-
-- Parse an Option like a Maybe.
1359-
instance {-# INCOHERENT #-} (Selector s, FromJSON a) =>
1360-
RecordFromJSON' arity (S1 s (K1 i (Semigroup.Option a))) where
1361-
recordParseJSON' p obj = wrap <$> recordParseJSON' p obj
1362-
where
1363-
wrap :: S1 s (K1 i (Maybe a)) p -> S1 s (K1 i (Semigroup.Option a)) p
1364-
wrap (M1 (K1 a)) = M1 (K1 (Semigroup.Option a))
1376+
instance {-# OVERLAPPING #-}
1377+
(Selector s, FromJSON a) =>
1378+
RecordFromJSON' arity (S1 s (Rec0 a)) where
1379+
recordParseJSON' args obj =
1380+
recordParseJSONImpl (fmap K1 omittedField) gParseJSON args obj
1381+
{-# INLINE recordParseJSON' #-}
1382+
1383+
instance (Selector s, GFromJSON arity (Rec1 f), FromJSON1 f) =>
1384+
RecordFromJSON' arity (S1 s (Rec1 f)) where
1385+
recordParseJSON' args obj = recordParseJSONImpl Nothing gParseJSON args obj
13651386
{-# INLINE recordParseJSON' #-}
1366-
#endif
1387+
1388+
recordParseJSONImpl :: forall s arity a f i
1389+
. (Selector s)
1390+
=> Maybe (f a)
1391+
-> (Options -> FromArgs arity a -> Value -> Parser (f a))
1392+
-> (ConName :* TypeName :* Options :* FromArgs arity a)
1393+
-> Object -> Parser (M1 i s f a)
1394+
recordParseJSONImpl mdef parseVal (cname :* tname :* opts :* fargs) obj =
1395+
handleMissingKey (M1 <$> mdef) $ do
1396+
fv <- contextCons cname tname (obj .: label)
1397+
M1 <$> parseVal opts fargs fv <?> Key label
1398+
where
1399+
handleMissingKey Nothing p = p
1400+
handleMissingKey (Just def) p = if label `KM.member` obj then p else pure def
1401+
1402+
label = Key.fromString $ fieldLabelModifier opts sname
1403+
sname = selName (undefined :: M1 _i s _f _p)
1404+
{-# INLINE recordParseJSONImpl #-}
13671405

13681406
--------------------------------------------------------------------------------
13691407

@@ -1507,7 +1545,7 @@ instance FromJSON1 Maybe where
15071545

15081546
instance (FromJSON a) => FromJSON (Maybe a) where
15091547
parseJSON = parseJSON1
1510-
1548+
omittedField = Just Nothing
15111549

15121550
instance FromJSON2 Either where
15131551
liftParseJSON2 pA _ pB _ (Object (KM.toList -> [(key, value)]))
@@ -2274,6 +2312,7 @@ instance FromJSON1 Semigroup.Option where
22742312

22752313
instance FromJSON a => FromJSON (Semigroup.Option a) where
22762314
parseJSON = parseJSON1
2315+
omittedField = Just (Semigroup.Option Nothing)
22772316
#endif
22782317

22792318
-------------------------------------------------------------------------------

0 commit comments

Comments
 (0)