[Haskell-beginners] More Context for Failures (Data.Aeson)

Brent Yorgey byorgey at seas.upenn.edu
Thu Feb 23 20:51:57 CET 2012


On Thu, Feb 23, 2012 at 02:21:25PM -0500, Darrin Thompson wrote:
> 
> Wouldn't it be neato if I could do this...
> 
> instance FromJSON Whatever where
>  parseJSON (Object o) = do
>    a <- failureContext "branchA" $ parseSomething o
>    b <- failureContext "branchB" parseSomethingElse o
>    return $ Whatever a b
>  parseJSON _ = fail "dude"
> 
> Now when it dies, the error message will be "branchB: expected [a] but
> got Object".

What immediately comes to mind would be to use ReaderT [String] along
with the 'local' method to maintain an explicit stack of parsing
contexts.  However, parseJSON is not polymorphic in the monad used --
so there's no way to use ReaderT in the implementation of parseJSON
methods.

However, parseJSON returns a 'Parser' which is defined like this:

-- | Failure continuation.
type Failure f r   = String -> f r
-- | Success continuation.
type Success a f r = a -> f r

-- | A continuation-based parser type.
newtype Parser a = Parser {
      runParser :: forall f r.
                   Failure f r
                -> Success a f r
                -> f r
    }

So I think it is possible to leverage the "failure continuation" to do
what you want.  In particular,

  failureContext :: String -> Parser a -> Parser a
  failureContext branch p = Parser (\f s -> runParser p (f . (++ (branch ++ ": "))) s)

Untested but I'm pretty sure it will work.  The idea is that
'failureContext' transforms a parser by modifying its "failure
continuation" to first tack the current branch onto the front of the
error message.  These can be stacked just like you would expect.

Argh, I just realized that this *would* work except that
Data.Aeson.Types.Internal does not export the Parser constructor!  In
fact, the aeson package also does not export the
Data.Aeson.Types.Internal module at all.  So to make this work you
would have to build your own customized version of aeson.  This is not
too difficult (cabal unpack aeson; cd aeson; export more stuff; bump
version number in cabal file; cabal install) but if this is something
you want to release then obviously you can't have it depending on a
customized version of aeson.  If it's just an internal tool though,
this may work fine.  Of course, you can also submit a patch to the
aeson maintainer adding the relevant exports.

-Brent



More information about the Beginners mailing list