Skip to content

Commit a09ecee

Browse files
committed
Address PR feedback.
1 parent e8d263d commit a09ecee

File tree

6 files changed

+33
-13
lines changed

6 files changed

+33
-13
lines changed

Data/Aeson.hs

Lines changed: 1 addition & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,3 @@
1-
{-# LANGUAGE CPP #-}
2-
31
-- |
42
-- Module: Data.Aeson
53
-- Copyright: (c) 2011-2016 Bryan O'Sullivan
@@ -113,6 +111,7 @@ module Data.Aeson
113111
, withNumber
114112
, withScientific
115113
, withBool
114+
, withEmbeddedJSON
116115
-- * Constructors and accessors
117116
, Series
118117
, pairs
@@ -122,7 +121,6 @@ module Data.Aeson
122121
, (.:!)
123122
, (.!=)
124123
, object
125-
, embeddedJSON
126124
-- * Parsing
127125
, json
128126
, json'
@@ -138,7 +136,6 @@ import Data.Aeson.Types
138136
import Data.Aeson.Types.Internal (JSONPath, formatError)
139137
import qualified Data.ByteString as B
140138
import qualified Data.ByteString.Lazy as L
141-
import qualified Data.Text.Encoding as T
142139

143140
-- | Efficiently serialize a JSON value as a lazy 'L.ByteString'.
144141
--
@@ -224,15 +221,6 @@ eitherDecodeStrict' =
224221
eitherFormatError . eitherDecodeStrictWith jsonEOF' ifromJSON
225222
{-# INLINE eitherDecodeStrict' #-}
226223

227-
-- | Decode a nested JSON-encoded string.
228-
embeddedJSON :: (FromJSON a) => String -> (Value -> Parser a)
229-
embeddedJSON str = withText str (either fail return . eitherDecode . fromStrict . T.encodeUtf8)
230-
where
231-
#if MIN_VERSION_bytestring(0, 9, 2)
232-
fromStrict = L.fromChunks . (:[])
233-
#else
234-
fromStrict = L.fromStrict
235-
#endif
236224
-- $use
237225
--
238226
-- This section contains basic information on the different ways to

Data/Aeson/Compat.hs

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,16 @@
1+
{-# LANGUAGE CPP #-}
2+
3+
module Data.Aeson.Compat
4+
(
5+
fromStrict
6+
) where
7+
8+
import qualified Data.ByteString as S
9+
import qualified Data.ByteString.Lazy as L
10+
11+
fromStrict :: S.ByteString -> L.ByteString
12+
#if MIN_VERSION_bytestring(0, 9, 2)
13+
fromStrict = L.fromChunks . (:[])
14+
#else
15+
fromStrict = L.fromStrict
16+
#endif

Data/Aeson/Types.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -84,6 +84,7 @@ module Data.Aeson.Types
8484
, withNumber
8585
, withScientific
8686
, withBool
87+
, withEmbeddedJSON
8788

8889
, pairs
8990
, foldable

Data/Aeson/Types/Class.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -73,6 +73,7 @@ module Data.Aeson.Types.Class
7373
, withNumber
7474
, withScientific
7575
, withBool
76+
, withEmbeddedJSON
7677

7778
-- * Functions
7879
, fromJSON

Data/Aeson/Types/FromJSON.hs

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,7 @@ module Data.Aeson.Types.FromJSON
5555
, withNumber
5656
, withScientific
5757
, withBool
58+
, withEmbeddedJSON
5859

5960
-- * Functions
6061
, fromJSON
@@ -82,6 +83,7 @@ import Prelude.Compat
8283
import Control.Applicative ((<|>), Const(..))
8384
import Control.Monad ((<=<), zipWithM)
8485
import Data.Aeson.Internal.Functions (mapKey)
86+
import Data.Aeson.Parser.Internal (eitherDecodeWith, jsonEOF)
8587
import Data.Aeson.Types.Generic
8688
import Data.Aeson.Types.Internal
8789
import Data.Attoparsec.Number (Number(..))
@@ -114,6 +116,7 @@ import GHC.Generics
114116
import Numeric.Natural (Natural)
115117
import Text.ParserCombinators.ReadP (readP_to_S)
116118
import Unsafe.Coerce (unsafeCoerce)
119+
import qualified Data.Aeson.Compat as Compat
117120
import qualified Data.Aeson.Parser.Time as Time
118121
import qualified Data.Attoparsec.ByteString.Char8 as A (endOfInput, parseOnly, scientific)
119122
import qualified Data.DList as DList
@@ -665,6 +668,16 @@ withBool _ f (Bool arr) = f arr
665668
withBool expected _ v = typeMismatch expected v
666669
{-# INLINE withBool #-}
667670

671+
-- | Decode a nested JSON-encoded string.
672+
withEmbeddedJSON :: (FromJSON a) => String -> (Value -> Parser a) -> Value -> Parser a
673+
withEmbeddedJSON _ innerParser (String txt) =
674+
either fail innerParser $ eitherDecode (Compat.fromStrict $ T.encodeUtf8 txt)
675+
where
676+
eitherDecode = eitherFormatError . eitherDecodeWith jsonEOF ifromJSON
677+
eitherFormatError = either (Left . uncurry formatError) Right
678+
withEmbeddedJSON name _ v = typeMismatch name v
679+
{-# INLINE withEmbeddedJSON #-}
680+
668681
-- | Convert a value from JSON, failing if the types do not match.
669682
fromJSON :: (FromJSON a) => Value -> Result a
670683
fromJSON = parse parseJSON

aeson.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -100,6 +100,7 @@ library
100100
Data.Aeson.Encode
101101

102102
other-modules:
103+
Data.Aeson.Compat
103104
Data.Aeson.Encoding.Builder
104105
Data.Aeson.Internal.Functions
105106
Data.Aeson.Parser.Unescape

0 commit comments

Comments
 (0)