Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module defines a JSON parser, like Aeson's FromJSON
, but
with more detailed error-reporting capabilities. In particular, it
reports errors in a structured format, and can report multiple
independent errors rather than stopping on the first one
encountered.
Synopsis
- data ParserWithErrs a
- data ParseFlags
- defaultParseFlags :: ParseFlags
- runParserWithErrsTop :: ParseFlags -> ParserWithErrs a -> Either [(JSONError, Position)] (a, [(JSONWarning, Position)])
- class FromJSONWithErrs a where
- parseJSONWithErrs :: Value -> ParserWithErrs a
- fromJSONWithErrs :: FromJSONWithErrs a => Value -> Either [(JSONError, Position)] a
- fromJSONWithErrs' :: FromJSONWithErrs a => ParseFlags -> Value -> Either [(JSONError, Position)] a
- fromJSONWithErrs'' :: FromJSONWithErrs a => ParseFlags -> Value -> Either [(JSONError, Position)] (a, [(JSONWarning, Position)])
- decodeWithErrs :: FromJSONWithErrs a => ByteString -> Either [(JSONError, Position)] a
- decodeWithErrs' :: FromJSONWithErrs a => ParseFlags -> ByteString -> Either [(JSONError, Position)] a
- parseJSONDefault :: FromJSONWithErrs a => Value -> Parser a
- withParseFlags :: (ParseFlags -> ParserWithErrs a) -> ParserWithErrs a
- withInt :: String -> (Int -> ParserWithErrs a) -> Value -> ParserWithErrs a
- withIntRange :: IntRange -> String -> (Int -> ParserWithErrs a) -> Value -> ParserWithErrs a
- withBinary :: String -> (Binary -> ParserWithErrs a) -> Value -> ParserWithErrs a
- withBool :: String -> (Bool -> ParserWithErrs a) -> Value -> ParserWithErrs a
- withText :: String -> (Text -> ParserWithErrs a) -> Value -> ParserWithErrs a
- withRegEx :: RegEx -> String -> (Text -> ParserWithErrs a) -> Value -> ParserWithErrs a
- withUTC :: String -> (UTCTime -> ParserWithErrs a) -> Value -> ParserWithErrs a
- withUTCRange :: UTCRange -> String -> (UTCTime -> ParserWithErrs a) -> Value -> ParserWithErrs a
- withVersion :: String -> (Version -> ParserWithErrs a) -> Value -> ParserWithErrs a
- withField :: Text -> (Value -> ParserWithErrs a) -> Object -> ParserWithErrs a
- withDefaultField :: Bool -> Maybe Value -> Text -> (Value -> ParserWithErrs a) -> Object -> ParserWithErrs a
- (.:.) :: FromJSONWithErrs a => Object -> Text -> ParserWithErrs a
- (.::) :: FromJSONWithErrs a => Object -> Text -> ParserWithErrs a
- withUnion :: [(Text, Value -> ParserWithErrs a)] -> Value -> ParserWithErrs a
- data JSONError
- type JSONWarning = JSONError
- data Expected
- data FormatExpected
- type Position = [Step]
- data Step
- prettyJSONErrorPositions :: [(JSONError, Position)] -> String
- prettyJSONError :: JSONError -> String
- prettyStep :: Step -> String
- failWith :: JSONError -> ParserWithErrs a
- expectedArray :: Value -> JSONError
- expectedBool :: Value -> JSONError
- expectedInt :: Value -> JSONError
- expectedObject :: Value -> JSONError
- expectedString :: Value -> JSONError
- badFormat :: String -> Text -> JSONError
Parser with multiple error support
data ParserWithErrs a Source #
Like Parser
, but keeping track of locations within the JSON
structure and able to report multiple errors.
Careful! The Monad
instance does not agree with the Applicative
instance in all circumstances, and you should use the Applicative
instance where possible. In particular:
pf <*> ps
returns errors from both argumentspf `ap` ps
returns errors frompf
only
Instances
data ParseFlags Source #
Options to modify the behaviour of the JSON parser
defaultParseFlags :: ParseFlags Source #
Use this as a basis for overriding individual fields of the
ParseFlags
record, in case more flags are added in the future.
runParserWithErrsTop :: ParseFlags -> ParserWithErrs a -> Either [(JSONError, Position)] (a, [(JSONWarning, Position)]) Source #
Run a parser with given flags, starting in the outermost location, and returning warnings even if the parse was successful
FromJSON class with multiple error support
class FromJSONWithErrs a where Source #
Like FromJSON
, but keeping track of multiple errors and their
positions. Moreover, this class is more liberal in accepting
invalid inputs:
- a string like
"3"
is accepted as an integer; and - the integers
0
and1
are accepted as booleans.
Nothing
parseJSONWithErrs :: Value -> ParserWithErrs a Source #
Parse a JSON value with structured error-reporting support. If
this method is omitted, fromJSON
will be used instead: note
that this will result in less precise errors.
default parseJSONWithErrs :: FromJSON a => Value -> ParserWithErrs a Source #
Instances
fromJSONWithErrs :: FromJSONWithErrs a => Value -> Either [(JSONError, Position)] a Source #
Run the JSON parser on a value to produce a result or a list of
errors with their positions. This should not be used inside an
implementation of parseJSONWithErrs
as it will not pass on the
current position.
fromJSONWithErrs' :: FromJSONWithErrs a => ParseFlags -> Value -> Either [(JSONError, Position)] a Source #
Run the JSON parser on a value to produce a result or a list of
errors with their positions. This version allows the ParseFlags
to be specified.
fromJSONWithErrs'' :: FromJSONWithErrs a => ParseFlags -> Value -> Either [(JSONError, Position)] (a, [(JSONWarning, Position)]) Source #
Run the JSON parser on a value to produce a result or a list of
errors with their positions. This version allows the ParseFlags
to be specified, and produces warnings even if the parse succeeded.
decodeWithErrs :: FromJSONWithErrs a => ByteString -> Either [(JSONError, Position)] a Source #
Decode a ByteString
and run the JSON parser
decodeWithErrs' :: FromJSONWithErrs a => ParseFlags -> ByteString -> Either [(JSONError, Position)] a Source #
Decode a ByteString
and run the JSON parser, allowing the
ParseFlags
to be specified
parseJSONDefault :: FromJSONWithErrs a => Value -> Parser a Source #
Suitable as an implementation of parseJSON
that uses the
FromJSONWithErrs
instance (provided said instance was not defined
using fromJSON
!).
ParserWithErrs combinators
withParseFlags :: (ParseFlags -> ParserWithErrs a) -> ParserWithErrs a Source #
withInt :: String -> (Int -> ParserWithErrs a) -> Value -> ParserWithErrs a Source #
It's contrary to my principles, but I'll accept a string containing a number instead of an actual number, and will silently truncate floating point numbers to integers...
withIntRange :: IntRange -> String -> (Int -> ParserWithErrs a) -> Value -> ParserWithErrs a Source #
withBinary :: String -> (Binary -> ParserWithErrs a) -> Value -> ParserWithErrs a Source #
withBool :: String -> (Bool -> ParserWithErrs a) -> Value -> ParserWithErrs a Source #
withText :: String -> (Text -> ParserWithErrs a) -> Value -> ParserWithErrs a Source #
withRegEx :: RegEx -> String -> (Text -> ParserWithErrs a) -> Value -> ParserWithErrs a Source #
withUTC :: String -> (UTCTime -> ParserWithErrs a) -> Value -> ParserWithErrs a Source #
withUTCRange :: UTCRange -> String -> (UTCTime -> ParserWithErrs a) -> Value -> ParserWithErrs a Source #
withVersion :: String -> (Version -> ParserWithErrs a) -> Value -> ParserWithErrs a Source #
withField :: Text -> (Value -> ParserWithErrs a) -> Object -> ParserWithErrs a Source #
Look up the value of a field, treating missing fields as null
withDefaultField :: Bool -> Maybe Value -> Text -> (Value -> ParserWithErrs a) -> Object -> ParserWithErrs a Source #
Look up the value of a field, which may be read-only or use a
default value (depending on the ParseFlags
).
(.:.) :: FromJSONWithErrs a => Object -> Text -> ParserWithErrs a Source #
Parse the value of a field, treating missing fields as null
(.::) :: FromJSONWithErrs a => Object -> Text -> ParserWithErrs a Source #
Parse the value of a field, failing on missing fields
withUnion :: [(Text, Value -> ParserWithErrs a)] -> Value -> ParserWithErrs a Source #
Match an inhabitant of a disjoint union, which should be an object with a single field, and call the continuation corresponding to the field name.
Representation of JSON parsing errors
Represents an error that can be encountered while parsing
type JSONWarning = JSONError Source #
At present, we do not distinguish between errors and warnings
JSON type expected at a particular position, when a value of a different type was encountered
data FormatExpected Source #
Special format expected of a string
Instances
Eq FormatExpected Source # | |
Defined in Data.API.Error (==) :: FormatExpected -> FormatExpected -> Bool # (/=) :: FormatExpected -> FormatExpected -> Bool # | |
Show FormatExpected Source # | |
Defined in Data.API.Error showsPrec :: Int -> FormatExpected -> ShowS # show :: FormatExpected -> String # showList :: [FormatExpected] -> ShowS # | |
ToJSON FormatExpected Source # | |
Defined in Data.API.Error toJSON :: FormatExpected -> Value # toEncoding :: FormatExpected -> Encoding # toJSONList :: [FormatExpected] -> Value # toEncodingList :: [FormatExpected] -> Encoding # | |
FromJSON FormatExpected Source # | |
Defined in Data.API.Error parseJSON :: Value -> Parser FormatExpected # parseJSONList :: Value -> Parser [FormatExpected] # |
type Position = [Step] Source #
A position inside a JSON value is a list of steps, ordered innermost first (so going inside an object prepends a step).
Each step may be into a field of an object, or a specific element of an array.
prettyJSONErrorPositions :: [(JSONError, Position)] -> String Source #
Human-readable presentation of a list of parse errors with their positions
prettyJSONError :: JSONError -> String Source #
Human-readable description of a JSON parse error
prettyStep :: Step -> String Source #
Human-readable description of a single step in a position
Error construction
failWith :: JSONError -> ParserWithErrs a Source #
expectedArray :: Value -> JSONError Source #
expectedBool :: Value -> JSONError Source #
expectedInt :: Value -> JSONError Source #
expectedObject :: Value -> JSONError Source #
expectedString :: Value -> JSONError Source #