| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
SimpleParser.Explain
Synopsis
- class TextBuildable a where
- newtype ShowTextBuildable a = ShowTextBuildable {
- unShowTextBuildable :: a
- class ExplainLabel l where
- explainLabel :: l -> Builder
- explainLabelText :: l -> Text
- data ErrorExplanation = ErrorExplanation {}
- class ExplainError e where
- explainError :: e -> ErrorExplanation
- type Explainable l s e = (PosStream s, ExplainLabel l, ExplainError e)
- data ParseErrorExplanation p = ParseErrorExplanation {
- peeSpan :: !(Span p)
- peeContext :: !(Seq Text)
- peeDetails :: !(Maybe Text)
- peeErrExp :: !ErrorExplanation
- explainParseError :: (TextBuildable (Token s), TextBuildable (Chunk s), Explainable l s e) => ParseError l s e -> ParseErrorExplanation (Pos s)
- buildParseErrorExplanation :: HasLinePos p => ParseErrorExplanation p -> Builder
- buildAllParseErrorExplanations :: (HasLinePos p, Foldable f) => f (ParseErrorExplanation p) -> Builder
Documentation
class TextBuildable a where Source #
Types that can be rendered into a textual error message (Effectively a fancy Show)
Instances
| TextBuildable Atom Source # | |
| TextBuildable Text Source # | |
| TextBuildable Builder Source # | |
| TextBuildable String Source # | |
| TextBuildable Char Source # | |
| TextBuildable a => TextBuildable (Seq a) Source # | |
| Show a => TextBuildable (ShowTextBuildable a) Source # | |
Defined in SimpleParser.Explain Methods buildText :: ShowTextBuildable a -> Builder Source # | |
| TextBuildable a => TextBuildable [a] Source # | |
Defined in SimpleParser.Explain | |
newtype ShowTextBuildable a Source #
Deriving-Via wrapper for TextBuildable for types with Show
Constructors
| ShowTextBuildable | |
Fields
| |
Instances
| Show a => TextBuildable (ShowTextBuildable a) Source # | |
Defined in SimpleParser.Explain Methods buildText :: ShowTextBuildable a -> Builder Source # | |
class ExplainLabel l where Source #
Minimal complete definition
Instances
| ExplainLabel Void Source # | |
Defined in SimpleParser.Explain | |
| ExplainLabel TextLabel Source # | |
Defined in SimpleParser.Explain | |
| ExplainLabel AstLabel Source # | |
Defined in SimpleParser.Examples.Direct.Ast | |
| ExplainLabel SexpLabel Source # | |
Defined in SimpleParser.Examples.Direct.Sexp | |
| ExplainLabel SexpTokLabel Source # | |
Defined in SimpleParser.Examples.Lexed.Sexp Methods explainLabel :: SexpTokLabel -> Builder Source # explainLabelText :: SexpTokLabel -> Text Source # | |
| ExplainLabel l => ExplainLabel (CompoundTextLabel l) Source # | |
Defined in SimpleParser.Explain Methods explainLabel :: CompoundTextLabel l -> Builder Source # explainLabelText :: CompoundTextLabel l -> Text Source # | |
data ErrorExplanation Source #
Constructors
| ErrorExplanation | |
Instances
| Show ErrorExplanation Source # | |
Defined in SimpleParser.Explain Methods showsPrec :: Int -> ErrorExplanation -> ShowS # show :: ErrorExplanation -> String # showList :: [ErrorExplanation] -> ShowS # | |
| Eq ErrorExplanation Source # | |
Defined in SimpleParser.Explain Methods (==) :: ErrorExplanation -> ErrorExplanation -> Bool # (/=) :: ErrorExplanation -> ErrorExplanation -> Bool # | |
class ExplainError e where Source #
Methods
explainError :: e -> ErrorExplanation Source #
Instances
| ExplainError Void Source # | |
Defined in SimpleParser.Explain Methods explainError :: Void -> ErrorExplanation Source # | |
| (TextBuildable (Token s), TextBuildable (Chunk s)) => ExplainError (StreamError s) Source # | |
Defined in SimpleParser.Explain Methods explainError :: StreamError s -> ErrorExplanation Source # | |
| (TextBuildable (Token s), TextBuildable (Chunk s), ExplainError e) => ExplainError (CompoundError s e) Source # | |
Defined in SimpleParser.Explain Methods explainError :: CompoundError s e -> ErrorExplanation Source # | |
type Explainable l s e = (PosStream s, ExplainLabel l, ExplainError e) Source #
data ParseErrorExplanation p Source #
Constructors
| ParseErrorExplanation | |
Fields
| |
Instances
| Show p => Show (ParseErrorExplanation p) Source # | |
Defined in SimpleParser.Explain Methods showsPrec :: Int -> ParseErrorExplanation p -> ShowS # show :: ParseErrorExplanation p -> String # showList :: [ParseErrorExplanation p] -> ShowS # | |
| Eq p => Eq (ParseErrorExplanation p) Source # | |
Defined in SimpleParser.Explain Methods (==) :: ParseErrorExplanation p -> ParseErrorExplanation p -> Bool # (/=) :: ParseErrorExplanation p -> ParseErrorExplanation p -> Bool # | |
explainParseError :: (TextBuildable (Token s), TextBuildable (Chunk s), Explainable l s e) => ParseError l s e -> ParseErrorExplanation (Pos s) Source #
buildParseErrorExplanation :: HasLinePos p => ParseErrorExplanation p -> Builder Source #
buildAllParseErrorExplanations :: (HasLinePos p, Foldable f) => f (ParseErrorExplanation p) -> Builder Source #