aeson-better-errors-0.9.0.1: Better error messages when decoding JSON values.

Safe HaskellNone
LanguageHaskell2010

Data.Aeson.BetterErrors.Internal

Synopsis

Documentation

newtype ParseT err m a Source #

The type of parsers: things which consume JSON values and produce either detailed errors or successfully parsed values (of other types).

The err type parameter is for custom validation errors; for parsers that don't produce any custom validation errors, I recommend you just stick a type variable in for full generality:

    asTuple :: Parse e (Int, Int)
    asTuple = (,) <$> nth 0 asIntegral <*> nth 1 asIntegral

The m parameter allows you to run the parser within an abitrary underlying Monad. You may want to use Parse in most cases instead, and all functions in this module work on either.

Constructors

ParseT (ReaderT ParseReader (ExceptT (ParseError err) m) a) 

Instances

Monad m => MonadReader ParseReader (ParseT err m) Source # 

Methods

ask :: ParseT err m ParseReader #

local :: (ParseReader -> ParseReader) -> ParseT err m a -> ParseT err m a #

reader :: (ParseReader -> a) -> ParseT err m a #

MonadTrans (ParseT err) Source # 

Methods

lift :: Monad m => m a -> ParseT err m a #

Monad m => MonadError (ParseError err) (ParseT err m) Source # 

Methods

throwError :: ParseError err -> ParseT err m a #

catchError :: ParseT err m a -> (ParseError err -> ParseT err m a) -> ParseT err m a #

Monad m => Monad (ParseT err m) Source # 

Methods

(>>=) :: ParseT err m a -> (a -> ParseT err m b) -> ParseT err m b #

(>>) :: ParseT err m a -> ParseT err m b -> ParseT err m b #

return :: a -> ParseT err m a #

fail :: String -> ParseT err m a #

Functor m => Functor (ParseT err m) Source # 

Methods

fmap :: (a -> b) -> ParseT err m a -> ParseT err m b #

(<$) :: a -> ParseT err m b -> ParseT err m a #

Monad m => Applicative (ParseT err m) Source # 

Methods

pure :: a -> ParseT err m a #

(<*>) :: ParseT err m (a -> b) -> ParseT err m a -> ParseT err m b #

(*>) :: ParseT err m a -> ParseT err m b -> ParseT err m b #

(<*) :: ParseT err m a -> ParseT err m b -> ParseT err m a #

type Parse err a = ParseT err Identity a Source #

This is the standard version of ParseT over the Identity Monad, for running pure parsers.

runParseT :: ParseT err m a -> Value -> m (Either (ParseError err) a) Source #

runParse :: Parse err a -> Value -> Either (ParseError err) a Source #

mapParseT :: (ReaderT ParseReader (ExceptT (ParseError err) m) a -> ReaderT ParseReader (ExceptT (ParseError err') m') a') -> ParseT err m a -> ParseT err' m' a' Source #

mapError :: Functor m => (err -> err') -> ParseT err m a -> ParseT err' m a Source #

Transform the error of a parser according to the given function.

(.!) :: Functor m => ParseT err m a -> (err -> err') -> ParseT err' m a Source #

An infix version of mapError.

type Parse' a = Parse Void a Source #

The type of parsers which never produce custom validation errors.

runParserT :: Monad m => (s -> Either String Value) -> ParseT err m a -> s -> m (Either (ParseError err) a) Source #

runParser :: (s -> Either String Value) -> Parse err a -> s -> Either (ParseError err) a Source #

parseM :: Monad m => ParseT err m a -> ByteString -> m (Either (ParseError err) a) Source #

Like parse but runs the parser on an arbitrary underlying Monad.

parse :: Parse err a -> ByteString -> Either (ParseError err) a Source #

Run a parser with a lazy ByteString containing JSON data. Note that the normal caveat applies: the JSON supplied must contain either an object or an array for this to work.

parseStrictM :: Monad m => ParseT err m a -> ByteString -> m (Either (ParseError err) a) Source #

Like parseStrict but runs the parser on an arbitrary underlying Monad.

parseStrict :: Parse err a -> ByteString -> Either (ParseError err) a Source #

Run a parser with a strict ByteString containing JSON data. Note that the normal caveat applies: the JSON supplied must contain either an object or an array for this to work.

parseValueM :: Monad m => ParseT err m a -> Value -> m (Either (ParseError err) a) Source #

Like parseValue but runs the parser on an arbitrary underlying Monad.

parseValue :: Parse err a -> Value -> Either (ParseError err) a Source #

Run a parser with a pre-parsed JSON Value.

toAesonParser :: (err -> Text) -> Parse err a -> Value -> Parser a Source #

This function is useful when you have a Parse err a and you want to obtain an instance for FromJSON a. Simply define:

   parseJSON = toAesonParser showMyCustomError myParser

toAesonParser' :: Parse' a -> Value -> Parser a Source #

Take a parser which never produces custom validation errors and turn it into an Aeson parser. Note that in this case, there is no need to provide a display function.

fromAesonParser :: (Functor m, Monad m) => FromJSON a => ParseT e m a Source #

Create a parser for any type, using its FromJSON instance. Generally, you should prefer to write parsers using the other functions in this module; key, asString, etc, since they will usually generate better error messages. However this function is also useful occasionally.

data ParseReader Source #

Data used internally by the Parse type.

Constructors

ParseReader 

Instances

Monad m => MonadReader ParseReader (ParseT err m) Source # 

Methods

ask :: ParseT err m ParseReader #

local :: (ParseReader -> ParseReader) -> ParseT err m a -> ParseT err m a #

reader :: (ParseReader -> a) -> ParseT err m a #

data PathPiece Source #

A piece of a path leading to a specific part of the JSON data. Internally, a list of these is maintained as the parser traverses the JSON data. This list is included in the error if one occurs.

Constructors

ObjectKey Text 
ArrayIndex Int 

data ParseError err Source #

A value indicating that the JSON could not be decoded successfully.

Constructors

InvalidJSON String

Indicates a syntax error in the JSON string. Unfortunately, in this case, Aeson's errors are not very helpful.

BadSchema [PathPiece] (ErrorSpecifics err)

Indicates a decoding error; the input was parsed as JSON successfully, but a value of the required type could not be constructed, perhaps because of a missing key or type mismatch.

Instances

Functor ParseError Source # 

Methods

fmap :: (a -> b) -> ParseError a -> ParseError b #

(<$) :: a -> ParseError b -> ParseError a #

Eq err => Eq (ParseError err) Source # 

Methods

(==) :: ParseError err -> ParseError err -> Bool #

(/=) :: ParseError err -> ParseError err -> Bool #

Show err => Show (ParseError err) Source # 

Methods

showsPrec :: Int -> ParseError err -> ShowS #

show :: ParseError err -> String #

showList :: [ParseError err] -> ShowS #

Monad m => MonadError (ParseError err) (ParseT err m) Source # 

Methods

throwError :: ParseError err -> ParseT err m a #

catchError :: ParseT err m a -> (ParseError err -> ParseT err m a) -> ParseT err m a #

type ParseError' = ParseError Void Source #

The type of parse errors which never involve custom validation errors.

data ErrorSpecifics err Source #

Detailed information in the case where a value could be parsed as JSON, but a value of the required type could not be constructed from it, for some reason.

Constructors

KeyMissing Text 
OutOfBounds Int 
WrongType JSONType Value

Expected type, actual value

ExpectedIntegral Double 
FromAeson String

An error arising inside a FromJSON instance.

CustomError err 

Instances

type ErrorSpecifics' = ErrorSpecifics Void Source #

The type of error specifics which never involve custom validation errors.

data JSONType Source #

An enumeration of the different types that JSON values may take.

displayError :: (err -> Text) -> ParseError err -> [Text] Source #

Turn a ParseError into a human-readable list of Text values. They will be in a sensible order. For example, you can feed the result to mapM putStrLn, or unlines.

displayError' :: ParseError' -> [Text] Source #

A version of displayError for parsers which do not produce custom validation errors.

displaySpecifics' :: ErrorSpecifics' -> [Text] Source #

A version of displaySpecifics for parsers which do not produce custom validation errors.

jsonTypeOf :: Value -> JSONType Source #

Get the type of a JSON value.

liftParseT :: (Functor m, Monad m) => (Value -> ExceptT (ErrorSpecifics err) m a) -> ParseT err m a Source #

liftParseM :: (Functor m, Monad m) => (Value -> m (Either (ErrorSpecifics err) a)) -> ParseT err m a Source #

liftParse :: (Functor m, Monad m) => (Value -> Either (ErrorSpecifics err) a) -> ParseT err m a Source #

Lift any parsing function into the Parse type.

badSchema :: (Functor m, Monad m) => ErrorSpecifics err -> ParseT err m a Source #

Aborts parsing, due to an error in the structure of the JSON - that is, any error other than the JSON not actually being parseable into a Value.

as :: (Functor m, Monad m) => (Value -> Maybe a) -> JSONType -> ParseT err m a Source #

asValue :: (Functor m, Monad m) => ParseT err m Value Source #

Return the current JSON Value as is. This does no error checking and thus always succeeds. You probably don't want this parser unless the JSON at the current part of your structure is truly arbitrary. You should prefer to use more specific parsers, like asText or asIntegral, where possible.

asText :: (Functor m, Monad m) => ParseT err m Text Source #

Parse a single JSON string as Text.

asString :: (Functor m, Monad m) => ParseT err m String Source #

Parse a single JSON string as a String.

asScientific :: (Functor m, Monad m) => ParseT err m Scientific Source #

Parse a single JSON number as a Scientific.

asIntegral :: (Functor m, Monad m, Integral a) => ParseT err m a Source #

Parse a single JSON number as any Integral type.

asRealFloat :: (Functor m, Monad m, RealFloat a) => ParseT err m a Source #

Parse a single JSON number as any RealFloat type.

asBool :: (Functor m, Monad m) => ParseT err m Bool Source #

Parse a single JSON boolean as a Bool.

asObject :: (Functor m, Monad m) => ParseT err m Object Source #

Parse a JSON object, as an Object. You should prefer functions like eachInObject where possible, since they will usually generate better error messages.

asArray :: (Functor m, Monad m) => ParseT err m Array Source #

Parse a JSON array, as an Array. You should prefer functions like eachInArray where possible, since they will usually generate better error messages.

asNull :: (Functor m, Monad m) => ParseT err m () Source #

Parse a single JSON null value. Useful if you want to throw an error in the case where something is not null.

perhaps :: (Functor m, Monad m) => ParseT err m a -> ParseT err m (Maybe a) Source #

Given a parser, transform it into a parser which returns Nothing when supplied with a JSON null, and otherwise, attempts to parse with the original parser; if this succeeds, the result becomes a Just value.

key :: (Functor m, Monad m) => Text -> ParseT err m a -> ParseT err m a Source #

Take the value corresponding to a given key in the current object.

keyOrDefault :: (Functor m, Monad m) => Text -> a -> ParseT err m a -> ParseT err m a Source #

Take the value corresponding to a given key in the current object, or if no property exists with that key, use the supplied default.

keyMay :: (Functor m, Monad m) => Text -> ParseT err m a -> ParseT err m (Maybe a) Source #

Take the value corresponding to a given key in the current object, or if no property exists with that key, return Nothing .

key' :: (Functor m, Monad m) => ParseT err m a -> Text -> ParseT err m a -> ParseT err m a Source #

nth :: (Functor m, Monad m) => Int -> ParseT err m a -> ParseT err m a Source #

Take the nth value of the current array.

nthOrDefault :: (Functor m, Monad m) => Int -> a -> ParseT err m a -> ParseT err m a Source #

Take the nth value of the current array, or if no value exists with that index, use the supplied default.

nthMay :: (Functor m, Monad m) => Int -> ParseT err m a -> ParseT err m (Maybe a) Source #

Take the nth value of the current array, or if no value exists with that index, return Nothing.

nth' :: (Functor m, Monad m) => ParseT err m a -> Int -> ParseT err m a -> ParseT err m a Source #

eachInArray :: (Functor m, Monad m) => ParseT err m a -> ParseT err m [a] Source #

Attempt to parse each value in the array with the given parser, and collect the results.

forEachInObject :: (Functor m, Monad m) => (Text -> ParseT err m a) -> ParseT err m [a] Source #

Parse each property in an object with the given parser, given the key as an argument, and collect the results.

eachInObject :: (Functor m, Monad m) => ParseT err m a -> ParseT err m [(Text, a)] Source #

Attempt to parse each property value in the object with the given parser, and collect the results.

eachInObjectWithKey :: (Functor m, Monad m) => (Text -> Either err k) -> ParseT err m a -> ParseT err m [(k, a)] Source #

Attempt to parse each property in the object: parse the key with the given validation function, parse the value with the given parser, and collect the results.

withValue :: (Functor m, Monad m) => (Value -> Either err a) -> ParseT err m a Source #

Lifts a function attempting to validate an arbitrary JSON value into a parser. You should only use this if absolutely necessary; the other functions in this module will generally give better error reporting.

withValueM :: (Functor m, Monad m) => (Value -> m (Either err a)) -> ParseT err m a Source #

liftEither :: (Functor m, Monad m) => Either err a -> ParseT err m a Source #

withM :: (Functor m, Monad m) => ParseT err m a -> (a -> m (Either err b)) -> ParseT err m b Source #

with :: (Functor m, Monad m) => ParseT err m a -> (a -> Either err b) -> ParseT err m b Source #

withTextM :: (Functor m, Monad m) => (Text -> m (Either err a)) -> ParseT err m a Source #

withText :: (Functor m, Monad m) => (Text -> Either err a) -> ParseT err m a Source #

withStringM :: (Functor m, Monad m) => (String -> m (Either err a)) -> ParseT err m a Source #

withString :: (Functor m, Monad m) => (String -> Either err a) -> ParseT err m a Source #

withScientificM :: (Functor m, Monad m) => (Scientific -> m (Either err a)) -> ParseT err m a Source #

withScientific :: (Functor m, Monad m) => (Scientific -> Either err a) -> ParseT err m a Source #

withIntegralM :: (Functor m, Monad m, Integral a) => (a -> m (Either err b)) -> ParseT err m b Source #

withIntegral :: (Functor m, Monad m, Integral a) => (a -> Either err b) -> ParseT err m b Source #

withRealFloatM :: (Functor m, Monad m, RealFloat a) => (a -> m (Either err b)) -> ParseT err m b Source #

withRealFloat :: (Functor m, Monad m, RealFloat a) => (a -> Either err b) -> ParseT err m b Source #

withBoolM :: (Functor m, Monad m) => (Bool -> m (Either err a)) -> ParseT err m a Source #

withBool :: (Functor m, Monad m) => (Bool -> Either err a) -> ParseT err m a Source #

withObjectM :: (Functor m, Monad m) => (Object -> m (Either err a)) -> ParseT err m a Source #

Prefer to use functions like key or eachInObject to this one where possible, as they will generate better error messages.

withObject :: (Functor m, Monad m) => (Object -> Either err a) -> ParseT err m a Source #

Prefer to use functions like key or eachInObject to this one where possible, as they will generate better error messages.

withArrayM :: (Functor m, Monad m) => (Array -> m (Either err a)) -> ParseT err m a Source #

Prefer to use functions like nth or eachInArray to this one where possible, as they will generate better error messages.

withArray :: (Functor m, Monad m) => (Array -> Either err a) -> ParseT err m a Source #

Prefer to use functions like nth or eachInArray to this one where possible, as they will generate better error messages.

throwCustomError :: (Functor m, Monad m) => err -> ParseT err m a Source #

Throw a custom validation error.

liftCustomT :: (Functor m, Monad m) => ExceptT err m a -> ParseT err m a Source #