@@ -52,7 +52,6 @@ module Data.Aeson.Types.FromJSON
52
52
, withObject
53
53
, withText
54
54
, withArray
55
- , withNumber
56
55
, withScientific
57
56
, withBool
58
57
, withEmbeddedJSON
@@ -86,7 +85,6 @@ import Data.Aeson.Internal.Functions (mapKey)
86
85
import Data.Aeson.Parser.Internal (eitherDecodeWith , jsonEOF )
87
86
import Data.Aeson.Types.Generic
88
87
import Data.Aeson.Types.Internal
89
- import Data.Attoparsec.Number (Number (.. ))
90
88
import Data.Bits (unsafeShiftR )
91
89
import Data.Fixed (Fixed , HasResolution )
92
90
import Data.Functor.Compose (Compose (.. ))
@@ -100,7 +98,7 @@ import Data.Maybe (fromMaybe)
100
98
import Data.Semigroup ((<>) )
101
99
import Data.Proxy (Proxy (.. ))
102
100
import Data.Ratio ((%) , Ratio )
103
- import Data.Scientific (Scientific )
101
+ import Data.Scientific (Scientific , base10Exponent )
104
102
import Data.Tagged (Tagged (.. ))
105
103
import Data.Text (Text , pack , unpack )
106
104
import Data.Time (Day , DiffTime , LocalTime , NominalDiffTime , TimeOfDay , UTCTime , ZonedTime )
@@ -173,15 +171,6 @@ parseIndexedJSONPair keyParser valParser idx value = p value <?> Index idx
173
171
parseJSONElemAtIndex :: (Value -> Parser a ) -> Int -> V. Vector Value -> Parser a
174
172
parseJSONElemAtIndex p idx ary = p (V. unsafeIndex ary idx) <?> Index idx
175
173
176
- scientificToNumber :: Scientific -> Number
177
- scientificToNumber s
178
- | e < 0 = D $ Scientific. toRealFloat s
179
- | otherwise = I $ c * 10 ^ e
180
- where
181
- e = Scientific. base10Exponent s
182
- c = Scientific. coefficient s
183
- {-# INLINE scientificToNumber #-}
184
-
185
174
parseRealFloat :: RealFloat a => String -> Value -> Parser a
186
175
parseRealFloat _ (Number s) = pure $ Scientific. toRealFloat s
187
176
parseRealFloat _ Null = pure (0 / 0 )
@@ -197,7 +186,7 @@ parseIntegralFromScientific expected s =
197
186
198
187
parseIntegral :: Integral a => String -> Value -> Parser a
199
188
parseIntegral expected =
200
- withScientific expected $ parseIntegralFromScientific expected
189
+ withBoundedScientific expected $ parseIntegralFromScientific expected
201
190
{-# INLINE parseIntegral #-}
202
191
203
192
parseBoundedIntegralFromScientific :: (Bounded a , Integral a ) => String -> Scientific -> Parser a
@@ -219,8 +208,13 @@ parseScientificText
219
208
. T. encodeUtf8
220
209
221
210
parseIntegralText :: Integral a => String -> Text -> Parser a
222
- parseIntegralText expected t =
223
- parseScientificText t >>= parseIntegralFromScientific expected
211
+ parseIntegralText expected t
212
+ = parseScientificText t
213
+ >>= rejectLargeExponent
214
+ >>= parseIntegralFromScientific expected
215
+ where
216
+ rejectLargeExponent :: Scientific -> Parser Scientific
217
+ rejectLargeExponent s = withBoundedScientific expected pure (Number s)
224
218
{-# INLINE parseIntegralText #-}
225
219
226
220
parseBoundedIntegralText :: (Bounded a , Integral a ) => String -> Text -> Parser a
@@ -646,21 +640,33 @@ withArray _ f (Array arr) = f arr
646
640
withArray expected _ v = typeMismatch expected v
647
641
{-# INLINE withArray #-}
648
642
649
- -- | @'withNumber' expected f value@ applies @f@ to the 'Number' when @value@
650
- -- is a 'Number' and fails using @'typeMismatch' expected@ otherwise.
651
- withNumber :: String -> (Number -> Parser a ) -> Value -> Parser a
652
- withNumber expected f = withScientific expected (f . scientificToNumber)
653
- {-# INLINE withNumber #-}
654
- {-# DEPRECATED withNumber "Use withScientific instead" #-}
655
-
656
643
-- | @'withScientific' expected f value@ applies @f@ to the 'Scientific' number
657
644
-- when @value@ is a 'Number' and fails using @'typeMismatch' expected@
658
645
-- otherwise.
646
+ -- .
647
+ -- /Warning/: If you are converting from a scientific to an unbounded
648
+ -- type such as 'Integer' you may want to add a restriction on the
649
+ -- size of the exponent (see 'withBoundedScientific') to prevent
650
+ -- malicious input from filling up the memory of the target system.
659
651
withScientific :: String -> (Scientific -> Parser a ) -> Value -> Parser a
660
652
withScientific _ f (Number scientific) = f scientific
661
653
withScientific expected _ v = typeMismatch expected v
662
654
{-# INLINE withScientific #-}
663
655
656
+ -- | @'withBoundedScientific' expected f value@ applies @f@ to the 'Scientific' number
657
+ -- when @value@ is a 'Number' and fails using @'typeMismatch' expected@
658
+ -- otherwise.
659
+ --
660
+ -- The conversion will also fail wyth a @'typeMismatch' if the
661
+ -- 'Scientific' exponent is larger than 1024.
662
+ withBoundedScientific :: String -> (Scientific -> Parser a ) -> Value -> Parser a
663
+ withBoundedScientific _ f v@ (Number scientific) =
664
+ if base10Exponent scientific > 1024
665
+ then typeMismatch " a number with exponent <= 1024" v
666
+ else f scientific
667
+ withBoundedScientific expected _ v = typeMismatch expected v
668
+ {-# INLINE withBoundedScientific #-}
669
+
664
670
-- | @'withBool' expected f value@ applies @f@ to the 'Bool' when @value@ is a
665
671
-- 'Bool' and fails using @'typeMismatch' expected@ otherwise.
666
672
withBool :: String -> (Bool -> Parser a ) -> Value -> Parser a
@@ -1240,12 +1246,6 @@ instance FromJSONKey Double where
1240
1246
" -Infinity" -> pure (negate 1 / 0 )
1241
1247
_ -> Scientific. toRealFloat <$> parseScientificText t
1242
1248
1243
- instance FromJSON Number where
1244
- parseJSON (Number s) = pure $ scientificToNumber s
1245
- parseJSON Null = pure (D (0 / 0 ))
1246
- parseJSON v = typeMismatch " Number" v
1247
- {-# INLINE parseJSON #-}
1248
-
1249
1249
instance FromJSON Float where
1250
1250
parseJSON = parseRealFloat " Float"
1251
1251
{-# INLINE parseJSON #-}
@@ -1266,12 +1266,12 @@ instance (FromJSON a, Integral a) => FromJSON (Ratio a) where
1266
1266
else pure $ numerator % denominator
1267
1267
{-# INLINE parseJSON #-}
1268
1268
1269
- -- | /WARNING:/ Only parse fixed-precision numbers from trusted input
1270
- -- since an attacker could easily fill up the memory of the target
1271
- -- system by specifying a scientific number with a big exponent like
1272
- -- @1e1000000000@ .
1269
+ -- | This instance includes a bounds check to prevent maliciously
1270
+ -- large inputs to fill up the memory of the target system. You can
1271
+ -- newtype 'Scientific' and provide your own instance using
1272
+ -- 'withScientific' if you want to allow larger inputs .
1273
1273
instance HasResolution a => FromJSON (Fixed a ) where
1274
- parseJSON = withScientific " Fixed" $ pure . realToFrac
1274
+ parseJSON = withBoundedScientific " Fixed" $ pure . realToFrac
1275
1275
{-# INLINE parseJSON #-}
1276
1276
1277
1277
instance FromJSON Int where
@@ -1281,10 +1281,10 @@ instance FromJSON Int where
1281
1281
instance FromJSONKey Int where
1282
1282
fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText " Int"
1283
1283
1284
- -- | /WARNING:/ Only parse Integers from trusted input since an
1285
- -- attacker could easily fill up the memory of the target system by
1286
- -- specifying a scientific number with a big exponent like
1287
- -- @1e1000000000@ .
1284
+ -- | This instance includes a bounds check to prevent maliciously
1285
+ -- large inputs to fill up the memory of the target system. You can
1286
+ -- newtype 'Scientific' and provide your own instance using
1287
+ -- 'withScientific' if you want to allow larger inputs .
1288
1288
instance FromJSON Integer where
1289
1289
parseJSON = parseIntegral " Integer"
1290
1290
{-# INLINE parseJSON #-}
@@ -1723,21 +1723,21 @@ instance FromJSONKey UTCTime where
1723
1723
fromJSONKey = FromJSONKeyTextParser (Time. run Time. utcTime)
1724
1724
1725
1725
1726
- -- | /WARNING:/ Only parse lengths of time from trusted input
1727
- -- since an attacker could easily fill up the memory of the target
1728
- -- system by specifying a scientific number with a big exponent like
1729
- -- @1e1000000000@ .
1726
+ -- | This instance includes a bounds check to prevent maliciously
1727
+ -- large inputs to fill up the memory of the target system. You can
1728
+ -- newtype 'Scientific' and provide your own instance using
1729
+ -- 'withScientific' if you want to allow larger inputs .
1730
1730
instance FromJSON NominalDiffTime where
1731
- parseJSON = withScientific " NominalDiffTime" $ pure . realToFrac
1731
+ parseJSON = withBoundedScientific " NominalDiffTime" $ pure . realToFrac
1732
1732
{-# INLINE parseJSON #-}
1733
1733
1734
1734
1735
- -- | /WARNING:/ Only parse lengths of time from trusted input
1736
- -- since an attacker could easily fill up the memory of the target
1737
- -- system by specifying a scientific number with a big exponent like
1738
- -- @1e1000000000@ .
1735
+ -- | This instance includes a bounds check to prevent maliciously
1736
+ -- large inputs to fill up the memory of the target system. You can
1737
+ -- newtype 'Scientific' and provide your own instance using
1738
+ -- 'withScientific' if you want to allow larger inputs .
1739
1739
instance FromJSON DiffTime where
1740
- parseJSON = withScientific " DiffTime" $ pure . realToFrac
1740
+ parseJSON = withBoundedScientific " DiffTime" $ pure . realToFrac
1741
1741
{-# INLINE parseJSON #-}
1742
1742
1743
1743
-------------------------------------------------------------------------------
0 commit comments