| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
ParseLib.Error
Synopsis
- data Config = Config {
- errorCount :: Int
- symbolsBefore :: Int
- symbolsAfter :: Int
- defaultConfig :: Config
- errorCountSet :: Int -> Config -> Config
- symbolsBeforeSet :: Int -> Config -> Config
- symbolsAfterSet :: Int -> Config -> Config
- newtype ParseErrorBundle symbols = ParseErrorBundle [(WithLength symbols, NonEmpty (BundledParseError symbols))]
- data BundledParseError symbols
- = BundledParseError symbols
- | BundledFail String
- data WithLength a = WithLength a Int
- class Show symbol => ErrorsPretty symbol where
- errorBundlePrettyImproved :: Config -> [symbol] -> ParseErrorBundle [symbol] -> String
- errorBundlePretty :: (Ord symbol, Show symbol) => Config -> [symbol] -> ParseErrorBundle [symbol] -> String
- traceErrorMessage :: Either String (NonEmpty (a, [s])) -> [(a, [s])]
- data ParseError symbols
- = ParseError symbols symbols
- | Fail String symbols
- toBundle :: Ord s => [ParseError [s]] -> [(WithLength [s], NonEmpty (BundledParseError [s]))]
- toMegaparsecBundle :: Ord s => [s] -> ParseErrorBundle [s] -> Maybe (ParseErrorBundle [s] Void)
- toMegaparsecBundled :: Ord s => Int -> (WithLength [s], NonEmpty (BundledParseError [s])) -> [ParseError [s] Void]
- toErrorItem :: [s] -> ErrorItem (Token [s])
- toBundled :: ParseError symbols -> BundledParseError symbols
- inputRestGet :: ParseError symbols -> symbols
- groupWithKey :: Ord b => (a -> b) -> [a] -> [(b, NonEmpty a)]
configuration
Constructors
| Config | |
Fields
| |
defaultConfig :: Config Source #
default configuration, setting errorCount to 1, symbolsBefore to
16, and symbolsAfter to 15.
Arguments
| :: Int | new |
| -> Config | |
| -> Config |
set a configuration's errorCount
Arguments
| :: Int | new |
| -> Config | |
| -> Config |
set a configuration's symbolsBefore
Arguments
| :: Int | new |
| -> Config | |
| -> Config |
set a configuration's symbolsAfter
parse error bundle
newtype ParseErrorBundle symbols Source #
Constructors
| ParseErrorBundle [(WithLength symbols, NonEmpty (BundledParseError symbols))] |
Instances
data BundledParseError symbols Source #
Constructors
| BundledParseError symbols | expected |
| BundledFail String | message |
Instances
data WithLength a Source #
Constructors
| WithLength a Int |
Instances
| Show a => Show (WithLength a) Source # | |
Defined in ParseLib.Error Methods showsPrec :: Int -> WithLength a -> ShowS # show :: WithLength a -> String # showList :: [WithLength a] -> ShowS # | |
| Eq a => Eq (WithLength a) Source # | |
Defined in ParseLib.Error | |
| Ord a => Ord (WithLength a) Source # | |
Defined in ParseLib.Error Methods compare :: WithLength a -> WithLength a -> Ordering # (<) :: WithLength a -> WithLength a -> Bool # (<=) :: WithLength a -> WithLength a -> Bool # (>) :: WithLength a -> WithLength a -> Bool # (>=) :: WithLength a -> WithLength a -> Bool # max :: WithLength a -> WithLength a -> WithLength a # min :: WithLength a -> WithLength a -> WithLength a # | |
pretty printing parse error bundles
class Show symbol => ErrorsPretty symbol where Source #
Methods
errorBundlePrettyImproved Source #
Arguments
| :: Config | |
| -> [symbol] | entire input |
| -> ParseErrorBundle [symbol] | |
| -> String |
pretty prints a ParseErrorBundle like errorBundlePretty but
makes error messages bearable for Parser Char.
errorBundlePrettyImproved is always preferable to
errorBundlePretty.
if you see the following GHC error, you usually need to add an
ErrorsPretty constraint to your function.
Overlapping instances for ErrorsPretty arising from a use of ‘errorBundlePrettyImproved’
Instances
| ErrorsPretty Char Source # | |
Defined in ParseLib.Error Methods errorBundlePrettyImproved :: Config -> [Char] -> ParseErrorBundle [Char] -> String Source # | |
| (Show symbol, Ord symbol) => ErrorsPretty symbol Source # | an |
Defined in ParseLib.Error Methods errorBundlePrettyImproved :: Config -> [symbol] -> ParseErrorBundle [symbol] -> String Source # | |
Arguments
| :: (Ord symbol, Show symbol) | |
| => Config | |
| -> [symbol] | entire input |
| -> ParseErrorBundle [symbol] | |
| -> String |
pretty prints a ParseErrorBundle like errorBundlePrettyImproved
but with much worse error messages for Parser Char.
errorBundlePrettyImproved is always preferable to errorBundlePretty.
unbundled parse error
data ParseError symbols Source #
Constructors
| ParseError | |
Fields
| |
| Fail | |
Fields
| |
Instances
| Eq symbols => Eq (ParseError symbols) Source # | |
Defined in ParseLib.Error Methods (==) :: ParseError symbols -> ParseError symbols -> Bool # (/=) :: ParseError symbols -> ParseError symbols -> Bool # | |
toBundle :: Ord s => [ParseError [s]] -> [(WithLength [s], NonEmpty (BundledParseError [s]))] Source #
utilities
toMegaparsecBundle :: Ord s => [s] -> ParseErrorBundle [s] -> Maybe (ParseErrorBundle [s] Void) Source #
toMegaparsecBundled :: Ord s => Int -> (WithLength [s], NonEmpty (BundledParseError [s])) -> [ParseError [s] Void] Source #
toErrorItem :: [s] -> ErrorItem (Token [s]) Source #
toBundled :: ParseError symbols -> BundledParseError symbols Source #
inputRestGet :: ParseError symbols -> symbols Source #
groupWithKey :: Ord b => (a -> b) -> [a] -> [(b, NonEmpty a)] Source #