Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Synopsis
- data Expected t s p
- = ExBaseEnd
- | ExBaseNameOf Space
- | ExBaseNameAny
- | ExBaseNat
- | ExBaseText
- | ExBasePunc Char
- | ExBaseMsg String
- | ExContextDecl Text (Bag (Blocker t (Expected t s p)))
- | ExContextBind Text (Bag (Blocker t (Expected t s p)))
- pprExpected :: (Show s, Show p) => Expected (Located Token) s p -> String
- pprBlocker :: (Show s, Show p) => Blocker (Located Token) (Expected (Located Token) s p) -> String
- pprLocation :: Location -> String
- data ParseError t e = ParseError [Blocker t e]
- pprParseError :: (Show s, Show p) => ParseError (Located Token) (Expected (Located Token) s p) -> String
Documentation
What we were expecting at the point there was a parse error.
ExBaseEnd | Expecting end of input. |
ExBaseNameOf Space | Expecting a name in the given namespace. |
ExBaseNameAny | Expecting a name in any namespace. |
ExBaseNat | Expecting a natural number. |
ExBaseText | Expecting a text string. |
ExBasePunc Char | Expecting a punctuation character. |
ExBaseMsg String | Expecting something described by the given message. |
ExContextDecl Text (Bag (Blocker t (Expected t s p))) | Expecting something while parsing a declaration. |
ExContextBind Text (Bag (Blocker t (Expected t s p))) | Expecting something while parsing a binding. |
pprExpected :: (Show s, Show p) => Expected (Located Token) s p -> String Source #
Pretty print an expected thing.
pprBlocker :: (Show s, Show p) => Blocker (Located Token) (Expected (Located Token) s p) -> String Source #
Pretty print a blocker.
pprLocation :: Location -> String Source #
data ParseError t e Source #
Parser error.
ParseError [Blocker t e] |
Instances
(Show t, Show e) => Show (ParseError t e) Source # | |
Defined in SMR.Source.Expected showsPrec :: Int -> ParseError t e -> ShowS # show :: ParseError t e -> String # showList :: [ParseError t e] -> ShowS # |