Skip to content

Commit

Permalink
Add (.:!) and partially revert d0414be
Browse files Browse the repository at this point in the history
  • Loading branch information
phadej committed Sep 19, 2015
1 parent a04c627 commit 1df7cad
Show file tree
Hide file tree
Showing 5 changed files with 18 additions and 6 deletions.
1 change: 1 addition & 0 deletions Data/Aeson.hs
Original file line number Diff line number Diff line change
Expand Up @@ -78,6 +78,7 @@ module Data.Aeson
, foldable
, (.:)
, (.:?)
, (.:!)
, (.!=)
, object
-- * Parsing
Expand Down
3 changes: 1 addition & 2 deletions Data/Aeson/TH.hs
Original file line number Diff line number Diff line change
Expand Up @@ -100,7 +100,6 @@ import Data.Aeson.Types ( Value(..), Parser
, defaultTaggedObject
)
import Data.Aeson.Types.Internal (Encoding(..))
import Control.Monad ( return, mapM, liftM2, fail, join )
import Data.Bool ( Bool(False, True), otherwise, (&&), not )
import Data.Either ( Either(Left, Right) )
import Data.Eq ( (==) )
Expand Down Expand Up @@ -954,7 +953,7 @@ instance (FromJSON a) => LookupField a where
Just v -> parseJSON v

instance (FromJSON a) => LookupField (Maybe a) where
lookupField _ _ obj key = join <$> obj .:? key
lookupField _ _ = (.:?)

unknownFieldFail :: String -> String -> String -> Parser fail
unknownFieldFail tName rec key =
Expand Down
1 change: 1 addition & 0 deletions Data/Aeson/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,6 +55,7 @@ module Data.Aeson.Types
, foldable
, (.:)
, (.:?)
, (.:!)
, (.!=)
, object

Expand Down
6 changes: 3 additions & 3 deletions Data/Aeson/Types/Generic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@
module Data.Aeson.Types.Generic ( ) where

import Control.Applicative ((<*>), (<$>), (<|>), pure)
import Control.Monad ((<=<), join)
import Control.Monad ((<=<))
import Control.Monad.ST (ST)
import Data.Aeson.Encode.Builder (emptyArray_)
import Data.Aeson.Encode.Functions (builder)
Expand Down Expand Up @@ -656,8 +656,8 @@ instance (Selector s, GFromJSON a) => FromRecord (S1 s a) where
{-# INLINE parseRecord #-}

instance (Selector s, FromJSON a) => FromRecord (S1 s (K1 i (Maybe a))) where
parseRecord _ (Just lab) obj = (M1 . K1) . join <$> obj .:? lab
parseRecord opts Nothing obj = (M1 . K1) . join <$> obj .:? pack label
parseRecord _ (Just lab) obj = (M1 . K1) <$> obj .:? lab
parseRecord opts Nothing obj = (M1 . K1) <$> obj .:? pack label
where
label = fieldLabelModifier opts $
selName (undefined :: t s (K1 i (Maybe a)) p)
Expand Down
13 changes: 12 additions & 1 deletion Data/Aeson/Types/Instances.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,7 @@ module Data.Aeson.Types.Instances
, ifromJSON
, (.:)
, (.:?)
, (.:!)
, (.!=)
, tuple
, (>*<)
Expand Down Expand Up @@ -1544,11 +1545,21 @@ obj .: key = case H.lookup key obj of
obj .:? key = case H.lookup key obj of
Nothing -> pure Nothing
Just v -> modifyFailure addKeyName
$ Just <$> parseJSON v <?> Key key
$ parseJSON v <?> Key key
where
addKeyName = (("failed to parse field " <> unpack key <> ": ") <>)
{-# INLINE (.:?) #-}

-- | Like `(.:?)` but fail if the key is present but is 'Null'.
(.:!) :: (FromJSON a) => Object -> Text -> Parser (Maybe a)
obj .:! key = case H.lookup key obj of
Nothing -> pure Nothing
Just v -> modifyFailure addKeyName
$ Just <$> parseJSON v <?> Key key
where
addKeyName = (("failed to parse field " <> unpack key <> ": ") <>)
{-# INLINE (.:??) #-}

-- | Helper for use in combination with '.:?' to provide default
-- values for optional JSON object fields.
--
Expand Down

0 comments on commit 1df7cad

Please sign in to comment.