@@ -43,9 +43,11 @@ module Data.Aeson.Types.Internal
43
43
, parse
44
44
, parseEither
45
45
, parseMaybe
46
+ , liftP2
46
47
, modifyFailure
47
48
, parserThrowError
48
49
, parserCatchError
50
+ , parserCatchErrors
49
51
, formatError
50
52
, (<?>)
51
53
-- * Constructors and accessors
@@ -87,6 +89,7 @@ import Data.Foldable (foldl')
87
89
import Data.HashMap.Strict (HashMap )
88
90
import Data.Hashable (Hashable (.. ))
89
91
import Data.List (intercalate )
92
+ import Data.List.NonEmpty (NonEmpty ((:|) ))
90
93
import Data.Scientific (Scientific )
91
94
import Data.Semigroup (Semigroup ((<>) ))
92
95
import Data.String (IsString (.. ))
@@ -98,6 +101,7 @@ import Data.Vector (Vector)
98
101
import GHC.Generics (Generic )
99
102
import qualified Control.Monad.Fail as Fail
100
103
import qualified Data.HashMap.Strict as H
104
+ import qualified Data.List.NonEmpty as NonEmpty
101
105
import qualified Data.Scientific as S
102
106
import qualified Data.Vector as V
103
107
import qualified Language.Haskell.TH.Syntax as TH
@@ -118,7 +122,7 @@ data JSONPathElement = Key Text
118
122
type JSONPath = [JSONPathElement ]
119
123
120
124
-- | The internal result of running a 'Parser'.
121
- data IResult a = IError JSONPath String
125
+ data IResult a = IError ( NonEmpty ( JSONPath , String ))
122
126
| ISuccess a
123
127
deriving (Eq , Show , Typeable )
124
128
@@ -133,15 +137,15 @@ instance NFData JSONPathElement where
133
137
134
138
instance (NFData a ) => NFData (IResult a ) where
135
139
rnf (ISuccess a) = rnf a
136
- rnf (IError path err) = rnf path `seq` rnf err
140
+ rnf (IError err) = rnf err
137
141
138
142
instance (NFData a ) => NFData (Result a ) where
139
143
rnf (Success a) = rnf a
140
144
rnf (Error err) = rnf err
141
145
142
146
instance Functor IResult where
143
- fmap f (ISuccess a) = ISuccess (f a)
144
- fmap _ (IError path err) = IError path err
147
+ fmap f (ISuccess a) = ISuccess (f a)
148
+ fmap _ (IError err) = IError err
145
149
{-# INLINE fmap #-}
146
150
147
151
instance Functor Result where
@@ -153,15 +157,15 @@ instance Monad IResult where
153
157
return = pure
154
158
{-# INLINE return #-}
155
159
156
- ISuccess a >>= k = k a
157
- IError path err >>= _ = IError path err
160
+ ISuccess a >>= k = k a
161
+ IError err >>= _ = IError err
158
162
{-# INLINE (>>=) #-}
159
163
160
164
fail = Fail. fail
161
165
{-# INLINE fail #-}
162
166
163
167
instance Fail. MonadFail IResult where
164
- fail err = IError [] err
168
+ fail err = IError (( [] , err) :| [] )
165
169
{-# INLINE fail #-}
166
170
167
171
instance Monad Result where
@@ -238,11 +242,11 @@ instance Monoid (Result a) where
238
242
{-# INLINE mappend #-}
239
243
240
244
instance Foldable IResult where
241
- foldMap _ (IError _ _) = mempty
245
+ foldMap _ (IError _) = mempty
242
246
foldMap f (ISuccess y) = f y
243
247
{-# INLINE foldMap #-}
244
248
245
- foldr _ z (IError _ _) = z
249
+ foldr _ z (IError _) = z
246
250
foldr f z (ISuccess y) = f y z
247
251
{-# INLINE foldr #-}
248
252
@@ -256,8 +260,8 @@ instance Foldable Result where
256
260
{-# INLINE foldr #-}
257
261
258
262
instance Traversable IResult where
259
- traverse _ (IError path err) = pure (IError path err)
260
- traverse f (ISuccess a) = ISuccess <$> f a
263
+ traverse _ (IError err) = pure (IError err)
264
+ traverse f (ISuccess a) = ISuccess <$> f a
261
265
{-# INLINE traverse #-}
262
266
263
267
instance Traversable Result where
@@ -266,7 +270,7 @@ instance Traversable Result where
266
270
{-# INLINE traverse #-}
267
271
268
272
-- | Failure continuation.
269
- type Failure f r = JSONPath -> String -> f r
273
+ type Failure f r = NonEmpty ( JSONPath , String ) -> f r
270
274
-- | Success continuation.
271
275
type Success a f r = a -> f r
272
276
@@ -289,7 +293,7 @@ instance Monad Parser where
289
293
{-# INLINE fail #-}
290
294
291
295
instance Fail. MonadFail Parser where
292
- fail msg = Parser $ \ path kf _ks -> kf (reverse path) msg
296
+ fail msg = Parser $ \ path kf _ks -> kf (( reverse path, msg) :| [] )
293
297
{-# INLINE fail #-}
294
298
295
299
instance Functor Parser where
@@ -309,10 +313,11 @@ instance Alternative Parser where
309
313
(<|>) = mplus
310
314
{-# INLINE (<|>) #-}
311
315
316
+ {- TODO accumulate errors -}
312
317
instance MonadPlus Parser where
313
318
mzero = fail " mzero"
314
319
{-# INLINE mzero #-}
315
- mplus a b = Parser $ \ path kf ks -> let kf' _ _ = runParser b path kf ks
320
+ mplus a b = Parser $ \ path kf ks -> let kf' _ = runParser b path kf ks
316
321
in runParser a path kf' ks
317
322
{-# INLINE mplus #-}
318
323
@@ -333,6 +338,14 @@ apP d e = do
333
338
return (b a)
334
339
{-# INLINE apP #-}
335
340
341
+ -- | A variant of 'liftA2' that lazily accumulates errors from both subparsers.
342
+ liftP2 :: (a -> b -> c ) -> Parser a -> Parser b -> Parser c
343
+ liftP2 f pa pb = Parser $ \ path kf ks ->
344
+ runParser pa path
345
+ (\ (e :| es) -> kf (e :| es ++ runParser pb path NonEmpty. toList (const [] )))
346
+ (\ a -> runParser pb path kf (\ b -> ks (f a b)))
347
+ {-# INLINE liftP2 #-}
348
+
336
349
-- | A JSON \"object\" (key\/value map).
337
350
type Object = HashMap Text Value
338
351
@@ -423,7 +436,7 @@ emptyObject = Object H.empty
423
436
424
437
-- | Run a 'Parser'.
425
438
parse :: (a -> Parser b ) -> a -> Result b
426
- parse m v = runParser (m v) [] (const Error ) Success
439
+ parse m v = runParser (m v) [] (Error . snd . NonEmpty. head ) Success
427
440
{-# INLINE parse #-}
428
441
429
442
-- | Run a 'Parser'.
@@ -433,14 +446,14 @@ iparse m v = runParser (m v) [] IError ISuccess
433
446
434
447
-- | Run a 'Parser' with a 'Maybe' result type.
435
448
parseMaybe :: (a -> Parser b ) -> a -> Maybe b
436
- parseMaybe m v = runParser (m v) [] (\ _ _ -> Nothing ) Just
449
+ parseMaybe m v = runParser (m v) [] (const Nothing ) Just
437
450
{-# INLINE parseMaybe #-}
438
451
439
452
-- | Run a 'Parser' with an 'Either' result type. If the parse fails,
440
453
-- the 'Left' payload will contain an error message.
441
454
parseEither :: (a -> Parser b ) -> a -> Either String b
442
455
parseEither m v = runParser (m v) [] onError Right
443
- where onError path msg = Left (formatError path msg )
456
+ where onError (( path, err) :| _) = Left (formatError path err )
444
457
{-# INLINE parseEither #-}
445
458
446
459
-- | Annotate an error message with a
@@ -510,21 +523,26 @@ p <?> pathElem = Parser $ \path kf ks -> runParser p (pathElem:path) kf ks
510
523
-- Since 0.6.2.0
511
524
modifyFailure :: (String -> String ) -> Parser a -> Parser a
512
525
modifyFailure f (Parser p) = Parser $ \ path kf ks ->
513
- p path (\ p' m -> kf p' ( f m)) ks
526
+ p path (\ m -> kf (( fmap . fmap ) f m)) ks
514
527
515
528
-- | Throw a parser error with an additional path.
516
529
--
517
530
-- @since 1.2.1.0
518
531
parserThrowError :: JSONPath -> String -> Parser a
519
532
parserThrowError path' msg = Parser $ \ path kf _ks ->
520
- kf (reverse path ++ path') msg
533
+ kf (( reverse path ++ path', msg) :| [] )
521
534
522
535
-- | A handler function to handle previous errors and return to normal execution.
523
536
--
524
537
-- @since 1.2.1.0
525
538
parserCatchError :: Parser a -> (JSONPath -> String -> Parser a ) -> Parser a
526
- parserCatchError (Parser p) handler = Parser $ \ path kf ks ->
527
- p path (\ e msg -> runParser (handler e msg) path kf ks) ks
539
+ parserCatchError p handler = parserCatchErrors p (\ ((e, msg) :| _) -> handler e msg)
540
+
541
+ -- | A handler function to handle multiple previous errors and return to normal
542
+ -- execution.
543
+ parserCatchErrors :: Parser a -> (NonEmpty (JSONPath , String ) -> Parser a ) -> Parser a
544
+ parserCatchErrors (Parser p) handler = Parser $ \ path kf ks ->
545
+ p path (\ es -> runParser (handler es) path kf ks) ks
528
546
529
547
--------------------------------------------------------------------------------
530
548
-- Generic and TH encoding configuration
0 commit comments